Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
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")
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})
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})
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"
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"
type S a = WrappedMonoid a #
synonym for wrapping a monoid
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}))
similar to mempty
>>>
pl @(MEmptyT' Id) (Just (SG.Sum 12))
Present Nothing (MEmptyT Nothing) Val Nothing