Skip to content

Instantly share code, notes, and snippets.

@AndrasKovacs
Created October 12, 2013 10:02
Show Gist options
  • Save AndrasKovacs/6948201 to your computer and use it in GitHub Desktop.
Save AndrasKovacs/6948201 to your computer and use it in GitHub Desktop.
Church numerals.
{-# LANGUAGE RankNTypes, TypeSynonymInstances, FlexibleInstances #-}
type ChNat a = (a -> a) -> a -> a
generalize :: ChNat Int -> (forall a. ChNat a)
generalize n = foldr (.) id . replicate (fromEnum n)
instance Num (ChNat Int) where
fromInteger = toEnum . fromIntegral
a + b = \f -> a f . b f
(*) = (.)
a - b = generalize b pred a
abs = id
signum = const 1
instance Enum (ChNat Int) where
succ n = \f x -> f (n f x)
pred n = \f x -> generalize n (\g h -> h (g f)) (const x) id
toEnum n = foldr (.) id . replicate n
fromEnum n = n succ 0
instance Show (ChNat Int) where
show = show . fromEnum
instance Eq (ChNat Int) where
a == b = fromEnum a == fromEnum b
exponentiate :: ChNat Int -> ChNat Int -> ChNat Int
exponentiate = flip generalize
tetrate :: ChNat Int -> ChNat Int -> ChNat Int
tetrate = (($1).).(flip generalize . flip generalize)
main = print (tetrate 2 4)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment