| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.String
Description
promoted String functions
Synopsis
- data TrimBoth
- data TrimL
- data TrimR
- data StripR p q
- data StripL p q
- data IsPrefixC p q
- data IsInfixC p q
- data IsSuffixC p q
- data IsPrefixCI p q
- data IsInfixCI p q
- data IsSuffixCI p q
- data ToString
- data FromString (t :: Type) p
- data FromString' t s
Documentation
similar to strip
>>>pz @(Snd >> TrimBoth) (20," abc ")Val "abc"
>>>pz @(Snd >> TrimBoth) (20,T.pack " abc ")Val "abc"
>>>pz @(" " >> TrimBoth) ()Val ""
>>>pz @("" >> TrimBoth) ()Val ""
similar to stripStart
>>>pz @(Snd >> TrimL) (20," abc ")Val "abc "
similar to stripEnd
>>>pz @(Snd >> TrimR) (20," abc ")Val " abc"
>>>pz @(" abc " >> TrimR) ()Val " abc"
>>>pz @("" >> TrimR) ()Val ""
similar to stripRight
>>>pz @(StripR "xyz" Id) "Hello xyz"Val (Just "Hello ")
>>>pz @(StripR "xyz" Id) "xyzHelloxyw"Val Nothing
>>>pz @(StripR "xyz" Id) ""Val Nothing
>>>pz @(StripR "xyz" "xyz") ()Val (Just "")
similar to stripLeft
>>>pz @(StripL "xyz" Id) "xyzHello"Val (Just "Hello")
>>>pz @(StripL "xyz" Id) (T.pack "xyzHello")Val (Just "Hello")
>>>pz @(StripL "xyz" Id) "xywHello"Val Nothing
similar to isPrefixOf for strings
>>>pl @(IsPrefixC "xy" Id) "xyzabw"True (IsPrefixC | xy xyzabw) Val True
>>>pl @(IsPrefixC "ab" Id) "xyzbaw"False (IsPrefixC | ab xyzbaw) Val False
>>>pz @(IsPrefixC "abc" "aBcbCd") ()Val False
similar to isInfixOf for strings
>>>pl @(IsInfixC "ab" Id) "xyzabw"True (IsInfixC | ab xyzabw) Val True
>>>pl @(IsInfixC "aB" Id) "xyzAbw"False (IsInfixC | aB xyzAbw) Val False
>>>pl @(IsInfixC "ab" Id) "xyzbaw"False (IsInfixC | ab xyzbaw) Val False
>>>pl @(IsInfixC Fst Snd) ("ab","xyzabw")True (IsInfixC | ab xyzabw) Val True
similar to isSuffixOf for strings
>>>pl @(IsSuffixC "bw" Id) "xyzabw"True (IsSuffixC | bw xyzabw) Val True
>>>pl @(IsSuffixC "bw" Id) "xyzbaw"False (IsSuffixC | bw xyzbaw) Val False
>>>pz @(IsSuffixC "bCd" "aBcbCd") ()Val True
data IsPrefixCI p q #
similar to case insensitive isPrefixOf for strings
>>>pz @(IsPrefixCI "abc" "aBcbCd") ()Val True
Instances
| P (IsPrefixCIT p q) x => P (IsPrefixCI p q :: Type) x # | |
Defined in Predicate.Data.String Associated Types type PP (IsPrefixCI p q) x :: Type # Methods eval :: MonadEval m => proxy (IsPrefixCI p q) -> POpts -> x -> m (TT (PP (IsPrefixCI p q) x)) # | |
| Show (IsPrefixCI p q) # | |
Defined in Predicate.Data.String Methods showsPrec :: Int -> IsPrefixCI p q -> ShowS # show :: IsPrefixCI p q -> String # showList :: [IsPrefixCI p q] -> ShowS # | |
| type PP (IsPrefixCI p q :: Type) x # | |
Defined in Predicate.Data.String | |
similar to case insensitive isInfixOf for strings
>>>pl @(IsInfixCI "aB" Id) "xyzAbw"True (IsInfixCI | aB xyzAbw) Val True
>>>pz @(IsInfixCI "abc" "axAbCd") ()Val True
data IsSuffixCI p q #
similar to case insensitive isSuffixOf for strings
Instances
| P (IsSuffixCIT p q) x => P (IsSuffixCI p q :: Type) x # | |
Defined in Predicate.Data.String Associated Types type PP (IsSuffixCI p q) x :: Type # Methods eval :: MonadEval m => proxy (IsSuffixCI p q) -> POpts -> x -> m (TT (PP (IsSuffixCI p q) x)) # | |
| Show (IsSuffixCI p q) # | |
Defined in Predicate.Data.String Methods showsPrec :: Int -> IsSuffixCI p q -> ShowS # show :: IsSuffixCI p q -> String # showList :: [IsSuffixCI p q] -> ShowS # | |
| type PP (IsSuffixCI p q :: Type) x # | |
Defined in Predicate.Data.String | |
very simple conversion to a string
data FromString (t :: Type) p #
fromString function where you need to provide the type t of the result
>>>pz @(FromString (Identity _) Id) "abc"Val (Identity "abc")
>>>pz @(FromString (Seq.Seq Char) Id) "abc"Val (fromList "abc")
Instances
| P (FromStringPT t p) x => P (FromString t p :: Type) x # | |
Defined in Predicate.Data.String Associated Types type PP (FromString t p) x :: Type # Methods eval :: MonadEval m => proxy (FromString t p) -> POpts -> x -> m (TT (PP (FromString t p) x)) # | |
| Show (FromString t p) # | |
Defined in Predicate.Data.String Methods showsPrec :: Int -> FromString t p -> ShowS # show :: FromString t p -> String # showList :: [FromString t p] -> ShowS # | |
| type PP (FromString t p :: Type) x # | |
Defined in Predicate.Data.String | |
data FromString' t s #
fromString function where you need to provide the type t of the result
Instances
| (P s a, PP s a ~ String, Show (PP t a), IsString (PP t a)) => P (FromString' t s :: Type) a # | |
Defined in Predicate.Data.String Associated Types type PP (FromString' t s) a :: Type # Methods eval :: MonadEval m => proxy (FromString' t s) -> POpts -> a -> m (TT (PP (FromString' t s) a)) # | |
| Show (FromString' t s) # | |
Defined in Predicate.Data.String Methods showsPrec :: Int -> FromString' t s -> ShowS # show :: FromString' t s -> String # showList :: [FromString' t s] -> ShowS # | |
| type PP (FromString' t s :: Type) a # | |
Defined in Predicate.Data.String | |