Re: [Haskell-cafe] Database connection pool

2010-05-06 Thread Bryan O'Sullivan
On Wed, May 5, 2010 at 10:51 PM, Michael Snoyman mich...@snoyman.comwrote: * When a connection is released, is goes to the end of the pool, so connections get used evenly (not sure if this actually matters in practice). In practice, you're better off letting idle connections stay that way,

[Haskell-cafe] {-# LANGUAGE DeriveApplicative #-} ?

2010-05-06 Thread Pavel Perikov
Hi, list!. Now in 6.12.1 we have DeriveFunctor, DeriveFoldable and DeriveTraversable. This greatly simplifies the reuse structure style of programming. Some structure (not just _data_ structure) got captured in ADT and can be reused for various purposes. Wouldn't it be nice to have the

Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread Eugene Dzhurinsky
On Wed, May 05, 2010 at 02:54:27PM -0700, Ryan Ingram wrote: ErrorT is just a newtype wrapper, changing the order/application of the type variables. newtype ErrorT e m a = ErrorT (m (Either e a)) runErrorT (ErrorT action) = action This gives the bijection: ErrorT :: m (Either e a) -

Re: [Haskell-cafe] posting UTF8 data with Curl library

2010-05-06 Thread Eugene Dzhurinsky
On Wed, May 05, 2010 at 11:15:05PM +0200, Daniel Fischer wrote: It's the same type, so you can encode it using Data.ByteString.UTF8 and send it over the network as a plain old ByteString. On the receiving end, you read it as a plain ByteString and then interpret it as a utf-8 encoded

Re: [Haskell-cafe] Re: Why cabal forces reinstallation of happstack-utils?

2010-05-06 Thread Henning Thielemann
Daniel Fischer schrieb: On Wednesday 05 May 2010 15:45:38, Henning Thielemann wrote: Surprisingly using plain Cabal (runhaskell Setup configure; runhaskell Setup build; runhaskell Setup install) often works in these cases. That's not surprising. runhaskell ./Setup.hs configure can only go

Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread David Virebayre
On Thu, May 6, 2010 at 9:56 AM, Eugene Dzhurinsky b...@redwerk.com wrote: On Wed, May 05, 2010 at 02:54:27PM -0700, Ryan Ingram wrote: ErrorT is just a newtype wrapper, changing the order/application of the type variables. newtype ErrorT e m a = ErrorT (m (Either e a)) runErrorT (ErrorT

Re: [Haskell-cafe] Haskell XML Parsers

2010-05-06 Thread Malcolm Wallace
I have been looking at using XML for a little program I have been writing. The file I am currently trying to load is about 9MB, and I have now tried to use HaXml and HST. Without any of my own code, just a simple call to the basic parsers, they both use huge amount of memory. HST is the

Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread Eugene Dzhurinsky
On Thu, May 06, 2010 at 10:05:05AM +0200, David Virebayre wrote: A constructor can be seen as a function that takes some parameters and produces a value for example with the type Maybe a, which has 2 constructors ; Just and Nothing : Prelude :t Just Just :: a - Maybe a the

[Haskell-cafe] Please ignore :) {-# LANGUAGE DeriveApplicative #-}

2010-05-06 Thread Pavel Perikov
Please ignore the previous message :) Screwed :) P. Begin forwarded message: From: Pavel Perikov peri...@gmail.com Date: 6 мая 2010 г. 11:55:36 Московское летнее время To: haskell-cafe list Cafe mailing haskell-cafe@haskell.org Cc: Беркгаут Борис boris.berkg...@transas.com Subject: {-#

Re: [Haskell-cafe] forall (What does it do)

2010-05-06 Thread Alexander Solla
On May 5, 2010, at 9:52 PM, John Creighton wrote: I've seen forall used in a few places related to Haskell. I know their is a type extension call explicit forall but by the way it is documnted in some places, the documentation makes it sound like it does nothing usefull. However on Page 27 of

Re: [Haskell-cafe] nun.haskell.org http services down?

2010-05-06 Thread Erik de Castro Lopo
Jens Petersen wrote: http://{code,community,projects}.haskell..org/ seem to be inaccessible. Could someone please look into it? For me, it seems to be down everyday around 5-6pm (0700-0800 UTC) which is prime hacking time for me. Anyone know what's going on with the machine at that time?

Re: [Haskell-cafe] Re: Why cabal forces reinstallation of happstack-utils?

2010-05-06 Thread Ivan Lazar Miljenovic
Henning Thielemann schlepp...@henning-thielemann.de writes: This makes sense. It would be certainly better if cabal-install would alert about the found inconsistency instead of trying to fix it. Then there might an additional cabal-install flag, that makes cabal-install prefer the output of

[Haskell-cafe] Re: nun.haskell.org http services down?

2010-05-06 Thread Andy Stewart
Ivan Lazar Miljenovic ivan.miljeno...@gmail.com writes: Erik de Castro Lopo mle...@mega-nerd.com writes: Jens Petersen wrote: http://{code,community,projects}.haskell..org/ seem to be inaccessible. Could someone please look into it? For me, it seems to be down everyday around 5-6pm

Re: [Haskell-cafe] Re: class Arbitrary in quickcheck

2010-05-06 Thread Malcolm Wallace
So the good news is that quickcheck 2.1 behaves as I expected. I'm still curious as to the behaviour of the older version. In QC 1.2, the instance of Arbitrary for the Maybe type uses the sized combinator to choose between Nothing and Just, whereas in QC 2.1, the instance uses the

Re: [Haskell-cafe] Re: Why cabal forces reinstallation of happstack-utils?

2010-05-06 Thread Ivan Lazar Miljenovic
Henning Thielemann schlepp...@henning-thielemann.de writes: I meant it the other way round: Given that package X-a.b.c.d does not compile due to dependencies that turn out to be too restricted, then I could relax the dependency version bounds in X.cabal. If I also increase X's version to

Re: [Haskell-cafe] Re: nun.haskell.org http services down?

2010-05-06 Thread Malcolm Wallace
http://{code,community,projects}.haskell..org/ seem to be inaccessible. Could someone please look into it? For me, it seems to be down everyday around 5-6pm (0700-0800 UTC) which is prime hacking time for me. Anyone know what's going on with the machine at that time? Well, it's hosted

Re: [Haskell-cafe] Re: nun.haskell.org http services down?

2010-05-06 Thread Ivan Lazar Miljenovic
Malcolm Wallace malcolm.wall...@cs.york.ac.uk writes: We think that the apache web server [snip] Well, _there's_ your problem! You're relying on some random project written using that completely unsafe C language rather than one written using a pure garbage-collected language with strong static

Re: [Haskell-cafe] Re: Set Operations In Haskell's Type System

2010-05-06 Thread Bartek Ćwikłowski
hello, 2010/5/6 John Creighton johns2...@gmail.com: a isa d if their exists a b and c such that the following conditions hold: a isa subset of b, b isa c c is a subset of d This definition doesn't make sense - it's recursive, but there's no base case, unless this is some kind of

Re: [Haskell-cafe] Would it be evil to add deriving Typeable to newtype Q?

2010-05-06 Thread Ben Millwood
On Thu, May 6, 2010 at 4:05 AM, Ivan Miljenovic ivan.miljeno...@gmail.com wrote: Re-CC'ing -cafe: On 6 May 2010 12:54, Leonel Fonseca leone...@gmail.com wrote: I wasn't aware of GeneralizedNewtypeDeriving.  I just edited the source file Language.Haskell.TH.Syntax and left: newtype Q a = Q

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread Bill Atkins
Almost - liftM modificationTime has type Status - IO EpochTime. Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the modification time) Also, I like this style: import Control.Applicative (($)) blah = do times - mapM (PF.modificationTime $

Re: [Haskell-cafe] {-# LANGUAGE DeriveApplicative #-} ?

2010-05-06 Thread Ben Millwood
On Thu, May 6, 2010 at 8:55 AM, Pavel Perikov peri...@gmail.com wrote: Hi, list!. Now in 6.12.1 we have DeriveFunctor, DeriveFoldable and DeriveTraversable. This greatly simplifies the reuse structure style of programming. Some structure (not just _data_ structure) got captured in ADT and

Re: [Haskell-cafe] Re: nun.haskell.org http services down?

2010-05-06 Thread Henning Thielemann
Ivan Lazar Miljenovic schrieb: Malcolm Wallace malcolm.wall...@cs.york.ac.uk writes: We think that the apache web server [snip] Well, _there's_ your problem! You're relying on some random project written using that completely unsafe C language rather than one written using a pure

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread Neil Brown
Bill Atkins wrote: Almost - liftM modificationTime has type Status - IO EpochTime. Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the modification time) Also, I like this style: import Control.Applicative (($)) blah = do times - mapM

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread Ben Millwood
On Thu, May 6, 2010 at 11:51 AM, Bill Atkins watk...@alum.rpi.edu wrote: Almost - liftM modificationTime has type Status - IO EpochTime.  Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the modification time) ghci :m +Control.Monad

Re: [Haskell-cafe] Re: Is anyone using Haddock's support for frames?

2010-05-06 Thread David Waern
2010/5/4 Evan Laforge qdun...@gmail.com: On Tue, May 4, 2010 at 1:23 PM, David Waern david.wa...@gmail.com wrote: 2010/5/4 Sean Leather leat...@cs.uu.nl: Somewhat OT, but is there a place where we can request/review features in the new HTML presentation of Haddock. Are there any mockups of

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread Bill Atkins
Yep, you and Ben are both correct. Mea culpa and sorry for the bad answer. Just curious: why does getModificationTime take an IO FileStatus rather than a FileStatus? On Thu, May 6, 2010 at 7:00 AM, Neil Brown nc...@kent.ac.uk wrote: Bill Atkins wrote: Almost - liftM modificationTime has

Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread David Virebayre
By the way, I didn't exactly reply your question : [...] Basically, i don't understand what does ErrorT :: means - it should name the function - but it starts with capital letter? It's a type signature, it describes the type of ErrorT: Prelude import Control.Monad.Error Prelude

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread Ben Millwood
On Thu, May 6, 2010 at 12:37 PM, Bill Atkins watk...@alum.rpi.edu wrote: Just curious: why does getModificationTime take an IO FileStatus rather than a FileStatus? It doesn't. getModificationTime is a pure function (think of it like a record accessor). liftM makes it take IO FileStatus

[Haskell-cafe] Mixing mtl- and transformers-using libraries

2010-05-06 Thread Joachim Breitner
Hi, I have a rather large project here that uses standard mtl stuff. This program now wants to use salvia, which in turn uses the transformers library. The result is this: X.hs:163:29: Overlapping instances for Monad (Either String) arising from a use of `neuePersonCommit' at

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread Pierre-Etienne Meunier
This way : do times-mapM PF.getFileStatus filenames = return.(map PF.modificationTime) Or also : do times-mapM (PF.getFileStatus = (return.(PF.modificationTime))) filenames let sorted=... I do not know exactly how ghc compiles the IO monad, but it seems to me that

Re: [Haskell-cafe] Mixing mtl- and transformers-using libraries

2010-05-06 Thread Ivan Lazar Miljenovic
Joachim Breitner m...@joachim-breitner.de writes: I have a rather large project here that uses standard mtl stuff. This program now wants to use salvia, which in turn uses the transformers library. The result is this: X.hs:163:29: Overlapping instances for Monad (Either String)

Re: [Haskell-cafe] Mixing mtl- and transformers-using libraries

2010-05-06 Thread Joachim Breitner
Hi, Am Donnerstag, den 06.05.2010, 22:42 +1000 schrieb Ivan Lazar Miljenovic: Joachim Breitner m...@joachim-breitner.de writes: I have a rather large project here that uses standard mtl stuff. This program now wants to use salvia, which in turn uses the transformers library. The result is

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread Ivan Lazar Miljenovic
Pierre-Etienne Meunier pierreetienne.meun...@gmail.com writes: This way : do times-mapM PF.getFileStatus filenames = return.(map PF.modificationTime) Or also : do times-mapM (PF.getFileStatus = (return.(PF.modificationTime))) filenames let sorted=... I do not

Re: [Haskell-cafe] Re: lhs2TeX - lhs2TeX.fmt missing

2010-05-06 Thread Ozgur Akgun
On 6 May 2010 01:23, Ivan Miljenovic ivan.miljeno...@gmail.com wrote: El 05/05/2010, a las 12:42, Ozgur Akgun escribió: OK, I've found them! They were under /Users/username/.cabal/share/lhs2tex-1.15 and this path was not in the search path of lhs2TeX. I'm using Snow Leoprad. This

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread briand
On Thu, 06 May 2010 12:00:01 +0100 Neil Brown nc...@kent.ac.uk wrote: At which point I prefer Ivan's liftM version rather than the above section (or worse: using ($) prefix). The original request is a relatively common thing to want to do, so I was slightly surprised that hoogling for:

Re: [Haskell-cafe] Database connection pool

2010-05-06 Thread Michael Snoyman
On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan b...@serpentine.com wrote: On Wed, May 5, 2010 at 10:51 PM, Michael Snoyman mich...@snoyman.comwrote: * When a connection is released, is goes to the end of the pool, so connections get used evenly (not sure if this actually matters in

[Haskell-cafe] A query to users of graphviz

2010-05-06 Thread Ivan Lazar Miljenovic
For anyone who uses my graphviz library: who uses the graphNodes and functions? Note that this also applies to anyone who uses augmentation functions as well (more specifically, when they define global attributes for use with an augmentation function). If so, would it be a problem if I switched

Re: [Haskell-cafe] Re: lhs2TeX - lhs2TeX.fmt missing

2010-05-06 Thread Ivan Lazar Miljenovic
Ozgur Akgun ozgurak...@gmail.com writes: On 6 May 2010 01:23, Ivan Miljenovic ivan.miljeno...@gmail.com wrote: El 05/05/2010, a las 12:42, Ozgur Akgun escribió: OK, I've found them! They were under /Users/username/.cabal/share/lhs2tex-1.15 and this path was not in the search path

Re: [Haskell-cafe] Re: Haskell and scripting

2010-05-06 Thread Limestraël
^^ That's an interesting debate: How do you imagine the future programming languages? But not today's topic. It's strange that, since Lisp is still used now, especially for teaching purposes, and since everybody complains about parenthesises, nobody developed a Lisp-like just based on

[Haskell-cafe] ANNOUNCE: wai-handler-fastcgi 0.0.0

2010-05-06 Thread Michael Snoyman
Hi all, I finally scratched an itch I've had for a while, and put together wai-handler-fastcgi. It is built on top of Dan Knapp's wonderful direct-fastcgi[1] package, so it is free from dependencies on C libraries. This package allows WAI[2] applications to be run on a FastCGI-supporting server.

[Haskell-cafe] DTP10 Call for Participation

2010-05-06 Thread Conor McBride
Remember, Haskell is the world's most popular dependently typed functional programming language... (s:S)*(p:P s)-(s:S)*(p:P s)-(s:S)*(p:P s)-(s:S)*(p:P s)-(s:S)*(p:P s)- DTP 2010 --- Call for Participation EARLY REGISTRATION ENDS 17 MAY 2010

[Haskell-cafe] Mystery Parse Error in LHS file

2010-05-06 Thread Iæfai
I have an lhs file, 'starsystem.lhs' that is not compiling because of a parse error. Specifically: $ cabal build Preprocessing executables for starsystem-0.1... Building starsystem-0.1... [1 of 4] Compiling Render ( Render.lhs, dist/build/ starsystem/starsystem-tmp/Render.o ) [2 of 4]

Re: [Haskell-cafe] DTP10 Call for Participation

2010-05-06 Thread Colin Paul Adams
Conor == Conor McBride co...@strictlypositive.org writes: Conor Remember, Haskell is the world's most popular dependently Conor typed functional programming language... Could you justify that claim please? -- Colin Adams Preston Lancashire () ascii ribbon campaign - against html

Re: [Haskell-cafe] Re: Haskell and scripting

2010-05-06 Thread Donn Cave
Quoth =?ISO-8859-1?Q?Limestra=EBl?= limestr...@gmail.com, That's an interesting debate: How do you imagine the future programming languages? But not today's topic. I think you're in a position to make the premise much more interesting, by elaborating the kind of programming interface you want

Re: [Haskell-cafe] Re: Haskell and scripting

2010-05-06 Thread Daniel Fischer
On Thursday 06 May 2010 16:32:50, Limestraël wrote: ^^ That's an interesting debate: How do you imagine the future programming languages? But not today's topic. It's strange that, since Lisp is still used now, especially for teaching purposes, and since everybody complains about

Re: [Haskell-cafe] Mystery Parse Error in LHS file

2010-05-06 Thread John Millikin
Bird-style LHS adds an implied layer of indentation, so it's difficult to use both styles within the same file. You can run ghc -E starsystem.lhs; cat starsystem.hspp to see what GHC is reading the file as, after pre-processing. But, **why** would you use both in the same file? The resulting code

Re: [Haskell-cafe] Mystery Parse Error in LHS file

2010-05-06 Thread Daniel Fischer
On Thursday 06 May 2010 17:02:59, Iæfai wrote: I have an lhs file, 'starsystem.lhs' that is not compiling because of a parse error. I cannot figure out what the problem here is. Apparently, unlit doesn't manage to cope with mixed LaTeX and bird-track.

Re: [Haskell-cafe] Database connection pool

2010-05-06 Thread Bas van Dijk
On Thu, May 6, 2010 at 3:24 PM, Michael Snoyman mich...@snoyman.com wrote: On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan b...@serpentine.com wrote: On Wed, May 5, 2010 at 10:51 PM, Michael Snoyman mich...@snoyman.com wrote: * When a connection is released, is goes to the end of the

[Haskell-cafe] Re: Mystery Parse Error in LHS file

2010-05-06 Thread Iæfai
I can certainly see the parse error there, yes. Might file a bug then, it should work, despite John's logic that there is no reason to. On May 6, 11:35 am, Daniel Fischer daniel.is.fisc...@web.de wrote: On Thursday 06 May 2010 17:02:59, Iæfai wrote: I have an lhs file, 'starsystem.lhs' that

[Haskell-cafe] Re: Mystery Parse Error in LHS file

2010-05-06 Thread Iæfai
The reason why is that bird is better for short code and \begin{code} is better for longer code. I will just add a bird-track support to my editor. On May 6, 11:29 am, John Millikin jmilli...@gmail.com wrote: Bird-style LHS adds an implied layer of indentation, so it's difficult to use both

Re: [Haskell-cafe] Re: nun.haskell.org http services down?

2010-05-06 Thread Jason Dagit
On Thu, May 6, 2010 at 2:15 AM, Malcolm Wallace malcolm.wall...@cs.york.ac.uk wrote: http://{code,community,projects}.haskell..org/ seem to be inaccessible. Could someone please look into it? For me, it seems to be down everyday around 5-6pm (0700-0800 UTC) which is prime hacking time for

Re: [Haskell-cafe] Mystery Parse Error in LHS file

2010-05-06 Thread Daniel Fischer
On Thursday 06 May 2010 17:35:58, Daniel Fischer wrote: Apparently, unlit doesn't manage to cope with mixed LaTeX and bird-track. Ah, overlooked The program text is recovered by taking only those lines beginning with , and replacing the leading with a space. Layout and comments apply exactly

Re: [Haskell-cafe] Re: Haskell and scripting

2010-05-06 Thread Limestraël
Don Cave said: We've been through the generalities of this discussion before - is map hard, are for loops easy? what if you never learned an imperative language, does that make a difference, aren't functional languages the most natural because everyone knows about equations, ... etc. Oh yes.

[Haskell-cafe] Re: Interest in a Mathematics AI strike force ?

2010-05-06 Thread Neal Alexander
Alp Mestanogullari wrote: Anyway, would you be willing to integrate your library in that project ? Yea, it's much better to work with a group on stuff like this. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Re: Interest in a Mathematics AI strike force ?

2010-05-06 Thread Alp Mestanogullari
Ok, then just subscribe to the mailing list, and follow the instructions I gave earlier, so that we'll start discussing about your code's integration in hasklab. Thanks! On Thu, May 6, 2010 at 6:32 PM, Neal Alexander relapse@gmx.com wrote: Alp Mestanogullari wrote: Anyway, would you be

Re: [Haskell-cafe] DTP10 Call for Participation

2010-05-06 Thread Conor McBride
On 6 May 2010, at 16:04, Colin Paul Adams wrote: Conor == Conor McBride co...@strictlypositive.org writes: Conor Remember, Haskell is the world's most popular dependently Conor typed functional programming language... Could you justify that claim please? Is that a feature request or

[Haskell-cafe] Re: Re: Haskell and scripting

2010-05-06 Thread Maciej Piechotka
On Wed, 2010-05-05 at 17:18 -0400, Kyle Murphy wrote: Concerning your second point, I think just about any functional language isn't going to be simple or quick to learn. It's simply not a way of approaching problems that your average person (even your average programmer) is used to dealing

[Haskell-cafe] Re: Haskell and the Software design process

2010-05-06 Thread Maciej Piechotka
On Sun, 2010-05-02 at 21:35 -0700, Alexander Dunlap wrote: f ys = let xs = (1:ys) in last xs uses the partial function last. Rewriting it in the non-partial style gives f ys = case (1:ys) of [] - Nothing xs - Just (last xs) I guess it is more like f :: Num a = [a] - a f =

Re: [Haskell-cafe] Database connection pool

2010-05-06 Thread Bas van Dijk
On Thu, May 6, 2010 at 3:24 PM, Michael Snoyman mich...@snoyman.com wrote: On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan b...@serpentine.com wrote: On Wed, May 5, 2010 at 10:51 PM, Michael Snoyman mich...@snoyman.com wrote: * When a connection is released, is goes to the end of the

[Haskell-cafe] Re: mixing map and mapM ?

2010-05-06 Thread Maciej Piechotka
On Thu, 2010-05-06 at 12:09 +0100, Ben Millwood wrote: On Thu, May 6, 2010 at 11:51 AM, Bill Atkins watk...@alum.rpi.edu wrote: Almost - liftM modificationTime has type Status - IO EpochTime. Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the

[Haskell-cafe] ANNOUNCE: gt-tools-0.1.4

2010-05-06 Thread Sergei Trofimovich
Hey, -cafe! I'm glad to announce release of Google Translate Service[1] Tools[2]. Currently it's a command line tool 'gtc' (queen of this post) and 'gtg' (more a hello-world type gtk2hs user). So let's play with that beast a little! PREREQUISITES * ghs-6.12+ - gt-tools relies on proper locale

[Haskell-cafe] haskell on suse?

2010-05-06 Thread gladstein
I've been spoiled by package managers that download and install everything for you, and I've forgotten how RPM works. In particular, I want to install Haskell on suse, and I read that RPMs are available from openSUSE. I followed the link, and found a bunch of folders of folders of RPM files.

Re: [Haskell-cafe] haskell on suse?

2010-05-06 Thread Edward Z. Yang
Excerpts from gladstein's message of Thu May 06 14:33:38 -0400 2010: I've been spoiled by package managers that download and install everything for you, and I've forgotten how RPM works. In particular, I want to install Haskell on suse, and I read that RPMs are available from openSUSE. I

Re: [Haskell-cafe] Database connection pool

2010-05-06 Thread Bas van Dijk
On Thu, May 6, 2010 at 7:48 PM, Bas van Dijk v.dijk@gmail.com wrote: On Thu, May 6, 2010 at 3:24 PM, Michael Snoyman mich...@snoyman.com wrote: On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan b...@serpentine.com wrote: On Wed, May 5, 2010 at 10:51 PM, Michael Snoyman mich...@snoyman.com

Re: [Haskell-cafe] Database connection pool

2010-05-06 Thread Bas van Dijk
On Thu, May 6, 2010 at 11:54 PM, Bas van Dijk v.dijk@gmail.com wrote: On Thu, May 6, 2010 at 7:48 PM, Bas van Dijk v.dijk@gmail.com wrote: On Thu, May 6, 2010 at 3:24 PM, Michael Snoyman mich...@snoyman.com wrote: On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan b...@serpentine.com

[Haskell-cafe] Dynamic CSV Parsing - Parsec

2010-05-06 Thread Günther Schmidt
Hello, I'm trying to build a CSV parser that can dynamically assemble a parser from the values of the first line. As the most simple example the parse of the first line would return a parser with which subsequent lines would then be parsed. This parser would, for instance, only parse lines

Re: [Haskell-cafe] Fwd: Error instaling Happstack on Windows - cabal bug?

2010-05-06 Thread Flavio Botelho
Manually removing -fvia-c solved it. Thanks On Wed, May 5, 2010 at 7:11 AM, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: Stephen Tetley stephen.tet...@gmail.com writes: Hi all A cursory look at Happstack.Crypto.MD5 shows it uses -fvia-c: {-# LANGUAGE BangPatterns #-} {-#

[Haskell-cafe] [Long, probably not-beginners anymore] Parallel folds and folds as arrows (was: Re: [Haskell-beginners] Re: When, if ever, does Haskell calculate once?)

2010-05-06 Thread Maciej Piechotka
On Thu, 2010-05-06 at 23:46 +0200, Daniel Fischer wrote: Share.share :: GHC.Types.Int GblId [Str: DmdType] Share.share = case GHC.List.$wlen @ GHC.Integer.Type.Integer Share.share_a 0 of ww_amc { __DEFAULT - GHC.Types.I# (GHC.Prim.+# ww_amc ww_amc) } Hmm. What's the name of

Re: [Haskell-cafe] ANNOUNCE: gt-tools-0.1.4

2010-05-06 Thread Felipe Lessa
On Thu, May 06, 2010 at 09:30:50PM +0300, Sergei Trofimovich wrote: /me wonders if Miss lambdabot might like to have such functionality. What do you think? Do the terms of use of Google Translate allow it? Cheers, -- Felipe. ___ Haskell-Cafe mailing

Re: [Haskell-cafe] ANNOUNCE: gt-tools-0.1.4

2010-05-06 Thread Ivan Miljenovic
On 7 May 2010 12:12, Felipe Lessa felipe.le...@gmail.com wrote: On Thu, May 06, 2010 at 09:30:50PM +0300, Sergei Trofimovich wrote: /me wonders if Miss lambdabot might like to have such functionality. What do you think? Do the terms of use of Google Translate allow it? I can't see any reason