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

Predicate.Data.Monoid

Description

promoted Semigroup and Monoid functions

Synopsis

Documentation

data p <> q infixr 6 Source #

similar to <>

>>> pz @(Fst <> Snd) ("abc","def")
Val "abcdef"
>>> pz @("abcd" <> "ef" <> Id) "ghi"
Val "abcdefghi"
>>> pz @("abcd" <> "ef" <> Id) "ghi"
Val "abcdefghi"
>>> pz @(Wrap (SG.Sum _) Id <> (10 >> FromInteger _)) 13
Val (Sum {getSum = 23})
>>> pz @(Wrap (SG.Product _) Id <> Lift (FromInteger _) 10) 13
Val (Product {getProduct = 130})
>>> pz @('(10 >> FromInteger _,"def") <> Id) (SG.Sum 12, "_XYZ")
Val (Sum {getSum = 22},"def_XYZ")

Instances

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

Methods

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

Show (p <> q) Source # 
Instance details

Defined in Predicate.Data.Monoid

Methods

showsPrec :: Int -> (p <> q) -> ShowS #

show :: (p <> q) -> String #

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

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]
Val (Sum {getSum = 59})
>>> pz @(Map '(Pure SG.Sum Id, Pure SG.Max Id) >> MConcat Id) [7 :: Int,6,1,3,5] -- monoid so need eg Int
Val (Sum {getSum = 22},Max {getMax = 7})

Instances

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

Methods

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

Show (MConcat p) Source # 
Instance details

Defined in Predicate.Data.Monoid

Methods

showsPrec :: Int -> MConcat p -> ShowS #

show :: MConcat p -> String #

showList :: [MConcat p] -> ShowS #

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]
Val (Sum {getSum = 59})
>>> pz @(Map '(Pure SG.Sum Id, Pure SG.Max Id) >> ToNEList >> SConcat Id) [7,6,1,3,5]
Val (Sum {getSum = 22},Max {getMax = 7})

Instances

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

Methods

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

Show (SConcat p) Source # 
Instance details

Defined in Predicate.Data.Monoid

Methods

showsPrec :: Int -> SConcat p -> ShowS #

show :: SConcat p -> String #

showList :: [SConcat p] -> ShowS #

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)
Val (Sum {getSum = 12})
>>> pz @(STimes 4 Id) "ab"
Val "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})
Val (Sum {getSum = 52})
>>> pl @(STimes Fst Snd) (4,['x','y'])
Present "xyxyxyxy" (STimes 4 p="xy" "xyxyxyxy" | n=4 | "xy")
Val "xyxyxyxy"
>>> pl @(STimes Fst Snd) (4,"abc")
Present "abcabcabcabc" (STimes 4 p="abc" "abcabcabcabc" | n=4 | "abc")
Val "abcabcabcabc"
>>> pl @(STimes 4 Id) "abc"
Present "abcabcabcabc" (STimes 4 p="abc" "abcabcabcabc" | n=4 | "abc")
Val "abcabcabcabc"

Instances

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

Methods

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

Show (STimes n p) Source # 
Instance details

Defined in Predicate.Data.Monoid

Methods

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

show :: STimes n p -> String #

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

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 Sap (t :: Type) Source #

semigroup append both sides of a tuple (ie uncurry (<>)) using Wrap and then unwraps the final result

>>> pz @(Sap (SG.Sum _)) (4,5)
Val 9
>>> pz @(Sap (SG.Sum _)) (13,44)
Val 57
>>> pz @(Sap SG.Any) (True,False)
Val True
>>> pz @(Sap SG.All) (True,False)
Val False
>>> pz @(Sap (SG.Max _)) (10,12)
Val 12
>>> pz @(Sap (SG.Sum _)) (10,12)
Val 22
>>> pz @(Sap (S _)) ("abc","def")
Val "abcdef"
>>> pz @(Fst <> Snd) ("abc","def") -- same as above but more direct
Val "abcdef"

Instances

Instances details
Show (Sap t) Source # 
Instance details

Defined in Predicate.Data.Monoid

Methods

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

show :: Sap t -> String #

showList :: [Sap t] -> ShowS #

P (SapT t) x => P (Sap t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP (Sap t) x Source #

Methods

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

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

Defined in Predicate.Data.Monoid

type PP (Sap t :: Type) x

type S a = WrappedMonoid a Source #

synonym for wrapping a monoid

data MEmptyT (t :: Type) Source #

similar to mempty

>>> pz @(MEmptyT (SG.Sum Int)) ()
Val (Sum {getSum = 0})
>>> pl @(MEmptyT _ ||| Ones) (Right "abc")
Present ["a","b","c"] ((|||) Right ["a","b","c"] | "abc")
Val ["a","b","c"]
>>> pl @(MEmptyT _ ||| Ones) (Left ["ab"])
Present [] ((|||) Left [] | ["ab"])
Val []
>>> pl @(MEmptyT (Maybe ())) 'x'
Present Nothing (MEmptyT Nothing)
Val Nothing
>>> pl @(MEmptyT (SG.Sum _) >> Unwrap >> Id + 4) ()
Present 4 ((>>) 4 | {0 + 4 = 4})
Val 4
>>> pz @(FMap (MEmptyT (SG.Product Int))) [Identity (-13), Identity 4, Identity 99]
Val [Product {getProduct = 1},Product {getProduct = 1},Product {getProduct = 1}]
>>> pl @(FMap (MEmptyT (SG.Sum _))) (Just ())
Present Just (Sum {getSum = 0}) (FMap MEmptyT Sum {getSum = 0})
Val (Just (Sum {getSum = 0}))

Instances

Instances details
Show (MEmptyT t) Source # 
Instance details

Defined in Predicate.Data.Monoid

Methods

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

show :: MEmptyT t -> String #

showList :: [MEmptyT t] -> ShowS #

P (MEmptyTT t) x => P (MEmptyT t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP (MEmptyT t) x 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)
Val Nothing

Instances

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

Methods

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

Show (MEmptyT' t) Source # 
Instance details

Defined in Predicate.Data.Monoid

Methods

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

show :: MEmptyT' t -> String #

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

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

Instances

Instances details
Show MEmptyP Source # 
Instance details

Defined in Predicate.Data.Monoid

P MEmptyPT x => P MEmptyP x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP MEmptyP x 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