Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides two functions,
and toChurch
. These form
an isomorphism between a type and its church representation of a type
To use this, simply define an empty instance of fromChurch
for a type with a
ChurchRep
Generic
instance and defaulting magic will take care of the rest. For example
{-# LANGUAGE DeriveGeneric #-} data MyType = Foo Int Bool | Bar | Baz Char deriving(Generic, Show) instance ChurchRep MyType
Then if we fire up GHCi
>>>
toChurch (Foo 1 True) (\int bool -> int + 1) 0 (const 1)
2
>>>
fromChurch (\foo bar baz -> bar) :: MyType
Bar
- type Church t c = ChurchSum (ToList (StripMeta (Rep t ())) (ListTerm ())) c
- class ChurchRep a where
- toChurchP :: ChurchRep a => Proxy r -> a -> Church a r
- fromChurchP :: ChurchRep a => Proxy a -> Church a (Rep a ()) -> a
- churchCast :: forall a b. (ChurchRep a, ChurchRep b, Church a (Rep b ()) ~ Church b (Rep b ())) => a -> b
- churchCastP :: forall a b. (ChurchRep a, ChurchRep b, Church a (Rep b ()) ~ Church b (Rep b ())) => Proxy b -> a -> b
Documentation
type Church t c = ChurchSum (ToList (StripMeta (Rep t ())) (ListTerm ())) c Source
This is the central type for this package. Unfortunately, it's
built around type families so it's not so easy to read. A helpful
algorithm for figuring out what the Church
of a type Foo
is,
For each constructor, write out its type signature
- Replace the
Foo
at the end of each signature withc
- Join these type signatures together with arrows
(a -> b -> c) -> c -> ...
- Append a final
-> c
to the end of this
- Replace the
For example, for Maybe
class ChurchRep a where Source
Nothing