Skip to content

Instantly share code, notes, and snippets.

@spockz
Created September 21, 2010 08:39
Show Gist options
  • Save spockz/589403 to your computer and use it in GitHub Desktop.
Save spockz/589403 to your computer and use it in GitHub Desktop.
{-# LANGUAGE GADTs, RankNTypes, RecordWildCards, ScopedTypeVariables #-}
module Main where
data UnitT = Unit deriving Show
data Sum aT bT = Inl aT | Inr bT deriving Show
data Prod aT bT = Prod aT bT deriving Show
data EP bT cT = EP {from :: (bT -> cT), to :: (cT -> bT)}
data Rep tT where
RUnit :: Rep UnitT
RInt :: Rep Int
RChar :: Rep Char
RSum :: Rep aT -> Rep bT -> Rep (Sum aT bT)
RProd :: Rep aT -> Rep bT -> Rep (Prod aT bT)
RString :: Rep String
RCon :: String -> Rep aT -> Rep aT
RType :: EP bT cT -> Rep cT -> Rep bT
data RepAlgebra r = RepAlgebra {
unit, int, char, string :: r
, sum, prod :: forall a b. a -> b -> r
, con :: forall a. String -> a -> r
, typ :: forall a b. EP a b -> r -> r
}
foldRep' :: forall r a. RepAlgebra r -> Rep a -> r
foldRep' RepAlgebra{..} = f
where f :: forall b. Rep b -> r
f (RUnit) = unit
f (RInt) = int
f (RChar) = char
f (RString) = string
f (RSum ra rb) = sum (f ra) (f rb)
f (RProd ra rb) = prod (f ra) (f rb)
f (RCon l ra) = con l (f ra)
f (RType ep ra) = typ ep (f ra)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment