Copyright | (c) Justin Le 2021 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Contains the classes Inply
and Inplicative
, the invariant
counterparts to Apply
Divise
and Applicative
Divisible
.
Since: 0.4.0.0
Synopsis
- class Invariant f => Inply f where
- class Inply f => Inplicative f where
- knot :: a -> f a
- newtype WrappedApplicativeOnly f a = WrapApplicativeOnly {
- unwrapApplicativeOnly :: f a
- newtype WrappedDivisibleOnly f a = WrapDivisibleOnly {
- unwrapDivisibleOnly :: f a
- runDay :: Inply h => (f ~> h) -> (g ~> h) -> Day f g ~> h
- dather :: Inply f => Day f f ~> f
- 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
- gatheredN :: Inplicative f => NP f as -> f (NP I as)
- gatheredNMap :: Inplicative f => (NP I as -> b) -> (b -> NP I as) -> NP f as -> f b
- gatheredN1 :: Inply f => NP f (a ': as) -> f (NP I (a ': as))
- gatheredN1Map :: Inplicative f => (NP I (a ': as) -> b) -> (b -> NP I (a ': as)) -> NP f (a ': as) -> f b
- gatheredNRec :: Inplicative f => Rec f as -> f (XRec Identity as)
- gatheredNMapRec :: Inplicative f => (XRec Identity as -> b) -> (b -> XRec Identity as) -> Rec f as -> f b
- gatheredN1Rec :: Inply f => Rec f (a ': as) -> f (XRec Identity (a ': as))
- gatheredN1MapRec :: Inplicative f => (XRec Identity (a ': as) -> b) -> (b -> XRec Identity (a ': as)) -> Rec f (a ': as) -> f b
- gatherN :: forall f as b. (Inplicative f, IsoXRec Identity as, RecordCurry as) => Curried as b -> (b -> XRec Identity as) -> CurriedF f as (f b)
- gatherN1 :: forall f a as b. (Inply f, IsoXRec Identity as, RecordCurry as) => Curried (a ': as) b -> (b -> XRec Identity (a ': as)) -> CurriedF f (a ': as) (f b)
Typeclass
class Invariant f => Inply f where Source #
The invariant counterpart of Apply
and Divise
.
Conceptually you can think of Apply
as, given a way to "combine" a
and
b
to c
, lets you merge f a
(producer of a
) and f b
(producer
of b
) into a f c
(producer of c
). Divise
can be thought of as,
given a way to "split" a c
into an a
and a b
, lets you merge f
a
(consumer of a
) and f b
(consumder of b
) into a f c
(consumer
of c
).
Inply
, for gather
, requires both a combining function and
a splitting function in order to merge f b
(producer and consumer of
b
) and f c
(producer and consumer of c
) into a f a
. You can
think of it as, for the f a
, it "splits" the a into b
and c
with
the a -> (b, c)
, feeds it to the original f b
and f c
, and then
re-combines the output back into a a
with the b -> c -> a
.
Since: 0.4.0.0
gather :: (b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a Source #
Like <.>
, <*>
, divise
, or divide
, but requires both
a splitting and a recombining function. <.>
and <*>
require
only a combining function, and divise
and divide
require only
a splitting function.
It is used to merge f b
(producer and consumer of b
) and f c
(producer and consumer of c
) into a f a
. You can think of it
as, for the f a
, it "splits" the a into b
and c
with the a ->
(b, c)
, feeds it to the original f b
and f c
, and then
re-combines the output back into a a
with the b -> c -> a
.
An important property is that it will always use both
of the
ccomponents given in order to fulfil its job. If you gather an f
a
and an f b
into an f c
, in order to consume/produdce the c
,
it will always use both the f a
or the f b
-- exactly one of
them.
Since: 0.4.0.0
Instances
class Inply f => Inplicative f where Source #
The invariant counterpart of Applicative
and Divisible
.
The main important action is described in Inply
, but this adds knot
,
which is the counterpart to pure
and conquer
. It's the identity to
gather
; if combine two f a
s with gather
, and one of them is
knot
, it will leave the structure unchanged.
Conceptually, if you think of gather
as "splitting and re-combining"
along multiple forks, then knot
introduces a fork that is never taken.
Since: 0.4.0.0
Instances
Deriving
newtype WrappedApplicativeOnly f a Source #
Wrap an Applicative
that is not necessarily an Apply
.
Instances
newtype WrappedDivisibleOnly f a Source #
Instances
Invariant Day
runDay :: Inply h => (f ~> h) -> (g ~> h) -> Day f g ~> h Source #
Interpret out of a contravariant Day
into any instance of Inply
by
providing two interpreting functions.
This should go in Data.Functor.Invariant.Day, but that module is in a different package.
Since: 0.4.0.0
dather :: Inply f => Day f f ~> f Source #
Squash the two items in a Day
using their natural Inply
instances.
This should go in Data.Functor.Invariant.Day, but that module is in a different package.
Since: 0.4.0.0
runDayApply :: forall f g h. Apply h => (f ~> h) -> (g ~> h) -> Day f g ~> h Source #
Interpret out of a contravariant Day
into any instance of Apply
by
providing two interpreting functions.
In theory, this should not need to exist, since you should always be
able to use runDay
because every instance of Apply
is also an
instance of Inply
. However, this can be handy if you are using an
instance of Apply
that has no Inply
instance. Consider also
unsafeInplyCo
if you are using a specific, concrete type for h
.
runDayDivise :: forall f g h. Divise h => (f ~> h) -> (g ~> h) -> Day f g ~> h Source #
Interpret out of a contravariant Day
into any instance of Divise
by providing two interpreting functions.
In theory, this should not need to exist, since you should always be
able to use runDay
because every instance of Divise
is also an
instance of Inply
. However, this can be handy if you are using an
instance of Divise
that has no Inply
instance. Consider also
unsafeInplyContra
if you are using a specific, concrete type for h
.
Assembling Helpers
gatheredN :: Inplicative f => NP f as -> f (NP I as) Source #
Convenient wrapper to build up an Inplicative
instance 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 and Inplicative
instance 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) $ gatheredN $ intPrim :* boolPrim :* stringPrim :* Nil
Some notes on usefulness depending on how many components you have:
- If you have 0 components, use
knot
directly. - If you have 1 component, you don't need anything.
- If you have 2 components, use
gather
directly. - If you have 3 or more components, these combinators may be useful; otherwise you'd need to manually peel off tuples one-by-one.
Since: 0.4.1.0
gatheredNMap :: Inplicative f => (NP I as -> b) -> (b -> NP I as) -> NP f as -> f b Source #
Given a function to "break out" a data type into a NP
(tuple) and one to
put it back together from the tuple, gather
all of the components
together.
For example, if you had a data type
data MyType = MT Int Bool String
and an invariant functor and Inplicative
instance 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:
concaMapInplicative ((MyType x y z) -> I x :* I y :* I z :* Nil) ((I x :* I y :* I z :* Nil) -> MyType x y z) $ intPrim :* boolPrim :* stringPrim :* Nil
See notes on gatheredNMap
for more details and caveats.
Since: 0.4.1.0
gatheredN1Map :: Inplicative f => (NP I (a ': as) -> b) -> (b -> NP I (a ': as)) -> NP f (a ': as) -> f b Source #
A version of gatheredNMap
for non-empty NP
, but only
requiring an Inply
instance.
Since: 0.4.1.0
gatheredNRec :: Inplicative f => Rec f as -> f (XRec Identity as) Source #
gatheredNMapRec :: Inplicative f => (XRec Identity as -> b) -> (b -> XRec Identity as) -> Rec f as -> f b Source #
A version of gatheredNMap
using XRec
from vinyl instead of
NP
from sop-core. This can be more convenient because it doesn't
require manual unwrapping/wrapping of tuple components.
Since: 0.4.1.0
gatheredN1Rec :: Inply f => Rec f (a ': as) -> f (XRec Identity (a ': as)) Source #
A version of gatheredN1
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.
Since: 0.4.1.0
gatheredN1MapRec :: Inplicative f => (XRec Identity (a ': as) -> b) -> (b -> XRec Identity (a ': as)) -> Rec f (a ': as) -> f b Source #
A version of gatheredNMap
using XRec
from vinyl instead of
NP
from sop-core. This can be more convenient because it doesn't
require manual unwrapping/wrapping of tuple components.
Since: 0.4.1.0
gatherN :: forall f as b. (Inplicative f, IsoXRec Identity as, RecordCurry as) => Curried as b -> (b -> XRec Identity as) -> CurriedF f as (f b) Source #
Convenient wrapper to gather
over multiple arguments using tine
vinyl library's multi-arity uncurrying facilities. Makes it a lot more
convenient than using gather
multiple times and needing to accumulate
intermediate types.
For example, if you had a data type
data MyType = MT Int Bool String
and an invariant functor and Inplicative
instance 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:
gatherN
MT -- ^ curried assembling function
((MT x y z) -> x ::& y ::& z ::& XRNil) -- ^ disassembling function
(intPrim :: Prim Int)
(boolPrim :: Prim Bool)
(stringPrim :: Prim String)
Really only useful with 3 or more arguments, since with two arguments
this is just gather
(and with zero arguments, you can just use
knot
).
The generic type is a bit tricky to understand, but it's easier to understand what's going on if you instantiate with concrete types:
ghci> :t gatherN MyInplicative
'[Int, Bool, String]
(Int -> Bool -> String -> b)
-> (b -> XRec Identity '[Int, Bool, String])
-> MyInplicative Int
-> MyInplicative Bool
-> MyInplicative String
-> MyInplicative b
Since: 0.4.1.0