[Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread Donald Bruce Stewart
simonmarhaskell: Forwarding on behalf of Andrzej Jaworski [EMAIL PROTECTED]: Original Message From: Andrzej Jaworski [EMAIL PROTECTED] Dear fellows, It is ironic that just after SPJ disclosed Comments from Brent Fulgham on Haskell and the shootout the situation has

Re: [Haskell-cafe] basic field questions

2007-01-25 Thread jamin1001
Well, it seems this approach doesn't allow you to group some fields together like colour and weight, but instead you need to relist them piecemeal for each new data constructor. Also, you get a run-time error (rather than compile-time) if you happen to reference a field that didn't happen to

Re: [Haskell-cafe] Monomorphism restriction

2007-01-25 Thread Yitzchak Gale
Neil Mitchell wrote: http://haskell.org/hawiki/MonomorphismRestriction Note to others (esp Cale): does this page not appear on the new wiki? I did a very rough quick conversion: http://www.haskell.org/haskellwiki/MonomorphismRestriction The old wiki is locked, for obvious reasons. But

Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-25 Thread Brian Hulley
On Thursday, January 25, 2007 7:08 AM, John Ky wrote: On 1/25/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: I'm probably missing something, but: (a) Why not: data ANode = Branch { name :: String, description :: String, children :: [AnyNode] }

Re: [Haskell-cafe] basic field questions

2007-01-25 Thread Neil Mitchell
Hi sq = squishiness $ Table {colour = Black, weight=1, height= 2} main = putStr $ show sq squishiness is just translated to: squishiness :: Furniture - Double squishiness (Chair _ _ x) = x squishiness _ = error doh main: No match in record selector Main.squishiness Hence this is a

Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-25 Thread Chris Kuklewicz
This is how I would write getLeaves, based on your GADT: data IsLeaf data IsBranch newtype Node = Node { getNode :: (forall c. ANode c) } data ANode :: * - * where Branch :: String - String - (ANode a,ANode b) - [Node] - ANode IsBranch Leaf :: String - String - ANode IsLeaf

Re: [Haskell-cafe] IO is not a monad

2007-01-25 Thread Yitzchak Gale
Scott Turner wrote: Paul B. Levy's studies of call-by-push-value model strictness/laziness using a category theoretic approach. That sounds interesting. Do you have a reference for that? Thanks, Yitz ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Type infer

2007-01-25 Thread Marco Túlio Gontijo e Silva
Em Qua, 2007-01-24 às 20:36 -0500, Bryan Donlan escreveu: Marco Túlio Gontijo e Silva wrote: Hello, I'm trying to define a partition__ function that is like Data.Set.partition, but use State Monad: import Data.Set import Control.Monad.State partition__ f = do

[Haskell-cafe] Old wiki page source text - was Monomorphism restriction

2007-01-25 Thread Bayley, Alistair
Neil Mitchell wrote: http://haskell.org/hawiki/MonomorphismRestriction Note to others (esp Cale): does this page not appear on the new wiki? I did a very rough quick conversion: http://www.haskell.org/haskellwiki/MonomorphismRestriction The old wiki is locked, for obvious reasons.

Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-25 Thread John Ky
Let me try this option and see how I go. Thanks -John On 1/25/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: (b) I think you *can* do this with a class: class Node a where name :: a - String data Branch = Branch { brName :: String, ... } data Leaf = Leaf { lName :: String,

Re: [Haskell-cafe] IO is not a monad

2007-01-25 Thread Yitzchak Gale
I wrote: 1. Find a way to model strictness/laziness properties of Haskell functions in a category in a way that is reasonably rich. Duncan Coutts wrote: The reason it's not obvious for categories is because the semantics for Haskell comes from domain theory (CPOs etc) not categories. The

[Haskell-cafe] Re: Old wiki page source text - was Monomorphism restriction

2007-01-25 Thread Yitzchak Gale
I wrote: I did a very rough quick conversion: http://haskell.org/hawiki/MonomorphismRestriction http://www.haskell.org/haskellwiki/MonomorphismRestriction Oops. Moved to: http://www.haskell.org/haskellwiki/Monomorphism_Restriction Alistair Bayley wrote: You can see the source for the page

[Haskell-cafe] A function for Maybes

2007-01-25 Thread John Ky
Is there a built-in function that already does this? foo :: (a - b) - Maybe a - Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f (fromJust m)) *Main foo (+2) (Just 3) Just 5 *Main foo (+2) Nothing Nothing If so what is it? If not, what should I call it? Thanks -John

Re: [Haskell-cafe] A function for Maybes

2007-01-25 Thread Brandon S. Allbery KF8NH
On Jan 25, 2007, at 9:15 , John Ky wrote: Is there a built-in function that already does this? foo :: (a - b) - Maybe a - Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f (fromJust m)) Nothing specific to Maybe, because the more general liftM (over monads) or fmap (over

Re: [Haskell-cafe] A function for Maybes

2007-01-25 Thread J. Garrett Morris
fmap. e.g.: Prelude fmap ('c':) (Just a) Just ca Prelude fmap ('c':) Nothing Nothing Prelude /g On 1/25/07, John Ky [EMAIL PROTECTED] wrote: Is there a built-in function that already does this? foo :: (a - b) - Maybe a - Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f

Re: [Haskell-cafe] A function for Maybes

2007-01-25 Thread Andrew Wagner
:t liftM forall r (m :: * - *) a1. (Monad m) = (a1 - r) - m a1 - m r liftM (+2) (Just 3 Just 5 liftM (+2) Nothing Nothing (Thanks to allbery_b for contributing to the discussion on #haskell) On 1/25/07, John Ky [EMAIL PROTECTED] wrote: Is there a built-in function that already does this?

Re: [Haskell-cafe] IO is not a monad

2007-01-25 Thread Robert Dockins
On Jan 25, 2007, at 6:57 AM, Yitzchak Gale wrote: Scott Turner wrote: Paul B. Levy's studies of call-by-push-value model strictness/ laziness using a category theoretic approach. That sounds interesting. Do you have a reference for that? http://www.cs.bham.ac.uk/~pbl/papers/ The first

[Haskell-cafe] RE: Old wiki page source text - was Monomorphism restriction

2007-01-25 Thread Bayley, Alistair
I wrote: I did a very rough quick conversion: http://haskell.org/hawiki/MonomorphismRestriction http://www.haskell.org/haskellwiki/MonomorphismRestriction Oops. Moved to: http://www.haskell.org/haskellwiki/Monomorphism_Restriction Alistair Bayley wrote: You can see the source for

RE: [Haskell-cafe] Type infer

2007-01-25 Thread Simon Peyton-Jones
This isn't a type-soundness bug; but it could be considered a user-interface sort of bug. After all, it's caused users to be puzzled. It arises really because it was convenient for the implementation. Do go ahead and file it as a Trac bug if it tripped you up enough to be worth fixing. A

Re: [Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread Kirsten Chevalier
On 1/25/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote: The degradation is due to two things: * several entries have been disqualified (some fairly, some unfairly) Fix: fix is to submit more * the shootout haskellers stopped submitting once it was clear we'd need

Re: [Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread Neil Mitchell
Hi I have to disagree with this. That is, I don't object to Don's explanation of why the shootout entries degraded in this particular case, but I do think that Andrzej was right to point this out: Perhaps making a collective effort towards benchmarking Haskell programs and analyzing the results

Re: [Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread Philippa Cowderoy
On Thu, 25 Jan 2007, Kirsten Chevalier wrote: Anything better than staring at intermediate code would be an improvement, since time spent staring at intermediate code usually is time spent narrowing down the 2 lines out of 1000 that are relevant. Maybe it's possible to design tools that could

Re: [Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread Neil Mitchell
Hi Sorry for being unclear. I agree with your comments on GHC, and one thing I was suggesting was that somebody should think about profiling tools for improving our understanding of how those transformations interact with each other, not just profiling tools for understanding the end result.

[Haskell-cafe] Re: A function for Maybes

2007-01-25 Thread Al Falloon
John Ky wrote: Is there a built-in function that already does this? Usually, when I have a question like this, I try Hoogle first: http://www.haskell.org/hoogle/?q=%28a+-%3E+b%29+-%3E+Maybe+a+-%3E+Maybe+b Unfortunatly, the right answer (fmap) is on the second page of results. (I am really

Re: [Haskell-cafe] Re: A function for Maybes

2007-01-25 Thread Neil Mitchell
Hi Alan, Usually, when I have a question like this, I try Hoogle first: http://www.haskell.org/hoogle/?q=%28a+-%3E+b%29+-%3E+Maybe+a+-%3E+Maybe+b Unfortunatly, the right answer (fmap) is on the second page of results. The reason for this is that Hoogle 3 doesn't understand higher-kinded type

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

2007-01-25 Thread Alfonso Acosta
Hi all, I'm using Template Haskell to design a small subset of a Hardware Description DSEL (Domain Specific Embedded Language). My language supports higher order as the user can supply small functions as arguments. I chose to parse them with TH because it allows me to use plain Haskell for the

[Haskell-cafe] Concurrency in Haskell

2007-01-25 Thread Alexy Khrabrov
What's the state of concurrency in Haskell? If Erlang's main strength is light-weight parallelism, can something like that be done in Haskell? Are there good examples of useful code employing GHC concurrency features one can play with? Cheers, Alexy

Re: [Haskell-cafe] Concurrency in Haskell

2007-01-25 Thread Chris Eidhof
Yes, I'm curious too. For example, it would be great if we could change a function that uses map almost automatically to a function that does the map in parallel. Ofcourse it should be in the IO monad, so maybe mapM would be a better choice to start with. -chris On 25 Jan, 2007, at 21:13

Re: [Haskell-cafe] Concurrency in Haskell

2007-01-25 Thread Alec Berryman
Chris Eidhof on 2007-01-25 22:04:18 +0100: Yes, I'm curious too. For example, it would be great if we could change a function that uses map almost automatically to a function that does the map in parallel. Ofcourse it should be in the IO monad, so maybe mapM would be a better choice to

Re: [Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread SevenThunders
Neil Mitchell wrote: The problem is that something like GHC is very complex, with lots of transformations. When transformations are firing other transformations, which in turn fire other transformations, it doesn't take a great deal to disrupt this flow of optimisation and end up with a

Re: [Haskell-cafe] Concurrency in Haskell

2007-01-25 Thread Donald Bruce Stewart
deliverable: What's the state of concurrency in Haskell? If Erlang's main strength is light-weight parallelism, can something like that be done in Haskell? http://haskell.org/haskellwiki/Libraries_and_tools/Concurrency_and_parallelism

[Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread apfelmus
Neil Mitchell wrote: That would be very neat. Another neat trick would be generalising optimisations so that there are fewer and more independant passes, this would make it easier to understand (and is what I was working on for Yhc). Well, it's the nature of repeatedly applying local

Re: [Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread Neil Mitchell
Hi Yhc has intermediate code that is substantially more Haskell like, and with the command: Wow, the core looks really cool! One look and you see it all. I would even rename the local variables to single letters like a,b,c because the cryptic numbers are quite hard to track. This is

Re: [Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread Neil Mitchell
Hi Although there may not be a lot of optimizing Haskell compilers, there are compilers for languages similar to Haskell that consistently perform well. One could point to O'caml or others in the ML family, or even more interesting is the case of Clean, whose syntax heavily borrows from

Re: [Haskell-cafe] Trouble understanding records and existential typesy

2007-01-25 Thread John Meacham
On Wed, Jan 24, 2007 at 05:03:18PM -0800, Stefan O'Rear wrote: Haskell-98 style records are widely acknowledged as sucking, and there are something like half a dozen proposals all of which are widely acknowledged as vastly superior. Expect to be stuck with H98 records for the remainder of

Re: [Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread Donald Bruce Stewart
Uniqueness types does give some extra optimisation potential, such as destructive updates if you can guarantee a variable is only referred to once. But even with that, the language that has impressed me most on the shootout is Clean. Where the Haskell community spends significant time they

Re: [Haskell-cafe] No Derived Read for Unboxed Arrays

2007-01-25 Thread Neil Mitchell
Hi, I was trying to convert some code from ordinary boxed array to unboxed arrays for performance reasons. However my code ultimately failed because I load a large array saved as a text file using the derived Read, Show mechanism. I found that Read was maybe 30 times slower than the

Re: [Haskell-cafe] No Derived Read for Unboxed Arrays

2007-01-25 Thread Donald Bruce Stewart
ndmitchell: Hi, I was trying to convert some code from ordinary boxed array to unboxed arrays for performance reasons. However my code ultimately failed because I load a large array saved as a text file using the derived Read, Show mechanism. I found that Read was maybe 30 times

Re: [Haskell-cafe] No Derived Read for Unboxed Arrays

2007-01-25 Thread Neil Mitchell
HI Don (But of course, having Read/Show defined for UArray may well be useful, and sounds a good idea) There's also an instance Binary for UArray. That might be useful? Is there an instance Binary in a released library? Thanks Neil ___

Re: [Haskell-cafe] No Derived Read for Unboxed Arrays

2007-01-25 Thread Donald Bruce Stewart
ndmitchell: HI Don (But of course, having Read/Show defined for UArray may well be useful, and sounds a good idea) There's also an instance Binary for UArray. That might be useful? Is there an instance Binary in a released library? If in doubt, look on hackage:

Re: [Haskell-cafe] No Derived Read for Unboxed Arrays

2007-01-25 Thread SevenThunders
Neil Mitchell wrote: I found that Read was maybe 30 times slower than the slowest binary serialisation method I could possibly think of. If performance matters to you, and the array is more than a few elements long, switching away from Read/Show should be the first step - before going

[Haskell-cafe] Pure serialisation and compression [Was: No Derived Read for Unboxed Arrays]

2007-01-25 Thread Donald Bruce Stewart
mattcbro: No doubt any kind of binary serialization would be a lot faster. In my case, however, I just wanted it to work out of the box. I need to read in about 5-10 arrays of only 1000 entries or so, saved in files. I suspect even the ascii parser could do that within a few seconds.

Re: [Haskell-cafe] A function for Maybes (RESOLVED)

2007-01-25 Thread John Ky
Thanks -John On 1/26/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: On Jan 25, 2007, at 9:15 , John Ky wrote: Is there a built-in function that already does this? foo :: (a - b) - Maybe a - Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f (fromJust m)) Nothing

[Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-25 Thread Donald Bruce Stewart
Binary: high performance, pure binary serialisation for Haskell -- The Binary Strike Team is pleased to announce the release of a new, pure, efficient binary serialisation library for Haskell, now available from

[Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-25 Thread Donald Bruce Stewart
dons: Binary: high performance, pure binary serialisation for Haskell -- The Binary Strike Team is pleased to announce the release of a new, pure, efficient binary serialisation library for Haskell, now

Re: [Haskell-cafe] Pure serialisation and compression [Was: No Derived Read for Unboxed Arrays]

2007-01-25 Thread SevenThunders
Donald Bruce Stewart wrote: mattcbro: Faster, and trivial to write! Here's a complete example: ... ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe Thanks for the example.

[Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-25 Thread John Meacham
Yay! I knew if I waited long enough someone would write this. Is the binary format portable? I need the produced files to work on both 32 and 64 bit architectures and with big and little endian machines. And of course, between different versions of a compiler or different compilers. John

Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-25 Thread Donald Bruce Stewart
john: Yay! I knew if I waited long enough someone would write this. Is the binary format portable? I need the produced files to work on both 32 and 64 bit architectures and with big and little endian machines. And of course, between different versions of a compiler or different compilers.

Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-25 Thread John Meacham
On Thu, Jan 25, 2007 at 07:11:55PM -0800, John Meacham wrote: Is the binary format portable? I need the produced files to work on both 32 and 64 bit architectures and with big and little endian machines. And of course, between different versions of a compiler or different compilers. Sorry to

Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-25 Thread Donald Bruce Stewart
john: On Thu, Jan 25, 2007 at 07:11:55PM -0800, John Meacham wrote: Is the binary format portable? I need the produced files to work on both 32 and 64 bit architectures and with big and little endian machines. And of course, between different versions of a compiler or different compilers.

Re: [Haskell-cafe] IO is not a monad

2007-01-25 Thread Scott Turner
On 2007 January 23 Tuesday 17:33, Yitzchak Gale wrote: 1. Find a way to model strictness/laziness properties of Haskell functions in a category in a way that is reasonably rich. 2. Map monads in that category to Haskell, and see what we get. 3. Compare that to the traditional concept of a

[Haskell-cafe] ANNOUNCE: DrIFT 2.2.1 - support for Data.Binary

2007-01-25 Thread John Meacham
DrIFT 2.2.1 is out and now has support for the Data.Binary module. The old 'Binary' has been moved to 'BitsBinary' and 'Binary' now refers to the new 'Data.Binary' version of the library. the homepage is at: http://repetae.net/~john/computer/haskell/DrIFT/ the current list of deriving rules it

Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-25 Thread Brian Hulley
Chris Kuklewicz wrote: This is how I would write getLeaves, based on your GADT: data IsLeaf data IsBranch newtype Node = Node { getNode :: (forall c. ANode c) } data ANode :: * - * where Branch :: String - String - (ANode a,ANode b) - [Node] - ANode IsBranch Leaf :: String - String