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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Foldable

Description

promoted foldable functions

Synopsis

Documentation

data Concat p Source #

similar to concat

>>> pz @(Concat Id) ["abc","D","eF","","G"]
PresentT "abcDeFG"
>>> pz @(Concat (Snd Id)) ('x',["abc","D","eF","","G"])
PresentT "abcDeFG"
Instances
(Show a, Show (t [a]), PP p x ~ t [a], P p x, Foldable t) => P (Concat p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Foldable

type PP (Concat p :: Type) x = ExtractAFromTA (PP p x)

data ConcatMap p q Source #

similar to concatMap

Instances
P (ConcatMapT p q) x => P (ConcatMap p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Foldable

type PP (ConcatMap p q :: Type) x

data Cycle n p Source #

similar to cycle but for a fixed number 'n'

>>> pz @(Cycle 5 Id) [1,2]
PresentT [1,2,1,2,1]
Instances
(Show a, Show (t a), PP p x ~ t a, P p x, Integral (PP n x), P n x, Foldable t) => P (Cycle n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (Cycle n p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.Foldable

type PP (Cycle n p :: Type) x = [ExtractAFromTA (PP p x)]

data FoldMap (t :: Type) p Source #

similar to a limited form of foldMap

>>> pz @(FoldMap (SG.Sum _) Id) [44, 12, 3]
PresentT 59
>>> pz @(FoldMap (SG.Product _) Id) [44, 12, 3]
PresentT 1584
>>> type Ands' p = FoldMap SG.All p
>>> pz @(Ands' Id) [True,False,True,True]
PresentT False
>>> pz @(Ands' Id) [True,True,True]
PresentT True
>>> pz @(Ands' Id) []
PresentT True
>>> type Ors' p = FoldMap SG.Any p
>>> pz @(Ors' Id) [False,False,False]
PresentT False
>>> pz @(Ors' Id) []
PresentT False
>>> pz @(Ors' Id) [False,False,False,True]
PresentT True
>>> type AllPositive' = FoldMap SG.All (Map Positive Id)
>>> pz @AllPositive' [3,1,-5,10,2,3]
PresentT False
>>> type AllNegative' = FoldMap SG.All (Map Negative Id)
>>> pz @AllNegative' [-1,-5,-10,-2,-3]
PresentT True
>>> :set -XKindSignatures
>>> type Max' (t :: Type) = FoldMap (SG.Max t) Id -- requires t be Bounded for monoid instance
>>> pz @(Max' Int) [10,4,5,12,3,4]
PresentT 12
>>> pl @(FoldMap (SG.Sum _) Id) [14,8,17,13]
Present 52 ((>>) 52 | {getSum = 52})
PresentT 52
>>> pl @(FoldMap (SG.Max _) Id) [14 :: Int,8,17,13] -- cos Bounded!
Present 17 ((>>) 17 | {getMax = 17})
PresentT 17
>>> pl @((Len >> (Elem Id '[4,7,1] || (Mod Id 3 >> Same 0))) || (FoldMap (SG.Sum _) Id >> Gt 200)) [1..20]
True (False || True)
TrueT
>>> pl @((Len >> (Elem Id '[4,7,1] || (Mod Id 3 >> Same 0))) || (FoldMap (SG.Sum _) Id >> Gt 200)) [1..19]
False (False || False | ((>>) False | {1 == 0})}) || ((>>) False | {190 > 200}))
FalseT
>>> pl @((Len >> (Elem Id '[4,7,1] || (Mod Id 3 >> Same 0))) || (FoldMap (SG.Sum _) Id >> Gt 200)) []
True (True || False)
TrueT
>>> pl @((Len >> (Elem Id '[4,7,1] || (Mod Id 3 >> Same 0))) &&& FoldMap (SG.Sum _) Id) [1..20]
Present (False,210) (W '(False,210))
PresentT (False,210)
>>> pl @(FoldMap SG.Any Id) [False,False,True,False]
Present True ((>>) True | {getAny = True})
PresentT True
>>> pl @(FoldMap SG.All Id) [False,False,True,False]
Present False ((>>) False | {getAll = False})
PresentT False
>>> pl @(FoldMap (SG.Sum _) Id) (Just 13)
Present 13 ((>>) 13 | {getSum = 13})
PresentT 13
>>> pl @(FoldMap (SG.Sum _) Id) [1..10]
Present 55 ((>>) 55 | {getSum = 55})
PresentT 55
Instances
P (FoldMapT t p) x => P (FoldMap t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (FoldMap t p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.Foldable

type PP (FoldMap t p :: Type) x

data ToListExt Source #

invokes toList

>>> pz @ToListExt (M.fromList [(1,'x'),(4,'y')])
PresentT [(1,'x'),(4,'y')]
>>> pz @ToListExt (T.pack "abc")
PresentT "abc"
Instances
(Show l, IsList l, Show (Item l)) => P ToListExt l Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP ToListExt l :: Type Source #

Methods

eval :: MonadEval m => proxy ToListExt -> POpts -> l -> m (TT (PP ToListExt l)) Source #

type PP ToListExt l Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP ToListExt l = [Item l]

data FromList (t :: Type) Source #

invokes fromList

>>> run @('OMsg "Fred" ':# 'OLite ':# 'OColorOff) @(FromList (Set.Set Int) << '[2,1,5,5,2,5,2]) ()
Fred >>> Present fromList [1,2,5] ((>>) fromList [1,2,5] | {FromList fromList [1,2,5]})
PresentT (fromList [1,2,5])
>>> pl @(FromList (M.Map _ _) >> I !! Char1 "y") [('x',True),('y',False)]
Present False ((>>) False | {IxL('y') False | p=fromList [('x',True),('y',False)] | q='y'})
PresentT False
>>> pl @(FromList (M.Map _ _) >> Id !! Char1 "z") [('x',True),('y',False)]
Error (!!) index not found (fromList [('x',True),('y',False)] (>>) rhs failed)
FailT "(!!) index not found"
Instances
(a ~ Item t, Show t, IsList t, [a] ~ x) => P (FromList t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (FromList t) x :: Type Source #

Methods

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

type PP (FromList t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP (FromList t :: Type) x = t

data FromListExt (t :: Type) Source #

invokes fromList

requires the OverloadedLists extension

>>> :set -XOverloadedLists
>>> pz @(FromListExt (M.Map _ _)) [(4,"x"),(5,"dd")]
PresentT (fromList [(4,"x"),(5,"dd")])
Instances
(Show l, IsList l, l ~ l') => P (FromListExt l' :: Type) l Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (FromListExt l') l :: Type Source #

Methods

eval :: MonadEval m => proxy (FromListExt l') -> POpts -> l -> m (TT (PP (FromListExt l') l)) Source #

type PP (FromListExt l' :: Type) l Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP (FromListExt l' :: Type) l = l'

data ToList Source #

similar to toList

>>> pz @ToList "aBc"
PresentT "aBc"
>>> pz @ToList (Just 14)
PresentT [14]
>>> pz @ToList Nothing
PresentT []
>>> pz @ToList (Left "xx")
PresentT []
>>> pz @ToList (These 12 "xx")
PresentT ["xx"]
>>> pl @ToList (M.fromList $ zip [0..] "abcd")
Present "abcd" (ToList fromList [(0,'a'),(1,'b'),(2,'c'),(3,'d')])
PresentT "abcd"
>>> pl @ToList (Just 123)
Present [123] (ToList Just 123)
PresentT [123]
>>> pl @ToList (M.fromList (zip ['a'..] [9,2,7,4]))
Present [9,2,7,4] (ToList fromList [('a',9),('b',2),('c',7),('d',4)])
PresentT [9,2,7,4]
Instances
(Show (t a), Foldable t) => P ToList (t a) Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP ToList (t a) :: Type Source #

Methods

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

type PP ToList (t a) Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP ToList (t a) = [a]

data ToList' p Source #

similar to toList

>>> pz @(ToList' Id) ("aBc" :: String)
PresentT "aBc"
>>> pz @(ToList' Id) (Just 14)
PresentT [14]
>>> pz @(ToList' Id) Nothing
PresentT []
>>> pz @(ToList' Id) (Left ("xx" :: String))
PresentT []
>>> pz @(ToList' Id) (These 12 ("xx" :: String))
PresentT ["xx"]
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t, Show a) => P (ToList' p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (ToList' p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.Foldable

type PP (ToList' p :: Type) x = [ExtractAFromTA (PP p x)]

data IToList (t :: Type) p Source #

Instances
P (IToListT t p) x => P (IToList t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (IToList t p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.Foldable

type PP (IToList t p :: Type) x

data IToList' t p Source #

similar to itoList

>>> pz @(IToList _ Id) ("aBc" :: String)
PresentT [(0,'a'),(1,'B'),(2,'c')]
>>> pl @(IToList _ Id) ("abcd" :: String)
Present [(0,'a'),(1,'b'),(2,'c'),(3,'d')] (IToList(Int) [(0,'a'),(1,'b'),(2,'c'),(3,'d')] | "abcd")
PresentT [(0,'a'),(1,'b'),(2,'c'),(3,'d')]
>>> pl @(IToList _ Id) (M.fromList $ itoList ("abcd" :: String))
Present [(0,'a'),(1,'b'),(2,'c'),(3,'d')] (IToList(Int) [(0,'a'),(1,'b'),(2,'c'),(3,'d')] | fromList [(0,'a'),(1,'b'),(2,'c'),(3,'d')])
PresentT [(0,'a'),(1,'b'),(2,'c'),(3,'d')]
>>> pl @(IToList _ Id) [9,2,7,4]
Present [(0,9),(1,2),(2,7),(3,4)] (IToList(Int) [(0,9),(1,2),(2,7),(3,4)] | [9,2,7,4])
PresentT [(0,9),(1,2),(2,7),(3,4)]
>>> pl @(IToList _ Id) (M.fromList (zip ['a'..] [9,2,7,4]))
Present [('a',9),('b',2),('c',7),('d',4)] (IToList(Char) [('a',9),('b',2),('c',7),('d',4)] | fromList [('a',9),('b',2),('c',7),('d',4)])
PresentT [('a',9),('b',2),('c',7),('d',4)]
>>> pl @(IToList _ Id) (Just 234)
Present [((),234)] (IToList(()) [((),234)] | Just 234)
PresentT [((),234)]
>>> pl @(IToList _ Id) (Nothing @Double)
Present [] (IToList(()) [] | Nothing)
PresentT []
>>> pl @(IToList _ Id) [1..5]
Present [(0,1),(1,2),(2,3),(3,4),(4,5)] (IToList(Int) [(0,1),(1,2),(2,3),(3,4),(4,5)] | [1,2,3,4,5])
PresentT [(0,1),(1,2),(2,3),(3,4),(4,5)]
>>> pl @(IToList _ Id) ['a','b','c']
Present [(0,'a'),(1,'b'),(2,'c')] (IToList(Int) [(0,'a'),(1,'b'),(2,'c')] | "abc")
PresentT [(0,'a'),(1,'b'),(2,'c')]
Instances
(Show x, P p x, Typeable (PP t (PP p x)), Show (PP t (PP p x)), FoldableWithIndex (PP t (PP p x)) f, PP p x ~ f a, Show a) => P (IToList' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (IToList' t p) x :: Type Source #

Methods

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

type PP (IToList' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP (IToList' t p :: Type) x = [(PP t (PP p x), ExtractAFromTA (PP p x))]

data ToNEList Source #

create a NonEmpty list from a Foldable

>>> pz @ToNEList []
FailT "empty list"
>>> pz @ToNEList [1,2,3,4,5]
PresentT (1 :| [2,3,4,5])
Instances
(Show (t a), Foldable t) => P ToNEList (t a) Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP ToNEList (t a) :: Type Source #

Methods

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

type PP ToNEList (t a) Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP ToNEList (t a) = NonEmpty a

data Null Source #

similar to null using Foldable

>>> pz @Null [1,2,3,4]
FalseT
>>> pz @Null []
TrueT
>>> pz @Null Nothing
TrueT
Instances
P NullT a => P Null a Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP Null a :: Type Source #

Methods

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

type PP Null a Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP Null a = Bool

data Null' p Source #

Instances
(Show (t a), Foldable t, t a ~ PP p x, P p x) => P (Null' p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (Null' p) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.Foldable

type PP (Null' p :: Type) x = Bool

data IsEmpty Source #

similar to null using AsEmpty

>>> pz @IsEmpty [1,2,3,4]
FalseT
>>> pz @IsEmpty []
TrueT
>>> pz @IsEmpty LT
FalseT
>>> pz @IsEmpty EQ
TrueT
>>> pl @IsEmpty ("failed11" :: T.Text)
False (IsEmpty | "failed11")
FalseT
>>> pl @IsEmpty ("" :: T.Text)
True (IsEmpty | "")
TrueT
Instances
(Show as, AsEmpty as) => P IsEmpty as Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP IsEmpty as :: Type Source #

Methods

eval :: MonadEval m => proxy IsEmpty -> POpts -> as -> m (TT (PP IsEmpty as)) Source #

type PP IsEmpty as Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP IsEmpty as = Bool