RE: Instruction Cache Flush in createAdjustor on SPARC

2002-04-22 Thread Simon Marlow
Wolfgang Thaller wrote: [...] Can anyone with sparc experience think of a reason why cache flushing should _not_ be necessary here? Synchronizing the data/instruction caches *and* the caches of different processors (most people forget the latter) is necessary for both PowerPC

Re: scoped type variables in instance?

2002-04-22 Thread Ross Paterson
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.

RE: scoped type variables in instance?

2002-04-22 Thread Simon Peyton-Jones
That's a bug; I'll fix it. | -Original Message- | From: Ross Paterson [mailto:[EMAIL PROTECTED]] | Sent: 22 April 2002 14:15 | To: [EMAIL PROTECTED] | Subject: Re: scoped type variables in instance? | | | OK, I see this was intentional: | | The type variables in the head of a

More pointer-equality weirdness

2002-04-22 Thread Conal Elliott
I'm getting some _really_ weird results under ghci from the unsafePtrEq I'm using (thanks to Sigbjorn). It works fine under ghc. I'm running 5.03.20020208 under Windows XP. Is there a work-around, perhaps via a different implementation of unsafePtrEq? - Conal module Main where import

Re: ghc-pkg info

2002-04-22 Thread Ashley Yakeley
At 2002-04-21 12:52, Sven Panne wrote: It would be nice if ghc-pkg had options to display the value of $libdir or at least the given conf file. [...] I had *major* pains with this for the upcoming HOpenGL release, too. :-P Right. I need to find the location of Rts.h. Ideally, I would do

RE: -fspecialize-all or the like?

2002-04-22 Thread Simon Peyton-Jones
Actually, GHC does automatically specialise for all types at which the function is called in that module, but it doesn't do it across modules. Why not? Because it compiles bottom-up, whereas the specialisation info is really top-down. Have often thought that we could spit out specialisation

RE: ANNOUNCE: GHC 5.03.20020410 snapshot released

2002-04-22 Thread Simon Peyton-Jones
| Do I have to hoist the forall quantifiers in bla - forall a | . blub myself? At least, the code typechecks then. Sigh. I forgot to make the forall-hoisting feature apply recursively when I added the rank-N stuff. It's a 2 line change to make it so, but it is a change. Workaround: do the

misplaces SPECIALISE

2002-04-22 Thread Hal Daume III
/nfs/isd/hdaume/projects/NLP/Trie.lhs:162: Misplaced SPECIALISE instance pragma: {-# SPECIALIZE instance {Binary (Trie Token Double)} #-} Failed, modules loaded: NLP.NLPPrelude, Util.BinUtil, Util.Binary, NLP.HashMap, Util.ShrinkString, Util.FastMutInt, NLP.Util. what does that mean?

ICLP02 Call for Participation

2002-04-22 Thread Peter Stuckey
--- Blind-Carbon-Copy X-Mailer: exmh version 2.5 10/15/1999 with version: MH 6.8.4 #1[UCI] To: pjs Subject: ICLP02 Call for Participation Reply-to: [EMAIL PROTECTED] Mime-Version: 1.0 Content-Type: text/plain; charset=iso-8859-1 Content-Transfer-Encoding: quoted-printable Date: Mon, 22 Apr

RDP'03 - First announcement

2002-04-22 Thread Salvador Lucas Alba
[Apologies for multiple copies of this announcement] ** * First announcement *** **

RE: do notation and

2002-04-22 Thread Simon Peyton-Jones
| So, changing the translation in GHC might actually introduce | a very nasty space leak in existing programs! It might, conceivably. But the H98 report doesn't seem the right place to try to tweak full laziness. So I'm going to leave the report as it is. Hugs and GHC have changed to match.

module namespaces with Prelude

2002-04-22 Thread Hal Daume III
I'm developing my package NLP for supporting common NLP functions and have a set of functions/datatypes that are common to almost all of my modules and I wanted to separate them off into an NLP.Prelude file, but this seems not to work. One of my modules imports Prelude (the Haskell one) directly

defining (- Bool) as a set

2002-04-22 Thread Hal Daume III
I'd like to be able to define something like instance Eq a = Coll (- Bool) a where empty= \_ - False single x = \y - if x == y then True else False union a b = \x - a x || b x insert s x = \y - x == y || s y and the like However, this seems to be impossible. Is this the type

Re: defining (- Bool) as a set

2002-04-22 Thread Jorge Adriano
On Monday 22 April 2002 23:31, Hal Daume III wrote: I'd like to be able to define something like instance Eq a = Coll (- Bool) a where empty= \_ - False single x = \y - if x == y then True else False union a b = \x - a x || b x insert s x = \y - x == y || s y and the like

Re: how to call Fortran Procedures in Haskell Program?

2002-04-22 Thread Mike Thomas
Hi there. Does anybody know how to call Fortran procedures in Haskell program? I tried Green Card, but seems it only works with C codes. Sigbjorn Finne posted a way of doing this a while back, possibly on this list, maybe the GHC one. He used the FFI and a simple squaring function.

Re: defining (- Bool) as a set

2002-04-22 Thread Jorge Adriano
class Collection e ce | ce - e where empty :: ce insert :: e - ce - ce member :: e - ce - Bool instance Eq a = Collection a (a - Bool) where empty = (\x - False) insert e f = (\x - if x == e then True else f x) member e f = f e This is way better than my

Re: defining (- Bool) as a set

2002-04-22 Thread Hal Daume III
Yeah, both options suggested are valid, of course. But I really don't want to have a constructor and I'm using Edison where Coll is defined something like: class Coll c e where empty :: c e insert :: c e - e - c e etc., which precludes the fun dep solution. - Hal -- Hal Daume III

Re: module namespaces with Prelude

2002-04-22 Thread Alastair Reid
#Hal == Hal Daume [EMAIL PROTECTED] writes: I'm developing my package NLP for supporting common NLP functions and have a set of functions/datatypes that are common to almost all of my modules and I wanted to separate them off into an NLP.Prelude file, but this seems not to work. One of my

Re: module namespaces with Prelude

2002-04-22 Thread Hal Daume III
Ah, so the problem was that even though I had the superdir of NLP in my path, I was actually loading the modules in ghci from the NLP directory. Still, I find this behavior odd, since even if I were in the NLP directory I could not import NLP.Foo simply as Foo, I don't see why I should be

semi-private exports

2002-04-22 Thread Hal Daume III
Hi again, all. 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