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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Monoid

Contents

Description

promoted Semigroup and Monoid functions

Synopsis

semigroup / monoid expressions

data p <> q infixr 6 Source #

similar to <>

>>> pz @(Fst Id <> Snd Id) ("abc","def")
PresentT "abcdef"
>>> pz @("abcd" <> "ef" <> Id) "ghi"
PresentT "abcdefghi"
>>> pz @("abcd" <> "ef" <> Id) "ghi"
PresentT "abcdefghi"
>>> pz @(Wrap (SG.Sum _) Id <> FromInteger _ 10) 13
PresentT (Sum {getSum = 23})
>>> pz @(Wrap (SG.Product _) Id <> FromInteger _ 10) 13
PresentT (Product {getProduct = 130})
>>> pz @('(FromInteger _ 10,"def") <> Id) (SG.Sum 12, "_XYZ")
PresentT (Sum {getSum = 22},"def_XYZ")
>>> pz @(SapA' (SG.Max _)) (10,12)
PresentT (Max {getMax = 12})
>>> pz @(SapA' (SG.Sum _)) (10,12)
PresentT (Sum {getSum = 22})
>>> pl @((Id <> Id) >> Unwrap Id) (SG.Sum 12)
Present 24 ((>>) 24 | {getSum = 24})
PresentT 24
Instances
(Semigroup (PP p x), PP p x ~ PP q x, P p x, Show (PP q x), P q x) => P (p <> q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP (p <> q) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.Monoid

type PP (p <> q :: Type) x = PP p x

data MConcat p Source #

similar to mconcat

>>> pz @(MConcat Id) [SG.Sum 44, SG.Sum 12, SG.Sum 3]
PresentT (Sum {getSum = 59})
>>> pz @(Map '(Pure SG.Sum Id, Pure SG.Max Id) Id >> MConcat Id) [7 :: Int,6,1,3,5] -- monoid so need eg Int
PresentT (Sum {getSum = 22},Max {getMax = 7})
Instances
(PP p x ~ [a], P p x, Show a, Monoid a) => P (MConcat p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Monoid

type PP (MConcat p :: Type) x = ExtractAFromList (PP p x)

data SConcat p Source #

similar to sconcat

>>> pz @(ToNEList >> SConcat Id) [SG.Sum 44, SG.Sum 12, SG.Sum 3]
PresentT (Sum {getSum = 59})
>>> pz @(Map '(Pure SG.Sum Id, Pure SG.Max Id) Id >> ToNEList >> SConcat Id) [7,6,1,3,5]
PresentT (Sum {getSum = 22},Max {getMax = 7})
Instances
(PP p x ~ NonEmpty a, P p x, Show a, Semigroup a) => P (SConcat p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Monoid

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

data STimes n p Source #

similar to stimes

>>> pz @(STimes 4 Id) (SG.Sum 3)
PresentT (Sum {getSum = 12})
>>> pz @(STimes 4 Id) "ab"
PresentT "abababab"
>>> pl @(STimes 4 Id) (SG.Sum 13)
Present Sum {getSum = 52} (STimes 4 p=Sum {getSum = 13} Sum {getSum = 52} | n=4 | Sum {getSum = 13})
PresentT (Sum {getSum = 52})
>>> pl @(STimes (Fst Id) (Snd Id)) (4,['x','y'])
Present "xyxyxyxy" (STimes 4 p="xy" "xyxyxyxy" | n=4 | "xy")
PresentT "xyxyxyxy"
>>> pl @(STimes (Fst Id) (Snd Id)) (4,"abc")
Present "abcabcabcabc" (STimes 4 p="abc" "abcabcabcabc" | n=4 | "abc")
PresentT "abcabcabcabc"
>>> pl @(STimes 4 Id) "abc"
Present "abcabcabcabc" (STimes 4 p="abc" "abcabcabcabc" | n=4 | "abc")
PresentT "abcabcabcabc"
Instances
(P n a, Integral (PP n a), Semigroup (PP p a), P p a, Show (PP p a)) => P (STimes n p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP (STimes n p) a :: Type Source #

Methods

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

type PP (STimes n p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Monoid

type PP (STimes n p :: Type) a = PP p a

data SapA Source #

semigroup append both sides of a tuple (ie uncurry (<>))

>>> pz @(Snd Id >> SapA) (4,("abc","def"))
PresentT "abcdef"
Instances
P SapAT x => P SapA x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP SapA x :: Type Source #

Methods

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

type PP SapA x Source # 
Instance details

Defined in Predicate.Data.Monoid

type PP SapA x

data SapA' (t :: Type) Source #

semigroup append both sides of a tuple (ie uncurry (<>)) using Wrap

>>> pl @(SapA' (SG.Sum _) >> Unwrap Id) (4,5)
Present 9 ((>>) 9 | {getSum = 9})
PresentT 9
Instances
P (SapAT' t) x => P (SapA' t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP (SapA' t) x :: Type Source #

Methods

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

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

Defined in Predicate.Data.Monoid

type PP (SapA' t :: Type) x

data MEmptyT (t :: Type) Source #

similar to mempty

>>> pz @(MEmptyT (SG.Sum Int)) ()
PresentT (Sum {getSum = 0})
>>> pl @(MEmptyT _ ||| Ones Id) (Right "abc")
Present ["a","b","c"] ((|||) Right ["a","b","c"] | "abc")
PresentT ["a","b","c"]
>>> pl @(MEmptyT _ ||| Ones Id) (Left ["ab"])
Present [] ((|||) Left [] | ["ab"])
PresentT []
>>> pl @(MEmptyT (Maybe ())) 'x'
Present Nothing (MEmptyT Nothing)
PresentT Nothing
Instances
P (MEmptyTT t) x => P (MEmptyT t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Monoid

type PP (MEmptyT t :: Type) x

data MEmptyT' t Source #

similar to mempty

>>> pl @(MEmptyT' Id) (Just (SG.Sum 12))
Present Nothing (MEmptyT Nothing)
PresentT Nothing
>>> pl @(MEmptyT (SG.Sum _) >> Unwrap Id >> Id + 4) ()
Present 4 ((>>) 4 | {0 + 4 = 4})
PresentT 4
Instances
(Show (PP t a), Monoid (PP t a)) => P (MEmptyT' t :: Type) a Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP (MEmptyT' t) a :: Type Source #

Methods

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

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

Defined in Predicate.Data.Monoid

type PP (MEmptyT' t :: Type) a = PP t a

data MEmptyP Source #

creates a mempty value for the proxy

>>> pl @('Proxy >> MEmptyP) "abc"
Present "" ((>>) "" | {MEmptyT ""})
PresentT ""
Instances
P MEmptyPT x => P MEmptyP x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP MEmptyP x :: Type Source #

Methods

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

type PP MEmptyP x Source # 
Instance details

Defined in Predicate.Data.Monoid

type PP MEmptyP x

data MEmpty2 (t :: Type) Source #

lift mempty over a Functor

>>> pz @(MEmpty2 (SG.Product Int)) [Identity (-13), Identity 4, Identity 99]
PresentT [Product {getProduct = 1},Product {getProduct = 1},Product {getProduct = 1}]
>>> pl @(MEmpty2 (SG.Sum _)) (Just ())
Present Just (Sum {getSum = 0}) (MEmpty2 Just (Sum {getSum = 0}) | Just ())
PresentT (Just (Sum {getSum = 0}))
Instances
P (MEmpty2T t) x => P (MEmpty2 t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Monoid

type PP (MEmpty2 t :: Type) x

data MEmpty2' t Source #

lift mempty over a Functor

Instances
(Show (f a), Show (f (PP t (f a))), Functor f, Monoid (PP t (f a))) => P (MEmpty2' t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP (MEmpty2' t) (f a) :: Type Source #

Methods

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

type PP (MEmpty2' t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Data.Monoid

type PP (MEmpty2' t :: Type) (f a) = f (PP t (f a))