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

2010-01-03 Thread 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.


---
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)

-}
___
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 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


Re: [Haskell-cafe] pcre-light install fails with undefined reference to _impure_ptr

2009-12-27 Thread Patrick Caldon

Stephen Tetley wrote:

2009/12/27 Stephen Tetley stephen.tet...@gmail.com:

  

I'll try next with MinGW to see if that works...



Aye, it builds fine under MinGW.
  


Thanks for your help, I'll get a MinGW setup together.

Cheers, Patrick.

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


[Haskell-cafe] pcre-light install fails with undefined reference to _impure_ptr

2009-12-26 Thread Patrick Caldon


Not seen this one before.

I'm trying to install pcre-light with WinXP 64, Cygwin 1.7.1, Cabal 
0.8.0, and ghc 6.12.1. Trying to reinstall base with cabal fails as 
well with an internal error (see below), but I'm assuming that's 
quasi-intentional/unsupported feature or something.


Any ideas?  My ultimate goal is to install ghc-core to help track down 
some performance problems I'm having.


Thanks,
Patrick.


p...@rose ~/rp4/loansim
$ cabal install pcre-light --extra-lib-dirs=C:\\cygwin\\lib   
--extra-include-dirs=C:\\cygwin\\usr\\include 
--reinstall   Resolving dependencies...

Configuring pcre-light-0.3.1...
Preprocessing library pcre-light-0.3.1...
In file included from C:/cygwin/usr/include/pcre.h:90,
from Text\Regex\PCRE\Light\Base.hsc:103:
C:/cygwin/usr/include/stdlib.h:104: warning: `warning' attribute 
directive ignored
C:/cygwin/usr/include/stdlib.h:109: warning: `warning' attribute 
directive ignored
dist\build\Text\Regex\PCRE\Light\Base_hsc_make.o:Base_hsc_make.c:(.text+0x47): 
undefined reference to `_impure_ptr'
dist\build\Text\Regex\PCRE\Light\Base_hsc_make.o:Base_hsc_make.c:(.text+0x7b): 
undefined reference to `_impure_ptr'
dist\build\Text\Regex\PCRE\Light\Base_hsc_make.o:Base_hsc_make.c:(.text+0x93): 
undefined reference to `_impure_ptr'
dist\build\Text\Regex\PCRE\Light\Base_hsc_make.o:Base_hsc_make.c:(.text+0xc7): 
undefined reference to `_impure_ptr'
dist\build\Text\Regex\PCRE\Light\Base_hsc_make.o:Base_hsc_make.c:(.text+0xf3): 
undefined reference to `_impure_ptr'
dist\build\Text\Regex\PCRE\Light\Base_hsc_make.o:Base_hsc_make.c:(.text+0x127): 
more undefined references to `_impure_ptr' follow

collect2: ld returned 1 exit status
linking dist\build\Text\Regex\PCRE\Light\Base_hsc_make.o failed
command was: C:\ghc\ghc-6.12.1\mingw\bin\gcc.exe -LC:\cygwin\lib -lpcre 
-LC:\ghc\ghc-6.12.1\bytestring-0.9.1.5 -LC:\ghc\ghc-6.12.1\base-3.0.3.2 
-LC:\ghc\ghc-6.12.1\syb-0.1.0.2 -LC:\ghc\ghc-6.12.1\base-4.2.0.0 
-lwsock32 -luser32 -lshell32 -LC:\ghc\ghc-6.12.1\integer-gmp-0.2.0.0 
-LC:\ghc\ghc-6.12.1\ghc-prim-0.2.0.0 -LC:\ghc\ghc-6.12.1 
-LC:\ghc\ghc-6.12.1/gcc-lib -lm -lwsock32 -LC:\ghc\ghc-6.12.1 
dist\build\Text\Regex\PCRE\Light\Base_hsc_make.o -o 
dist\build\Text\Regex\PCRE\Light\Base_hsc_make.exe

cabal.exe: Error: some packages failed to install:
pcre-light-0.3.1 failed during the building phase. The exception was:
exit: ExitFailure 1

p...@rose ~/rp4/loansim
$ cabal --version
cabal-install version 0.8.0
using version 1.8.0.2 of the Cabal library

p...@rose ~/rp4/loansim
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.12.1

p...@rose ~/rp4/loansim
$ cabal install base --reinstall -p
Resolving dependencies...
cabal.exe: internal error: impossible

p...@rose ~/rp4/loansim
$





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


[Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Patrick Caldon


I'm looking for the right concurrency library/semantics for what 
should be a reasonably simple problem.


I have a little simulator:

runWorldSim :: MTGen - SimState - IO SimState

it takes about a second to run on a PC. It's functional except it whacks 
the rng, which needs IO. I run 5-10 of these jobs, and then use:


mergeWorld :: [SimState] - SimState

to pick the best features of the runs and build another possible world 
(state).  Then I use this new world to run another 5-10 jobs and so on.  
I run this through ~2 iterations.


It's an obvious place for parallelism.

I'm looking for a concurrency library with something like:

forkSequence :: Int - [IO a] - IO [a]

which I could call with something like this:

forkSequence 4 (take 10 (repeat  (runWorldSim g ss)))

this would construct 4 threads, then dispatch the 10 jobs onto the 
threads, and pack up the

results into a list I could run through my merger.

It strikes me as something someone would already have done, but I can't 
find anything in hackage.  Probably I've missed something obvious?  Any 
pointers?


If not, what would be the best/easiest existing package to write an 
extension to?


Thanks,
Patrick.


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


Re: [Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Patrick Caldon

Ivan Lazar Miljenovic wrote:

Patrick Caldon p...@pessce.net writes:
  

it takes about a second to run on a PC. It's functional except it
whacks the rng, which needs IO. I run 5-10 of these jobs, and then
use:


Which RNG are you using that it needs so much IO?
Mersenne Twister, System.Random.Mersenne.  The ordinary rng kills 
performance.


Patrick.

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


Re: [Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Patrick Caldon

Neil Brown wrote:

Patrick Caldon wrote:


I'm looking for the right concurrency library/semantics for what 
should be a reasonably simple problem.


I have a little simulator:

runWorldSim :: MTGen - SimState - IO SimState

it takes about a second to run on a PC. It's functional except it 
whacks the rng, which needs IO. I run 5-10 of these jobs, and then use:


mergeWorld :: [SimState] - SimState

to pick the best features of the runs and build another possible 
world (state).  Then I use this new world to run another 5-10 jobs 
and so on.  I run this through ~2 iterations.


It's an obvious place for parallelism.

I'm looking for a concurrency library with something like:

forkSequence :: Int - [IO a] - IO [a]

which I could call with something like this:

forkSequence 4 (take 10 (repeat  (runWorldSim g ss)))

this would construct 4 threads, then dispatch the 10 jobs onto the 
threads, and pack up the

results into a list I could run through my merger.
Why particularly do you want to run the 10 jobs on 4 threads?  
Haskell's run-time is quite good at spreading out the lightweight 
threads onto all your cores, so the easiest thing to do is run the 10 
jobs on 10 (light-weight) threads and let the run-time sort out the 
rest.  


Thanks so much for that! I'll give it a go.

Different threads is just because some of the jobs are memory hogs, and 
I want to minimize the number running simultaneously.  I'll see what 
happens with a runPar-like approach, and use a queue-based approach if 
it becomes a problem.

So if what you want is a function:

runPar :: [IO a] - IO [a]

you can easily construct this.  Shameless plug: my CHP library 
effectively has this function already, runParallel :: [CHP a] - CHP 
[a] (CHP being a slight layer on top of IO).  But you can do it just 
as easily with, say, STM.  Here is a version where order doesn't 
matter (apologies for the point-free style):


import Control.Concurrent
import Control.Concurrent.STM
import Control.Monad

modifyTVar :: TVar a - (a - a) - STM ()
modifyTVar tv f = readTVar tv = writeTVar tv . f

runPar :: [IO a] - IO [a]
runPar ps
 = do resVar - newTVarIO []
  mapM_ (forkIO . (= atomically . modifyTVar resVar . (:))) ps
  atomically $ do res - readTVar resVar
  when (length res  length ps) retry
  return res

If order does matter, you can zip the results with an index, and sort 
by the index afterwards.  If efficiency matters, you can perform other 
tweaks.  But the principle is quite straightforward.  Or you can 
refactor your code to take the IO dependency out of your random number 
generation, and run the sets of pure code in parallel using the 
parallel library.  If all you are using IO for is random numbers, 
that's probably the nicest approach.


Good, fast random numbers are unfortunately necessary - I had a nice 
implementation using System.Random, but had to rewrite it because 
performance was poor :( .



P.S. take 10 . repeat is the same as replicate 10


Thanks again!

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