
Hi, I'm trying to write a generic nominal abstract syntax library, and I ran into a problem using ext1T. I asked around at #haskell but no one was able to help me, I hope this is not too off topic here. substAbs works just fine by itself, but when I try to combine it with something using ext1T, it stops working. I can't figure out what's the problem with this, am I doing something wrong? *Main> substAbs $ a :\\: a Name "a" (Just 1) :\\: Name "a" (Just 1) *Main> id `ext1T` substAbs $ a :\\: a Name "a" Nothing :\\: Name "a" Nothing Here is my code:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Generics
data Name = Name String (Maybe Int) deriving (Eq, Show, Data, Typeable)
refresh (Name s Nothing) = Name s (Just 1) refresh (Name s (Just i)) = Name s (Just $ i+1)
data Abs a = Name :\\: a deriving (Eq, Show, Data, Typeable)
swapName (a,b) x = if a == x then b else if b == x then a else x
swap (a,b) = everywhere (mkT $ swapName (a,b))
substAbs (n :\\: x) = (m :\\: (x')) where m = refresh n x' = swap (n,m) x
a = Name "a" Nothing b = Name "b" Nothing
Thanks in advance, Daniel.