Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-26 Thread Pedro Baltazar Vasconcelos
Two solutions using immutable and mutable arrays and no unsafe operations: module Main where import Control.Monad.ST import Data.Ix import Data.Array import Data.Array.MArray import Data.Array.ST -- using immutable arrays hist1 :: String - Array Char Int hist1 str = accumArray (+) 0

RE: [Haskell-cafe] lockFile: fd out of range

2005-10-26 Thread Simon Marlow
On 25 October 2005 17:02, Joel Reymont wrote: Is there a set limit on the number of file descriptors that a Haskell program can open? I'm using hs-plugins on FreeBSD to transparently compile, load and launch scripts that establish a connection to a server. I'm getting this error:

[Haskell-cafe] Re: Fwd: Parsing in Practice

2005-10-26 Thread Sylvain Schmitz
Tomasz Zielonka tomasz.zielonka at gmail.com writes: The problem is that the set of LALR grammars is not closed under composition (as I've read in some paper on GLR parsing). If I'm right, the set of unambiguous grammars is not closed under concatenation nor union. This makes things rather

Re: [Haskell-cafe] Typeclasses and GADT [Was: Regular Expressions without GADTs]

2005-10-26 Thread Tomasz Zielonka
On 10/19/05, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: I never argued about convenience of GADTs. They can be quite handy when dealing with existentials: GADT embody a safe cast and so spare us form writing the boring casting code ourselves. And perhaps this is the only compelling case for

Re: [Haskell-cafe] Typeclasses and GADT [Was: Regular Expressions without GADTs]

2005-10-26 Thread Tomasz Zielonka
On 10/26/05, Tomasz Zielonka [EMAIL PROTECTED] wrote: See code in the attachment. I forgot to attach it :-) Best regards Tomasz {-# OPTIONS -fglasgow-exts #-} module Type where import Control.Monad data Type t where Bool:: Type Bool Int :: Type Int Char:: Type Char

RE: [Haskell-cafe] Template Haskell -- Bug?

2005-10-26 Thread Simon Peyton-Jones
| $ ghc --make THTest1.hs | Chasing modules from: THTest1.hs | Compiling THTest1TH( ./THTest1TH.hs, ./THTest1TH.o ) | Compiling THTest1 ( THTest1.hs, THTest1.o ) | | THTest1.hs:10:4: `incrSelf' is not a (visible) method of class `IncrSelf' I've now fixed this bug, in the HEAD.

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-26 Thread Udo Stenzel
Pedro Baltazar Vasconcelos wrote: Two solutions using immutable and mutable arrays and no unsafe operations: Both solutions certainly count as nice, but both exhibit an ugly memory leak. As usual, this is due to too much laziness: no intermediate result is ever evaluated until it is too late.

RE: [Haskell-cafe] Help using QuickCheck

2005-10-26 Thread Simon Peyton-Jones
I'm afraid this fix didn't make it into the 6.4 branch, but the double error (which is bad) is certainly fixed in the HEAD Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of | Andrew Pimlott | Sent: 21 October 2005 20:45 | To:

Re: [Fwd: Re: [Haskell-cafe] Typeclasses and GADT [Was: Regular Expressions without GADTs]]

2005-10-26 Thread kahl
Tomasz Zielonka [EMAIL PROTECTED] wrote Wed, 26 Oct 2005 13:37:29 +0200: Speaking about casts, I was playing with using GADTs to create a non-extensible version of Data.Typeable and Data.Dynamic. I wonder if it's possible to write such a thing without GADTs (and unsafeCoerce, which is

[Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-26 Thread Scherrer, Chad
Sorry to drag this thread out, but here's one more thing you might try... I was thinking, if we just wanted something like intTable :: [Int] - [(Int, Int)] we could just replace Map with IntMap in the previous solution: intTable xs = IntMap.assocs $! foldl' f IntMap.empty xs where f m x =

Re: [Fwd: Re: [Haskell-cafe] Typeclasses and GADT [Was: Regular Expressions without GADTs]]

2005-10-26 Thread Tomasz Zielonka
On 26 Oct 2005 10:11:25 -0400, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Tomasz Zielonka [EMAIL PROTECTED] wrote Wed, 26 Oct 2005 13:37:29 +0200: Speaking about casts, I was playing with using GADTs to create a non-extensible version of Data.Typeable and Data.Dynamic. I wonder if

Re: [Fwd: Re: [Haskell-cafe] Typeclasses and GADT [Was: Regular Expressions without GADTs]]

2005-10-26 Thread kahl
On 26 Oct 2005 10:11:25 -0400, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Tomasz Zielonka [EMAIL PROTECTED] wrote Wed, 26 Oct 2005 13:37:29 +0200: Speaking about casts, I was playing with using GADTs to create a non-extensible version of Data.Typeable and Data.Dynamic.

Re: [Haskell-cafe] Typeclasses and GADT [Was: Regular Expressions without GADTs]

2005-10-26 Thread John Meacham
On Wed, Oct 26, 2005 at 01:37:29PM +0200, Tomasz Zielonka wrote: On 10/19/05, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: I never argued about convenience of GADTs. They can be quite handy when dealing with existentials: GADT embody a safe cast and so spare us form writing the boring casting