[Haskell-cafe] Happy parsing wierdness

2007-12-02 Thread Mike Menzel
Hi, I'm using the Happy parser, and I've threaded a Success/Failure monad-like thing through it so that if the parse succeeds, Success AST (AST is the datatype I want to turn my tokens into) is returned and if it fails, Fail String is returned (in a similar manner to how such threading is

[Haskell-cafe] Array copying

2007-12-02 Thread Andrew Coppin
Andrew Coppin wrote: copy :: Word32 - IOUArray Word32 Bool - Word32 - IO (IOUArray Word32 Bool) copy p grid size = do let size' = size * p grid' - newArray (1,size') False mapM_ (\n - do b - readArray grid n if b then mapM_ (\x - writeArray grid' (n + size*x) True)

[Haskell-cafe] Re: Array copying

2007-12-02 Thread ChrisK
Andrew Coppin wrote: Andrew Coppin wrote: copy :: Word32 - IOUArray Word32 Bool - Word32 - IO (IOUArray Word32 Bool) copy p grid size = do let size' = size * p grid' - newArray (1,size') False mapM_ (\n - do b - readArray grid n if b then mapM_ (\x - writeArray

Re: [Haskell-cafe] Re: Array copying

2007-12-02 Thread Andrew Coppin
ChrisK wrote: For GHC 6.6 I created foreign import ccall unsafe memcpy memcpy :: MutableByteArray# RealWorld - MutableByteArray# RealWorld - Int# - IO () {-# INLINE copySTU #-} copySTU :: (Show i,Ix i,MArray (STUArray s) e (ST s)) = STUArray s i e - STUArray s i e - ST s ()

[Haskell-cafe] c2hs and cabal

2007-12-02 Thread Stefan Kersten
hi, i'm looking for a way to integrate c2hs (single .chs file) in a cabal build setup; can anybody give me some hints? thanks, sk ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] c2hs and cabal

2007-12-02 Thread Eric Sessoms
Just add Build-Tools: c2hs And cabal will take it from there. Stefan Kersten wrote: hi, i'm looking for a way to integrate c2hs (single .chs file) in a cabal build setup; can anybody give me some hints? thanks, sk ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] fast Array operations: foldl, drop

2007-12-02 Thread Don Stewart
rl: Don Stewart wrote: I forgot to mention this early, but possibly you could use the ndp array library. There are some people using its UArr type for (non parallel) strict arrays, that support map/fold/zip et al. http://darcs.haskell.org/packages/ndp/ This blog post recently,

Re: [Haskell-cafe] fast Array operations: foldl, drop

2007-12-02 Thread Roman Leshchinskiy
Don Stewart wrote: I forgot to mention this early, but possibly you could use the ndp array library. There are some people using its UArr type for (non parallel) strict arrays, that support map/fold/zip et al. http://darcs.haskell.org/packages/ndp/ This blog post recently,

Re: [Haskell-cafe] fast Array operations: foldl, drop

2007-12-02 Thread Roman Leshchinskiy
Don Stewart wrote: rl: Don Stewart wrote: I forgot to mention this early, but possibly you could use the ndp array library. There are some people using its UArr type for (non parallel) strict arrays, that support map/fold/zip et al. http://darcs.haskell.org/packages/ndp/ This blog post

[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 51, Issue 180

2007-12-02 Thread Don Stewart
emmanuel.delaborde: I'm trying to build diverse packages from Hackage with ghc 6.8.1, they usually fail to build because of missing language extensions. Sometimes I am unable to determine the proper name of the extension missing in .cabal I tend to slap {- #OPTIONS -fglasgow-exts #-} at

[Haskell-cafe] who develops and maintains the Unix package?

2007-12-02 Thread Galchin Vasili
Hello, I am starting to get in the groove related to runhaskell -- config/builds on top of cygwin (I haven't had time to carve up hard drive and install Linux). In any case, I really want to get the Unix package to build on cgywin (as advertised at

Re: [Haskell-cafe] who develops and maintains the Unix package?

2007-12-02 Thread Tim Chevalier
On 12/2/07, Galchin Vasili [EMAIL PROTECTED] wrote: Hello, I am starting to get in the groove related to runhaskell -- config/builds on top of cygwin (I haven't had time to carve up hard drive and install Linux). In any case, I really want to get the Unix package to build

[Haskell-cafe] Re: who develops and maintains the Unix package?

2007-12-02 Thread Galchin Vasili
On Dec 2, 2007 10:49 PM, Galchin Vasili [EMAIL PROTECTED] wrote: Hello, I am starting to get in the groove related to runhaskell -- config/builds on top of cygwin (I haven't had time to carve up hard drive and install Linux). In any case, I really want to get the Unix

[Haskell-cafe] Possible Improvements

2007-12-02 Thread PR Stanley
Hi data Tree = Leaf Int | Node Tree Int Tree occurs :: Int - Tree - Bool occurs m (Leaf n) = m == n occurs m (Node l n r) = m == n || occurs m l || occurs m r It works but I'd like to know if it can be improved in any way. Thanks, Paul ___

Re: [Haskell-cafe] Possible Improvements

2007-12-02 Thread Don Stewart
prstanley: Hi data Tree = Leaf Int | Node Tree Int Tree occurs :: Int - Tree - Bool occurs m (Leaf n) = m == n occurs m (Node l n r) = m == n || occurs m l || occurs m r It works but I'd like to know if it can be improved in any way. You could probably get away with: data Tree =

Re: [Haskell-cafe] Possible Improvements

2007-12-02 Thread Tim Chevalier
On 12/2/07, Don Stewart [EMAIL PROTECTED] wrote: prstanley: Hi data Tree = Leaf Int | Node Tree Int Tree occurs :: Int - Tree - Bool occurs m (Leaf n) = m == n occurs m (Node l n r) = m == n || occurs m l || occurs m r It works but I'd like to know if it can be improved in any

Re: [Haskell-cafe] Possible Improvements

2007-12-02 Thread Don Stewart
catamorphism: On 12/2/07, Don Stewart [EMAIL PROTECTED] wrote: prstanley: Hi data Tree = Leaf Int | Node Tree Int Tree occurs :: Int - Tree - Bool occurs m (Leaf n) = m == n occurs m (Node l n r) = m == n || occurs m l || occurs m r It works but I'd like to know if it

Re: [Haskell-cafe] doing builds using cygwin on Windows ....help

2007-12-02 Thread nanothief
VasiliIGalchin wrote: .. however, I don't see in which file PATH can be set. Any help? I really want to get my Haskell build environment set up and cranking away. Unless I misunderstood what you want, you can add a path to the PATH variable by adding the line: export

Re: [Haskell-cafe] Possible Improvements

2007-12-02 Thread Don Stewart
Fully lazy: data Tree = Leaf Int | Node Tree Int Tree $ time ./A 25 49 ./A 25 18.20s user 0.04s system 99% cpu 18.257 total ^^ 3556K heap use. Strict in the elements, lazy in the spine: data Tree

Re: [Haskell-cafe] Possible Improvements

2007-12-02 Thread Tomasz Zielonka
On Mon, Dec 03, 2007 at 05:20:35AM +, PR Stanley wrote: Hi data Tree = Leaf Int | Node Tree Int Tree occurs :: Int - Tree - Bool occurs m (Leaf n) = m == n occurs m (Node l n r) = m == n || occurs m l || occurs m r It works but I'd like to know if it can be improved in any way.

Re: [Haskell-cafe] Possible Improvements

2007-12-02 Thread Don Stewart
dons: * Full strictness == teh suckness. * Mixed lazy and strict == flexible and efficient data types. Makes me wonder why Map is strict in the spine, data Map k a = Tip | Bin {-# UNPACK #-} !Size !k a !(Map k a) !(Map k a) Spencer points out that

Re: [Haskell-cafe] Possible Improvements

2007-12-02 Thread Derek Elkins
On Sun, 2007-12-02 at 21:54 -0800, Don Stewart wrote: catamorphism: On 12/2/07, Don Stewart [EMAIL PROTECTED] wrote: prstanley: Hi data Tree = Leaf Int | Node Tree Int Tree occurs :: Int - Tree - Bool occurs m (Leaf n) = m == n occurs m (Node l n r) = m == n || occurs

[Haskell-cafe] Trees

2007-12-02 Thread Adrian Neumann
Good morning, as an exercise for my Algorithms and Programming course I have to program a couple of simple functions over trees. Until now everything we did in Java could be done in Haskell (usually much nicer too) using the naive data Tree a = Leaf a | Node a [Tree a] But now the

Re: [Haskell-cafe] Trees

2007-12-02 Thread Don Stewart
aneumann: Good morning, as an exercise for my Algorithms and Programming course I have to program a couple of simple functions over trees. Until now everything we did in Java could be done in Haskell (usually much nicer too) using the naive data Tree a = Leaf a | Node a [Tree a]

Re: [Haskell-cafe] Trees

2007-12-02 Thread Stefan O'Rear
On Mon, Dec 03, 2007 at 08:13:57AM +0100, Adrian Neumann wrote: Good morning, as an exercise for my Algorithms and Programming course I have to program a couple of simple functions over trees. Until now everything we did in Java could be done in Haskell (usually much nicer too) using the

[Haskell-cafe] more info on building the Unix package on cygwin

2007-12-02 Thread Galchin Vasili
Hello, I put an ugly kludge(on my laptop) in the unix.cabal file For the includes-dir attribute I explicited specified the path to the cygwin include directory. The Unix package build gets farther and then gets errors. At this point, it appears that the cygwin sys/types.h has a bug .. id_t