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

Predicate.Data.Foldable

Description

promoted foldable functions

Synopsis

Documentation

data Concat Source #

similar to concat

>>> pz @Concat ["abc","D","eF","","G"]
Val "abcDeFG"
>>> pz @(Lift Concat Snd) ('x',["abc","D","eF","","G"])
Val "abcDeFG"

Instances

Instances details
Show Concat Source # 
Instance details

Defined in Predicate.Data.Foldable

(Show a, Show x, x ~ t [a], Foldable t) => P Concat x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP Concat x Source #

Methods

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

type PP Concat x Source # 
Instance details

Defined in Predicate.Data.Foldable

data ConcatMap p q Source #

similar to concatMap

Instances

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

Methods

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

Show (ConcatMap p q) Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

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

show :: ConcatMap p q -> String #

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

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]
Val [1,2,1,2,1]

Instances

Instances details
(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 Source #

Methods

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

Show (Cycle n p) Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> Cycle n p -> ShowS #

show :: Cycle n p -> String #

showList :: [Cycle n p] -> ShowS #

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 #

wraps each item in the foldable container and then unwraps the mconcatenated result: uses Wrapped

>>> pz @(FoldMap (SG.Sum _) Id) [44, 12, 3]
Val 59
>>> pz @(FoldMap (SG.Product _) Id) [44, 12, 3]
Val 1584
>>> type Ands' p = FoldMap SG.All p
>>> pz @(Ands' Id) [True,False,True,True]
Val False
>>> pz @(Ands' Id) [True,True,True]
Val True
>>> pz @(Ands' Id) []
Val True
>>> type Ors' p = FoldMap SG.Any p
>>> pz @(Ors' Id) [False,False,False]
Val False
>>> pz @(Ors' Id) []
Val False
>>> pz @(Ors' Id) [False,False,False,True]
Val True
>>> type AllPositive' = FoldMap SG.All (Map Positive)
>>> pz @AllPositive' [3,1,-5,10,2,3]
Val False
>>> type AllNegative' = FoldMap SG.All (Map Negative)
>>> pz @AllNegative' [-1,-5,-10,-2,-3]
Val 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]
Val 12
>>> pl @(FoldMap (SG.Sum _) Id) [14,8,17,13]
Present 52 ((>>) 52 | {getSum = 52})
Val 52
>>> pl @(FoldMap (SG.Max _) Id) [14 :: Int,8,17,13] -- allowed as the values are Bounded!
Present 17 ((>>) 17 | {getMax = 17})
Val 17
>>> pl @((Len >> (Elem Id '[4,7,1] || (Mod Id 3 >> Same 0))) || (FoldMap (SG.Sum _) Id >> Gt 200)) [1..20]
True (False || True)
Val True
>>> 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}))
Val False
>>> pl @((Len >> (Elem Id '[4,7,1] || (Mod Id 3 >> Same 0))) || (FoldMap (SG.Sum _) Id >> Gt 200)) []
True (True || False)
Val True
>>> pl @((Len >> (Elem Id '[4,7,1] || (Mod Id 3 >> Same 0))) &&& FoldMap (SG.Sum _) Id) [1..20]
Present (False,210) ('(False,210))
Val (False,210)
>>> pl @(FoldMap SG.Any Id) [False,False,True,False]
Present True ((>>) True | {getAny = True})
Val True
>>> pl @(FoldMap SG.All Id) [False,False,True,False]
Present False ((>>) False | {getAll = False})
Val False
>>> pl @(FoldMap (SG.Sum _) Id) (Just 13)
Present 13 ((>>) 13 | {getSum = 13})
Val 13
>>> pl @(FoldMap (SG.Sum _) Id) [1..10]
Present 55 ((>>) 55 | {getSum = 55})
Val 55

Instances

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

Methods

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

Show (FoldMap t p) Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> FoldMap t p -> ShowS #

show :: FoldMap t p -> String #

showList :: [FoldMap t p] -> ShowS #

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')])
Val [(1,'x'),(4,'y')]
>>> pz @ToListExt (T.pack "abc")
Val "abc"

Instances

Instances details
Show ToListExt Source # 
Instance details

Defined in Predicate.Data.Foldable

(Show l, IsList l, Show (Item l)) => P ToListExt l Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP ToListExt l 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]})
Val (fromList [1,2,5])
>>> pl @(FromList (M.Map _ _) >> Id !! C "y") [('x',True),('y',False)]
Present False ((>>) False | {IxL('y') False | p=fromList [('x',True),('y',False)] | q='y'})
Val False
>>> pl @(FromList (M.Map _ _) >> Id !! C "z") [('x',True),('y',False)]
Error (!!) index not found (IxL('z') | fromList [('x',True),('y',False)])
Fail "(!!) index not found"
>>> pl @(FromList (M.Map _ _)) [(4,"x"),(5,"dd")]
Present fromList [(4,"x"),(5,"dd")] (FromList fromList [(4,"x"),(5,"dd")])
Val (fromList [(4,"x"),(5,"dd")])

Instances

Instances details
Show (FromList t) Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> FromList t -> ShowS #

show :: FromList t -> String #

showList :: [FromList t] -> ShowS #

(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 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")]
Val (fromList [(4,"x"),(5,"dd")])

Instances

Instances details
Show (FromListExt t) Source # 
Instance details

Defined in Predicate.Data.Foldable

(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 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"
Val "aBc"
>>> pz @ToList (Just 14)
Val [14]
>>> pz @ToList Nothing
Val []
>>> pz @ToList (Left "xx")
Val []
>>> pz @ToList (These 12 "xx")
Val ["xx"]
>>> pl @ToList (M.fromList $ zip [0..] "abcd")
Present "abcd" (ToList fromList [(0,'a'),(1,'b'),(2,'c'),(3,'d')])
Val "abcd"
>>> pl @ToList (Just 123)
Present [123] (ToList Just 123)
Val [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)])
Val [9,2,7,4]

Instances

Instances details
Show ToList Source # 
Instance details

Defined in Predicate.Data.Foldable

(Show (t a), Foldable t) => P ToList (t a) Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP ToList (t a) 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 IToList (t :: Type) Source #

similar to itoList

>>> pz @(IToList _) ("aBc" :: String)
Val [(0,'a'),(1,'B'),(2,'c')]
>>> pl @(IToList _) ("abcd" :: String)
Present [(0,'a'),(1,'b'),(2,'c'),(3,'d')] (IToList(Int) [(0,'a'),(1,'b'),(2,'c'),(3,'d')] | "abcd")
Val [(0,'a'),(1,'b'),(2,'c'),(3,'d')]
>>> pl @(IToList _) (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')])
Val [(0,'a'),(1,'b'),(2,'c'),(3,'d')]
>>> pl @(IToList _) [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])
Val [(0,9),(1,2),(2,7),(3,4)]
>>> pl @(IToList _) (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)])
Val [('a',9),('b',2),('c',7),('d',4)]
>>> pl @(IToList _) (Just 234)
Present [((),234)] (IToList(()) [((),234)] | Just 234)
Val [((),234)]
>>> pl @(IToList _) (Nothing @Double)
Present [] (IToList(()) [] | Nothing)
Val []
>>> pl @(IToList _) [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])
Val [(0,1),(1,2),(2,3),(3,4),(4,5)]
>>> pl @(IToList _) ['a','b','c']
Present [(0,'a'),(1,'b'),(2,'c')] (IToList(Int) [(0,'a'),(1,'b'),(2,'c')] | "abc")
Val [(0,'a'),(1,'b'),(2,'c')]

Instances

Instances details
Show (IToList t) Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> IToList t -> ShowS #

show :: IToList t -> String #

showList :: [IToList t] -> ShowS #

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

Defined in Predicate.Data.Foldable

Associated Types

type PP (IToList t) x Source #

Methods

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

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

Defined in Predicate.Data.Foldable

type PP (IToList t :: Type) x

data IToList' t Source #

Instances

Instances details
(Show (f a), Typeable (PP t x), Show (PP t x), FoldableWithIndex (PP t x) f, x ~ f a, Show a) => P (IToList' t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (IToList' t) x Source #

Methods

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

Show (IToList' t) Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> IToList' t -> ShowS #

show :: IToList' t -> String #

showList :: [IToList' t] -> ShowS #

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

Defined in Predicate.Data.Foldable

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

data ToNEList Source #

create a NonEmpty list from a Foldable

>>> pz @ToNEList []
Fail "empty list"
>>> pz @ToNEList [1,2,3,4,5]
Val (1 :| [2,3,4,5])

Instances

Instances details
Show ToNEList Source # 
Instance details

Defined in Predicate.Data.Foldable

(Show (t a), Foldable t) => P ToNEList (t a) Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP ToNEList (t a) 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]
Val False
>>> pz @Null []
Val True
>>> pz @Null Nothing
Val True

Instances

Instances details
Show Null Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> Null -> ShowS #

show :: Null -> String #

showList :: [Null] -> ShowS #

P NullT a => P Null a Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP Null a 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

Instances details
(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 Source #

Methods

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

Show (Null' p) Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> Null' p -> ShowS #

show :: Null' p -> String #

showList :: [Null' p] -> ShowS #

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]
Val False
>>> pz @IsEmpty []
Val True
>>> pz @IsEmpty LT
Val False
>>> pz @IsEmpty EQ
Val True
>>> pl @IsEmpty ("failed11" :: T.Text)
False (IsEmpty | "failed11")
Val False
>>> pl @IsEmpty ("" :: T.Text)
True (IsEmpty | "")
Val True

Instances

Instances details
Show IsEmpty Source # 
Instance details

Defined in Predicate.Data.Foldable

(Show as, AsEmpty as) => P IsEmpty as Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP IsEmpty as 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

data Ands Source #

similar to and

>>> pz @Ands [True,True,True]
Val True
>>> pl @Ands [True,True,True,False]
False (Ands(4) i=3 | [True,True,True,False])
Val False
>>> pz @Ands []
Val True

Instances

Instances details
Show Ands Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> Ands -> ShowS #

show :: Ands -> String #

showList :: [Ands] -> ShowS #

(x ~ t a, Show (t a), Foldable t, a ~ Bool) => P Ands x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP Ands x Source #

Methods

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

type PP Ands x Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP Ands x = Bool

data Ors Source #

similar to or

>>> pz @Ors [False,False,False]
Val False
>>> pl @Ors [True,True,True,False]
True (Ors(4) i=0 | [True,True,True,False])
Val True
>>> pl @Ors []
False (Ors(0) | [])
Val False

Instances

Instances details
Show Ors Source # 
Instance details

Defined in Predicate.Data.Foldable

Methods

showsPrec :: Int -> Ors -> ShowS #

show :: Ors -> String #

showList :: [Ors] -> ShowS #

(x ~ t a, Show x, Foldable t, a ~ Bool) => P Ors x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP Ors x Source #

Methods

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

type PP Ors x Source # 
Instance details

Defined in Predicate.Data.Foldable

type PP Ors x = Bool