RE: Bugs?

2002-04-23 Thread Simon Peyton-Jones
It's a bug all right. The definition of A should be rejected. It's not legal H98 Will fix. Thanks for the report Simon | -Original Message- | From: Jorge Adriano [mailto:[EMAIL PROTECTED]] | Sent: 17 April 2002 18:26 | To: [EMAIL PROTECTED] | Subject: Bugs? | | | I've sent this

Re: scoped type variables in instance?

2002-04-23 Thread Ross Paterson
I wrote: | OK, I see this was intentional: | | The type variables in the head of a class or instance | declaration scope over the methods defined in the where part. | | But both provisions cause Haskell 98 modules to be rejected, | even without -fglasgow-exts. On Mon, Apr 22,

RE: scoped type variables in instance?

2002-04-23 Thread Simon Peyton-Jones
| Is rejecting Haskell 98 modules when -fglasgow-exts is on | also a bug? (i.e. does GHC Haskell aim to be a conservative | extension of H98?) Yes, we do so aim, but this seems to be an occasion where there's no obvious way to make the extension 100% conservative without making the extended

RE: misplaces SPECIALISE

2002-04-23 Thread Simon Peyton-Jones
It is really hard to help you if you don't supply the context. Which version of GHC? Send the code for Trie.lhs. etc. Otherwise we're all guessing. Simon | -Original Message- | From: Hal Daume III [mailto:[EMAIL PROTECTED]] | Sent: 22 April 2002 23:46 | To: GHC Users Mailing List |

RE: module namespaces with Prelude

2002-04-23 Thread Hal Daume III
It happens in Hugs, too, but somewhat differently. Here's a test case. Go to /foo and do mkdir Bar. In Bar, create IO.hs and make its contents: module Bar.IO where then also in Bar create Foo.hs module Bar.Foo where import IO Then when in directory Bar load ghci (using 5.02.1) and

RE: misplaces SPECIALISE

2002-04-23 Thread Hal Daume III
Here is sufficient code, using ghc5.02.1 for solaris: module Test where import Util.Binary -- this is the GHC binary distribution import PrelWord import Array newtype Token = Token [Word8] class TrieKey key where mkKey :: key - [Word8] unKey :: [Word8] - key data Trie key elem =

RE: module namespaces with Prelude

2002-04-23 Thread Simon Marlow
It happens in Hugs, too, but somewhat differently. Here's a test case. Go to /foo and do mkdir Bar. In Bar, create IO.hs and make its contents: module Bar.IO where then also in Bar create Foo.hs module Bar.Foo where import IO Then when in directory Bar load ghci

Re: module namespaces with Prelude

2002-04-23 Thread Alastair Reid
[copied to original recipients along with the original bug report] On ghc-bugs, Hal Daume reported problems with Hugs (and ghci) where importing IO.hs causes a module called Bar.IO (i.e., Bar/IO.hs) to be loaded - leading to the load to fail. I've systematically tried every way of invoking

RE: defining (- Bool) as a set

2002-04-23 Thread Simon Peyton-Jones
Hal, [I think this sort of question would be better on the haskell-cafe list.] I don't think what you want can be done directly. It's the old thing about not having lambdas at the type level. You want: instance Eq a = Coll (\x. x - Bool) a where ... and you just can't do that.

Matrix library in Haskell

2002-04-23 Thread Jan Kybic
Hello, I am just discovering Haskell, so sorry if this is not the right place to ask. I want to use it for some numerical calculations. I need something higher level than C++ and faster than Python or Matlab and from the initial experiments it seems that Haskell could be the right

RE: semi-private exports

2002-04-23 Thread Simon Marlow
In my NLP.Prelude file, I define: newtype Token = Token [Word8] and I export only the type, not the constructor because I don't users of my package to be able to inspect/modify the list directly. However, in my NLP.IO module, in which I define IO for some of my data types, I need

SAS'02 CFP Reminder -- Submission Deadline May 5, 2002

2002-04-23 Thread SAS2002
(Apologies for multiple postings) -- CALL FOR PAPERS (SAS'02) The 9th International Static Analysis Symposium September 17 - 20 2002, Madrid, Spain

style questino: where to put instances

2002-04-23 Thread Hal Daume III
I know you're all probably pretty tired of hearing from me, but I have a style question. Let's say I'm defining a hashmap. I have a module HashMap which defines a class Hashable a where hash :: a - Int or something like that. I have a common datastructure called a Foo which I want to be able

Re: defining (- Bool) as a set

2002-04-23 Thread Christian Sievers
Hal Daume III wrote: I'd like to be able to define something like single x = \y - if x == y then True else False Just a note on style: it always hurts me to see something like if term then True else False -- this is just the same as 'term'. So you could say single x = \y - x==y

Re: defining (- Bool) as a set

2002-04-23 Thread Hal Daume III
Yeah, I realized that right after I sent the email (I was composing on the fly and not copy-and-pasting). I think the main reason I wrote it as an explicit lambda expression rather than just single = (==) was because I wanted it to parallel the other definitions. IMO, the preferred way to write