[Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Jeff Wheeler
On Fri, Jul 10, 2009 at 10:10 PM, Don Stewart wrote: >> ## Control.Monad.void m a -> m () >> Don Stewart >> Iavor Diatchki For whatever it's worth, I prefer void as well, for the exact reason Don said. Indeed, 'ignore' indicates to me that the argument won't even be evaluated: it'll be ignored, a

Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Johan Tibell
On Sat, Jul 11, 2009 at 9:35 AM, Jeff Wheeler wrote: > On Fri, Jul 10, 2009 at 10:10 PM, Don Stewart wrote: > > >> ## Control.Monad.void m a -> m () > >> Don Stewart > >> Iavor Diatchki > > For whatever it's worth, I prefer void as well, for the exact reason > Don said. Indeed, 'ignore' indicates

Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Dan Doel
On Saturday 11 July 2009 3:35:27 am Jeff Wheeler wrote: > On Fri, Jul 10, 2009 at 10:10 PM, Don Stewart wrote: > >> ## Control.Monad.void m a -> m () > >> Don Stewart > >> Iavor Diatchki > > For whatever it's worth, I prefer void as well, for the exact reason > Don said. Indeed, 'ignore' indicates

Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Stephan Friedrichs
Johan Tibell wrote: > [...] > > I also think void is clearer than ignore. So do I. Another point is, that it's familiar from other languages; a function "void f(...)" doesn't return anything but may have an effect on the environment. Stephan -- Früher hieß es ja: Ich denke, also bin ich. Heut

Re: [Haskell-cafe] [Haskell Cafe] Parsec: buildExpressionParser and parens typecheck problem

2009-07-11 Thread Bas van Gijzel
Hello Paul, As far as I can see you're calling the parens accessor function of the TokenParser record instead of supplying a parser. Here is a working example grammar I made for my bachelor paper a while ago: module ExpressionsWithLexer where import Text.ParserCombinators.Parsec.Expr import Text.

Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Malcolm Wallace
Johan Tibell wrote: [...] I also think void is clearer than ignore. So do I. Another point is, that it's familiar from other languages; a function "void f(...)" doesn't return anything but may have an effect on the environment. +1. Regards, Malcolm __

[Haskell-cafe] Re: ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-11 Thread Jon Fairbairn
Wolfgang Jeltsch writes: > Am Freitag, 10. Juli 2009 05:26 schrieb rocon...@theorem.ca: >> I find it amazing that you independently chose to spell colour with a `u'. >> It makes me feel better about my choice. > > I have to admit that it makes me unhappy. :-( > > Why do we use English for identi

Re: [Haskell-cafe] Flipping *->*->* kinds, or monadic finally-tagless madness

2009-07-11 Thread Kim-Ee Yeoh
>Kim-Ee Yeoh wrote: >> As for fixing the original bug, I've found that the real magic lies >> in the incantation (Y . unY) inserted at the appropriate places. >Aka unsafeCoerce, changing the phantom type |a|. The type of (Y . unY) is (Y . unY) :: forall a b c. Y c a -> Y c b so modulo (Y c),

[Haskell-cafe] Re: excercise - a completely lazy sorting algorithm

2009-07-11 Thread Heinrich Apfelmus
Matthias Görgens wrote: > Thanks. I heard about the hylo-, ana- and catamorphisms before, but > never explicitly used them. Time to get started. You did use them explicitly :) , namely in treeSort = bootstrap partitionOnMedian bootstrap f = Fix . helper . f where helper = fmap (Fix .

Re: [Haskell-cafe] get cabal info for self?

2009-07-11 Thread Keith Sheppard
That's perfect. Thanks! On Sat, Jul 11, 2009 at 12:10 AM, Gwern Branwen wrote: > -BEGIN PGP SIGNED MESSAGE- > Hash: SHA512 > > On Fri, Jul 10, 2009 at 11:46 PM, Keith Sheppard wrote: >> Is there a way for a cabalized program to get its own info. I'm >> specifically interested in version in

Re: [Haskell-cafe] Colour tutorial (Was: AC-Vector, AC-Colour and AC-EasyRaster-GTK)

2009-07-11 Thread Derek Elkins
On Fri, Jul 10, 2009 at 12:42 AM, wrote: > On Thu, 9 Jul 2009, rocon...@theorem.ca wrote: > >> You can use by lib without worrying about the CIE.  You can use my library >> without ever importing or using the word CIE.  However, the CIE stuff is >> there for those who need it. >> >> Perhaps I (may

[Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Jeremy Yallop
Why does compiling the following program give an error? {-# LANGUAGE TypeFamilies, RankNTypes #-} type family TF a identity :: (forall a. TF a) -> (forall a. TF a) identity x = x GHC 6.10.3 gives me: Couldn't match expected type `TF a1' against inferred type `TF a' In the expression

Re: [Haskell-cafe] Colour tutorial (Was: AC-Vector, AC-Colour and AC-EasyRaster-GTK)

2009-07-11 Thread Derek Elkins
On Sat, Jul 11, 2009 at 12:54 PM, Derek Elkins wrote: > On Fri, Jul 10, 2009 at 12:42 AM, wrote: >> On Thu, 9 Jul 2009, rocon...@theorem.ca wrote: >> >>> You can use by lib without worrying about the CIE.  You can use my library >>> without ever importing or using the word CIE.  However, the CIE s

Re: [Haskell-cafe] following up on space leak

2009-07-11 Thread Uwe Hollerbach
Hi, George, thanks for the pointer, it led me to some interesting reading. Alas, the problem which it solves was already solved, and the unsolved problem didn't yield any further... At this point, I've concluded that my interpreter just simply isn't tail-recursive enough: in the Collatz test case

Re: [Haskell-cafe] About the return type

2009-07-11 Thread Brent Yorgey
On Thu, Jul 09, 2009 at 10:57:19AM -0400, xu zhang wrote: > I have trouble in returning a list of Figures. I want return a type of m > (Maybe [Figure IO]), but the type of dv_findFigure is :: a -> Point -> s > (Maybe (Figure s)). How can change the code below to get a s (Maybe [Figure > s])? > Than

Re: [Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Brandon S. Allbery KF8NH
On Jul 11, 2009, at 14:31 , Jeremy Yallop wrote: Why does compiling the following program give an error? {-# LANGUAGE TypeFamilies, RankNTypes #-} type family TF a identity :: (forall a. TF a) -> (forall a. TF a) identity x = x The scope of each a is the surrounding parentheses, so the de

Re: [Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Roman Cheplyaka
* Brandon S. Allbery KF8NH [2009-07-11 17:01:35-0400] > On Jul 11, 2009, at 14:31 , Jeremy Yallop wrote: >> Why does compiling the following program give an error? >> >>> {-# LANGUAGE TypeFamilies, RankNTypes #-} >>> >>> type family TF a >>> >>> identity :: (forall a. TF a) -> (forall a. TF a) >>>

Re: [Haskell-cafe] Text.JSON, Speed and Bytestrings

2009-07-11 Thread Don Stewart
mxcantor: > Hi Cafe, > > I am using the Text.JSON library to [un]marshall messages passed over > the network and was wondering if the speed would be significantly > improved by either changing the code or adding a module to implement the > same functionality using Bytestrings instead of classi

Re: [Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Dan Doel
On Saturday 11 July 2009 2:31:28 pm Jeremy Yallop wrote: > Why does compiling the following program give an error? > > > {-# LANGUAGE TypeFamilies, RankNTypes #-} > > > > type family TF a > > > > identity :: (forall a. TF a) -> (forall a. TF a) > > identity x = x > > GHC 6.10.3 gives me: > > C