| Safe Haskell | Safe-Inferred |
|---|
Data.Church
Description
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
ChurchRepGeneric 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) :: MyTypeBar
Documentation
type Church t c = ChurchSum (ToList (StripMeta (Rep t ())) (ListTerm ())) cSource
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
Fooat the end of each signature withc - Join these type signatures together with arrows
(a -> b -> c) -> c -> ... - Append a final
-> cto the end of this
For example, for Maybe
fromChurchP :: ChurchRep a => Proxy a -> Church a (Rep a ()) -> aSource
A version of fromChurch that avoids the need for a type signature
in many cases with a Proxy. Helpful for writing some programs without
-XScopedTypeVariables.