Skip to content

Instantly share code, notes, and snippets.

@laughedelic
Created November 1, 2011 23:29
Show Gist options
  • Save laughedelic/1332269 to your computer and use it in GitHub Desktop.
Save laughedelic/1332269 to your computer and use it in GitHub Desktop.
Names substitution in declaration templates (TH + SYB)
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Language.Haskell.TH.Lib hiding (rename)
import Control.Monad (liftM)
import Data.List (lookup)
import Data.Generics.Aliases (mkT)
import Data.Generics.Schemes (everywhere)
----------------------------------------------------------------
type NamesMap = [(String, String)]
rename :: NamesMap -> (Name -> Name)
rename namesMap = \ oldName ->
case lookup (show oldName) namesMap of
Nothing -> oldName
Just new -> mkName new
renameDecs :: NamesMap -> Q [Dec] -> Q [Dec]
renameDecs namesMap = liftM $ everywhere $ mkT $ rename namesMap
----------------------------------------------------------------
fooTemplate :: String -> Int -> Int -> String -> Q [Dec]
fooTemplate name y z blah = renameDecs [("foo", name)]
[d| foo :: Num a => a -> a -> String
foo x 1 = show $ x + y
foo x 2 = show $ x - z
foo x _ = show x ++ blah
|]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment