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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.String

Description

promoted String functions

Synopsis

Documentation

data TrimBoth p Source #

similar to strip

>>> pz @(TrimBoth (Snd Id)) (20," abc   " :: String)
PresentT "abc"
>>> pz @(TrimBoth (Snd Id)) (20,T.pack " abc   ")
PresentT "abc"
>>> pz @(TrimBoth "         ") ()
PresentT ""
>>> pz @(TrimBoth "") ()
PresentT ""
Instances
P (TrimBothT p) x => P (TrimBoth p :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (TrimBoth p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (TrimBoth p :: Type) x

data TrimL p Source #

similar to stripStart

>>> pz @(TrimL (Snd Id)) (20," abc   ")
PresentT "abc   "
Instances
P (TrimLT p) x => P (TrimL p :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (TrimL p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (TrimL p :: Type) x

data TrimR p Source #

similar to stripEnd

>>> pz @(TrimR (Snd Id)) (20," abc   ")
PresentT " abc"
>>> pz @(TrimR "  abc ") ()
PresentT "  abc"
>>> pz @(TrimR "") ()
PresentT ""
Instances
P (TrimRT p) x => P (TrimR p :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (TrimR p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (TrimR p :: Type) x

data StripR p q Source #

similar to stripRight

>>> pz @(StripR "xyz" Id) "Hello xyz"
PresentT (Just "Hello ")
>>> pz @(StripR "xyz" Id) "xyzHelloxyw"
PresentT Nothing
>>> pz @(StripR "xyz" Id) ""
PresentT Nothing
>>> pz @(StripR "xyz" "xyz") ()
PresentT (Just "")
Instances
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 :: Type Source #

Methods

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

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" :: String)
PresentT (Just "Hello")
>>> pz @(StripL "xyz" Id) (T.pack "xyzHello")
PresentT (Just "Hello")
>>> pz @(StripL "xyz" Id) "xywHello"
PresentT Nothing
Instances
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 :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (StripL p q :: Type) x

data IsPrefix p q Source #

similar to isPrefixOf for strings

>>> pl @(IsPrefix "xy" Id) "xyzabw"
True (IsPrefix(xy) xyzabw)
TrueT
>>> pl @(IsPrefix "ab" Id) "xyzbaw"
False (IsPrefix(ab) xyzbaw)
FalseT
Instances
P (IsPrefixT p q) x => P (IsPrefix p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsPrefix p q) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (IsPrefix p q :: Type) x

data IsInfix p q Source #

similar to isInfixOf for strings

>>> pl @(IsInfix "ab" Id) "xyzabw"
True (IsInfix(ab) xyzabw)
TrueT
>>> pl @(IsInfix "aB" Id) "xyzAbw"
False (IsInfix(aB) xyzAbw)
FalseT
>>> pl @(IsInfix "ab" Id) "xyzbaw"
False (IsInfix(ab) xyzbaw)
FalseT
>>> pl @(IsInfix (Fst Id) (Snd Id)) ("ab","xyzabw")
True (IsInfix(ab) xyzabw)
TrueT
Instances
P (IsInfixT p q) x => P (IsInfix p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsInfix p q) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (IsInfix p q :: Type) x

data IsSuffix p q Source #

similar to isSuffixOf for strings

>>> pl @(IsSuffix "bw" Id) "xyzabw"
True (IsSuffix(bw) xyzabw)
TrueT
>>> pl @(IsSuffix "bw" Id) "xyzbaw"
False (IsSuffix(bw) xyzbaw)
FalseT
Instances
P (IsSuffixT p q) x => P (IsSuffix p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsSuffix p q) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (IsSuffix p q :: Type) x

data IsPrefixI p q Source #

similar to case insensitive isPrefixOf for strings

Instances
P (IsPrefixIT p q) x => P (IsPrefixI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsPrefixI p q) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (IsPrefixI p q :: Type) x

data IsInfixI p q Source #

similar to case insensitive isInfixOf for strings

>>> pl @(IsInfixI "aB" Id) "xyzAbw"
True (IsInfixI(aB) xyzAbw)
TrueT
Instances
P (IsInfixIT p q) x => P (IsInfixI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsInfixI p q) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (IsInfixI p q :: Type) x

data IsSuffixI p q Source #

similar to case insensitive isSuffixOf for strings

Instances
P (IsSuffixIT p q) x => P (IsSuffixI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsSuffixI p q) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (IsSuffixI p q :: Type) x

data ToString p Source #

very simple conversion to a string

Instances
(ToStringC (PP p x), P p x) => P (ToString p :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (ToString p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.String

type PP (ToString p :: Type) x = 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"
PresentT (Identity "abc")
>>> pz @(FromString (Seq.Seq Char) Id) "abc"
PresentT (fromList "abc")
Instances
P (FromStringPT 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 :: Type Source #

Methods

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

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 s Source #

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

Defined in Predicate.Data.String

Associated Types

type PP (FromString' t s) a :: Type Source #

Methods

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

type PP (FromString' t s :: Type) a Source # 
Instance details

Defined in Predicate.Data.String

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