[Haskell-cafe] Re: Why the Prelude must die

2007-03-27 Thread Lennart Augustsson
I agree, I think this is what we need. Plus a decision of what names the builtin syntax refers to, like the type of 'a'. -- Lennart On Mar 26, 2007, at 23:30 , Ashley Yakeley wrote: Sebastian Sylvan wrote: The solution is simple: * If there is a module M where clause in the beginning

[Haskell-cafe] infinite lists

2007-03-27 Thread Matthias Fischmann
hi, it just took me an eternity to undestand a bug in my code *after* i had narrowed it down to eight lines or so. and as these bugs go, i feel very good about having found it and have to share it. although it's probably not that exciting to anybody except me. (-: here is the bug, narrowed

Re: [Haskell-cafe] infinite lists

2007-03-27 Thread Matthew Brecknell
Matthias Fischmann: g = do n - randomRIO (0,5) let l = replicate n '*' i | null l = [] | otherwise = join $ repeat l print (take 12 i) If you had written (cycle l) instead of (join $ repeat l), you would have figured it out much quicker. :-) Prelude cycle []

Re: [Haskell-cafe] Newbie: a parser for a list of objects?

2007-03-27 Thread Dmitri O.Kondratiev
Thanks Daniel! Things are getting more in shape, yet I still can not fully comprehend the expression: ((p * pList p) `build` (uncurry (:))) where (*) :: Parse a b - Parse a c - Parse a (b, c) (*) p1 p2 inp = [((x,y), rem2) |(x, rem1) - p1 inp, (y, rem2) - p2 rem1] build :: Parse a b - (b - c)

Re: [Haskell-cafe] infinite lists

2007-03-27 Thread Matthias Fischmann
On Tue, Mar 27, 2007 at 08:02:18PM +1000, Matthew Brecknell wrote: To: Matthias Fischmann [EMAIL PROTECTED] Cc: haskell-cafe@haskell.org From: Matthew Brecknell [EMAIL PROTECTED] Date: Tue, 27 Mar 2007 20:02:18 +1000 Subject: Re: [Haskell-cafe] infinite lists Matthias Fischmann: g = do

[Haskell-cafe] Re: A question about functional dependencies and existential quantification

2007-03-27 Thread Jean-Marie Gaillourdet
Hi, [EMAIL PROTECTED] wrote: The problem is not related to existentials, so we just drop them {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-} module TestCase where data Any root = ANY class T root pos sel | pos - root, root - sel where f :: pos - sel - Bool instance T

[Haskell-cafe] Re: [Haskell] Lift Info [moving to -cafe]

2007-03-27 Thread Andrew Wagner
I'm no expert, but I will point you to 2 links that I think will be helpful on this topic on the wiki: http://www.haskell.org/haskellwiki/Lifting (especially if you're familiar with functors) http://www.haskell.org/haskellwiki/Simple_StateT_use (for a simple example with a monad transformer) I'm

[Haskell-cafe] (newbie) instance Enum MyType where, smarter way?

2007-03-27 Thread Adrian Neumann
-BEGIN PGP SIGNED MESSAGE- Hash: RIPEMD160 Hello, I defined an enumeration datatype like this data MyType = One | Two | Four | Eight and want to make it an instance of the class Enum. deriving Enum won't do what I want, as it labels the items 0,1,2,3. Is there a better way to do this

Re: [Haskell-cafe] (newbie) instance Enum MyType where, smarter way?

2007-03-27 Thread Sven Panne
On Tuesday 27 March 2007 17:15, Adrian Neumann wrote: [...] Which doesn't work because succ and pred are not (properly?) defined. Is there a way to let deriving Enum do *some* of work (i.e. defining succ and pred) while manually defining the other functions? Hmmm, this seems to be a confusing

[Haskell-cafe] Monad/Functor Book

2007-03-27 Thread Dave
Given the amount of material posted at haskell.org and elsewhere explaining IO, monads and functors, has anyone considered publishing a comprehensive book explaining those subjects? (I am trying to read all the material online, but books are easier to read and don't require sitting in front of a

Re: [Haskell-cafe] (newbie) instance Enum MyType where, smarter way?

2007-03-27 Thread Jules Bean
Adrian Neumann wrote: I defined an enumeration datatype like this data MyType = One | Two | Four | Eight and want to make it an instance of the class Enum. deriving Enum won't do what I want, as it labels the items 0,1,2,3. Is there a better way to do this than Define them as deriving Enum.

Re: [Haskell-cafe] Re: Why the Prelude must die

2007-03-27 Thread Nicolas Frisby
Gut feeling: the quick'n dirty script case occurs far less than the whole module case. Thus I think the benefit of automatically importing the Prelude if the module declaration is omitted should not happen: the Principle of Least Surprise out-weighs the small benefit to a rare case. Correct me

Re: [Haskell-cafe] infinite lists

2007-03-27 Thread Albert Y. C. Lai
Matthias Fischmann wrote: here is the bug, narrowed to four lines. a function that only sometimes terminates. f = do n - randomRIO (0,5) let l = replicate n '*' i = join $ repeat l -- infinite extension print (take 12 i) In this paragraph I speak about just this program,

Re: [Haskell-cafe] Monad/Functor Book

2007-03-27 Thread Creighton Hogg
On 3/27/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Given the amount of material posted at haskell.org and elsewhere explaining IO, monads and functors, has anyone considered publishing a comprehensive book explaining those subjects? (I am trying to read all the material online, but books

Re: [Haskell-cafe] Re: Why the Prelude must die

2007-03-27 Thread Arthur van Leeuwen
On 27-mrt-2007, at 20:17, Nicolas Frisby wrote: Gut feeling: the quick'n dirty script case occurs far less than the whole module case. Thus I think the benefit of automatically importing the Prelude if the module declaration is omitted should not happen: the Principle of Least Surprise

Re: [Haskell-cafe] Re: A question about functional dependencies and existential quantification

2007-03-27 Thread Felipe Almeida Lessa
On 3/27/07, Jean-Marie Gaillourdet [EMAIL PROTECTED] wrote: I concur. The class declares T as being a ternary relation such that the following holds forall r p p' s s'. T(r,p,s) T(r,p',s') - s = s' Now, the instance `T root (Any root) sel' is satisfied when root=Int, sel = Bool and

Re: [Haskell-cafe] Monad/Functor Book

2007-03-27 Thread Dan Piponi
On 3/27/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Given the amount of material posted at haskell.org and elsewhere explaining IO, monads and functors, has anyone considered publishing a comprehensive book explaining those subjects? (I am trying to read all the material online, but books

Re: [Haskell-cafe] Monad/Functor Book

2007-03-27 Thread Andrzej Jaworski
Categories for the Working Mathematician a couple of months ago, and while it sometimes takes a bit of work it's a very good introduction. The only caution I have is that if you don't have that strong of a math background, or hadn't done it in a few years (like myself), you may have to lookup

Re: [Haskell-cafe] Monad/Functor Book

2007-03-27 Thread Creighton Hogg
On 3/27/07, Dan Piponi [EMAIL PROTECTED] wrote: On 3/27/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Given the amount of material posted at haskell.org and elsewhere explaining IO, monads and functors, has anyone considered publishing a comprehensive book explaining those subjects? (I am

[Haskell-cafe] cost of modules

2007-03-27 Thread Fawzi Mohamed
I decided to cleanup my program by splitting it in different modules. As I was curious about the cost of splitting it, or dually the efficiency of the intermodule optimization I timed it before and after the split. These are the results (ghc-6.6.20070129 on Linux AMD64): Original: 3 Modules

Re: [Haskell-cafe] cost of modules

2007-03-27 Thread Tim Chevalier
On 3/27/07, Fawzi Mohamed [EMAIL PROTECTED] wrote: I decided to cleanup my program by splitting it in different modules. As I was curious about the cost of splitting it, or dually the efficiency of the intermodule optimization I timed it before and after the split. These are the results

Re: [Haskell-cafe] cost of modules

2007-03-27 Thread Derek Elkins
Fawzi Mohamed wrote: I decided to cleanup my program by splitting it in different modules. As I was curious about the cost of splitting it, or dually the efficiency of the intermodule optimization I timed it before and after the split. These are the results (ghc-6.6.20070129 on Linux AMD64):

Re: [Haskell-cafe] cost of modules

2007-03-27 Thread Ricardo Herrmann
http://www.cs.utah.edu/~hal/HAllInOne/index.html On 3/27/07, Derek Elkins [EMAIL PROTECTED] wrote: Fawzi Mohamed wrote: I decided to cleanup my program by splitting it in different modules. As I was curious about the cost of splitting it, or dually the efficiency of the intermodule

Re: [Haskell-cafe] cost of modules

2007-03-27 Thread Jeremy Shaw
At Tue, 27 Mar 2007 23:10:21 +0200, Fawzi Mohamed wrote: If someone has an idea on how else I can improve timings please tell me. I believe you are seeing a speed decrease, because GHC is not inlining functions as much when you split them into modules. If you add explicit inline statements, I

Re: [Haskell-cafe] Newbie: a parser for a list of objects?

2007-03-27 Thread Daniel Fischer
Am Dienstag, 27. März 2007 12:15 schrieb Dmitri O.Kondratiev: Thanks Daniel! Things are getting more in shape, yet I still can not fully comprehend the expression: ((p * pList p) `build` (uncurry (:))) where (*) :: Parse a b - Parse a c - Parse a (b, c) (*) p1 p2 inp = [((x,y), rem2)

Re: [Haskell-cafe] cost of modules

2007-03-27 Thread Donald Bruce Stewart
jeremy.shaw: At Tue, 27 Mar 2007 23:10:21 +0200, Fawzi Mohamed wrote: If someone has an idea on how else I can improve timings please tell me. I believe you are seeing a speed decrease, because GHC is not inlining functions as much when you split them into modules. If you add explicit

Re: [Haskell-cafe] cost of modules

2007-03-27 Thread Tim Chevalier
On 3/27/07, Jeremy Shaw [EMAIL PROTECTED] wrote: At Tue, 27 Mar 2007 23:10:21 +0200, Fawzi Mohamed wrote: If someone has an idea on how else I can improve timings please tell me. I believe you are seeing a speed decrease, because GHC is not inlining functions as much when you split them into

Re: [Haskell-cafe] Monad/Functor Book

2007-03-27 Thread Derek Elkins
Creighton Hogg wrote: On 3/27/07, *Dan Piponi* [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote: On 3/27/07, [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote: Given the amount of material posted at haskell.org http://haskell.org

Re: [Haskell-cafe] Monad/Functor Book

2007-03-27 Thread Andrzej Jaworski
Haskell borrows from CT but it is too much engineered to be a model for computational CT. However you can study it with CT: http://www.cs.ut.ee/~varmo/papers/thesis.pdf ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Monad/Functor Book

2007-03-27 Thread Claus Reinke
I've thought about writing extended tutorials on the relationship between Haskell programming and category theory you might find this a useful reference/starting point then: http://citeseer.ist.psu.edu/62964.html An Introduction to Category Theory, Category Theory Monads, and Their

Re: [Haskell-cafe] cost of modules

2007-03-27 Thread Fawzi Mohamed
Thanks ! Il giorno Mar 28, 2007, alle ore 12:04 AM, Tim Chevalier ha scritto: On 3/27/07, Jeremy Shaw [EMAIL PROTECTED] wrote: At Tue, 27 Mar 2007 23:10:21 +0200, Fawzi Mohamed wrote: If someone has an idea on how else I can improve timings please tell me. I believe you are seeing a

Re: [Haskell-cafe] cost of modules

2007-03-27 Thread Tim Chevalier
On 3/27/07, Fawzi Mohamed [EMAIL PROTECTED] wrote: I did longer runs (all compiled with -O2 as before) with the same results. and indeed with a couple of {-# INLINE function #-} I was able to recover the previous performance and actually even get a better performace than before. If you had

[Haskell-cafe] (no subject)

2007-03-27 Thread Matthew Brecknell
I'm attempting to construct an abstract data type with a generalised (deferred) representation. For a simple motivating example, say I am building an abstract data type with this representation: newtype Foo1 k e = Foo1 (Data.Map.Map k (Data.Set.Set e)) While this is a fine default

[Haskell-cafe] Re: A question about functional dependencies and existential

2007-03-27 Thread oleg
Jean-Marie Gaillourdet wrote: class T root pos sel | pos - root, root - sel where f :: pos - sel - Bool instance T root (Any root) sel If that is correct, I don't understand why this instance should be to general, as every instantiation of root exactly determines the corresponding