Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- newtype DecAlt f a where
- runCoDecAlt :: forall f g. Plus g => (f ~> g) -> DecAlt f ~> g
- runContraDecAlt :: forall f g. Conclude g => (f ~> g) -> DecAlt f ~> g
- decAltListF :: Functor f => DecAlt f ~> ListF f
- decAltListF_ :: DecAlt f ~> ComposeT ListF Coyoneda f
- decAltDec :: DecAlt f ~> Dec f
- foldDecAlt :: (forall x. (x -> Void) -> g x) -> (Night f g ~> g) -> DecAlt f ~> g
- assembleDecAlt :: NP f as -> DecAlt f (NS I as)
- newtype DecAlt1 f a where
- runCoDecAlt1 :: forall f g. Alt g => (f ~> g) -> DecAlt1 f ~> g
- runContraDecAlt1 :: forall f g. Decide g => (f ~> g) -> DecAlt1 f ~> g
- decAltNonEmptyF :: Functor f => DecAlt1 f ~> NonEmptyF f
- decAltNonEmptyF_ :: DecAlt1 f ~> ComposeT NonEmptyF Coyoneda f
- decAltDec1 :: DecAlt1 f ~> Dec1 f
- foldDecAlt1 :: (f ~> g) -> (Night f g ~> g) -> DecAlt1 f ~> g
- assembleDecAlt1 :: Invariant f => NP f (a ': as) -> DecAlt1 f (NS I (a ': as))
Chain
The invariant version of ListF
and Dec
: combines the capabilities of
both ListF
and Dec
together.
Conceptually you can think of
as a way of consuming and
producing DecAlt
f aa
s that contains a collection of f x
s of different x
s.
When interpreting this, a specific f
is chosen to handle the
interpreting; the a
is sent to that f
, and the single result is
returned back out.
To do this, the main tools to combine DecAlt
s are its Inalt
instance, using swerve
to combine two DecAlt
s in a choice-like
manner (with the choosing and re-injecting function), and its Inplus
instance, using reject
to create an "empty" choice that is never
taken.
This does have an Interpret
function, but the target typeclass
(Inplus
) doesn't have too many useful instances. Instead, you are
probably going to run it into either Plus
instance (to "produce" an
a
from a
) with DecAlt
f arunCoDecAlt
, or a Choose
instance
(to "consume" an a
from a
) with DecAlt
f arunContraDecAlt
.
If you think of this type as a combination of ListF
and Dec
, then
you can also extract the ListF
part out using decAltListF
, and
extract the Dec
part out using decAltDec
.
Note that this type's utility is similar to that of
,
except PostT
Dec
lets you use PostT
Dec
Conclude
typeclass methods to
assemble it.
Since: 0.3.5.0
pattern Swerve :: (b -> a) -> (c -> a) -> (a -> Either b c) -> f b -> DecAlt f c -> DecAlt f a | Match on a non-empty |
pattern Reject :: (a -> Void) -> DecAlt f a | Match on an "empty" |
Instances
Inject DecAlt Source # | |
FreeOf Inplus DecAlt Source # | Since: 0.4.0.0 |
HTraversable DecAlt Source # | |
Defined in Data.HFunctor.Chain.Internal | |
Inplus f => Interpret DecAlt (f :: Type -> TYPE LiftedRep) Source # | A free |
Inalt (DecAlt f) Source # | |
Inplus (DecAlt f) Source # | |
Invariant (DecAlt f) Source # | |
Defined in Data.HFunctor.Chain.Internal | |
HFunctor DecAlt Source # | |
type FreeFunctorBy DecAlt Source # | |
Defined in Data.HFunctor.Final |
runCoDecAlt :: forall f g. Plus g => (f ~> g) -> DecAlt f ~> g Source #
In the covariant direction, we can interpret into any Plus
.
In theory, this shouldn't never be necessary, because you should just be
able to use interpret
, since any instance of Plus
is also an instance
of Inplus
. However, this can be handy if you are using an instance of
Plus
that has no Inplus
instance. Consider also unsafeInplusCo
if
you are using a specific, concrete type for g
.
runContraDecAlt :: forall f g. Conclude g => (f ~> g) -> DecAlt f ~> g Source #
In the contravariant direction, we can interpret into any Decide
.
In theory, this shouldn't never be necessary, because you should just be
able to use interpret
, since any instance of Conclude
is also an
instance of Inplus
. However, this can be handy if you are using an
instance of Conclude
that has no Inplus
instance. Consider also
unsafeInplusContra
if you are using a specific, concrete type for g
.
assembleDecAlt :: NP f as -> DecAlt f (NS I as) Source #
Convenient wrapper to build up a DecAlt
on by providing each
branch 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 = MTI Int | MTB Bool | MTS 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 (case MTI x -> Z (I x); MTB y -> S (Z (I y)); MTS z -> S (S (Z (I z)))) (case Z (I x) -> MTI x; S (Z (I y)) -> MTB y; S (S (Z (I z))) -> MTS z) $ assembleDecAlt $ intPrim :* boolPrim :* stringPrim :* Nil
Some notes on usefulness depending on how many components you have:
- If you have 0 components, use
Reject
directly. - If you have 1 component, use
inject
orinjectChain
directly. - If you have 2 components, use
toListBy
ortoChain
. - If you have 3 or more components, these combinators may be useful; otherwise you'd need to manually peel off eithers one-by-one.
If each component is itself a
(instead of DecAlt
ff
), you can use
concatInplus
.
Nonempty Chain
The invariant version of NonEmptyF
and Dec1
: combines the
capabilities of both NonEmptyF
and Dec1
together.
Conceptually you can think of
as a way of consuming and
producing DecAlt1
f aa
s that contains a (non-empty) collection of f x
s of
different x
s. When interpreting this, a specific f
is chosen to
handle the interpreting; the a
is sent to that f
, and the single
result is returned back out.
To do this, the main tools to combine DecAlt1
s are its Inalt
instance, using swerve
to combine two DecAlt1
s in a choice-like
manner (with the choosing and re-injecting function).
This does have an Interpret
function, but the target typeclass
(Inalt
) doesn't have too many useful instances. Instead, you are
probably going to run it into either an Alt
instance (to "produce" an
a
from a
) with DecAlt1
f arunCoDecAlt1
, or a Decide
instance
(to "consume" an a
from a
) with DecAlt1
f arunContraDecAlt1
.
If you think of this type as a combination of NonEmptyF
and Dec1
,
then you can also extract the NonEmptyF
part out using
decAltNonEmptyF
, and extract the Dec1
part out using decAltDec1
.
Note that this type's utility is similar to that of
,
except PostT
Dec1
lets you use PostT
Dec1
Decide
typeclass methods to
assemble it.
Since: 0.3.5.0
pattern DecAlt1 :: Invariant f => (b -> a) -> (c -> a) -> (a -> Either b c) -> f b -> DecAlt f c -> DecAlt1 f a | Match on a |
Instances
FreeOf Inalt DecAlt1 Source # | Since: 0.4.0.0 |
HTraversable DecAlt1 Source # | |
Defined in Data.HFunctor.Chain.Internal | |
HTraversable1 DecAlt1 Source # | |
Defined in Data.HFunctor.Chain.Internal | |
Inalt f => Interpret DecAlt1 (f :: Type -> TYPE LiftedRep) Source # | A free |
Invariant f => Inalt (DecAlt1 f) Source # | |
Invariant f => Invariant (DecAlt1 f) Source # | |
Defined in Data.HFunctor.Chain.Internal | |
Inject DecAlt1 Source # | |
HFunctor DecAlt1 Source # | |
type FreeFunctorBy DecAlt1 Source # | |
Defined in Data.HFunctor.Final |
runCoDecAlt1 :: forall f g. Alt g => (f ~> g) -> DecAlt1 f ~> g Source #
In the covariant direction, we can interpret into any Alt
.
In theory, this shouldn't never be necessary, because you should just be
able to use interpret
, since any instance of Alt
is also an instance
of Inalt
. However, this can be handy if you are using an instance of
Alt
that has no Inalt
instance. Consider also unsafeInaltCo
if
you are using a specific, concrete type for g
.
runContraDecAlt1 :: forall f g. Decide g => (f ~> g) -> DecAlt1 f ~> g Source #
In the contravariant direction, we can interpret into any Decide
.
In theory, this shouldn't never be necessary, because you should just be
able to use interpret
, since any instance of Decide
is also an instance
of Inalt
. However, this can be handy if you are using an instance of
Decide
that has no Inalt
instance. Consider also
unsafeInaltContra
if you are using a specific, concrete type for g
.
assembleDecAlt1 :: Invariant f => NP f (a ': as) -> DecAlt1 f (NS I (a ': as)) Source #
A version of assembleDecAlt
but for DecAlt1
instead. Can
be useful if you intend on interpreting it into something with only
a Decide
or Alt
instance, but no
Decidable
or Plus
or
Alternative
.
If each component is itself a
(instead of DecAlt1
ff
), you can
use concatInalt
.