bug

2002-11-20 Thread John Meacham
this is on a redhat 7.3 system with the 5.04.1 RPMs off the web site /usr/bin/ghc -i. -i. -prof -auto-all -package lang -package concurrent -package net -package posix -O -fasm -funbox-strict-fields -fglasgow-exts -fwarn-deprecations -fwarn-incomplete-patterns -fwarn-unused-binds

Re: bug

2002-11-20 Thread Wolfgang Thaller
it only happens when i try to compile with profiling enabled. Profiling (-prof) is incompatible with the native code generator (-fasm). Leave out -fasm if you want profiling. (Compiling will be slower without -fasm) It is only a tiny bug: GHC should complain about incompatible options

Bug in do expressions

2002-11-20 Thread Andrew J Bromage
G'day all. In a recent GHC checkout, the following program: module Main(main) where import Maybe import Control.Monad test :: (MonadPlus m) = [a] - m Bool test xs = do (_:_) - return xs return True `mplus` do

RE: -Werror Request

2002-11-20 Thread Simon Peyton-Jones
Done! SImon | -Original Message- | From: Ashley Yakeley [mailto:[EMAIL PROTECTED]] | Sent: 14 November 2002 02:25 | To: GHC List | Subject: -Werror Request | | If it's not too much work, I'd like to request a -Werror option for GHC | that would turn warnings into errors. Sometimes

Re: Native Threads in the RTS

2002-11-20 Thread Wolfgang Thaller
Great, thanks. I hope you'll keep it up to date so that by the time the discussion converges it can serve as a specification and rationale. We can put it in CVS too... Simon will think of where! Until then, I'll play the role of a human CVS server. Ultimately it'd be worth integrating with

adding new primitives to ghci...

2002-11-20 Thread Andre Rauber Du Bois
Hello! I am trying to add a new primitive to ghc (5.04.1) ... I followed the instructions in primops.txt.pp: -- - or, for an out-of-line primop: -- ghc/includes/PrimOps.h (just add the declaration) -- ghc/rts/PrimOps.hc (define it here) --

RE: re-opening a closed stdin?

2002-11-20 Thread Simon Marlow
There's probably a really obvious answer to this, but I can't find it. Is there any way in GHC to reopen stdin if it has been closed? There's no way to do this at present, except in GHCi where you can revert CAFs to their unevaluated state. You may wonder why I'd want this. Well I'm

RE: adding new primitives to ghci...

2002-11-20 Thread Simon Marlow
I am trying to add a new primitive to ghc (5.04.1) ... I followed the instructions in primops.txt.pp: --- or, for an out-of-line primop: -- ghc/includes/PrimOps.h (just add the declaration) -- ghc/rts/PrimOps.hc (define it here) --

Request: suppress specific warnings at specific places

2002-11-20 Thread Mike Gunter
GHC's excellent warnings are very helpful. They would be somewhat more so if it were possible to suppress a warning about a specific bit of code. One possible syntax (to which I gave no commitment) would be {-# WOFF non-exhaustive pattern matches #-} offending code {-# WON non-exhaustive

Re: re-opening a closed stdin?

2002-11-20 Thread Bernard James POPE
Simon Marlow writes: I've been thinking about duplicating/replacing Handles for a while. Here's a possible interface: -- |Returns a duplicate of the original handle, with its own buffer -- and file pointer. The original handle's buffer is flushed, including -- discarding any input

Re: ANNOUNCE: Hugs98 November 2002 release

2002-11-20 Thread Oliver Braun
* Sigbjorn Finne [EMAIL PROTECTED] [2002-11-19 23:08 -0800]: We are pleased to announce a new release of Hugs98, an interpreter and programming environment for developing Haskell programs. The FreeBSD port is now up-to-date. Regards, Olli -- {- IST IIS _ INF _ UniBwM :: [EMAIL

RE: Functional dependencies and Constructor Classes

2002-11-20 Thread Martin Sulzmann
Mark P Jones writes: | The issue I want to raise is whether constructor classes are | redundant in the presence of FDs No, they are not comparable. Allow me to make the following bold claim. Assume we are given a program that uses the Haskell functor class as in class Functor f

Why no findM ? simple Cat revisited

2002-11-20 Thread Ahn Ki-yung
Simple Cat (revisitied) \begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs } isLeft (Left _) = True isLeft _ = False main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h \end{code} This is my

Re: Why no findM ? simple Cat revisited

2002-11-20 Thread Jorge Adriano
Simple Cat (revisitied) \begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs } isLeft (Left _) = True isLeft _ = False main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h \end{code}

Feature Structures

2002-11-20 Thread Markus . Schnell
Has anybody tried to implement (typed) feature structures in Haskell with unification? I'm trying to build my own library, but if there is already support for it, I would consider using this alternative. Thanks, Markus -- Markus Schnell Speech Interface Group, Infineon Technologies AG Tel

RE: ANNOUNCE: Hugs98 November 2002 release

2002-11-20 Thread i
[mybox] gunzip hugs98-Nov2002.tar.gz [mybox] tar xvf hugs98-Nov2002.tar ... x hugs98-Nov2002/fptools/libraries/base/Text/ParserCombinators/Parsec/examples/Mondrian/Pretty.hs, 2918 bytes, 6 tape blocks tar: directory checksum error [mybox] :( --

Re: Feature Structures

2002-11-20 Thread Hal Daume III
Not surprisingly, I have written such a thing. It's not complete, but I think unification is done properly. The setting is optimality theoretic LFG, but the unification is pretty standard. I don't know if you'll find it useful, but all the code can be grabbed from

Call for Participation: PADL 2003

2002-11-20 Thread Logic Programming Rsrch Association
[Apologies for multiple messages.] CALL FOR PARTICIPATION Fifth International Symposium on Practical Aspects of Declarative Languages http://www.research.avayalabs.com/user/wadler/padl03/ (PADL '03)

Re: erreta, a couple of unimportant missing words :-(

2002-11-20 Thread Ahn Ki-yung
Ahn Ki-yung wrote: Simple Cat (revisitied) \begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs } isLeft (Left _) = True isLeft _ = False main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h

Why no findM ? simple Cat revisited

2002-11-20 Thread Ahn Ki-yung
Simple Cat (revisitied) \begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs } isLeft (Left _) = True isLeft _ = False main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h \end{code} This is my

Re: Why no findM ? simple Cat revisited

2002-11-20 Thread Jorge Adriano
Simple Cat (revisitied) \begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs } isLeft (Left _) = True isLeft _ = False main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h \end{code}

Re: Why no findM ? simple Cat revisited

2002-11-20 Thread Ahn Ki-yung
Jorge Adriano wrote: Seems to me like the name findM could be misleading mapM :: (Monad m) = (a - m b) - [a] - m [b] filterM :: (Monad m) = (a - m Bool) - [a] - m [a] These take a monadic function and a list of elements. Yours works the other way around (takes a function and a list of 'monadic

simple cat by joining two infinite lists (intput/ouput)

2002-11-20 Thread Ahn Ki-yung
\begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { b - f x; if b then return (Just x) else findM f xs } isLeft (Left _) = True isLeft _ = False main = findM (=return.isLeft) $ map (try . uncurry (=)) $ zip (hGetCharS stdin)

library of monadic functions [was: Why no findM ? simple Cat revisited]

2002-11-20 Thread Jorge Adriano
I appreciate your comment. I agree that the type of findM should be the one you suggested, and it still fits my original purpose. It's no more than a step arout. \begin{code} import IO findM f [] = return Nothing findM f (x:xs) = do { b - f x; if b then return (Just x) else findM f xs }

Re: library of monadic functions [was: Why no findM ? simple Cat revisited]

2002-11-20 Thread Andrew J Bromage
G'day all. On Wed, Nov 20, 2002 at 08:25:46PM +, Jorge Adriano wrote: I think both versions can be very useful: findM :: (Monad m) = (a - m Bool) - [a] - m (Maybe a) findM' :: (Monad m) = (a - Bool) - [m a] - m (Maybe a) I can also make a case for: findM'' :: (Monad

Random Color

2002-11-20 Thread Mike T. Machenry
I am trying to construct an infinate list of pairs of random colors. I am hung up on getting a random color. I have: data Color = Blue | Red | Green deriving (Eq, Ord, Show) am I supposed to instantiate a Random class instance from color? I am not sure exactly how the random number generator

Re: Random Color

2002-11-20 Thread Andrew J Bromage
G'day all. On Wed, Nov 20, 2002 at 08:44:36PM -0500, Mike T. Machenry wrote: I am trying to construct an infinate list of pairs of random colors. I am hung up on getting a random color. I have: data Color = Blue | Red | Green deriving (Eq, Ord, Show) am I supposed to instantiate a Random

Re: Random Color

2002-11-20 Thread Mike T. Machenry
Andrew and list, I am a beginer. I really don't know what I would do if I derived Color from Enum. You say I could create elements that way. Is there some simple example someone could post to the list? Thank you for your help. -mike On Thu, Nov 21, 2002 at 01:55:55PM +1100, Andrew J Bromage