Re: deriving...

2004-10-17 Thread Keean Schupke
for a template-haskell splice $(derivingX) when the compiler encounters a deriving X statement that is not built-in? Ulf Norell wrote: Keean Schupke [EMAIL PROTECTED] writes: Yes, I could quite easily write the generator in TemplateHaskell (have played with it before) _but_ I don't like

GHC CVS HEAD bug!

2004-11-03 Thread Keean Schupke
The CVS HEAD branch of GHC seems to ignore the fixity of type constructors imported from another module... This breaks compiling of code that uses this feature: module1: type a b = a :+ b infixr 1 :+ module2: a :: Int :+ Float :+ Double a = undefined Gives a the wrong type. Keean

GHC bug typo...

2004-11-03 Thread Keean Schupke
obviously I meant: type a :+ b = (a,b) In that last post! ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

typechecking too eager?

2004-11-07 Thread Keean Schupke
The following code should compile (If the constructor is valid, so is the function): data Test = Test (forall a . a) test a = Test a However this fails to compile with the following error: Test.hs:9:9: Inferred type is less polymorphic than expected Quantified type variable `a' escapes

Re: typechecking too eager?

2004-11-07 Thread Keean Schupke
So, does that mean that ideally we would like it to type check, but for implementation reasons it cannot easily be done without a type signature? I can use the type signature no problem. Keean. Andres Loeh wrote: Hi there, The following code should compile (If the constructor is valid, so is

Problems with CABAL in GHC head.

2004-11-15 Thread Keean Schupke
Trying to recompile GHC (for the template-haskell existential support), but keeps failing on CABAL (the import for Foreign.Marshal.Alloc is missing from ghc/lib/compat/Distribution/Version.hs as well as import paths for Data/Version.hi which is not compiled yet as it depends on ghc-inplace.

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: 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

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: Bug in touchForeignPtr?

2004-11-23 Thread Keean Schupke
How can I put this, it is a best efforts approach - it does its best to run the finalizers, even after a segmentation fault... however some of the pointers may be messed up... If the cleanup causes a segmentation fault (sometimes called a double bus fault) then we have to abandon the cleanup.

instances for bottom?

2004-11-23 Thread Keean Schupke
I was wondering whether the method by which default types are chosen for unresolved overloading could be made available to the programmer. It seems that if we consider the overlapping instances: class x instance Int instance Float instance x x overlaps with Int and Float... I was

Re: Bug in touchForeignPtr?

2004-11-23 Thread Keean Schupke
Simon Marlow wrote: Note that the GC only starts the finaliser thread. The program can still terminate before this thread has run to completion (this is one reason why we say that finalisers don't always run before program termination). This sounds like a bug to me... surely you should wait

Re: -fallow-incoherent-instances

2004-11-30 Thread Keean Schupke
Ralf Laemmel wrote: General conclusion: I still have to see a good reason to use -fallow-incoherent-instances. It's mostly good to shot yourself in the head. Maybe one day we will get -fallow-backtracking? now that would be useful... Keean. ___

Re: Scoped type variables

2004-12-17 Thread Keean Schupke
what about having -fno-lexically-scoped-types for old code? Keean. Simon Peyton-Jones wrote: OK, OK, I yield! This message is about lexically scoped type variables. I've gradually become convinced that if you write f :: [a] - [a] f x = body then the type variable 'a' should be

Re: dummy variables

2004-12-29 Thread Keean Schupke
Except for GHC, where a variable staring with an '_' will not report a warning if it is unused in the body of a funtion: let _ = x in y -- no warning let result = x in y -- waring about result being unused let _result = x in y -- no warning, but variable can still be used. Keean.

Re: recursive group context bug?

2005-01-17 Thread Keean Schupke
You cannot sequence two operations from different monads... p has type: m (IO ()) id has type, IO () (in this case because this is what p returns)... You can do: p :: (Monad m) = m (IO ()) p = q = (\a - return a) Or p :: (Monad m) = m (IO ()) p = run q = id -- provided an overloaded

Re: recursive group context bug?

2005-01-17 Thread Keean Schupke
Got the wrong type sig there... p :: IO () p = run q = id Keean. ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: recursive group context bug?

2005-01-17 Thread Keean Schupke
. Tomasz Zielonka wrote: On Mon, Jan 17, 2005 at 09:52:18AM +, Keean Schupke wrote: You cannot sequence two operations from different monads... Note that this compiles: module Bug where p :: IO (); p = q = id; q :: (Monad m) = m (IO ()); q = return (return ()); -- the only

Re: recursive group context bug?

2005-01-17 Thread Keean Schupke
This must be a bug then, because the following works! y :: Num a = a y = fromIntegral (y::Int) A simpler example might be: x :: Int x = y y :: Num a = a y = fromIntegral x I have not studied the report to see if this should be legal. ___

Re: Contents of Glasgow-haskell-users Digest, Vol 17, Issue 8

2005-01-18 Thread Keean Schupke
Jost Berthold wrote: In order to force the *complete* evaluation of your result, you could use Evaluation Strategies. Strategies are a concept introduced for increasing parallelism in Glasgow parallel Haskell. Parallelism and lazy evaluation are in a way contrary aims, since you want your parallel

Re: Contents of Glasgow-haskell-users Digest, Vol 17, Issue 8

2005-01-18 Thread Keean Schupke
Jost Berthold wrote: execution unit to do something more useful. Yes: the compiler could do a strictness analysis and hopefully (safe analysis) tell wether neededList is needed by mungeForResult. In the case of algebraic data structures (like lists), things get a bit more complex (different

Implicit parameters:

2005-01-19 Thread Keean Schupke
Question regarding implicit parameters... The GHC manual says: Dynamic binding constraints behave just like other type class constraints in that they are automatically propagated. But the following code produces an error:

Re: Implicit parameters:

2005-01-19 Thread Keean Schupke
Yes, adding -fno-monomorphism-restriction allows the example to compile. I guess I got confused by the error message, expecting it to mention the monomorphism restriction directly... I'm sure it does sometimes. Any chance of improving the error message for this? Jorge Adriano Aires wrote: Isn't it

Re: Restricted Types and Infinite Loops

2005-02-18 Thread Keean Schupke
I seem to remember that if you define the class: class DictXMLData h = XMLData h ... instance (Data d a,XMLNamespace a) = XMLData d where ... then providing you annotate the instance functions with the relavent scoped type variables (d and a) then the compiler will infer XMLNamespace correctly for

Re: Restricted Types and Infinite Loops

2005-02-18 Thread Keean Schupke
Having looked at some of my source code this relies on Data having a functional dependancy such that: class Data d a | d - a ... So it might not work for what you want. Keean. Keean Schupke wrote: I seem to remember that if you define the class: class DictXMLData h = XMLData h ... instance

Re: GHC 6.4 release candidates available

2005-03-02 Thread Keean Schupke
In the past having: {-# OPTIONS -fallow-overlapping-instances #-} in a module was enough to get ghci to allow the overlaps. so we do: ghci Test.hs now it does not work (but it did in 6.3), but: ghci -fallow-overlapping-instances Test.hs does... Even it Test.hs is the top level module. Keean.

Re: GHC 6.4 release candidates available

2005-03-02 Thread Keean Schupke
with the instance decl, but it doesn't (yet). A good feature request. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Keean Schupke | Sent: 02 March 2005 17:20 | To: Simon Peyton-Jones | Cc: glasgow-haskell-users

Re: GHC 6.4 release candidates available

2005-03-04 Thread Keean Schupke
There can only be one top level module in ghci (there can only be one module name before the '' prompt - that modules options should be in effect. The whole point of putting options at the top of the source file is so that the user/compiler of the code does not need to know which specific options

Re: GHC 6.4 release candidates available

2005-03-04 Thread Keean Schupke
Simon Marlow wrote: On 04 March 2005 12:58, Keean Schupke wrote: There can only be one top level module in ghci (there can only be one module name before the '' prompt - that modules options should be in effect. No, you can have multiple top-level module scopes in effect. See the GHCi

Re: GHC 6.4 release candidates available

2005-03-04 Thread Keean Schupke
Further to my last point, what if the top level module is Main... ghci Main.hs and that includes a main function, and pragmas, so that main runs when ghci is finished loading (automatically). If main runs automatically then the context of ghci must be the Main module, so why would the options

Re: GHC 6.4 release candidates available

2005-03-07 Thread Keean Schupke
Simon Peyton-Jones wrote: I explained in an earlier message in this thread why the new behaviour was an accidental consequence of lazy reporting of overlapping instances. So, {-# OPTIONS -fanything except overlapping instances #-} works as expected, only overlapping instances is affected. I

Re: GHC 6.4 release candidates available

2005-03-07 Thread Keean Schupke
Simon Marlow wrote: On 04 March 2005 20:49, Keean Schupke wrote: Further to my last point, what if the top level module is Main... ghci Main.hs and that includes a main function, and pragmas, so that main runs when ghci is finished loading (automatically). GHCi doesn't run anything

Re: [Haskell] Haskell 6.4 perfomance

2005-03-24 Thread Keean Schupke
Think this should really go to glasgow-haskell-users... If this is true - how do I get ghc to use C--, and is it really faster than using gcc as a backend with all the bells whistles turned on (for a pentium-III) something like -O3 -mcpu=pentium3 -march=pentium3 -pipe -fomit-frame-pointer

Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Robert van Herk wrote: Hi all, I need to use duplicate instances. I read in the documentation on GHC 6.4, that overlapping class instances checks are lazy instead of gready in 6.4. However, my code still gives duplicate instance errors when compiling in GHC 6.4. Is the duplicate instance check

Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Keean Schupke wrote: Robert van Herk wrote: Hi all, I need to use duplicate instances. I read in the documentation on GHC 6.4, that overlapping class instances checks are lazy instead of gready in 6.4. However, my code still gives duplicate instance errors when compiling in GHC 6.4

Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
There was a typo in the code I posted: class Fail data This_should_never_happen should read: class Fail x data This_should_never_happen Keean. ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org

Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Just thought I ought to point out that all this is only necessary if the datasources may return different types... If you want them to return the same type you only need: instance (Datasource l k v,Datasource r k v) = Datasource (JoinedDS l r) k v ... As both datasources have the same key and

Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Robert van Herk wrote: Keean Schupke wrote: Just thought I ought to point out that all this is only necessary if the datasources may return different types... If you want them to return the same type you only need: instance (Datasource l k v,Datasource r k v) = Datasource (JoinedDS l r) k v

Re: moving from ghc-6.2 to 6.4

2005-03-29 Thread Keean Schupke
Thought I would run some benchmarks with different compiler options, so I pulled out some code (that compiled fine with 6.2). The code uses MArrays to calculate a tree difference between two different XML files. Anyway tying to compile with 6.4 I get: ghc-6.3: panic! (the `impossible'

Re: Oops [Fwd: Re: Allowing duplicate instances in GHC 6.4]

2005-03-31 Thread Keean Schupke
Robert van Herk wrote: Sorry, this is the compiler error I get: No instances for (KeyHasValue MyKeyVal k' v', Datasource.Tools.FakePrelude.TypeEq Float k' z, Datasource' z [MyKeyVal] [MyKeyVal] Float Int) When I am trying to do do { createJoinedDS' x x;

Re: Oops [Fwd: Re: Allowing duplicate instances in GHC 6.4]

2005-03-31 Thread Keean Schupke
Some more fixes... Keean Schupke wrote: Hi Keean, First of all, thank you for your answers. I have tried your solution using TypeEq. instance (Datasource l k' v', TypeEq k k' z, Datasource' z l r k v) = Datasource (JoinedDS l r) k v where _dsread (JoinedDS refl refr) k = do { l - readIORef

Re: Oops [Fwd: Re: Allowing duplicate instances in GHC 6.4]

2005-03-31 Thread Keean Schupke
Not at all... You can have Datasource s k v | s k - v ... but I have't time to do it now... By the way that wasn't the change I was talking about! class Datasource' z l r k v | z l r k - v The 'z' was missing from your fundep. Keean. Robert van Herk wrote: See change above! Also note type of

Re: Oops [Fwd: Re: Allowing duplicate instances in GHC 6.4]

2005-03-31 Thread Keean Schupke
In the case where a datasource is determined by 's' and 'k', we need to return a different type depending on sucess or failure: data TJust t = TJust t data TNothing = TNothing class Datasource s k v | s k - v where dsread :: s - k - v instance (Datasource l k v',Datasource r k

Re: Functional dependencies, principal types, and decidable typechecking

2005-04-06 Thread Keean Schupke
Manuel M T Chakravarty wrote: I accept that this is the process by which GHC computes these types, but it does violate the principal types property, doesn't it? The relation Int - () = forall c. Int - c does not hold. I realise that principal types and principal typings are slightly

using the Intel compiler (icc)

2005-06-05 Thread Keean Schupke
Is it possible to get GCC to use the intel C compiler (ICC) instead of gcc? Keean. ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: using the Intel compiler (icc)

2005-06-05 Thread Keean Schupke
Sorry, yes I mean getting GHC to use ICC instead of GCC... is it just a matter of a command line switch to give GHC the path to the compiler? Keean. Seth Kurtzberg wrote: Keean Schupke wrote: Is it possible to get GCC to use the intel C compiler (ICC) instead of gcc? Do you mean

Re: Functional Dependencies

2005-08-16 Thread Keean Schupke
Picked up on this late... I have working examples of add etc under ghc/ghci... I can't remeber all the issues involved in getting it working, but I can post the code for add if its any use? Keean. Dirk Reckmann wrote: Am Donnerstag, 11. August 2005 11:41 schrieb Simon Peyton-Jones:

GHCI and archive libraries.

2005-12-03 Thread Keean Schupke
GHCI does not load archive libraries. Is it possible (easy?) to get it to load (.a) archive libraries as well as .o and .so files? The problem is some optimized cblas libraries are not available as shared libraries due to the performace loss. Regards, Keean.

Re: GHCI and archive libraries.

2005-12-04 Thread Keean Schupke
Thaks guys... I realise it is a simple matter of unpacking the object files, however when using ghci for prototyping, it can be more convenient to have all the '.o's packed into a '.a'. As it is a simple matter to extract the .o files from the .a, I would have thought a fairly small change to

Re : Extensible records in Haskell

2002-11-06 Thread Keean Schupke
a type encompassing all the built in types and then simply use a list of this type to achieve what you need. Obviously the more specialised the type you use the less cases you have to deal with, and so there is less chance of making an error. Regards, Keean Schupke. Nicolas Oury wrote

Re: Re: Extensible records in Haskell

2002-11-07 Thread Keean Schupke
Thanks, have read the paper, however also saw the paper by Simon Peyton-Jones and Mark Jones on Lightweight Extensible Records for Haskell, which I think Simon refered to in an earlier post... would it not be better to have this instead? Regards, Keean Schupke. Alastair Reid wrote

Re: readping fd's and flushing buffers

2003-01-09 Thread Keean Schupke
? Regards, Keean Schupke. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

signal masks and garbage collection.

2003-01-10 Thread Keean Schupke
(or a way of setting the signal mask of the garbage collector whilst running). Any ideas? Regards, Keean Schupke. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: Avoiding No explicit method ... warnings

2003-01-21 Thread Keean Schupke
I think if you define a default method in the class definition you will not get this message - the default one can do nothing. Regards, Keean Schupke George Russell wrote: This isn't a bug, just a suggestion. It's not even a very important suggestion, but one that might be worth

Re: MArray and runST

2003-02-13 Thread Keean Schupke
, Keean Schupke. Simon Marlow wrote: However the problem comes when I try and use runST to run it... runMatrix :: Array (Int,Int) Int runMatrix = runST $ wrapper This is becase 's' escapes Expected: ST s a - b Inferred: (forall s1. ST s1 a) - a Delete the dollar? Cheers, Simon

fix missing from 5.04.3 ???

2003-03-12 Thread Keean Schupke
in a production server, what happened - does this cause problems in other places? Regards, Keean Schupke. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

DuplexHandle finalizer fix missing...

2003-03-13 Thread Keean Schupke
(appologies if this is a repeat) Hi, I have also noticed the fix for DuplexHandle finalizers is not in this release, I believe the finalizer should be attached to the write side (which is pointed to by the read side) but its still attached to the read side as in previous versions... Once

Handle finalizer fix missing too...

2003-03-13 Thread Keean Schupke
handles... Keean Schupke ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: DuplexHandle finalizer fix missing...

2003-03-14 Thread Keean Schupke
that they will (hopefully) make it into the next rev. Keean Schupke Simon Marlow wrote: I have also noticed the fix for DuplexHandle finalizers is not in this release, I believe the finalizer should be attached to the write side (which is pointed to by the read side) but its still attached to the read

Re: Dynamic Compilation

2003-06-11 Thread Keean Schupke
into an application, although I haven't looked at the interface. Regards, Keean Schupke. Carsten Schultz wrote: Hallo, Ghci and Template Haskell show that it is possible to compile and load a module into a running program. Is there a user interface to do that? Would one be possible? Would that make

Re: Query regarding GHC handling of overlapping instances.

2003-09-12 Thread Keean Schupke
Thanks, I think I was just confused... (and other types elsewhere may have been interfearing)... there still seems something not quite right... If I add the following definiton to the test code: instance Test (a - m b) (m b) where test _ _ = Third then I add the following print:

Re: Type reps inside GHC...

2004-09-03 Thread Keean Schupke
Erm just thought isnt this precisely where having a 'kind' definition would be useful... so we can specify which types are valid by membersip of a kind... (with reference to Simon PJs post about a 'kind' statement) Playing with HsSyn types (like HsModule)... I have got down to the definition level

Re: deriving...

2004-10-13 Thread Keean Schupke
Yes, I could quite easily write the generator in TemplateHaskell (have played with it before) _but_ I don't like the $(xxx) syntax... Perhaps if Simon could be persuaded to allow deriving clauses to be defined in TH? data X x = X x $(deriveMyClass (reify X)) could perhaps be defined from data X