Lets say I have data type Expr a
as defined in Types
And I have some parser, the details really don’t matter at all here.
The problem arises in my renamer module. The representation for Type
is
exactly the same for both modules, yet I need boilerplate
to convince the
typechecker. Does there exist some nice way to avoid this?
The problem is exaggerated for modules that modify the tree even less, e.g a desugar module.
I know syb helps with this if the
type of the tree is the same, but that is not the case here.
{-# LANGUAGE TypeFamilies #-}
module Types where
type Pos = (Int, Int)
data Rn
data Ps
data Expr a
= Var (XVar a) String
| Lam (XLam a) String (Type a) (Expr a)
| App (XApp a) (Expr a) (Expr a)
data Type a = Int (XInt a) | Fun (XFun a) (Type a) (Type a)
type family XVar a
type family XLam a
type family XApp a
type family XInt a
type family XFun a
{-# LANGUAGE TypeFamilies #-}
module Parse where
import Types
type instance XVar Ps = Pos
type instance XLam Ps = Pos
type instance XApp Ps = Pos
type instance XInt Ps = ()
type instance XFun Ps = ()
parse :: String -> Expr Ps
parse input = error "todo"
{-# LANGUAGE TypeFamilies #-}
module Rename where
import Types
import Parse ()
type instance XVar Rn = Pos
type instance XLam Rn = Pos
type instance XApp Rn = Pos
type instance XInt Rn = ()
type instance XFun Rn = ()
rename :: Expr Ps -> Expr Rn
rename expr = case expr of
Lam pos var ty body -> Lam pos var (boilerplate ty) (rename body)
App pos l r -> App pos (rename l) (rename r)
Var _ _ -> error "..."
boilerplate :: Type Ps -> Type Rn
boilerplate (Int field) = Int field
boilerplate (Fun field l r) = Fun field (boilerplate l) (boilerplate r)