generic-church-0.3.0.0: Automatically convert Generic instances to and from church representations

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Church

Description

This module provides two functions, toChurch and fromChurch. These form an isomorphism between a type and its church representation of a type To use this, simply define an empty instance of ChurchRep for a type with a 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

Synopsis

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,

  1. For each constructor, write out its type signature

    1. Replace the Foo at the end of each signature with c
    2. Join these type signatures together with arrows (a -> b -> c) -> c -> ...
    3. Append a final -> c to the end of this

For example, for Maybe

  1. Nothing :: Maybe a and Just :: a -> Maybe a.
  2. We then have c and a -> c.
  3. Joining these gives c -> (a -> c)
  4. c -> (a -> c) -> c is our church representation

class ChurchRep a where Source

Minimal complete definition

Nothing

Methods

toChurch :: forall r. ChurchRep a => a -> Church a r Source

Reify a type to its church representation

fromChurch :: Church a (Rep a ()) -> a Source

Create a value from its church representation. This method may require an explicit signature.

Instances

ChurchRep Bool 
ChurchRep Ordering 
ChurchRep () 
ChurchRep [a] 
ChurchRep (Maybe a) 
ChurchRep (Either a b) 
ChurchRep (a, b) 
ChurchRep (a, b, c) 
ChurchRep (a, b, c, d) 
ChurchRep (a, b, c, d, e) 
ChurchRep (a, b, c, d, e, f) 
ChurchRep (a, b, c, d, e, f, g) 

toChurchP :: ChurchRep a => Proxy r -> a -> Church a r Source

fromChurchP :: ChurchRep a => Proxy a -> Church a (Rep a ()) -> a Source

churchCast :: forall a b. (ChurchRep a, ChurchRep b, Church a (Rep b ()) ~ Church b (Rep b ())) => a -> b Source

Since types with the same church representation are identical, we can cast between them.

churchCastP :: forall a b. (ChurchRep a, ChurchRep b, Church a (Rep b ()) ~ Church b (Rep b ())) => Proxy b -> a -> b Source

A more explicit version of churchCast that let's you specify the target of the cast with a Proxy.