| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.Char
Description
promoted character functions
Synopsis
- data C (s :: Symbol)
- data IsLower
- data IsUpper
- data IsDigit
- data IsSpace
- data IsPunctuation
- data IsControl
- data IsHexDigit
- data IsOctDigit
- data IsSeparator
- data IsLatin1
- data IsLowerAll
- data IsUpperAll
- data IsDigitAll
- data IsSpaceAll
- data IsPunctuationAll
- data IsControlAll
- data IsHexDigitAll
- data IsOctDigitAll
- data IsSeparatorAll
- data IsLatin1All
- data ToTitle
- data ToUpper
- data ToLower
constructor
extracts the first character from a non empty Symbol
>>>pz @(C "aBc") ()Val 'a'
character predicates
predicate similar to isLower
>>>pz @IsLower 'X'Val False
>>>pz @IsLower '1'Val False
>>>pz @IsLower 'a'Val True
predicate similar to isUpper
predicate similar to isSpace
>>>pz @IsSpace '\t'Val True
>>>pz @IsSpace ' 'Val True
>>>pz @IsSpace 'x'Val False
data IsPunctuation Source #
predicate similar to isPunctuation
Instances
| Show IsPunctuation Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsPunctuation -> ShowS # show :: IsPunctuation -> String # showList :: [IsPunctuation] -> ShowS # | |
| P IsPunctuationT x => P IsPunctuation x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsPunctuation x Source # Methods eval :: MonadEval m => proxy IsPunctuation -> POpts -> x -> m (TT (PP IsPunctuation x)) Source # | |
| type PP IsPunctuation x Source # | |
Defined in Predicate.Data.Char | |
predicate similar to isControl
data IsHexDigit Source #
Instances
| Show IsHexDigit Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsHexDigit -> ShowS # show :: IsHexDigit -> String # showList :: [IsHexDigit] -> ShowS # | |
| P IsHexDigitT x => P IsHexDigit x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsHexDigit x Source # Methods eval :: MonadEval m => proxy IsHexDigit -> POpts -> x -> m (TT (PP IsHexDigit x)) Source # | |
| type PP IsHexDigit x Source # | |
Defined in Predicate.Data.Char | |
data IsOctDigit Source #
predicate similar to isOctDigit
Instances
| Show IsOctDigit Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsOctDigit -> ShowS # show :: IsOctDigit -> String # showList :: [IsOctDigit] -> ShowS # | |
| P IsOctDigitT x => P IsOctDigit x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsOctDigit x Source # Methods eval :: MonadEval m => proxy IsOctDigit -> POpts -> x -> m (TT (PP IsOctDigit x)) Source # | |
| type PP IsOctDigit x Source # | |
Defined in Predicate.Data.Char | |
data IsSeparator Source #
predicate similar to isSeparator
Instances
| Show IsSeparator Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsSeparator -> ShowS # show :: IsSeparator -> String # showList :: [IsSeparator] -> ShowS # | |
| P IsSeparatorT x => P IsSeparator x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsSeparator x Source # Methods eval :: MonadEval m => proxy IsSeparator -> POpts -> x -> m (TT (PP IsSeparator x)) Source # | |
| type PP IsSeparator x Source # | |
Defined in Predicate.Data.Char | |
predicate similar to isLatin1
string predicates
data IsLowerAll Source #
predicate for determining if a string is all lowercase
>>>pz @IsLowerAll "abc"Val True
>>>pz @IsLowerAll "abcX"Val False
>>>pz @IsLowerAll (T.pack "abcX")Val False
>>>pz @IsLowerAll "abcdef213"Val False
>>>pz @IsLowerAll ""Val True
Instances
| Show IsLowerAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsLowerAll -> ShowS # show :: IsLowerAll -> String # showList :: [IsLowerAll] -> ShowS # | |
| P IsLowerAllT x => P IsLowerAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsLowerAll x Source # Methods eval :: MonadEval m => proxy IsLowerAll -> POpts -> x -> m (TT (PP IsLowerAll x)) Source # | |
| type PP IsLowerAll x Source # | |
Defined in Predicate.Data.Char | |
data IsUpperAll Source #
predicate for determining if a string is all uppercase
Instances
| Show IsUpperAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsUpperAll -> ShowS # show :: IsUpperAll -> String # showList :: [IsUpperAll] -> ShowS # | |
| P IsUpperAllT x => P IsUpperAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsUpperAll x Source # Methods eval :: MonadEval m => proxy IsUpperAll -> POpts -> x -> m (TT (PP IsUpperAll x)) Source # | |
| type PP IsUpperAll x Source # | |
Defined in Predicate.Data.Char | |
data IsDigitAll Source #
predicate for determining if the string is all digits
>>>pz @IsDigitAll "213G"Val False
>>>pz @IsDigitAll "929"Val True
Instances
| Show IsDigitAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsDigitAll -> ShowS # show :: IsDigitAll -> String # showList :: [IsDigitAll] -> ShowS # | |
| P IsDigitAllT x => P IsDigitAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsDigitAll x Source # Methods eval :: MonadEval m => proxy IsDigitAll -> POpts -> x -> m (TT (PP IsDigitAll x)) Source # | |
| type PP IsDigitAll x Source # | |
Defined in Predicate.Data.Char | |
data IsSpaceAll Source #
predicate for determining if the string is all spaces
>>>pz @IsSpaceAll "213G"Val False
>>>pz @IsSpaceAll " "Val True
>>>pz @IsSpaceAll ""Val True
Instances
| Show IsSpaceAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsSpaceAll -> ShowS # show :: IsSpaceAll -> String # showList :: [IsSpaceAll] -> ShowS # | |
| P IsSpaceAllT x => P IsSpaceAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsSpaceAll x Source # Methods eval :: MonadEval m => proxy IsSpaceAll -> POpts -> x -> m (TT (PP IsSpaceAll x)) Source # | |
| type PP IsSpaceAll x Source # | |
Defined in Predicate.Data.Char | |
data IsPunctuationAll Source #
predicate for determining if a string has all punctuation
Instances
| Show IsPunctuationAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsPunctuationAll -> ShowS # show :: IsPunctuationAll -> String # showList :: [IsPunctuationAll] -> ShowS # | |
| P IsPunctuationAllT x => P IsPunctuationAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsPunctuationAll x Source # Methods eval :: MonadEval m => proxy IsPunctuationAll -> POpts -> x -> m (TT (PP IsPunctuationAll x)) Source # | |
| type PP IsPunctuationAll x Source # | |
Defined in Predicate.Data.Char | |
data IsControlAll Source #
predicate for determining if a string has all control chars
Instances
| Show IsControlAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsControlAll -> ShowS # show :: IsControlAll -> String # showList :: [IsControlAll] -> ShowS # | |
| P IsControlAllT x => P IsControlAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsControlAll x Source # Methods eval :: MonadEval m => proxy IsControlAll -> POpts -> x -> m (TT (PP IsControlAll x)) Source # | |
| type PP IsControlAll x Source # | |
Defined in Predicate.Data.Char | |
data IsHexDigitAll Source #
predicate for determining if the string is all hex digits
>>>pz @IsHexDigitAll "01efA"Val True
>>>pz @IsHexDigitAll "01egfA"Val False
Instances
| Show IsHexDigitAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsHexDigitAll -> ShowS # show :: IsHexDigitAll -> String # showList :: [IsHexDigitAll] -> ShowS # | |
| P IsHexDigitAllT x => P IsHexDigitAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsHexDigitAll x Source # Methods eval :: MonadEval m => proxy IsHexDigitAll -> POpts -> x -> m (TT (PP IsHexDigitAll x)) Source # | |
| type PP IsHexDigitAll x Source # | |
Defined in Predicate.Data.Char | |
data IsOctDigitAll Source #
predicate for determining if the string is all octal digits
Instances
| Show IsOctDigitAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsOctDigitAll -> ShowS # show :: IsOctDigitAll -> String # showList :: [IsOctDigitAll] -> ShowS # | |
| P IsOctDigitAllT x => P IsOctDigitAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsOctDigitAll x Source # Methods eval :: MonadEval m => proxy IsOctDigitAll -> POpts -> x -> m (TT (PP IsOctDigitAll x)) Source # | |
| type PP IsOctDigitAll x Source # | |
Defined in Predicate.Data.Char | |
data IsSeparatorAll Source #
predicate for determining if the string has all separators
Instances
| Show IsSeparatorAll Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsSeparatorAll -> ShowS # show :: IsSeparatorAll -> String # showList :: [IsSeparatorAll] -> ShowS # | |
| P IsSeparatorAllT x => P IsSeparatorAll x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsSeparatorAll x Source # Methods eval :: MonadEval m => proxy IsSeparatorAll -> POpts -> x -> m (TT (PP IsSeparatorAll x)) Source # | |
| type PP IsSeparatorAll x Source # | |
Defined in Predicate.Data.Char | |
data IsLatin1All Source #
predicate for determining if the string is all latin chars
Instances
| Show IsLatin1All Source # | |
Defined in Predicate.Data.Char Methods showsPrec :: Int -> IsLatin1All -> ShowS # show :: IsLatin1All -> String # showList :: [IsLatin1All] -> ShowS # | |
| P IsLatin1AllT x => P IsLatin1All x Source # | |
Defined in Predicate.Data.Char Associated Types type PP IsLatin1All x Source # Methods eval :: MonadEval m => proxy IsLatin1All -> POpts -> x -> m (TT (PP IsLatin1All x)) Source # | |
| type PP IsLatin1All x Source # | |
Defined in Predicate.Data.Char | |
change case
converts a string IsText value to title case
>>>pz @ToTitle "HeLlO wOrld!"Val "Hello world!"
>>>data Color = Red | White | Blue | Green | Black deriving (Show,Eq,Enum,Bounded,Read)>>>pz @(ToTitle >> ReadP Color Id) "red"Val Red
converts a string IsText value to upper case
>>>pz @ToUpper "HeLlO wOrld!"Val "HELLO WORLD!"