Readline on Windows?

2004-11-22 Thread Koen Claessen
Hi, Compiling the following program (Bug.hs): module Main where import System.Console.Readline main = do ms - readline Hi print ms Using GHC 6.2.2 on Windows XP, using the command line: ghc --make Bug -o bug Produces the following message: Chasing modules from: Bug Compiling

Derivable type classes bug?

2004-11-22 Thread Koen Claessen
Hi, Take a look at the following program, making use of derivable type classes. module Bug where import Data.Generics class Foo a where foo :: a - Int foo{| Unit |}_ = 1 foo{| a :*: b |} _ = 2 foo{| a :+: b |} _ = 3 instance Foo [a] GHC 6.2.2 produces the following error

[ ghc-Bugs-1069656 ] ghc-ghci inconsisteny

2004-11-22 Thread SourceForge.net
Bugs item #1069656, was opened at 2004-11-19 19:57 Message generated for change (Settings changed) made by simonmar You can respond by visiting: https://sourceforge.net/tracker/?func=detailatid=108032aid=1069656group_id=8032 Category: None Group: None Status: Closed Resolution: None Priority: 5

RE: Derivable type classes bug?

2004-11-22 Thread Simon Peyton-Jones
Yes, you guessed right. Your generic class declaration gives rise to instance declarations like | instance (Foo a, Foo b) = Foo (a :*: b) where | foo _ = 2 You suggest that it could be cleverer about guessing the context for the instance decl, and that would make sense. But this'd then be

[ ghc-Bugs-1071030 ] internal error: update_fwd: unknown/strange object 12238336

2004-11-22 Thread SourceForge.net
Bugs item #1071030, was opened at 2004-11-22 15:45 Message generated for change (Tracker Item Submitted) made by Item Submitter You can respond by visiting: https://sourceforge.net/tracker/?func=detailatid=108032aid=1071030group_id=8032 Category: None Group: None Status: Open Resolution: None

RE: Readline on Windows?

2004-11-22 Thread Simon Marlow
On 16 November 2004 17:16, Koen Claessen wrote: Compiling the following program (Bug.hs): module Main where import System.Console.Readline main = do ms - readline Hi print ms Using GHC 6.2.2 on Windows XP, using the command line: ghc --make Bug -o bug Produces

filterSet

2004-11-22 Thread Serge D. Mechveliani
Dear GHC team, As there exists, say,Data.mapSet, is this natural to provide also filterSet ? - Serge Mechveliani [EMAIL PROTECTED] ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED]

RE: Bug in touchForeignPtr?

2004-11-22 Thread Simon Marlow
On 20 November 2004 23:02, Benjamin Franksen wrote: I am using Foreign.Concurrent.newForeignPtr and touchForeignPtr inside the finalizers to express liveness dependencies as hinted to by the documentation. This doesn't seem to work, though, or at least I can't see what I've done wrong. I

Re: Bug in touchForeignPtr?

2004-11-22 Thread Keean Schupke
Some thoughts on this, Whilst I agree that finalizers are best avoided, it must be possible to order the finalizers for running on exit... Perhaps a simple multi-pass algorith would do? (ie: run all finalizers that do not refer to other objects with finalizers - repeat until no objects with

RE: unlit/ghci does not work on DOS file

2004-11-22 Thread Simon Marlow
On 18 November 2004 20:31, Christian Maeder wrote: calling unlit on a DOS file fails, whereas hugs is able to process the same file (under unix). Christian Prelude readFile Test.lhs = putStrLn . show \r\n module Test where\r\n\r\n Prelude :l Test.lhs Test.lhs line 2: unlit: Program

User-defined operators and compound expressions using Happy

2004-11-22 Thread Frank-Andre Riess
Hi there folks, once again, I've got a question related to Happy (I've got version 1.13 at the moment). Maybe, it's even more a question on formal languages, but well... How can I write a grammar that can cope with user-defined operators (of different precedences/associativities) and compound

RE: proposal for ghc-pkg to use a directory of .conf files

2004-11-22 Thread Simon Marlow
On 21 November 2004 00:56, Isaac Jones wrote: The systems that would want to do this kind of thing, such as Debian, have other mechanisms for deciding whether packages conflict, etc. IIRC, this is the argument I just used against adding support for multiple libraries in Cabal, so I guess I

Re: Bug in touchForeignPtr?

2004-11-22 Thread Sven Panne
Keean Schupke wrote: [...] Whatever happens I think it must make sure all system resources allocated by a program are freed on exit - otherwise the machine will have a resource leak and will need rebooting eventually. That's an OS task IMHO, not really the task of an RTS. Looks like you're working

Re: Bug in touchForeignPtr?

2004-11-22 Thread Keean Schupke
Nope there are some unix resources that c exit routines do not free like semaphores. Sven Panne wrote: Keean Schupke wrote: [...] Whatever happens I think it must make sure all system resources allocated by a program are freed on exit - otherwise the machine will have a resource leak and will

Re: Bug in touchForeignPtr?

2004-11-22 Thread Benjamin Franksen
On Monday 22 November 2004 14:45, Simon Marlow wrote: On 20 November 2004 23:02, Benjamin Franksen wrote: I am using Foreign.Concurrent.newForeignPtr and touchForeignPtr inside the finalizers to express liveness dependencies as hinted to by the documentation. This doesn't seem to work,

Re: Bug in touchForeignPtr?

2004-11-22 Thread Abraham Egnor
If finalizers are not the right thing, what else is? I've found that when writing an interface to a C library that requires resource management, it's much better to use the withX (see Control.Exception.bracket) style of function than to use finalizers - programs are much easier to reason about

Re: Bug in touchForeignPtr?

2004-11-22 Thread Sven Panne
Abraham Egnor wrote: I've found that when writing an interface to a C library that requires resource management, it's much better to use the withX (see Control.Exception.bracket) style of function than to use finalizers - programs are much easier to reason about and debug. ... and have a much more

Re: Bug in touchForeignPtr?

2004-11-22 Thread Sven Panne
Keean Schupke wrote: Nope there are some unix resources that c exit routines do not free like semaphores. Which library/OS calls do you mean exactly? I always thought that files are the only resources surviving process termination. Cheers, S. ___

Re: User-defined operators and compound expressions using Happy

2004-11-22 Thread Duncan Coutts
On Mon, 2004-11-22 at 17:48 +0100, Frank-Andre Riess wrote: Hi there folks, once again, I've got a question related to Happy (I've got version 1.13 at the moment). Maybe, it's even more a question on formal languages, but well... How can I write a grammar that can cope with user-defined

Re: Bug in touchForeignPtr?

2004-11-22 Thread Keean Schupke
Semaphores (SYSV style) are not freed automatically. Currenly I am using C's at_exit funtion (which is even called on a signal)... Perhaps this is the way to deal with foreign resources... bracket notation and at_exit to clean up on signals? Keean. Sven Panne wrote: Keean Schupke wrote: Nope

Re: User-defined operators and compound expressions using Happy

2004-11-22 Thread Doaitse Swierstra
On 2004 nov 22, at 17:48, Frank-Andre Riess wrote: Hi there folks, once again, I've got a question related to Happy (I've got version 1.13 at the moment). Maybe, it's even more a question on formal languages, but well... How can I write a grammar that can cope with user-defined operators (of

Re: Bug in touchForeignPtr?

2004-11-22 Thread Benjamin Franksen
On Monday 22 November 2004 18:55, Sven Panne wrote: Abraham Egnor wrote: I've found that when writing an interface to a C library that requires resource management, it's much better to use the withX (see Control.Exception.bracket) style of function than to use finalizers - programs are

Re: Bug in touchForeignPtr?

2004-11-22 Thread Glynn Clements
Keean Schupke wrote: C exit routines aren't responsible for freeing OS resources; the OS is. The fact that the SysV IPC objects aren't freed on exit is intentional; they are meant to be persistent. For the same reason, the OS doesn't delete upon termination any files which the

Re: Bug in touchForeignPtr?

2004-11-22 Thread John Meacham
Although, this does remind me. A suitable atexit-equivalant in the haskell libraries would be much appreciated. John -- John Meacham - repetae.netjohn ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED]

Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-22 Thread Adrian Hey
On Friday 19 Nov 2004 2:27 pm, Benjamin Franksen wrote: Implicit parameters are evil, agreed. Their deficiencies should be added as a warning to the docs (with many exclamation marks). Well I dunno. Maybe whatever's currently wrong with them can be fixed up. But I can't say they're something

Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-22 Thread Keean Schupke
Adrian Hey wrote: Just repeating this again and again doesn't make it any more true. Ditto... I for one think the best solution is to use the language as intended and pass the values as function arguments. As pointed out on this list - the only possible situation where you cannot do this is when

Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-22 Thread John Velman
On Mon, Nov 22, 2004 at 07:27:44PM +0100, Lennart Augustsson wrote: [snip] I admit there are proper uses of global variables, but they are very rare. You have not convinced me you have one. -- Lennart It's with some trepidation I bring a problem as a total newbie, but I've been

Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-22 Thread Axel Simon
On Mon, 2004-11-22 at 23:34, John Velman wrote: In a nutshell: I want to use the old value of a tag to compute the new value, in a callback, I want to access the tag from other callbacks, and I want to the value to a mutable list from within the callback. I'd

Re: [Haskell-cafe] foldlWhile

2004-11-22 Thread Benjamin Franksen
On Saturday 20 November 2004 10:47, Serge D. Mechveliani wrote: Is such a function familia to the Haskell users? foldlWhile :: (a - b - a) - (a - Bool) - a - [b] - a Maybe this link is of interest to you: http://okmij.org/ftp/Haskell/#fold-stream Ben -- Top level things with identity are

[Haskell-cafe] Problem with overlapping class instances

2004-11-22 Thread Graham Klyne
Once again, the Haskell class system is proving rather subtle for me. On this occasion, I'm getting an overlapping class instance error which I think should be fully disambiguated by the supplied class context. The code below (end of message) is a .lhs file that reproduces the problem in Hugs,

Re: [Haskell-cafe] Problem with overlapping class instances

2004-11-22 Thread Ralf Laemmel
Instance selection and thereby overlapping resolution is *independent* of constraints. It is defined to be purely syntactical in terms of instance heads. See the HList paper for some weird examples. Ralf Graham Klyne wrote: The reported overlapping instance is [Char], which I take to be derived

[Haskell-cafe] Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-22 Thread Graham Klyne
[Switching to Haskell-cafe] At 11:26 22/11/04 +, you wrote: I would ask an alternative question - is it possible to live without unsafePerformIO? I have never needed to use it! I have used it once, with reservations, but at the time I didn't have the time/energy to find a better solution.

[Haskell-cafe] Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-22 Thread Keean Schupke
Obviously without knowing the details I am speculating, but would it not be possible to do a first pass of the XML and build a list of files to read (a pure function) this returns its result to the IO monad where the files are read and concatenated together, and passed to a second (pure

Re: [Haskell-cafe] Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-22 Thread Benjamin Franksen
On Monday 22 November 2004 23:22, Keean Schupke wrote: It seems to me that as unsafePerformIO is not in the standard and only implemented on some compilers/interpreters, that you limit the portability of code by using it, and that it is best avoided. Also as any safe use of unsafePerformIO

[Haskell-cafe] Re: Top Level TWI's again

2004-11-22 Thread Peter Simons
Benjamin Franksen writes: If a foreign function (e.g. from a C library) is really pure, then I see no way to tell that to the compiler other than using unsafePerformIO. What's the problem with importing it with a pure signature? Like this: foreign import ccall unsafe sin :: CDouble -