predicate-typed-0.7.4.3: Predicates, Refinement types and Dsl
Safe HaskellNone
LanguageHaskell2010

Predicate.Data.String

Contents

Description

promoted String functions

Synopsis

functions

data TrimBoth Source #

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 ""

Instances

Instances details
Show TrimBoth Source # 
Instance details

Defined in Predicate.Data.String

P TrimBothT x => P TrimBoth x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP TrimBoth x Source #

Methods

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

type PP TrimBoth x Source # 
Instance details

Defined in Predicate.Data.String

type PP TrimBoth x

data TrimL Source #

similar to stripStart

>>> pz @(Snd >> TrimL) (20," abc   ")
Val "abc   "

Instances

Instances details
Show TrimL Source # 
Instance details

Defined in Predicate.Data.String

Methods

showsPrec :: Int -> TrimL -> ShowS #

show :: TrimL -> String #

showList :: [TrimL] -> ShowS #

P TrimLT x => P TrimL x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP TrimL x Source #

Methods

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

type PP TrimL x Source # 
Instance details

Defined in Predicate.Data.String

type PP TrimL x

data TrimR Source #

similar to stripEnd

>>> pz @(Snd >> TrimR) (20," abc   ")
Val " abc"
>>> pz @("  abc " >> TrimR) ()
Val "  abc"
>>> pz @("" >> TrimR) ()
Val ""

Instances

Instances details
Show TrimR Source # 
Instance details

Defined in Predicate.Data.String

Methods

showsPrec :: Int -> TrimR -> ShowS #

show :: TrimR -> String #

showList :: [TrimR] -> ShowS #

P TrimRT x => P TrimR x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP TrimR x Source #

Methods

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

type PP TrimR x Source # 
Instance details

Defined in Predicate.Data.String

type PP TrimR x

data StripR p q Source #

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 "")

Instances

Instances details
P (StripRT p q) x => P (StripR p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (StripR p q) x Source #

Methods

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

Show (StripR p q) Source # 
Instance details

Defined in Predicate.Data.String

Methods

showsPrec :: Int -> StripR p q -> ShowS #

show :: StripR p q -> String #

showList :: [StripR p q] -> ShowS #

type PP (StripR p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

type PP (StripR p q :: Type) x

data StripL p q Source #

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

Instances

Instances details
P (StripLT p q) x => P (StripL p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (StripL p q) x Source #

Methods

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

Show (StripL p q) Source # 
Instance details

Defined in Predicate.Data.String

Methods

showsPrec :: Int -> StripL p q -> ShowS #

show :: StripL p q -> String #

showList :: [StripL p q] -> ShowS #

type PP (StripL p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

type PP (StripL p q :: Type) x

data IsPrefixC p q Source #

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

Instances

Instances details
P (IsPrefixCT p q) x => P (IsPrefixC p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsPrefixC p q) x Source #

Methods

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

Show (IsPrefixC p q) Source # 
Instance details

Defined in Predicate.Data.String

Methods

showsPrec :: Int -> IsPrefixC p q -> ShowS #

show :: IsPrefixC p q -> String #

showList :: [IsPrefixC p q] -> ShowS #

type PP (IsPrefixC p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

type PP (IsPrefixC p q :: Type) x

data IsInfixC p q Source #

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

Instances

Instances details
P (IsInfixCT p q) x => P (IsInfixC p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsInfixC p q) x Source #

Methods

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

Show (IsInfixC p q) Source # 
Instance details

Defined in Predicate.Data.String

Methods

showsPrec :: Int -> IsInfixC p q -> ShowS #

show :: IsInfixC p q -> String #

showList :: [IsInfixC p q] -> ShowS #

type PP (IsInfixC p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

type PP (IsInfixC p q :: Type) x

data IsSuffixC p q Source #

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

Instances

Instances details
P (IsSuffixCT p q) x => P (IsSuffixC p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsSuffixC p q) x Source #

Methods

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

Show (IsSuffixC p q) Source # 
Instance details

Defined in Predicate.Data.String

Methods

showsPrec :: Int -> IsSuffixC p q -> ShowS #

show :: IsSuffixC p q -> String #

showList :: [IsSuffixC p q] -> ShowS #

type PP (IsSuffixC p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

type PP (IsSuffixC p q :: Type) x

data IsPrefixCI p q Source #

similar to case insensitive isPrefixOf for strings

>>> pz @(IsPrefixCI "abc" "aBcbCd") ()
Val True

Instances

Instances details
P (IsPrefixCIT p q) x => P (IsPrefixCI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsPrefixCI p q) x Source #

Methods

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

Show (IsPrefixCI p q) Source # 
Instance details

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 Source # 
Instance details

Defined in Predicate.Data.String

type PP (IsPrefixCI p q :: Type) x

data IsInfixCI p q Source #

similar to case insensitive isInfixOf for strings

>>> pl @(IsInfixCI "aB" Id) "xyzAbw"
True (IsInfixCI | aB xyzAbw)
Val True
>>> pz @(IsInfixCI "abc" "axAbCd") ()
Val True

Instances

Instances details
P (IsInfixCIT p q) x => P (IsInfixCI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsInfixCI p q) x Source #

Methods

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

Show (IsInfixCI p q) Source # 
Instance details

Defined in Predicate.Data.String

Methods

showsPrec :: Int -> IsInfixCI p q -> ShowS #

show :: IsInfixCI p q -> String #

showList :: [IsInfixCI p q] -> ShowS #

type PP (IsInfixCI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

type PP (IsInfixCI p q :: Type) x

data IsSuffixCI p q Source #

similar to case insensitive isSuffixOf for strings

Instances

Instances details
P (IsSuffixCIT p q) x => P (IsSuffixCI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsSuffixCI p q) x Source #

Methods

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

Show (IsSuffixCI p q) Source # 
Instance details

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 Source # 
Instance details

Defined in Predicate.Data.String

type PP (IsSuffixCI p q :: Type) x

data ToString Source #

very simple conversion to a string

Instances

Instances details
Show ToString Source # 
Instance details

Defined in Predicate.Data.String

ToStringC x => P ToString x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP ToString x Source #

Methods

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

type PP ToString x Source # 
Instance details

Defined in Predicate.Data.String

type PP ToString x = String

class ToStringC (a :: Type) where Source #

Methods

toStringC :: a -> String Source #

Instances

Instances details
ToStringC String Source # 
Instance details

Defined in Predicate.Data.String

ToStringC ByteString Source # 
Instance details

Defined in Predicate.Data.String

ToStringC ByteString Source # 
Instance details

Defined in Predicate.Data.String

ToStringC Text Source # 
Instance details

Defined in Predicate.Data.String

ToStringC Text Source # 
Instance details

Defined in Predicate.Data.String

data FromString (t :: Type) p Source #

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

Instances details
P (FromStringT t p) x => P (FromString t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (FromString t p) x Source #

Methods

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

Show (FromString t p) Source # 
Instance details

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 Source # 
Instance details

Defined in Predicate.Data.String

type PP (FromString t p :: Type) x

data FromString' t p Source #

fromString function where you need to provide a reference to the type t of the result

Instances

Instances details
(P p a, PP p a ~ String, Show (PP t a), IsString (PP t a)) => P (FromString' t p :: Type) a Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (FromString' t p) a Source #

Methods

eval :: MonadEval m => proxy (FromString' t p) -> POpts -> a -> m (TT (PP (FromString' t p) a)) Source #

Show (FromString' t p) Source # 
Instance details

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) a Source # 
Instance details

Defined in Predicate.Data.String

type PP (FromString' t p :: Type) a = PP t a