[Haskell-cafe] unsafeInerleaveIO and randomIO

2007-04-17 Thread Marc Weber
stefan has pointed me a nice version: = === randomInts :: IO [Int] randomInts = randoms `fmap` newStdGen main = do ints - randomInts print $ take 5 ints ===

Re: [Haskell-cafe] Tutorial on Haskell

2007-04-17 Thread ajb
G'day all. I wrote: I think you could. What you need to convince a strict programmer of is that laziness gives you modularity. The Graham Hutton Sudoku solver is a nice example, but it'd be cool if we had a similar example that was less cheesy than Sudoku. OK, it's not pretty, but this is

Re: [Haskell-cafe] Zero-arity tests in QuickCheck and displaying expected result

2007-04-17 Thread Ketil Malde
On Mon, 2007-04-16 at 22:17 +0100, Joel Reymont wrote: On Apr 16, 2007, at 10:11 PM, Lennart Augustsson wrote: Why can't you just do 'f 1 2 3 == (4, 5, 6, 7)' to test f? That's what HUnit does but it's enticing to be able to standardize on QuickCheck for all of your testing. Prelude

Re: [Haskell-cafe] Zero-arity tests in QuickCheck and displaying expected result

2007-04-17 Thread Joel Reymont
On Apr 17, 2007, at 9:31 AM, Ketil Malde wrote: Prelude Test.QuickCheck let prop0 = List.sort [3,2,1] == [1,2,3] in quickCheck prop0 OK, passed 100 tests. My point is to be able to see that result generated was X and that it did not match expected Y, where both X and Y are printed out.

[Haskell-cafe] GHC 6.7 and Associated Types

2007-04-17 Thread Maxime Henrion
Hello guys, I've been documenting myself on associated types, which look like a very nice way to deal with the problems that arise with multi-parameter type classes. As an exercise, I am trying to rewrite the MonadState type class from the mtl package without functional dependencies.

Re: [Haskell-cafe] Efficient use of ByteString and type classes in template system

2007-04-17 Thread Thomas Hartman
Created wiki page http://haskell.org/haskellwiki/String_Interpolation and referenced various topics mentioned in this thread, there. 2007/4/16, Donald Bruce Stewart [EMAIL PROTECTED]: johan.tibell: Hi Haskell Caf?! I'm writing a perl/python like string templating system which I plan to

[Haskell-cafe] Re: Type classes and type equality

2007-04-17 Thread Neil Mitchell
Hi Oleg, I'm looking for a type class which checks whether two types are the same or not. For the full discussion of various solutions, please see Section 9 and Appendix D of the HList paper: http://homepages.cwi.nl/~ralf/HList/paper.pdf Thanks for pointing that out. As far as I

[Haskell-cafe] Re: Tutorial on Haskell

2007-04-17 Thread apfelmus
[EMAIL PROTECTED] wrote: OK, it's not pretty, but this is diff(1) in 120 lines: http://andrew.bromage.org/darcs/diff/ (Btw, pairs (Int,Int) are members of the Ix class as well, so there is no need to generate an array of arrays. You can just pretend that one array is indexed by pair of

[Haskell-cafe] Re: GHC 6.7 and Associated Types

2007-04-17 Thread apfelmus
Maxime Henrion wrote: class MonadState m where type StateType m :: * get :: m StateType put :: m StateType - m () As for instances: instance MonadState (State s) where type StateType = s -- this is line 22 When defining the type

Re: [Haskell-cafe] Re: GHC 6.7 and Associated Types

2007-04-17 Thread Maxime Henrion
apfelmus wrote: Maxime Henrion wrote: class MonadState m where type StateType m :: * get :: m StateType put :: m StateType - m () As for instances: instance MonadState (State s) where type StateType = s -- this is line 22

[Haskell-cafe] Re: GHC 6.7 and Associated Types

2007-04-17 Thread apfelmus
Maxime Henrion wrote: apfelmus wrote: Maxime Henrion wrote: class MonadState m where type StateType m :: * get :: m StateType put :: m StateType - m () As for instances: instance MonadState (State s) where type StateType = s -- this

[Haskell-cafe] Re: Parallel executing of actions

2007-04-17 Thread Simon Marlow
Mitar wrote: Hi! On 4/16/07, Bertram Felgenhauer [EMAIL PROTECTED] wrote: Since all the threads block on a single MVar how do they run in parallel? The idea is that before the threads block on the MVar, they run their action x to completion. The rendering crashes. I will have to

Re: [Haskell-cafe] Re: GHC 6.7 and Associated Types

2007-04-17 Thread Maxime Henrion
Simon Peyton-Jones wrote: Associated *data* types should work in the HEAD (=6.7). But associated *type synonyms* do not, I'm afraid. We are actively working on it, but it'll be a couple of months at least I guess. You can see the state of play, and description of where we are up to here

Re: [Haskell-cafe] Re: GHC 6.7 and Associated Types

2007-04-17 Thread Maxime Henrion
apfelmus wrote: Maxime Henrion wrote: apfelmus wrote: Maxime Henrion wrote: class MonadState m where type StateType m :: * get :: m StateType put :: m StateType - m () As for instances: instance MonadState (State s) where type StateType = s

[Haskell-cafe] Re: Partial parsers in Happy

2007-04-17 Thread Simon Marlow
Juan Carlos Arevalo Baeza wrote: More info: I managed to do a hack that works around it, but it is clearly not acceptable. Part of the Haskell code generated by Happy contains this: --- -- Accepting the parse -- If

[Haskell-cafe] Re: multithreading speedup

2007-04-17 Thread Simon Marlow
Fawzi Mohamed wrote: Il giorno Apr 14, 2007, alle ore 2:45 PM, Sebastian Sylvan ha scritto: I think you should probably consider the extremely lightweight forkIO threads as your work items and the GHC runtime as your thread pool system (it will find out how many threads you want using the

Re: [Haskell-cafe] Efficient use of ByteString and type classes in template system

2007-04-17 Thread Johan Tibell
Great! I've written some QuickCheck tests now (not commited) so I can start to swap out the implementation and benchmark it. After I get it to run fast enough and some nice utility methods (like the possibility of using records as context) I'll announce a version 1.0. Johan On 4/17/07, Thomas

Re: [Haskell-cafe] and sequencing [newbie]

2007-04-17 Thread David Powers
Like point free notation, I worry about what somebody somewhere is doing to it :) The existence of a well understood community standard (add a type signature to your functions and only use monad operators with the laws) helps a lot - but both pieces are optional. I suppose the shorter and

Re: [Haskell-cafe] implementing try for RWST ?

2007-04-17 Thread Chris Kuklewicz
Brandon S. Allbery KF8NH wrote: On Apr 17, 2007, at 0:03 , [EMAIL PROTECTED] wrote: eventually run in the IO monad. One may wonder then why do we need RWST transformer, given that the IO monad can implement both the state For what it's worth, I got the impression that RWST was an example

Re: [Haskell-cafe] unsafeInerleaveIO and randomIO

2007-04-17 Thread Matthew Brecknell
Bertram Felgenhauer: unsafeInterleaveSequence :: [IO a] - IO [a] unsafeInterleaveSequence [] = return [] unsafeInterleaveSequence (x:xs) = unsafeInterleaveIO $ liftM2 (:) x (unsafeInterleaveSequence xs) randomInts = unsafeInterleaveSequence $ repeat randomIO I took a peek at

[Haskell-cafe] Re: Export Haskell Libraries

2007-04-17 Thread Simon Marlow
Dan Weston wrote: In the GHC docs: http://www.haskell.org/ghc/docs/6.4.1/html/users_guide/sec-ffi-ghc.html#using-own-main There can be multiple calls to hs_init(), but each one should be matched by one (and only one) call to hs_exit()[8]. What exactly happens with nested calls? Is there

RE: [Haskell-cafe] Re: GHC 6.7 and Associated Types

2007-04-17 Thread Simon Peyton-Jones
Associated *data* types should work in the HEAD (=6.7). But associated *type synonyms* do not, I'm afraid. We are actively working on it, but it'll be a couple of months at least I guess. You can see the state of play, and description of where we are up to here

[Haskell-cafe] question about Data.Binary and Double instance

2007-04-17 Thread David Roundy
Hi all, I'm wondering what exactly inspired the decode/encodeFloat implementation for Data.Binary? It seems to me like it'd be much better to use a standard format like IEEE, which would also be much more efficient, since as far as I know, on every implementation a Double and a CDouble are

Re: [Haskell-cafe] Parallel executing of actions

2007-04-17 Thread Sebastian Sylvan
On 4/16/07, Mitar [EMAIL PROTECTED] wrote: Hi! On 4/16/07, Bertram Felgenhauer [EMAIL PROTECTED] wrote: Since all the threads block on a single MVar how do they run in parallel? The idea is that before the threads block on the MVar, they run their action x to completion. The rendering

Re: [Haskell-cafe] question about Data.Binary and Double instance

2007-04-17 Thread Brian Alliet
On Tue, Apr 17, 2007 at 10:32:02AM -0700, David Roundy wrote: I'm wondering what exactly inspired the decode/encodeFloat implementation I kind of wondered the same thing when I first saw it. Looks like it was just the quickest way to get it going. Are there any suggestions how I could use

Re: [Haskell-cafe] question about Data.Binary and Double instance

2007-04-17 Thread David Roundy
On Tue, Apr 17, 2007 at 02:50:14PM -0400, Brian Alliet wrote: I threw together a somewhat portable longBitsToDouble function a while ago for another project. http://darcs.brianweb.net/hsutils/src/Brianweb/Data/Float.lhs It doesn't depend on any unsafe operations or external ffi functions

Re: [Haskell-cafe] question about Data.Binary and Double instance

2007-04-17 Thread Brian Alliet
On Tue, Apr 17, 2007 at 12:18:29PM -0700, David Roundy wrote: machine ghc run on). It might not be fast enough for you though as it still goes via Integer in the conversion. It seems like this conversion shouldn't take any time at all, and we ought to be able to just copy the memory right

[Haskell-cafe] Re: Type classes and type equality

2007-04-17 Thread oleg
Thanks for pointing that out. As far as I can see, this requires a new instance declaration for every type? I guess it depends on how many extensions one may wish to enable. At the very least we need multi-parameter type classes with functional dependencies (because that's what TypeEq is in

Re: [Haskell-cafe] Parallel executing of actions

2007-04-17 Thread Mitar
Hi! On 4/17/07, Sebastian Sylvan [EMAIL PROTECTED] wrote: I would suggest chunking up your work (assuming that calculating your colour is indeed a significant amount of work) in tiles or something, then fork off a thread for each of them, sticking the final colours in a Chan. Then you have

Re: [Haskell-cafe] ... - what about introducing LazyIO ?

2007-04-17 Thread Marc Weber
sequence isn't lazy (not in the IO monad at least); it will try to run to completion, returning an infinite list of (as yet unevaluated, due I should have learned that lesson already.. This is the second time I could have needed a lazy IO monad version.. Does something like this already exist?

Re: [Haskell-cafe] Tutorial on Haskell

2007-04-17 Thread R Hayes
In my opinion, one of the things that makes Haskell difficult to learn is the value system. I'm not referring to pure vs. impure. Instead, I am referring to the beliefs and principles held by the Haskell community that are not shared with most of the programming world. Principles like

Re: [Haskell-cafe] Re: Tutorial on Haskell

2007-04-17 Thread ajb
G'day all. Quoting apfelmus [EMAIL PROTECTED]: (Btw, pairs (Int,Int) are members of the Ix class as well, so there is no need to generate an array of arrays. I know. It originally used lists, which is why it looks like that. I only allowed myself half an hour to write debug this, so what

Re: [Haskell-cafe] Tutorial on Haskell

2007-04-17 Thread David Brown
R Hayes wrote: They *enjoy* debugging ... I have to say this is one of the best things I've found for catching bad programmers during interviews, no matter what kind of system it is for. I learned this the hard way after watching someone who never really understood her program, but just kept

[Haskell-cafe] Tutorial on Haskell

2007-04-17 Thread dfeustel
What would be really useful is a Haskell Cookbook that shows how to do in Haskell things that are so easily done in imperative languages. How to solve simultaneous equations using Gaussian elimination comes to mind. Lots of examples would be great. Dave Feustel

Re: [Haskell-cafe] Tutorial on Haskell

2007-04-17 Thread R Hayes
On Apr 17, 2007, at 4:46 PM, David Brown wrote: R Hayes wrote: They *enjoy* debugging ... I have to say this is one of the best things I've found for catching bad programmers during interviews, no matter what kind of system it is for. I learned this the hard way after watching someone

[Haskell-cafe] Re: Type classes and type equality

2007-04-17 Thread Neil Mitchell
Hi I guess it depends on how many extensions one may wish to enable. At the very least we need multi-parameter type classes with functional dependencies (because that's what TypeEq is in any case). - If we permit no other extension, we need N^2 instances to compare N classes for equality

Re: [Haskell-cafe] Parallel executing of actions

2007-04-17 Thread Juan Carlos Arevalo Baeza
I may be talking out of my other end here, but... if you want something like parMap to calculate all the pixels in parallel, then... can't you use parMap itself? Something like: weirdParMap action = sequence_ . map action . parMap (id $!) This evaluates all the elements of the

Re: [Haskell-cafe] Parallel executing of actions

2007-04-17 Thread Stefan O'Rear
On Tue, Apr 17, 2007 at 05:49:11PM -0700, Juan Carlos Arevalo Baeza wrote: I may be talking out of my other end here, but... if you want something like parMap to calculate all the pixels in parallel, then... can't you use parMap itself? Something like: weirdParMap action =

Re: [Haskell-cafe] Re: Type classes and type equality

2007-04-17 Thread Stefan O'Rear
On Wed, Apr 18, 2007 at 01:47:04AM +0100, Neil Mitchell wrote: - If we permit undecidable instances, one may assign numerals to types. This gives us total order and hence comparison on types. In this approach, we only need N instances to cover N types. This is still better than Typeable

Re: [Haskell-cafe] question about Data.Binary and Double instance

2007-04-17 Thread Duncan Coutts
On Tue, 2007-04-17 at 10:32 -0700, David Roundy wrote: Hi all, I'm wondering what exactly inspired the decode/encodeFloat implementation for Data.Binary? It seems to me like it'd be much better to use a standard format like IEEE, which would also be much more efficient, since as far as I

Re: [Haskell-cafe] Parallel executing of actions

2007-04-17 Thread Juan Carlos Arevalo Baeza
:-) Thank you for your kindness. I mean... your frankness. I had another issue in that code which clearly shows that I don't know how to use parMap or strategies in general. Maybe this is better: weirdParMap action = sequence_ . map action . parMap rwhnf (\x - x `seq` x) or

Re: [Haskell-cafe] question about Data.Binary and Double instance

2007-04-17 Thread Brian Alliet
On Wed, Apr 18, 2007 at 12:34:58PM +1000, Duncan Coutts wrote: We'd like to use IEEE format as the default Data.Binary serialisation format for Haskell's Float and Double type, the only thing that makes this tricky is doing it portably and efficiently. You should note that your current method

Re: [Haskell-cafe] Tutorial on Haskell

2007-04-17 Thread Michael Vanier
R Hayes wrote: On Apr 17, 2007, at 4:46 PM, David Brown wrote: R Hayes wrote: They *enjoy* debugging ... I have to say this is one of the best things I've found for catching bad programmers during interviews, no matter what kind of system it is for. I learned this the hard way after