Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides tools for working with unary functor combinators that represent interpretable schemas.
These are types t
that take a functor f
and return a new functor t
f
, enhancing f
with new structure and abilities.
For these, we have:
inject
:: f a -> t f a
which lets you "lift" an f a
into its transformed version, and also:
interpret
:: C t g
=> (forall x. f a -> g a)
-> t f a
-> g a
that lets you "interpret" a t f a
into a context g a
, essentially
"running" the computaiton that it encodes. The context is required to
have a typeclass constraints that reflects what is "required" to be able
to run a functor combinator.
Every single instance provides different tools. Check out the instance list for a nice list of useful combinators, or also the README for a high-level rundown.
See Data.Functor.Tensor for binary functor combinators that mix together two or more different functors.
Synopsis
- class Inject t => Interpret t f where
- forI :: Interpret t f => t g a -> (g ~> f) -> f a
- iget :: Interpret t (AltConst b) => (forall x. f x -> b) -> t f a -> b
- icollect :: (forall m. Monoid m => Interpret t (AltConst m)) => (forall x. f x -> b) -> t f a -> [b]
- icollect1 :: (forall m. Semigroup m => Interpret t (AltConst m)) => (forall x. f x -> b) -> t f a -> NonEmpty b
- itraverse :: (Functor h, Interpret t (Comp h (t g))) => (forall x. f x -> h (g x)) -> t f a -> h (t g a)
- iapply :: Interpret t (Op b) => (forall x. f x -> x -> b) -> t f a -> a -> b
- ifanout :: (forall m. Monoid m => Interpret t (Op m)) => (forall x. f x -> x -> b) -> t f a -> a -> [b]
- ifanout1 :: (forall m. Semigroup m => Interpret t (Op m)) => (forall x. f x -> x -> b) -> t f a -> a -> NonEmpty b
- getI :: Interpret t (AltConst b) => (forall x. f x -> b) -> t f a -> b
- collectI :: (forall m. Monoid m => Interpret t (AltConst m)) => (forall x. f x -> b) -> t f a -> [b]
- newtype AltConst w a = AltConst {
- getAltConst :: w
- class (c a, d a) => AndC c d a
- newtype WrapHF t f a = WrapHF {
- unwrapHF :: t f a
Documentation
class Inject t => Interpret t f where Source #
An Interpret
lets us move in and out of the "enhanced" Functor
(t
f
) and the functor it enhances (f
). An instance
means we have Interpret
t ft f a -> f a
.
For example,
is Free
ff
enhanced with monadic structure. We get:
inject
:: f a ->Free
f ainterpret
::Monad
m => (forall x. f x -> m x) ->Free
f a -> m a
inject
will let us use our f
inside the enhanced
.
Free
finterpret
will let us "extract" the f
from a
if
we can give an interpreting function that interprets Free
ff
into some
target Monad
.
We enforce that:
interpret
id .inject
== id -- orretract
.inject
== id
That is, if we lift a value into our structure, then immediately interpret it out as itself, it should lave the value unchanged.
Note that instances of this class are intended to be written with t
as a fixed type constructor, and f
to be allowed to vary freely:
instance Monad f => Interpret Free f
Any other sort of instance and it's easy to run into problems with type
inference. If you want to write an instance that's "polymorphic" on
tensor choice, use the WrapHF
newtype wrapper over a type variable,
where the second argument also uses a type constructor:
instance Interpret (WrapHF t) (MyFunctor t)
This will prevent problems with overloaded instances.
Remove the f
out of the enhanced t f
structure, provided that
f
satisfies the necessary constraints. If it doesn't, it needs to
be properly interpret
ed out.
interpret :: (g ~> f) -> t g ~> f Source #
Given an "interpeting function" from f
to g
, interpret the f
out of the t f
into a final context g
.
Instances
Alternative f => Interpret Alt (f :: Type -> Type) Source # | A free |
Applicative f => Interpret Ap (f :: Type -> Type) Source # | A free |
Applicative f => Interpret Ap (f :: Type -> Type) Source # | A free |
Applicative f => Interpret Ap (f :: Type -> Type) Source # | A free |
Monad f => Interpret Free (f :: Type -> Type) Source # | A free |
Bind f => Interpret Free1 (f :: Type -> Type) Source # | A free |
Apply f => Interpret Ap1 (f :: Type -> Type) Source # | |
Conclude f => Interpret Dec (f :: Type -> Type) Source # | |
Decide f => Interpret Dec1 (f :: Type -> Type) Source # | |
Divisible f => Interpret Div (f :: Type -> Type) Source # | |
Divise f => Interpret Div1 (f :: Type -> Type) Source # | |
Inplus f => Interpret DecAlt (f :: Type -> TYPE LiftedRep) Source # | A free |
Inalt f => Interpret DecAlt1 (f :: Type -> TYPE LiftedRep) Source # | A free |
Contravariant f => Interpret Coyoneda (f :: Type -> Type) Source # | A free Since: 0.3.0.0 |
Functor f => Interpret Coyoneda (f :: Type -> Type) Source # | A free |
Pointed f => Interpret MaybeApply (f :: Type -> Type) Source # | A free |
Defined in Data.HFunctor.Interpret | |
Interpret WrappedApplicative (f :: Type -> Type) Source # | |
Defined in Data.HFunctor.Interpret | |
Pointed f => Interpret Lift (f :: Type -> Type) Source # | A free |
Monoid e => Interpret (EnvT e :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | |
Plus f => Interpret (ListF :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | A free |
Plus f => Interpret (MaybeF :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | Technically, |
Alt f => Interpret (NonEmptyF :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | A free |
Alt f => Interpret (Steps :: (Type -> TYPE LiftedRep) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | |
Monoid a => Interpret (Post a :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | |
Interpret t f => Interpret (PostT t :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | Since: 0.3.4.2 |
a ~ Void => Interpret (Pre a :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | |
Interpret t f => Interpret (PreT t :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | |
Plus f => Interpret (These1 g :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | Technically, |
MonadReader r f => Interpret (ReaderT r :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | A free |
Interpret (Flagged :: (k -> Type) -> k -> Type) (f :: k -> Type) Source # | |
Interpret (Step :: (k -> Type) -> k -> Type) (f :: k -> Type) Source # | |
Interpret (Backwards :: (k -> Type) -> k -> Type) (f :: k -> Type) Source # | |
Interpret (IdentityT :: (k -> Type) -> k -> Type) (f :: k -> Type) Source # | |
Interpret (Reverse :: (k -> Type) -> k -> Type) (f :: k -> Type) Source # | |
Plus g => Interpret (Product g :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | |
Plus f => Interpret (Sum g :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | Technically, |
Plus g => Interpret ((:*:) g :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | |
Plus f => Interpret ((:+:) g :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | Technically, |
(Monoid k, Plus f) => Interpret (MapF k :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | |
(Monoid k, Alt f) => Interpret (NEMapF k :: (Type -> TYPE LiftedRep) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | |
SemigroupIn t f => Interpret (Chain1 t :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | |
(Interpret s f, Interpret t f) => Interpret (ComposeT s t :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | |
Interpret t f => Interpret (HFree t :: (k -> Type) -> k -> Type) (f :: k -> Type) Source # | Never uses |
Interpret t f => Interpret (HLift t :: (k -> Type) -> k -> Type) (f :: k -> Type) Source # | Never uses |
c f => Interpret (Final c :: (k -> Type) -> k -> TYPE LiftedRep) (f :: k -> Type) Source # | |
Interpret (M1 i c :: (k -> Type) -> k -> Type) (f :: k -> Type) Source # | |
Interpret (RightF g :: (k2 -> Type) -> k2 -> Type) (f :: k2 -> Type) Source # | |
MonoidIn t i f => Interpret (Chain t i :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # | We can collapse and interpret an |
Inplicative f => Interpret DivAp (f :: Type -> TYPE LiftedRep) Source # | A free |
Inply f => Interpret DivAp1 (f :: Type -> TYPE LiftedRep) Source # | A free |
forI :: Interpret t f => t g a -> (g ~> f) -> f a Source #
A convenient flipped version of interpret
.
Utilities
iget :: Interpret t (AltConst b) => (forall x. f x -> b) -> t f a -> b Source #
Useful wrapper over interpret
to allow you to directly extract
a value b
out of the t f a
, if you can convert f x
into b
.
Note that depending on the constraints on f
in
, you
may have extra constraints on Interpret
t fb
.
- If
f
is unconstrained, there are no constraints onb
- If
f
must beApply
,Alt
,Divise
, orDecide
,b
needs to be an instance ofSemigroup
. - If
f
isApplicative
,Plus
,Divisible
, orConclude
,b
needs to be an instance ofMonoid
For some constraints (like Monad
), this will not be usable.
-- get the length of theMap String
in theStep
.icollect
length :: Step (Map String) Bool -> Int
Note that in many cases, you can also use
hfoldMap
and
hfoldMap1
.
Since: 0.3.1.0
icollect :: (forall m. Monoid m => Interpret t (AltConst m)) => (forall x. f x -> b) -> t f a -> [b] Source #
Useful wrapper over iget
to allow you to collect a b
from all
instances of f
inside a t f a
.
Will work if there is an instance of
if Interpret
t (AltConst
m)
, which will be the case if the constraint on the target
functor is Monoid
mFunctor
, Apply
, Applicative
, Alt
, Plus
,
Decide
, Divisible
, Decide
,
Conclude
, or unconstrained.
-- get the lengths of allMap String
s in theAp
.icollect
length :: Ap (Map String) Bool -> [Int]
Note that in many cases, you can also use
htoList
.
Since: 0.3.1.0
icollect1 :: (forall m. Semigroup m => Interpret t (AltConst m)) => (forall x. f x -> b) -> t f a -> NonEmpty b Source #
Useful wrapper over iget
to allow you to collect a b
from all
instances of f
inside a t f a
, into a non-empty collection of b
s.
Will work if there is an instance of
if
Interpret
t (AltConst
m)
, which will be the case if the constraint on the target
functor is Semigroup
mFunctor
, Apply
, Alt
, Divise
, Decide
, or
unconstrained.
-- get the lengths of allMap String
s in theAp
.icollect1
length :: Ap1 (Map String) Bool ->NonEmpty
Int
Note that in many cases, you can also use
htoNonEmpty
.
Since: 0.3.1.0
itraverse :: (Functor h, Interpret t (Comp h (t g))) => (forall x. f x -> h (g x)) -> t f a -> h (t g a) Source #
iapply :: Interpret t (Op b) => (forall x. f x -> x -> b) -> t f a -> a -> b Source #
Useful wrapper over interpret
to allow you to directly consume
a value of type a
with a t f a
to create a b
. Do this by
supplying the method by which each component f x
can consume an x
.
This works for contravariant functor combinators, where t f a
can be
interpreted as a consumer of a
s.
Note that depending on the constraints on f
in
, you
may have extra constraints on Interpret
t fb
.
- If
f
is unconstrained,Decide
, orConclude
, there are no constraints onb
. This will be the case for combinators like contravariantCoyoneda
,Dec
,Dec1
. - If
f
must beDivise
,b
needs to be an instance ofSemigroup
. This will be the case for combinators likeDiv1
. - If
f
isDivisible
,b
needs to be an instance ofMonoid
. This will be the case for combinators likeDiv
.
For any Functor
or Invariant
constraint, this is not usable.
Since: 0.3.2.0
ifanout :: (forall m. Monoid m => Interpret t (Op m)) => (forall x. f x -> x -> b) -> t f a -> a -> [b] Source #
Useful wrapper over interpret
to allow you to directly consume
a value of type a
with a t f a
to create a b
, and create a list of
all the b
s created by all the f
s. Do this by supplying the method
by which each component f x
can consume an x
. This works for
contravariant functor combinators, where t f a
can be interpreted as
a consumer of a
s.
Will work if there is an instance of
if Interpret
t (Op
m)
, which will be the case if the constraint on the target
functor is Monoid
mContravariant
, Decide
, Conclude
, Divise
, Divisible
,
or unconstrained.
Note that this is really only useful outside of iapply
for Div
and
Div1
, where a
which is a collection of many different Div
ff
s
consuming types of different values. You can use this with Dec
and
Dec1
and the contravarient Coyoneda
as well, but those would
always just give you a singleton list, so you might as well use
iapply
. This is really only here for completion alongside icollect
,
or if you define your own custom functor combinators.
ifanout1 :: (forall m. Semigroup m => Interpret t (Op m)) => (forall x. f x -> x -> b) -> t f a -> a -> NonEmpty b Source #
Useful wrapper over interpret
to allow you to directly consume
a value of type a
with a t f a
to create a b
, and create a list of
all the b
s created by all the f
s. Do this by supplying the method
by which each component f x
can consume an x
. This works for
contravariant functor combinators, where t f a
can be interpreted as
a consumer of a
s.
Will work if there is an instance of
if Interpret
t (Op
m)
, which will be the case if the constraint on the target
functor is Monoid
mContravariant
, Decide
, Divise
, or unconstrained.
Note that this is really only useful outside of iapply
and ifanout
for Div1
, where a
which is a collection of many different
Div1
ff
s consuming types of different values. You can use this with Dec
and Dec1
and the contravarient Coyoneda
as well, but those would
always just give you a singleton list, so you might as well use
iapply
. This is really only here for completion alongside
icollect1
, or if you define your own custom functor combinators.
getI :: Interpret t (AltConst b) => (forall x. f x -> b) -> t f a -> b Source #
Deprecated: Use iget instead
(Deprecated) Old name for getI
; will be removed in a future
version.
collectI :: (forall m. Monoid m => Interpret t (AltConst m)) => (forall x. f x -> b) -> t f a -> [b] Source #
Deprecated: Use icollect instead
(Deprecated) Old name for icollect
; will be removed in a future
version.
A version of Const
that supports Alt
, Plus
, Decide
, and
Conclude
instances. It does this
by avoiding having an Alternative
or Decidable
instance, which
causes all sorts of problems with the interactions between
Alternative
/Applicative
and
Decidable
/Divisible
.
Since: 0.3.1.0
AltConst | |
|
Instances
Foldable (AltConst w :: TYPE LiftedRep -> Type) Source # | |
Defined in Data.HFunctor.Interpret fold :: Monoid m => AltConst w m -> m # foldMap :: Monoid m => (a -> m) -> AltConst w a -> m # foldMap' :: Monoid m => (a -> m) -> AltConst w a -> m # foldr :: (a -> b -> b) -> b -> AltConst w a -> b # foldr' :: (a -> b -> b) -> b -> AltConst w a -> b # foldl :: (b -> a -> b) -> b -> AltConst w a -> b # foldl' :: (b -> a -> b) -> b -> AltConst w a -> b # foldr1 :: (a -> a -> a) -> AltConst w a -> a # foldl1 :: (a -> a -> a) -> AltConst w a -> a # toList :: AltConst w a -> [a] # null :: AltConst w a -> Bool # length :: AltConst w a -> Int # elem :: Eq a => a -> AltConst w a -> Bool # maximum :: Ord a => AltConst w a -> a # minimum :: Ord a => AltConst w a -> a # | |
Eq w => Eq1 (AltConst w :: Type -> Type) Source # | |
Ord w => Ord1 (AltConst w :: Type -> Type) Source # | |
Defined in Data.HFunctor.Interpret | |
Show w => Show1 (AltConst w :: TYPE LiftedRep -> Type) Source # | |
Contravariant (AltConst w :: Type -> Type) Source # | |
Traversable (AltConst w :: TYPE LiftedRep -> Type) Source # | |
Defined in Data.HFunctor.Interpret | |
Monoid w => Applicative (AltConst w :: Type -> Type) Source # | |
Defined in Data.HFunctor.Interpret | |
Functor (AltConst w :: TYPE LiftedRep -> Type) Source # | |
Monoid w => Divisible (AltConst w :: Type -> Type) Source # | |
Monoid w => Conclude (AltConst w :: Type -> Type) Source # | Unlike for |
Semigroup w => Decide (AltConst w :: Type -> Type) Source # | Unlike for |
Semigroup w => Divise (AltConst w :: Type -> Type) Source # | |
Invariant (AltConst w :: Type -> Type) Source # | |
Defined in Data.HFunctor.Interpret | |
Semigroup w => Alt (AltConst w :: Type -> Type) Source # | Unlike for |
Semigroup w => Apply (AltConst w :: Type -> Type) Source # | |
Monoid w => Plus (AltConst w :: Type -> Type) Source # | Unlike for |
Defined in Data.HFunctor.Interpret | |
(Typeable a, Typeable k, Data w) => Data (AltConst w a) Source # | |
Defined in Data.HFunctor.Interpret gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AltConst w a -> c (AltConst w a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AltConst w a) # toConstr :: AltConst w a -> Constr # dataTypeOf :: AltConst w a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AltConst w a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AltConst w a)) # gmapT :: (forall b. Data b => b -> b) -> AltConst w a -> AltConst w a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AltConst w a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AltConst w a -> r # gmapQ :: (forall d. Data d => d -> u) -> AltConst w a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AltConst w a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AltConst w a -> m (AltConst w a) # | |
Generic (AltConst w a) Source # | |
Show w => Show (AltConst w a) Source # | |
Eq w => Eq (AltConst w a) Source # | |
Ord w => Ord (AltConst w a) Source # | |
Defined in Data.HFunctor.Interpret | |
type Rep (AltConst w a) Source # | |
Defined in Data.HFunctor.Interpret |
class (c a, d a) => AndC c d a Source #
A constraint on a
for both c a
and d a
. Requiring
is the same as requiring AndC
Show
Eq
a(
.Show
a, Eq
a)
Instances
(c a, d a) => AndC (c :: k -> Constraint) (d :: k -> Constraint) (a :: k) Source # | |
Defined in Data.HFunctor.Interpret |
A newtype wrapper meant to be used to define polymorphic Interpret
instances. See documentation for Interpret
for more information.
Please do not ever define an instance of Interpret
"naked" on the
second parameter:
instance Interpret (WrapHF t) f
As that would globally ruin everything using WrapHF
.
Instances
HFunctor t => HFunctor (WrapHF t :: (k -> Type) -> k1 -> Type) Source # | |
HBind t => HBind (WrapHF t :: (k -> Type) -> k -> Type) Source # | |
Inject t => Inject (WrapHF t :: (k -> Type) -> k -> Type) Source # | |
Foldable (t f) => Foldable (WrapHF t f) Source # | |
Defined in Data.HFunctor.Interpret fold :: Monoid m => WrapHF t f m -> m # foldMap :: Monoid m => (a -> m) -> WrapHF t f a -> m # foldMap' :: Monoid m => (a -> m) -> WrapHF t f a -> m # foldr :: (a -> b -> b) -> b -> WrapHF t f a -> b # foldr' :: (a -> b -> b) -> b -> WrapHF t f a -> b # foldl :: (b -> a -> b) -> b -> WrapHF t f a -> b # foldl' :: (b -> a -> b) -> b -> WrapHF t f a -> b # foldr1 :: (a -> a -> a) -> WrapHF t f a -> a # foldl1 :: (a -> a -> a) -> WrapHF t f a -> a # toList :: WrapHF t f a -> [a] # null :: WrapHF t f a -> Bool # length :: WrapHF t f a -> Int # elem :: Eq a => a -> WrapHF t f a -> Bool # maximum :: Ord a => WrapHF t f a -> a # minimum :: Ord a => WrapHF t f a -> a # | |
Eq1 (t f) => Eq1 (WrapHF t f) Source # | |
Ord1 (t f) => Ord1 (WrapHF t f) Source # | |
Defined in Data.HFunctor.Interpret | |
Show1 (t f) => Show1 (WrapHF t f) Source # | |
Traversable (t f) => Traversable (WrapHF t f) Source # | |
Defined in Data.HFunctor.Interpret | |
Functor (t f) => Functor (WrapHF t f) Source # | |
(Typeable f, Typeable a, Typeable t, Typeable k1, Typeable k2, Data (t f a)) => Data (WrapHF t f a) Source # | |
Defined in Data.HFunctor.Interpret gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WrapHF t f a -> c (WrapHF t f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WrapHF t f a) # toConstr :: WrapHF t f a -> Constr # dataTypeOf :: WrapHF t f a -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (WrapHF t f a)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (WrapHF t f a)) # gmapT :: (forall b. Data b => b -> b) -> WrapHF t f a -> WrapHF t f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrapHF t f a -> r # gmapQ :: (forall d. Data d => d -> u) -> WrapHF t f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WrapHF t f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WrapHF t f a -> m (WrapHF t f a) # | |
Generic (WrapHF t f a) Source # | |
Read (t f a) => Read (WrapHF t f a) Source # | |
Show (t f a) => Show (WrapHF t f a) Source # | |
Eq (t f a) => Eq (WrapHF t f a) Source # | |
Ord (t f a) => Ord (WrapHF t f a) Source # | |
Defined in Data.HFunctor.Interpret | |
type Rep (WrapHF t f a) Source # | |
Defined in Data.HFunctor.Interpret |