| Copyright | (c) Justin Le 2019 | 
|---|---|
| License | BSD3 | 
| Maintainer | justin@jle.im | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.HFunctor.Final
Description
Synopsis
- newtype Final c f a = Final {- runFinal :: forall g. c g => (forall x. f x -> g x) -> g a
 
- fromFinal :: (Inject t, c (t f)) => Final c f ~> t f
- toFinal :: Interpret t (Final c f) => t f ~> Final c f
- class FreeOf c t | t -> c where- type FreeFunctorBy t :: (Type -> Type) -> Constraint
- fromFree :: t f ~> Final c f
- toFree :: FreeFunctorBy t f => Final c f ~> t f
 
- finalizing :: (FreeOf c t, FreeFunctorBy t f) => t f <~> Final c f
- hoistFinalC :: (forall g x. (c g => g x) -> d g => g x) -> Final c f a -> Final d f a
- liftFinal0 :: (forall g. c g => g a) -> Final c f a
- liftFinal1 :: (forall g. c g => g a -> g b) -> Final c f a -> Final c f b
- liftFinal2 :: (forall g. c g => g a -> g b -> g d) -> Final c f a -> Final c f b -> Final c f d
Documentation
A simple way to inject/reject into any eventual typeclass.
In a way, this is the "ultimate" multi-purpose Interpret instance.
 You can use this to inject an f into a free structure of any
 typeclass.  If you want f to have a Monad instance, for example,
 just use
inject:: f a ->FinalMonadf a
When you want to eventually interpret out the data, use:
interpret:: (f~>g) ->Finalc f a -> g a
Essentially, Final cFinal MonadMonad, etc.
Final can theoretically replace Ap, Ap1, ListF, NonEmptyF,
 MaybeF, Free, Identity, Coyoneda, and
 other instances of FreeOf, if you don't care about being able to
 pattern match on explicit structure.
However, it cannot replace Interpret instances that are not free
 structures, like Step,
 Steps,
 Backwards, etc.
Note that this doesn't have instances for all the typeclasses you
 could lift things into; you probably have to define your own if you want
 to use Final cc (using liftFinal0,
 liftFinal1, liftFinal2 for help).
Instances
fromFinal :: (Inject t, c (t f)) => Final c f ~> t f Source #
Concretize a Final.
fromFinal ::FinalFunctorf~>Coyonedaf fromFinal ::FinalApplicativef~>Apf fromFinal ::FinalAlternativef~>Altf fromFinal ::FinalMonadf~>Freef fromFinal ::FinalPointedf~>Liftf fromFinal ::FinalPlusf~>ListFf
This can be useful because Final doesn't have a concrete structure
 that you can pattern match on and inspect, but t might.
In the case that this forms an isomorphism with toFinal, the t will
 have an instance of FreeOf.
toFinal :: Interpret t (Final c f) => t f ~> Final c f Source #
Finalize an Interpret instance.
toFinal ::Coyonedaf~>FinalFunctorf toFinal ::Apf~>FinalApplicativef toFinal ::Altf~>FinalAlternativef toFinal ::Freef~>FinalMonadf toFinal ::Liftf~>FinalPointedf toFinal ::ListFf~>FinalPlusf
Note that the instance of c for Final c
This operation can potentially forget structure in t.  For example,
 we have:
toFinal::Stepsf ~>FinalAltf
In this process, we lose the "positional" structure of
 Steps.
In the case where toFinal doesn't lose any information, this will form
 an isomorphism with fromFinal, and t is known as the "Free c".
 For such a situation, t will have a FreeOf instance.
class FreeOf c t | t -> c where Source #
A typeclass associating a free structure with the typeclass it is free on.
This essentially lists instances of Interpret where a "trip" through
 Final will leave it unchanged.
fromFree.toFree== idtoFree.fromFree== id
This can be useful because Final doesn't have a concrete structure
 that you can pattern match on and inspect, but t might.  This lets you
 work on a concrete structure if you desire.
Minimal complete definition
Nothing
Associated Types
type FreeFunctorBy t :: (Type -> Type) -> Constraint Source #
What "type" of functor is expected: should be either
 Unconstrained, Functor, Contravariant, or Invariant.
Since: 0.3.0.0
type FreeFunctorBy t = Unconstrained
Instances
finalizing :: (FreeOf c t, FreeFunctorBy t f) => t f <~> Final c f Source #
The isomorphism between a free structure and its encoding as Final.
hoistFinalC :: (forall g x. (c g => g x) -> d g => g x) -> Final c f a -> Final d f a Source #
Re-interpret the context under a Final.
liftFinal0 :: (forall g. c g => g a) -> Final c f a Source #
Lift an action into a Final.