Re: [Haskell-cafe] Newbie: generating a truth table

2007-02-21 Thread Joe Thornber
On 2/10/07, Peter Berry [EMAIL PROTECTED] wrote: Prelude putStrLn $ concatMap (flip (++)\n) $ map show $ [(x,y,() x y) |x - [True,False],y - [True,False]] This can be simplified slightly to: Prelude putStrLn . unlines . map show $ [(x, y, x y) | x - [True, False], y - [True, False]] - Joe

[Haskell-cafe] Re: Haskell vs Ruby as a scripting language

2007-02-21 Thread Neil Mitchell
Hi Simon Benchmarks please! Let's see some comparisons on the nofib suite. If there's a factor of 2 or less between GHC -O2 and YHC for any of the nofib programs, I'll eat my keyboard for lunch :-) http://www.cse.unsw.edu.au/~dons/nobench/bench.results Test: pidigits (lazy, arbitrary

Re: [Haskell-cafe] Implementation of scaled integers

2007-02-21 Thread Henning Thielemann
On Tue, 13 Feb 2007, Stefan Heinzmann wrote: Hi all, is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type? I have implemented them in a generic way for

Data.Fixed and type encoded integers (Was: [Haskell-cafe] Implementation of scaled integers)

2007-02-21 Thread Henning Thielemann
On Tue, 13 Feb 2007, Twan van Laarhoven wrote: Stefan Heinzmann wrote: Hi all, is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type? Data.Fixed [1] does

Re: [Haskell-cafe] exists . a psuedo-standard non-empty list module

2007-02-21 Thread Henning Thielemann
On Thu, 15 Feb 2007, Nicolas Frisby wrote: I would also appreciate references to your favorite discussion about uses of head and other unsafe functions or various Oleg posts showing how they're all unnecessary. I'll find these on my own, but I would also like to know which ones strike a

[Haskell-cafe] Re: Haskell vs Ruby as a scripting language

2007-02-21 Thread Simon Marlow
Neil Mitchell wrote: Hi Simon Benchmarks please! Let's see some comparisons on the nofib suite. If there's a factor of 2 or less between GHC -O2 and YHC for any of the nofib programs, I'll eat my keyboard for lunch :-) http://www.cse.unsw.edu.au/~dons/nobench/bench.results Test:

Re: [Haskell-cafe] Re: Haskell vs Ruby as a scripting language

2007-02-21 Thread Donald Bruce Stewart
simonmarhaskell: Neil Mitchell wrote: Hi Simon Benchmarks please! Let's see some comparisons on the nofib suite. If there's a factor of 2 or less between GHC -O2 and YHC for any of the nofib programs, I'll eat my keyboard for lunch :-)

[Haskell-cafe] Multiparameter class error

2007-02-21 Thread Alfonso Acosta
Hi, I'm a newbie to multiparameter classes and I'm getting this error from GHC when compiling the following class definition: Could not deduce (Synchronous s f11) from the context (Synchronous s f1) arising from use of `delaySY' Possible fix: add (Synchronous s f11) to the

Re: [Haskell-cafe] Re: Map list of functions over a single argument

2007-02-21 Thread Henning Thielemann
On Tue, 20 Feb 2007 [EMAIL PROTECTED] wrote: Paul Moore wrote: I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument. The signature would be [a - b] - a - [b], but hoogle

Re: [Haskell-cafe] Multiparameter class error

2007-02-21 Thread Yitzchak Gale
Hi Alfonso, You wrote: Could not deduce (Synchronous s f11) from the context (Synchronous s f1) \begin{code} class Synchronous s f1 where mapSY :: f1 a b - s a - s b delaySY :: a- s a - s a sourceSY :: f1 a a - a- s a sourceSY f s0 = o where

[Haskell-cafe] functional database queries

2007-02-21 Thread Henning Thielemann
At http://www.haskell.org/hawiki/HaskellDbTutorial it is described, how database queries can be modelled with a monad. However, I wonder if this is also possible without monads. Say, writing DB.map col1 $ DB.filter (\row - col2 row == 10+2) myTable for SELECT col1 FROM MyTable where col2 =

Re: [Haskell-cafe] Multiparameter class error

2007-02-21 Thread Alfonso Acosta
Thanks, the functional dependency solved the problem On 2/21/07, Yitzchak Gale [EMAIL PROTECTED] wrote: Hi Alfonso, You wrote: Could not deduce (Synchronous s f11) from the context (Synchronous s f1) \begin{code} class Synchronous s f1 where mapSY :: f1 a b - s a -

Re: [Haskell-cafe] Re: Map list of functions over a single argument

2007-02-21 Thread Gene A
On 2/21/07, Henning Thielemann [EMAIL PROTECTED] wrote: On Tue, 20 Feb 2007 [EMAIL PROTECTED] wrote: Paul Moore wrote: I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument.

Re: [Haskell-cafe] Re: Map list of functions over a single argument

2007-02-21 Thread Jules Bean
Gene A wrote: Well this is not very sexy, no monads or anything, but I kinda believe in Keep It Simple: Prelude let revApply a f = f a Prelude let rMap a fs = map (revApply a) fs Prelude rMap 2 [(*4),(^2),(+12),(**0.5)] [8.0,4.0,14.0,1.4142135623730951] Note that revApply here is

[Haskell-cafe] Type-level lambdas in Haskell? ( was Multiparameter class error)

2007-02-21 Thread Alfonso Acosta
Now I'm facing another problem, sorry if it takes too long to reach the Type level lambdas issue ... The full definition of my class is class Synchronous s f1 f2 | s - f1, s - f2 where mapSY :: f1 a b - s a - s b delaySY :: a - s a - s a zipWithSY :: f2 a b c- s a - s b - s c

[Haskell-cafe] Re: Saving the AST generated by Template Haskell

2007-02-21 Thread Alfonso Acosta
The example wasn't really clear, I anyway solved the issue. Here is a summary. The problem: There are some cases (at least when developing a DSEL with Templpate Haskell like I am) in which it might be really useful to keep the AST gathered by the TH quasi quotes for later processing during

Re: [Haskell-cafe] functional database queries

2007-02-21 Thread Albert Y. C. Lai
Henning Thielemann wrote: At http://www.haskell.org/hawiki/HaskellDbTutorial it is described, how database queries can be modelled with a monad. However, I wonder if this is also possible without monads. Say, writing DB.map col1 $ DB.filter (\row - col2 row == 10+2) myTable for SELECT col1

Re: [Haskell-cafe] exists . a psuedo-standard non-empty list module

2007-02-21 Thread Alfonso Acosta
Hi Nick, On 2/16/07, Nicolas Frisby [EMAIL PROTECTED] wrote: I don't particularly like using fromJust or head, and there's been IMHO I think that isJust/fromJust could simply be removed. Using 'maybe' is a much better practice, it is safe and much even more expressive. head on the other hand

[Haskell-cafe] Re: functional database queries

2007-02-21 Thread apfelmus
Henning Thielemann wrote: At http://www.haskell.org/hawiki/HaskellDbTutorial it is described, how database queries can be modelled with a monad. However, I wonder if this is also possible without monads. Say, writing DB.map col1 $ DB.filter (\row - col2 row == 10+2) myTable for SELECT

Re: [Haskell-cafe] Re: functional database queries

2007-02-21 Thread Albert Y. C. Lai
[EMAIL PROTECTED] wrote: Albert Y. C. Lai wrote: If and only if the database is a purely functional immutable data structure, this can be done. [...] Many interesting databases are not purely functional immutable; most reside in the external world and can spontaneously change behind your

[Haskell-cafe] Leaves of a Tree

2007-02-21 Thread Tom Hawkins
Hello, Any recommendations for speeding up extracting the set of leaves from a tree? data Tree = Branch Tree Tree | Leaf Int deriving (Eq, Ord) My slow, naive function: leaves :: Tree - Set Int leaves (Leaf n) = singleton n leaves (Branch left right) = union (leaves left) (leaves right) In

Re: [Haskell-cafe] Leaves of a Tree

2007-02-21 Thread Jefferson Heard
Alternatively, the definition of your tree could include a list of linked lists, one for each level of the tree. Then you could just select the last list and it's the same as saving only the leaves from a complete inorder walk of the tree. data AltTree a = AltTree { tree_structure :: Tree a,

[Haskell-cafe] Re: functional database queries

2007-02-21 Thread apfelmus
Albert Y. C. Lai wrote: [EMAIL PROTECTED] wrote: Albert Y. C. Lai wrote: If and only if the database is a purely functional immutable data structure, this can be done. [...] Many interesting databases are not purely functional immutable; most reside in the external world and can

Re: [Haskell-cafe] Re: Map list of functions over a single argument

2007-02-21 Thread Gene A
On 2/21/07, Jules Bean [EMAIL PROTECTED] wrote: Gene A wrote: Prelude let revApply a f = f a Prelude let rMap a fs = map (revApply a) fs Prelude rMap 2 [(*4),(^2),(+12),(**0.5)] [8.0,4.0,14.0,1.4142135623730951] Note that revApply here is precisely flip ($). And ($a) is the same as flip

Re: [Haskell-cafe] Newbie: generating a truth table

2007-02-21 Thread Ricardo Herrmann
One possible way to generate the values would be using a generic function for permutation with repetition, such as: permuteRep :: [a] - [b] - [[(a,b)]] permuteRep [] _ = [] permuteRep (a:[]) bs = [ [ (a,b) ] | b - bs ] permuteRep (a:as) bs = concat [ [ (a,b):p | p - permuteRep as bs ] | b - bs ]

Re: [Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-21 Thread Dan Weston
I would be interested in seeing a multithreaded solution, with each child thread crossing off the multiples of its own prime. The parent thread would be blocked from spawning a new thread for multiples of the next prime p until all existing child threads are past p. It is not clear to me what

Re: [Haskell-cafe] Newbie: generating a truth table

2007-02-21 Thread Henk-Jan van Tuyl
On 2007-02-21, Joe Thornber [EMAIL PROTECTED] wrote: On 2007-02-10, Peter Berry [EMAIL PROTECTED] wrote: Prelude putStrLn $ concatMap (flip (++)\n) $ map show $ [(x,y,() x y) |x - [True,False],y - [True,False]] This can be simplified slightly to: Prelude putStrLn . unlines . map show $

Re: [Haskell-cafe] Leaves of a Tree

2007-02-21 Thread Donald Bruce Stewart
tomahawkins: Hello, Any recommendations for speeding up extracting the set of leaves from a tree? data Tree = Branch Tree Tree | Leaf Int deriving (Eq, Ord) My slow, naive function: leaves :: Tree - Set Int leaves (Leaf n) = singleton n leaves (Branch left right) = union (leaves

[Haskell-cafe] Re: Leaves of a Tree

2007-02-21 Thread Chad Scherrer
Tom, I think inserting elements would be a lot faster than multiple unions. I would try: leafList :: Tree - [Int] leafList (Leaf n) = [n] leafList (Branch left right) = leafList left ++ leafList right leaves = fromList . leafList If you're writing many functions on Trees (or maybe even if

Re: [Haskell-cafe] exists . a psuedo-standard non-empty list module

2007-02-21 Thread Neil Mitchell
Hi IMHO I think that isJust/fromJust could simply be removed. Using 'maybe' is a much better practice, it is safe and much even more expressive. Yes, its more expressive if you let someone write (error Umm, what should I do here?) as one of the options. And now you've gone from something with

Re: [Haskell-cafe] Leaves of a Tree

2007-02-21 Thread Neil Mitchell
Hi Tom data Tree = Branch Tree Tree | Leaf Int deriving (Eq, Ord) leaves :: Tree - Set Int leaves (Leaf n) = singleton n leaves (Branch left right) = union (leaves left) (leaves right) The standard method for a traversal over leaves with accumulation is: leaves :: Tree - Set Int leaves x

Re: [Haskell-cafe] Re: functional database queries

2007-02-21 Thread Bjorn Bringert
On Feb 21, 2007, at 20:47 , [EMAIL PROTECTED] wrote: Albert Y. C. Lai wrote: [EMAIL PROTECTED] wrote: Albert Y. C. Lai wrote: If and only if the database is a purely functional immutable data structure, this can be done. [...] Many interesting databases are not purely functional immutable;

Re: [Haskell-cafe] Re: Saving the AST generated by Template Haskell

2007-02-21 Thread Alfonso Acosta
Hi Ian, On 2/22/07, Ian Lynagh [EMAIL PROTECTED] wrote: I've just added th-lift to hackage (http://hackage.haskell.org/). You can use it to Derive lift for existing types. If only I knew about it before coding it by hand. It anyway it wasn't that bad cause I only support a subset of the AST

Re: [Haskell-cafe] FFI basics

2007-02-21 Thread Evan Laforge
On 2/19/07, Yitzchak Gale [EMAIL PROTECTED] wrote: Simon Peyton-Jones wrote: Yitz, Please do make time to do this! This is the moment, while it is still fresh in your mind. Of course, you are correct. Thanks for the push. I am a bit busy with work, but the information is not lost. I'll have

Re: [Haskell-cafe] exists . a psuedo-standard non-empty list module

2007-02-21 Thread Nicolas Frisby
Despite the fact that I like head/fromJust etc, a safe list library would be kind of handy. If someone wants to roll that into the Safe library, as Safe.List or something, I'd be happy to accept patches (saving someone else the hassle of setting up a new library etc, for roughly the same purpose)

Re: [Haskell-cafe] Type-level lambdas in Haskell? ( was Multiparameter class error)

2007-02-21 Thread Jim Apple
On 2/21/07, Alfonso Acosta [EMAIL PROTECTED] wrote: In my opinion adding Type-level lambdas would be the way to go, but they unfortunately are not part of Haskell. [snip] Is there any extension to the language covering type-level lambdas or even a plan to include them in next revision? SPJ

[Haskell-cafe] Type-level lambdas in Haskell?

2007-02-21 Thread oleg
On 2/21/07, Alfonso Acosta alfonso.acosta at gmail.com wrote: In my opinion adding Type-level lambdas would be the way to go, but they unfortunately are not part of Haskell. Type-level lambdas are already present in Haskell. Please see the messages On computable types. I. Typed lambda and

[Haskell-cafe] Re: Leaves of a Tree

2007-02-21 Thread Tom Hawkins
On 2/21/07, Chad Scherrer [EMAIL PROTECTED] wrote: Tom, I think inserting elements would be a lot faster than multiple unions. I would try: leafList :: Tree - [Int] leafList (Leaf n) = [n] leafList (Branch left right) = leafList left ++ leafList right leaves = fromList . leafList If you're

[Haskell-cafe] Re: Leaves of a Tree

2007-02-21 Thread Chad Scherrer
Neil, I think this idea is better than what I had suggested, but as it stands it doesn't typecheck. Did you mean something like this? leaves :: Tree - [Int] leaves = f [] where f rest (Leaf n) = n : rest f rest (Branch l r) = f (f rest r) l -Chad ---

Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-21 Thread P. R. Stanley
and can I please ask anyone thinking of using special symbols to resist the temptation. Symbols such as the 160 used liberally in the Haskell wikibook are totally invisible to screen readers. I would be happy to proof read any document before it goes to the wikibook to ensure it's fully

[Haskell-cafe] Is anyone using CUDA with haskell yet?

2007-02-21 Thread Jefferson Heard
I don't want to duplicate anyone's work, and I'm not sure that NDA would allow me to release the code in any case (have to check on it carefully), but is anyone currently using the CUDA framework from nVidia inside of Haskell for highly parallel programming? -- Jeff

Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-21 Thread Jefferson Heard
I second this plea. -- Jeff On Wednesday 21 February 2007 22:34, P. R. Stanley wrote: and can I please ask anyone thinking of using special symbols to resist the temptation. Symbols such as the 160 used liberally in the Haskell wikibook are totally invisible to screen readers. I would be

[Haskell-cafe] Type-level lambdas in Haskell? ( was Multiparameter class error)

2007-02-21 Thread oleg
Alfonso Acosta wrote: class Synchronous s f1 f2 | s - f1, s - f2 where mapSY :: f1 a b - s a - s b delaySY:: a - s a - s a zipWithSY :: f2 a b c- s a - s b - s c The goal of this class is to extend the name of the following functions (which BTW are already

[Haskell-cafe] Re: Type-level lambdas in Haskell? ( was Multiparameter class error)

2007-02-21 Thread Alfonso Acosta
On 2/22/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: First of all, the design already exhibits the problem: [snip] The reason is that [..] the function delaySY is declared *fully* polymorphic over 'a' -- there are no constraints on a and no restrictions. However, delaySY :: HDPrimType a

[Haskell-cafe] TFP 2007: Registration and Program

2007-02-21 Thread TFP 2007
Dear Colleagues, You may now resgister for TFP 2007! TFP 2007 will be held April 2-4, 2007 in New York City, USA. Our invited speaker is John McCarthy, Stanford University. Further details can be found at our homepage: http://cs.shu.edu/tfp2007/ . You may register at:

[Haskell-cafe] Re: Leaves of a Tree

2007-02-21 Thread Chad Scherrer
Hi Tom, Tom Hawkins wrote: Folding was my first approach: leaves :: Tree - Set Int leaves tree = accumLeaves Set.empty tree accumLeaves :: Set Int - Tree - Set Int accumLeaves set (Leaf n) = insert n set accumLeaves set (Branch l r) = foldl accumLeaves set [l,r] However, with this approach I