Re: Overlapping, undecidable, incoherent -- or worse?

2004-05-20 Thread Stefan Reich
Simon Peyton-Jones wrote: As a trivial example, try f a = a |= a What type shall we infer for f? f :: (Bounded a, Enum a, SemiRing a) => a -> a or f :: (CSemiRing a) => a -> a This has always confused me - GHC always seems to use the strongest possible conditions when inferring types (

What happened to constrFields?

2004-05-09 Thread Stefan Reich
In recent versions of the GHC libraries, constrFields (as defined here http://www.cs.vu.nl/boilerplate/library/Data.Generics.Basics.html) has disappeared. I failed to figure out another way to get the names of all fields of a constructor. Have I overlooked anything? Do I have to use Template Ha

Re: Two problems with heap profiling

2004-05-09 Thread Stefan Reich
Yes, same thing here on RedHat 9... apparently a problem specific to the Windows port. -Stefan Sven Panne wrote: Stefan Reich wrote: [...] The program crashes every time I run it (Windows XP this time, but I assume that doesn't make a difference). Hmmm, it works with GHC 6.2.1 and th

Re: Two problems with heap profiling

2004-05-09 Thread Stefan Reich
every time I run it (Windows XP this time, but I assume that doesn't make a difference). Thanks in advance for your help, -Stefan Simon Marlow wrote: On 16 April 2004 10:39, Stefan Reich wrote: I'm using GHC 6.2.1 on Windows 2000. Problem 1: -hr crashes in some circumstances. Ta

Haddock can't parse data declaration involving operator

2004-05-09 Thread Stefan Reich
Hi, I hope this is the right place to ask about Haddock problems? I'm using Haddock 0.6 (RedHat RPM module) under RedHat 9. When I invoke haddock on this file (Op.hs): module Op where infixl 4 := data a := b = a := b I get the error "Op.hs:Illegal data/newtype declaration". I

Two problems with heap profiling

2004-04-16 Thread Stefan Reich
I'm using GHC 6.2.1 on Windows 2000. Problem 1: -hr crashes in some circumstances. Take this program (Test.hs): module Main where import IO main = do readFile "large.csv" putStrLn "OK" where large.csv is an 800K CSV file (with very small files, the bug doesn't occur). I compile with:

Re: Collection framework

2004-03-07 Thread Stefan Reich
es too. Is that what you're attempting? If yes, how far along the way are you? Best, -Stefan JP Bernardy wrote: Hi, --- Stefan Reich <[EMAIL PROTECTED]> wrote: Hi everybody, is there a Haskell collections framework suitable for practical use? There's the Edison framework. Fro

Collection framework

2004-03-02 Thread Stefan Reich
Hi everybody, is there a Haskell collections framework suitable for practical use? I searched the Net and didn't really find anything. I'm growing tired of remembering the various (and partially inconsistent) function names for lists, sets, finite maps, arrays, ... For starters, take lookup and

Generics and type classes

2004-01-30 Thread Stefan Reich
Hi, please consider the following module: module TypeTest where import Data.Generics class Data a => MyClass a where special :: a -> a generic :: MyClass a => a -> a generic = everywhere (mkT special) The general idea is to define traversals about data types

Concurrent Haskell on Win32?

2004-01-24 Thread Stefan Reich
at to mention this in the GHC release notes in order to prevent people from figuring this out the hard way. Fixing concurrency would expand Haskell's potential range of applications tremendously... I'd really love to see that happen. -Stefan Reich (addicted Has

Re: Random number generator

2004-01-15 Thread Stefan Reich
That's definitely not a message for the bugs list :-) Please have a look at this page: http://www.zvon.org/other/haskell/Outputrandom/getStdRandom_f.html It gives the correct signature for drawInt as you defined it: Int -> Int -> IO Int The signature you gave doesn't work because it specifies

Re: GHC 6.2 breaks multiline string literals

2003-12-27 Thread Stefan Reich
o Perl's << and PHP's <<< operator. -Stefan Ferenc Wagner wrote: Stefan Reich <[EMAIL PROTECTED]> writes: multilineLiteral = " line1 line2" Use string gaps (see 2.6 in the Report): multilineLiteral = "\ \ line1\n\ \ line2" ___

-xc giving very little information

2003-12-26 Thread Stefan Reich
A complex program of mine fails with this message: Fail: Maybe.fromJust: Nothing I tried to extract more information about the error by compiling with -prof -auto-all and running the program with +RTS -xc, as advised on http://www.haskell.org/hawiki/TipsAndTricks . This yielded exactly one ad

GHC 6.2 breaks multiline string literals

2003-12-26 Thread Stefan Reich
This worked in GHC 6.0.1: multilineLiteral = " line1 line2" But doesn't work in GHC 6.2. Is this a bug or rather a bugfix? Anyway, I found it very convenient to embed verbatim string blocks this way. Is there maybe another way to achieve the same thing? Thanks in advance, -Stefan __

Re: DiffArray Performance

2003-11-07 Thread Stefan Reich
Simon Marlow wrote: DiffArray is an example of a good use for unsafePerformIO: it uses imperative operations to implement a pure API. The DiffArray is made of mutable objects under the hood, but as far as the programmer is concerned it behaves just like a pure Array. I'd like to ask a general que

Re: Making implicit parameters explicit

2003-11-06 Thread Stefan Reich
cit parameters are somewhat at odds with functional programming spirit. In a way, IP functions are more like macros than like first-class functions. They also tend to blur referential transparency. They should probably be used sparingly and with care. -Stefan Stefan Reich wrote: Hi, I discov

Making implicit parameters explicit

2003-11-05 Thread Stefan Reich
Hi, I discovered implicit parameters today and I'm very excited about them because they allow to express certain code constructs more elegantly. However, I stumbled upon a problem. Suppose I have these definitions (the definition of Request is irrelevant): type Controller = (?req :: Request) =