Re: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread Antoine Latter
On Sun, Jan 3, 2010 at 8:30 PM, Patrick Caldon p...@pessce.net 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

For the Pat, you would use eiter VarP or WildP for variable binding
patterns or wild-card patterns.

Or am I missing something?

Antoine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread Patrick Caldon

Antoine Latter wrote:

On Sun, Jan 3, 2010 at 8:30 PM, Patrick Caldon p...@pessce.net 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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread Tuomas Tynkkynen
2010/1/4 Patrick Caldon p...@pessce.net

 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 :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread Patrick Caldon

Tuomas Tynkkynen wrote:

Here's something pretty generic that gets the patterns right:
  

Thanks for that - about 2/3rds of the length of my proposed solution!

Cheers, Patrick.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe