predicate-typed-0.7.3.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Char

Contents

Description

promoted character functions

Synopsis

constructor

data Char1 (s :: Symbol) Source #

extracts the first character from a non empty Symbol

>>> pz @(Char1 "aBc") ()
PresentT 'a'
Instances
(KnownSymbol s, CmpSymbol s "" ~ GT) => P (Char1 s :: Type) a Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP (Char1 s) a :: Type Source #

Methods

eval :: MonadEval m => proxy (Char1 s) -> POpts -> a -> m (TT (PP (Char1 s) a)) Source #

type PP (Char1 s :: Type) a Source # 
Instance details

Defined in Predicate.Data.Char

type PP (Char1 s :: Type) a = Char

character predicates

data IsLower Source #

predicate similar to isLower

>>> pz @IsLower 'X'
FalseT
>>> pz @IsLower '1'
FalseT
>>> pz @IsLower 'a'
TrueT
Instances
P IsLowerT x => P IsLower x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsLower x :: Type Source #

Methods

eval :: MonadEval m => proxy IsLower -> POpts -> x -> m (TT (PP IsLower x)) Source #

type PP IsLower x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsLower x

data IsUpper Source #

predicate similar to isUpper

Instances
P IsUpperT x => P IsUpper x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsUpper x :: Type Source #

Methods

eval :: MonadEval m => proxy IsUpper -> POpts -> x -> m (TT (PP IsUpper x)) Source #

type PP IsUpper x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsUpper x

data IsDigit Source #

predicate similar to isDigit

>>> pz @IsDigit 'g'
FalseT
>>> pz @IsDigit '9'
TrueT
Instances
P IsDigitT x => P IsDigit x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsDigit x :: Type Source #

Methods

eval :: MonadEval m => proxy IsDigit -> POpts -> x -> m (TT (PP IsDigit x)) Source #

type PP IsDigit x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsDigit x = Bool

data IsSpace Source #

predicate similar to isSpace

>>> pz @IsSpace '\t'
TrueT
>>> pz @IsSpace ' '
TrueT
>>> pz @IsSpace 'x'
FalseT
Instances
P IsSpaceT x => P IsSpace x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsSpace x :: Type Source #

Methods

eval :: MonadEval m => proxy IsSpace -> POpts -> x -> m (TT (PP IsSpace x)) Source #

type PP IsSpace x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsSpace x = Bool

data IsPunctuation Source #

predicate similar to isPunctuation

Instances
P IsPunctuationT x => P IsPunctuation x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsPunctuation x :: Type Source #

Methods

eval :: MonadEval m => proxy IsPunctuation -> POpts -> x -> m (TT (PP IsPunctuation x)) Source #

type PP IsPunctuation x Source # 
Instance details

Defined in Predicate.Data.Char

data IsControl Source #

predicate similar to isControl

Instances
P IsControlT x => P IsControl x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsControl x :: Type Source #

Methods

eval :: MonadEval m => proxy IsControl -> POpts -> x -> m (TT (PP IsControl x)) Source #

type PP IsControl x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsControl x = Bool

data IsHexDigit Source #

predicate similar to isHexDigit

>>> pz @IsHexDigit 'A'
TrueT
>>> pz @IsHexDigit 'g'
FalseT
Instances
P IsHexDigitT x => P IsHexDigit x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsHexDigit x :: Type Source #

Methods

eval :: MonadEval m => proxy IsHexDigit -> POpts -> x -> m (TT (PP IsHexDigit x)) Source #

type PP IsHexDigit x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsHexDigit x = Bool

data IsOctDigit Source #

predicate similar to isOctDigit

Instances
P IsOctDigitT x => P IsOctDigit x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsOctDigit x :: Type Source #

Methods

eval :: MonadEval m => proxy IsOctDigit -> POpts -> x -> m (TT (PP IsOctDigit x)) Source #

type PP IsOctDigit x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsOctDigit x = Bool

data IsSeparator Source #

predicate similar to isSeparator

Instances
P IsSeparatorT x => P IsSeparator x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsSeparator x :: Type Source #

Methods

eval :: MonadEval m => proxy IsSeparator -> POpts -> x -> m (TT (PP IsSeparator x)) Source #

type PP IsSeparator x Source # 
Instance details

Defined in Predicate.Data.Char

data IsLatin1 Source #

predicate similar to isLatin1

Instances
P IsLatin1T x => P IsLatin1 x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsLatin1 x :: Type Source #

Methods

eval :: MonadEval m => proxy IsLatin1 -> POpts -> x -> m (TT (PP IsLatin1 x)) Source #

type PP IsLatin1 x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsLatin1 x = Bool

string predicates

data IsLowerAll Source #

predicate for determining if a string is all lowercase

>>> pz @IsLowerAll "abc"
TrueT
>>> pz @IsLowerAll "abcX"
FalseT
>>> pz @IsLowerAll (T.pack "abcX")
FalseT
>>> pz @IsLowerAll "abcdef213"
FalseT
>>> pz @IsLowerAll ""
TrueT
Instances
P IsLowerAllT x => P IsLowerAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsLowerAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsLowerAll -> POpts -> x -> m (TT (PP IsLowerAll x)) Source #

type PP IsLowerAll x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsLowerAll x

data IsUpperAll Source #

Instances
P IsUpperAllT x => P IsUpperAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsUpperAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsUpperAll -> POpts -> x -> m (TT (PP IsUpperAll x)) Source #

type PP IsUpperAll x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsUpperAll x

data IsDigitAll Source #

predicate for determining if the string is all digits

>>> pz @IsDigitAll "213G"
FalseT
>>> pz @IsDigitAll "929"
TrueT
Instances
P IsDigitAllT x => P IsDigitAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsDigitAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsDigitAll -> POpts -> x -> m (TT (PP IsDigitAll x)) Source #

type PP IsDigitAll x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsDigitAll x = Bool

data IsSpaceAll Source #

predicate for determining if the string is all spaces

>>> pz @IsSpaceAll "213G"
FalseT
>>> pz @IsSpaceAll "    "
TrueT
>>> pz @IsSpaceAll ""
TrueT
Instances
P IsSpaceAllT x => P IsSpaceAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsSpaceAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsSpaceAll -> POpts -> x -> m (TT (PP IsSpaceAll x)) Source #

type PP IsSpaceAll x Source # 
Instance details

Defined in Predicate.Data.Char

type PP IsSpaceAll x = Bool

data IsPunctuationAll Source #

Instances
P IsPunctuationAllT x => P IsPunctuationAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsPunctuationAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsPunctuationAll -> POpts -> x -> m (TT (PP IsPunctuationAll x)) Source #

type PP IsPunctuationAll x Source # 
Instance details

Defined in Predicate.Data.Char

data IsControlAll Source #

Instances
P IsControlAllT x => P IsControlAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsControlAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsControlAll -> POpts -> x -> m (TT (PP IsControlAll x)) Source #

type PP IsControlAll x Source # 
Instance details

Defined in Predicate.Data.Char

data IsHexDigitAll Source #

predicate for determining if the string is all hex digits

>>> pz @IsHexDigitAll "01efA"
TrueT
>>> pz @IsHexDigitAll "01egfA"
FalseT
Instances
P IsHexDigitAllT x => P IsHexDigitAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsHexDigitAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsHexDigitAll -> POpts -> x -> m (TT (PP IsHexDigitAll x)) Source #

type PP IsHexDigitAll x Source # 
Instance details

Defined in Predicate.Data.Char

data IsOctDigitAll Source #

Instances
P IsOctDigitAllT x => P IsOctDigitAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsOctDigitAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsOctDigitAll -> POpts -> x -> m (TT (PP IsOctDigitAll x)) Source #

type PP IsOctDigitAll x Source # 
Instance details

Defined in Predicate.Data.Char

data IsSeparatorAll Source #

Instances
P IsSeparatorAllT x => P IsSeparatorAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsSeparatorAll x :: Type Source #

Methods

eval :: MonadEval m => proxy IsSeparatorAll -> POpts -> x -> m (TT (PP IsSeparatorAll x)) Source #

type PP IsSeparatorAll x Source # 
Instance details

Defined in Predicate.Data.Char

data IsLatin1All Source #

Instances
P IsLatin1AllT x => P IsLatin1All x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsLatin1All x :: Type Source #

Methods

eval :: MonadEval m => proxy IsLatin1All -> POpts -> x -> m (TT (PP IsLatin1All x)) Source #

type PP IsLatin1All x Source # 
Instance details

Defined in Predicate.Data.Char

change case

data ToTitle Source #

converts a string IsText value to title case

>>> pz @ToTitle "HeLlO wOrld!"
PresentT "Hello world!"
>>> data Color = Red | White | Blue | Green | Black deriving (Show,Eq,Enum,Bounded,Read)
>>> pz @(ToTitle >> ReadP Color Id) "red"
PresentT Red
Instances
(Show a, IsText a) => P ToTitle a Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP ToTitle a :: Type Source #

Methods

eval :: MonadEval m => proxy ToTitle -> POpts -> a -> m (TT (PP ToTitle a)) Source #

type PP ToTitle a Source # 
Instance details

Defined in Predicate.Data.Char

type PP ToTitle a = a

data ToUpper Source #

converts a string IsText value to upper case

>>> pz @ToUpper "HeLlO wOrld!"
PresentT "HELLO WORLD!"
Instances
(Show a, IsText a) => P ToUpper a Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP ToUpper a :: Type Source #

Methods

eval :: MonadEval m => proxy ToUpper -> POpts -> a -> m (TT (PP ToUpper a)) Source #

type PP ToUpper a Source # 
Instance details

Defined in Predicate.Data.Char

type PP ToUpper a = a

data ToLower Source #

converts a string IsText value to lower case

>>> pz @ToLower "HeLlO wOrld!"
PresentT "hello world!"
Instances
(Show a, IsText a) => P ToLower a Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP ToLower a :: Type Source #

Methods

eval :: MonadEval m => proxy ToLower -> POpts -> a -> m (TT (PP ToLower a)) Source #

type PP ToLower a Source # 
Instance details

Defined in Predicate.Data.Char

type PP ToLower a = a