
2010/1/4 Patrick Caldon
I'm trying to write some template haskell which will transform:
$(buildCP 0) into \(SimpleM d1 d2 d3) (SimpleM _ _ _) -> (SimpleM d1 d2 d3) $(buildCP 1) into \(SimpleM _ d2 d3) (SimpleM d1 _ _) -> (SimpleM d1 d2 d3) $(buildCP 1) into \(SimpleM d1 _ d3) (SimpleM _ d2 _) -> (SimpleM d1 d2 d3) and so on.
Ultimately I want to generalize this to more variables.
I can't seem to get anything to substitute for the pattern variables in a lambda. Is there a straightforward way of doing this?
Below is what I've been playing with to try to make this work.
Thanks, Patrick.
Here's something pretty generic that gets the patterns right: module THTest where import Language.Haskell.TH import Data.List import Control.Monad type Policy = Int data Management = SimpleM Policy Policy Policy deriving Show buildCP :: Name -> Int -> Int -> ExpQ buildCP ctor nVars nth = do names <- replicateM nVars $ newName "pat" let p1 = replaceAt nth WildP $ map VarP names p2 = replaceAt nth (VarP $ names!!nth) $ replicate nVars WildP return $ LamE [ConP ctor p1, ConP ctor p2] (ListE $ map VarE names) replaceAt :: Int -> a -> [a] -> [a] replaceAt pos x xs = let (first,_:rest) = splitAt pos xs in first ++ [x] ++ rest -- for example: doFst = $(buildCP 'SimpleM 3 0) doFst (SimpleM 1 2 3) (SimpleM 4 5 6) ==> [4,2,3] (returns a list because it's easier to do. Modifying it to return SimpleM left as an exercise :)