Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Data.Piso.Generic
- mkPisoList :: (Generic a, MkPisoList (Rep a)) => PisoList (Rep a) a
Documentation
mkPisoList :: (Generic a, MkPisoList (Rep a)) => PisoList (Rep a) a Source #
Derive a list of partial isomorphisms, one for each constructor in the Generic
datatype a
. The list is wrapped in the unary constructor PisoList
. Within that constructor, the isomorphisms are separated by the right-associative binary infix constructor :&
. Finally, the individual isomorphisms are wrapped in the unary constructor I
. These constructors are all exported by this module, but no documentation is generated for them by Hackage.
As an example, here is how to define the isomorphisms nil
and cons
for [a]
, which is an instance of Generic
:
nil :: Piso t ([a] :- t) cons :: Piso (a :- [a] :- t) ([a] :- t) (nil, cons) = (nil', cons') where PisoList (I nil' :& I cons') = mkPisoList
GHC 7.6.3 requires the extra indirection through nil'
and cons'
, due to bug 7268 (http://ghc.haskell.org/trac/ghc/ticket/7268). When it is fixed, the example above can be written in a more direct way:
nil :: Piso t ([a] :- t) cons :: Piso (a :- [a] :- t) ([a] :- t) PisoList (I nil :& I cons) = mkPisoList
If you are familiar with the generic representations from Data.Generic
, you might be interested in the exact types of the various constructors in which the isomorphisms are wrapped:
I :: (forall t. Piso (PisoLhs f t) (a :- t)) -> PisoList (M1 C c f) a (:&) :: PisoList f a -> PisoList g a -> PisoList (f :+: g) a PisoList :: PisoList f a -> PisoList (M1 D c f) a
The type constructor PisoLhs
that appears in the type of I
is an internal type family that builds the proper heterogenous list of types (using :-
) based on the constructor's fields.