| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
| Extensions |
|
Church
Description
and churchEncode form
an isomorphism between a type and its church representation of a type
Simply define an empty instance of churchDecode (or using ChurchDeriveAnyClass)
for a type with a Generic instance and defaulting magic will take care of the rest.
For example:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
data MyType = Foo Int Bool | Bar | Baz Char deriving (Generic, Church, Show)>>>churchEncode (Foo 1 True) (\int bool -> int + 1) 0 (const 1)2
>>>churchDecode (\foo bar baz -> bar) :: MyTypeBar
Recursive datastructures only unfold one level:
data Nat = Z | S Nat deriving (Generic,Church,Show)
>>>:t churchEncode Nr -> (Nat -> r) -> r
But we can still write recursive folds over such data:
nat2int :: Nat -> Int nat2int a = churchEncode a 0 ((+1) . nat2int)
>>>nat2int (S (S (S Z)))3
Decoding recursive data is more cumbersome due to the Rep wrappings,
but fortunately should not need to be done by hand often.
decodeNat :: (Rep Nat () -> (Rep Nat () -> Rep Nat ()) -> Rep Nat ()) -> Nat decodeNat k = churchDecode (z s -> k z (s . to))
>>>decodeNat (\z s -> s . s . s . s $ z)S (S (S (S Z)))
Synopsis
- type ChurchRep t r = ChurchSum (ToList (StripMeta (Rep t ())) (ListTerm ())) r
- class Church a where
- churchEncode :: forall r. a -> ChurchRep a r
- churchDecode :: ChurchRep a (Rep a ()) -> a
- churchCast :: forall a b. (Church a, Church b, ChurchRep a (Rep b ()) ~ ChurchRep b (Rep b ())) => a -> b
Documentation
type ChurchRep t r = ChurchSum (ToList (StripMeta (Rep t ())) (ListTerm ())) r 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 ChurchRep of a type Foo is,
- For each constructor, write out its type signature
- Replace the
Fooat the end of each signature withr - Join these type signatures together with arrows
(a -> b -> r) -> r -> ... - Append a final
-> rto the end of this
For example, for Maybe
Minimal complete definition
Nothing
Methods
churchEncode :: forall r. a -> ChurchRep a r Source #
Reify a type to its church representation
churchEncode :: forall r. (Generic a, GStripMeta (Rep a ()), GList (StripMeta (Rep a ())) (ListTerm ()), GChurchSum (ToList (StripMeta (Rep a ())) (ListTerm ())) r) => a -> ChurchRep a r Source #
Reify a type to its church representation
churchDecode :: ChurchRep a (Rep a ()) -> a Source #
Create a value from its church representation. This method may require an explicit signature.
churchDecode :: (Generic a, GBuild (MakePaths (Rep a ()) '[] '[]) (ChurchRep a (Rep a ())) (Rep a ())) => ChurchRep a (Rep a ()) -> a Source #
Create a value from its church representation. This method may require an explicit signature.
Instances
| Church Bool Source # | |
| Church Ordering Source # | |
| Church () Source # | |
Defined in Church Methods churchEncode :: () -> ChurchRep () r Source # churchDecode :: ChurchRep () (Rep () ()) -> () Source # | |
| Church [a] Source # | |
Defined in Church Methods churchEncode :: [a] -> ChurchRep [a] r Source # churchDecode :: ChurchRep [a] (Rep [a] ()) -> [a] Source # | |
| Church (Maybe a) Source # | |
| Church (Either a b) Source # | |
| Church (a, b) Source # | |
Defined in Church Methods churchEncode :: (a, b) -> ChurchRep (a, b) r Source # churchDecode :: ChurchRep (a, b) (Rep (a, b) ()) -> (a, b) Source # | |
| Church (a, b, c) Source # | |
Defined in Church Methods churchEncode :: (a, b, c) -> ChurchRep (a, b, c) r Source # churchDecode :: ChurchRep (a, b, c) (Rep (a, b, c) ()) -> (a, b, c) Source # | |
| Church (a, b, c, d) Source # | |
Defined in Church Methods churchEncode :: (a, b, c, d) -> ChurchRep (a, b, c, d) r Source # churchDecode :: ChurchRep (a, b, c, d) (Rep (a, b, c, d) ()) -> (a, b, c, d) Source # | |
| Church (a, b, c, d, e) Source # | |
Defined in Church Methods churchEncode :: (a, b, c, d, e) -> ChurchRep (a, b, c, d, e) r Source # churchDecode :: ChurchRep (a, b, c, d, e) (Rep (a, b, c, d, e) ()) -> (a, b, c, d, e) Source # | |
| Church (a, b, c, d, e, f) Source # | |
Defined in Church Methods churchEncode :: (a, b, c, d, e, f) -> ChurchRep (a, b, c, d, e, f) r Source # churchDecode :: ChurchRep (a, b, c, d, e, f) (Rep (a, b, c, d, e, f) ()) -> (a, b, c, d, e, f) Source # | |
| Church (a, b, c, d, e, f, g) Source # | |
Defined in Church Methods churchEncode :: (a, b, c, d, e, f, g) -> ChurchRep (a, b, c, d, e, f, g) r Source # churchDecode :: ChurchRep (a, b, c, d, e, f, g) (Rep (a, b, c, d, e, f, g) ()) -> (a, b, c, d, e, f, g) Source # | |