| Copyright | (c) Justin Le 2019 |
|---|---|
| License | BSD3 |
| Maintainer | justin@jle.im |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Functor.Invariant.DivAp
Contents
Description
Synopsis
- newtype DivAp f a where
- runCoDivAp :: forall f g. Applicative g => (f ~> g) -> DivAp f ~> g
- runContraDivAp :: forall f g. Divisible g => (f ~> g) -> DivAp f ~> g
- divApAp :: DivAp f ~> Ap f
- divApDiv :: DivAp f ~> Div f
- foldDivAp :: (forall x. x -> g x) -> (Day f g ~> g) -> DivAp f ~> g
- gather :: (a -> (b, c)) -> (b -> c -> a) -> DivAp f b -> DivAp f c -> DivAp f a
- gathered :: DivAp f a -> DivAp f b -> DivAp f (a, b)
- assembleDivAp :: NP f as -> DivAp f (NP I as)
- assembleDivApRec :: Rec f as -> DivAp f (XRec Identity as)
- concatDivAp :: NP (DivAp f) as -> DivAp f (NP I as)
- concatDivApRec :: Rec (DivAp f) as -> DivAp f (XRec Identity as)
- newtype DivAp1 f a where
- runCoDivAp1 :: forall f g. Apply g => (f ~> g) -> DivAp1 f ~> g
- runContraDivAp1 :: forall f g. Divise g => (f ~> g) -> DivAp1 f ~> g
- divApAp1 :: DivAp1 f ~> Ap1 f
- divApDiv1 :: DivAp1 f ~> Div1 f
- foldDivAp1 :: (f ~> g) -> (Day f g ~> g) -> DivAp1 f ~> g
- gather1 :: Invariant f => (a -> (b, c)) -> (b -> c -> a) -> DivAp1 f b -> DivAp1 f c -> DivAp1 f a
- gathered1 :: Invariant f => DivAp1 f a -> DivAp1 f b -> DivAp1 f (a, b)
- assembleDivAp1 :: Invariant f => NP f (a ': as) -> DivAp1 f (NP I (a ': as))
- assembleDivAp1Rec :: Invariant f => Rec f (a ': as) -> DivAp1 f (XRec Identity (a ': as))
- concatDivAp1 :: Invariant f => NP (DivAp1 f) (a ': as) -> DivAp1 f (NP I (a ': as))
- concatDivAp1Rec :: Invariant f => Rec (DivAp1 f) (a ': as) -> DivAp1 f (XRec Identity (a ': as))
- runDayApply :: forall f g h. Apply h => (f ~> h) -> (g ~> h) -> Day f g ~> h
- runDayDivise :: forall f g h. Divise h => (f ~> h) -> (g ~> h) -> Day f g ~> h
Chain
The invariant version of Ap and Div: combines the capabilities of
both Ap and Div together.
Conceptually you can think of as a way of consuming and
producing DivAp f aas that contains a collection of f xs of different xs.
When interpreting this, each a is distributed across all f xs to
each interpret, and then re-combined again to produce the resulting a.
You run this in any Applicative context if you want to interpret it
covariantly, treating as a producer of DivAp f aa, using
runCoDivAp. You can run this in any Divisible context if you you
want to interpret it contravariantly, treating as
a consumer of DivAp f aas, using runContraDivAp.
Because there is no typeclass that combines both Applicative and
Divisible, this type is a little bit tricker to construct/use than
Ap or Div.
- Instead of
<*>anddivide(typeclass methods), usegatherand other variants, which work specifically on this type only. - Instead of
pureandconquer(typeclass methods), useKnot. - Instead of using
interpret(to run in a typeclass), either userunCoDivAp(to run inApplicative),runContraDivAp(to run inDivisible), orfoldDivAp(to interpret by manually providing handlers)
You can also extract the Ap part out using divApAp, and extract the
Div part out using divApDiv.
Note that this type's utility is similar to that of ,
except PreT Ap lets you use PreT ApApplicative typeclass methods to
assemble it.
Since: 0.3.5.0
Bundled Patterns
| pattern Gather :: (a -> (b, c)) -> (b -> c -> a) -> f b -> DivAp f c -> DivAp f a | Match on a non-empty |
| pattern Knot :: a -> DivAp f a | Match on an "empty" |
runCoDivAp :: forall f g. Applicative g => (f ~> g) -> DivAp f ~> g Source #
In the covariant direction, we can interpret out of a Chain of Day
into any Applicative.
assembleDivAp :: NP f as -> DivAp f (NP I as) Source #
Convenient wrapper to build up a DivAp by providing each
component of it. This makes it much easier to build up longer chains
because you would only need to write the splitting/joining functions in
one place.
For example, if you had a data type
data MyType = MT Int Bool String
and an invariant functor Prim (representing, say, a bidirectional
parser, where Prim Int is a bidirectional parser for an Int),
then you could assemble a bidirectional parser for a MyType@ using:
invmap ((MyType x y z) -> I x :* I y :* I z :* Nil)
((I x :* I y :* I z :* Nil) -> MyType x y z) $
assembleDivAp $ intPrim
:* boolPrim
:* stringPrim
:* Nil
Some notes on usefulness depending on how many components you have:
- If you have 0 components, use
Knotdirectly. - If you have 1 component, use
injectorinjectChaindirectly. - If you have 2 components, use
toListByortoChain. - If you have 3 or more components, these combinators may be useful; otherwise you'd need to manually peel off tuples one-by-one.
assembleDivApRec :: Rec f as -> DivAp f (XRec Identity as) Source #
A version of assembleDivAp using XRec from vinyl instead of
NP from sop-core. This can be more convenient because it doesn't
require manual unwrapping/wrapping of components.
data MyType = MT Int Bool String
invmap ((MyType x y z) -> x ::& y ::& z ::& RNil)
((x ::& y ::& z ::& RNil) -> MyType x y z) $
assembleDivApRec $ intPrim
:& boolPrim
:& stringPrim
:& Nil
concatDivAp :: NP (DivAp f) as -> DivAp f (NP I as) Source #
A version of assembleDivAp where each component is itself
a DivAp.
assembleDivAp (x :* y :* z :* Nil) = concatDivAp (injectChain x :* injectChain y :* injectChain z :* Nil)
concatDivApRec :: Rec (DivAp f) as -> DivAp f (XRec Identity as) Source #
A version of concatDivAp using XRec from vinyl instead of
NP from sop-core. This can be more convenient because it doesn't
require manual unwrapping/wrapping of components.
Nonempty Chain
The invariant version of Ap1 and Div1: combines the capabilities
of both Ap1 and Div1 together.
Conceptually you can think of as a way of consuming and
producing DivAp1 f aas that contains a (non-empty) collection of f xs of
different xs. When interpreting this, each a is distributed across
all f xs to each interpret, and then re-combined again to produce the
resulting a.
You run this in any Apply context if you want to interpret it
covariantly, treating as a producer of DivAp1 f aa, using
runCoDivAp1. You can run this in any Divise context if you you
want to interpret it contravariantly, treating as
a consumer of DivAp1 f aas, using runContraDivAp1.
Because there is no typeclass that combines both Apply and
Divise, this type is a little bit tricker to construct/use than
Ap1 or Div1.
- Instead of
<.>anddivide(typeclass methods), usegather1and other variants, which work specifically on this type only. - Instead of using
interpret(to run in a typeclass), either userunCoDivAp1(to run inApply),runContraDivAp1(to run inDivise), orfoldDivAp1(to interpret by manually providing handlers)
You can also extract the Ap1 part out using divApAp1, and extract the
Div1 part out using divApDiv1.
Note that this type's utility is similar to that of ,
except PreT Ap1 lets you use PreT Ap1Apply typeclass methods to assemble
it.
Since: 0.3.5.0
Bundled Patterns
| pattern DivAp1 :: Invariant f => (a -> (b, c)) -> (b -> c -> a) -> f b -> DivAp f c -> DivAp1 f a | Match on a |
gather1 :: Invariant f => (a -> (b, c)) -> (b -> c -> a) -> DivAp1 f b -> DivAp1 f c -> DivAp1 f a Source #
assembleDivAp1 :: Invariant f => NP f (a ': as) -> DivAp1 f (NP I (a ': as)) Source #
A version of assembleDivAp but for DivAp1 instead. Can be
useful if you intend on interpreting it into something with only
a Divise or Apply instance, but no Divisible or Applicative.
assembleDivAp1Rec :: Invariant f => Rec f (a ': as) -> DivAp1 f (XRec Identity (a ': as)) Source #
A version of assembleDivAp1 using XRec from vinyl instead of
NP from sop-core. This can be more convenient because it doesn't
require manual unwrapping/wrapping of components.
concatDivAp1 :: Invariant f => NP (DivAp1 f) (a ': as) -> DivAp1 f (NP I (a ': as)) Source #
A version of concatDivAp but for DivAp1 instead. Can be
useful if you intend on interpreting it into something with only
a Divise or Apply instance, but no Divisible or Applicative.
concatDivAp1Rec :: Invariant f => Rec (DivAp1 f) (a ': as) -> DivAp1 f (XRec Identity (a ': as)) Source #
A version of concatDivAp1 using XRec from vinyl instead of
NP from sop-core. This can be more convenient because it doesn't
require manual unwrapping/wrapping of components.