Template Haskell - substitution in pattern in a lambda

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. --- module THTest where import Language.Haskell.TH import qualified Data.Bits type Policy = Int data Management = SimpleM Policy Policy Policy deriving Show -- Compiles - but no substitution for the "aX" and "bX" variables buildCP :: Int -> ExpQ buildCP k = [|\(SimpleM a1 a2 a3) (SimpleM b1 b2 b3) -> (SimpleM $e1 $e2 $e3) |] where (e1,a1,b1) = bitToExprs 0 k (e2,a2,b2) = bitToExprs 1 k (e3,a3,b3) = bitToExprs 2 k -- Won't compile: buildCP2 :: Int -> ExpQ buildCP2 k = [|\(SimpleM $a1 $a2 $a3) (SimpleM $b1 $b2 $b3) -> (SimpleM $e1 $e2 $e3) |] where (e1,a1,b1) = bitToExprs 0 k (e2,a2,b2) = bitToExprs 1 k (e3,a3,b3) = bitToExprs 2 k cp1 0 = \(SimpleM d1 d2 d3) (SimpleM _ _ _) -> (SimpleM d1 d2 d3) {- -- idea is to use in calls like this: cp0 0 = $(buildCP 0) -- should be \(SimpleM d1 d2 d3) (SimpleM _ _ _) -> (SimpleM d1 d2 d3) cp0 1 = $(buildCP 1) -} -- There is also a template haskell [p| ... |] syntax, but not yet implemented ... bitToExprs:: Int -> Int -> (ExpQ,PatQ,PatQ) bitToExprs n k = if Data.Bits.testBit (k::Int) (n::Int) then (e,v1,v2) else (e,v2,v1) where v1 = return WildP v2 = return $ VarP (mkName name) e = return $ VarE (mkName name) name = "d" ++ (show $ n + 1) {- -- ulitmate goal is something like this with 10ish d variables: -- cp0 0 (SimpleM d1 d2 d3 m1) (SimpleM _ _ _ m2) = (SimpleM d1 d2 d3 (me1 m1 m2)) cp0 1 (SimpleM d1 d2 _ m1) (SimpleM _ _ d3 m2) = (SimpleM d1 d2 d3 (me2 m1 m2)) cp0 2 (SimpleM d1 _ d3 m1) (SimpleM _ d2 _ m2) = (SimpleM d1 d2 d3 (me1 m1 m2)) cp0 3 (SimpleM d1 _ _ m1) (SimpleM _ d2 d3 m2) = (SimpleM d1 d2 d3 (me2 m1 m2)) cp0 4 (SimpleM _ d2 d3 m1) (SimpleM d1 _ _ m2) = (SimpleM d1 d2 d3 (me1 m1 m2)) cp0 5 (SimpleM _ d2 _ m1) (SimpleM d1 _ d3 m2) = (SimpleM d1 d2 d3 (me2 m1 m2)) cp0 6 (SimpleM _ _ d3 m1) (SimpleM d1 d2 _ m2) = (SimpleM d1 d2 d3 (me1 m1 m2)) cp0 7 (SimpleM _ _ _ m1) (SimpleM d1 d2 d3 m2) = (SimpleM d1 d2 d3 (me2 m1 m2)) cp0 _ _ _ = (trace "cp0 error" undefined) -}

On Sun, Jan 3, 2010 at 8:30 PM, 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?
Hello, It looks like you want to construct expressions with the LamE constructor, which is declared like so: LamE [Pat] Exp For the Pat, you would use eiter VarP or WildP for variable binding patterns or wild-card patterns. Or am I missing something? Antoine

Antoine Latter wrote:
On Sun, Jan 3, 2010 at 8:30 PM, Patrick Caldon
wrote: 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?
Hello,
It looks like you want to construct expressions with the LamE constructor, which is declared like so:
LamE [Pat] Exp
Thanks - I see how that could work, I'll try it. But really I was wondering if there was something like: buildCP2 :: Int -> ExpQ buildCP2 k = [|\(SimpleM ~a1 ~a2 ~a3) (SimpleM ~b1 ~b2 ~b3) -> (SimpleM $e1 $e2 $e3) |] where (e1,a1,b1) = bitToExprs 0 k (e2,a2,b2) = bitToExprs 1 k (e3,a3,b3) = bitToExprs 2 k bitToExprs:: Int -> Int -> (ExpQ,PatQ,PatQ) Where ~a1 would mean "look for something called a1 returning a pattern, and slot it into the pattern part of the lambda in the appropriate spot". I'm guessing no such syntax exists? Thanks again, Patrick.

Hello Patrick, Monday, January 4, 2010, 5:59:18 AM, you wrote:
I'm guessing no such syntax exists?
you are right. look at http://www.haskell.org/bz/th3.htm http://www.haskell.org/bz/thdoc.htm -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Cool, Burat! Those are the first tutorials I've read on TH that have succeeded in giving me a sense of how I can actually use it! Thanks for writing them up. :-D Cheers, Greg On Jan 4, 2010, at 3:12 AM, Bulat Ziganshin wrote:
Hello Patrick,
Monday, January 4, 2010, 5:59:18 AM, you wrote:
I'm guessing no such syntax exists?
you are right. look at http://www.haskell.org/bz/th3.htm http://www.haskell.org/bz/thdoc.htm
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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 :)
participants (5)
-
Antoine Latter
-
Bulat Ziganshin
-
Gregory Crosswhite
-
Patrick Caldon
-
Tuomas Tynkkynen