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 the ghci code would have enabled using archive 
libraries. I think this change would aid usability. I don't know the 
ghci code at all, so it would take me a long time to make this change, 
as I would first have to understand the existing code. I was wondering 
if anyone familier with the ghci code could add archive library support? 
I suppose as a work around I could write a wrapper for ghci that 
extracts the .o files from the .a to a temp directory, and then calls 
ghci with the .o files on the command line.


   Regards,
   Keean.

Sven Panne wrote:


Am Samstag, 3. Dezember 2005 15:17 schrieb Lennart Augustsson:
 


And on many platforms (well, at least a few years ago) a "shared"
library doesn't have to be PIC.  The dynamic loader can do relocation
when it loads the file.  (Then it can't be shared.)

But this was a few years ago on Solaris and BSDs, it could be
different now.
   



After a quick look this seems to be the case on current x86 Linux systems, 
too: "Real" shared libraries consist of PIC to enhance sharing code at 
runtime, but nevertheless the dynamic loader seems to be able to load and 
relocate non-PIC, at the cost of less sharing, but often slightly better code 
quality. So the mentioned repacking of a static library into a partially 
linked object file might work for most common platforms.


Cheers,
  S.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Functional Dependencies

2005-08-16 Thread Keean Schupke
Attached are 3 Haskell modules used for type level programming. These 
were developed as background work for the HList paper, but are not in 
the final libraries as they are 'off topic' as it were. They were 
however useful in testing type-level programming concepts.


Control.hs - This contains type level control structures like 'apply' 
which is like Prolog's apply.

Logic.hs - This contains a Modal logic designed for type level computation:

   data AllTrue = AllTrue
   data SomeTrue = True | NotTrue
   data SomeFalse = False | NotFalse
   data AllFalse = AllFalse

Peano.hs - Contains type level numeric operators and constants, this is 
the bit you are interested in, but its implementation depends on the 
other modules... for example equality requires the type-level logic, and 
division, foldN and reify require Control constructs to work.


run like this:

ghci Lib/TIR/Peano.hs

   *Lib.TIR.Peano> :t three
   three :: Three
   *Lib.TIR.Peano> :t nine
   nine :: Nine
   *Lib.TIR.Peano> add three nine
   12
   *Lib.TIR.Peano> :t (add three nine)
   (add three nine) :: Suc (Suc (Suc (Suc Eight)))

The general 'trick' if you will is to imlement each funtion as a type 
class, pattern matching the

types to instances in a type-level analogue of the value level function.

Regards,
   Keean.


Dirk Reckmann wrote:


Hello Keean!

Am Dienstag, 16. August 2005 13:48 schrieb 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?
   



Yes, that would be nice. I'd like to see 'add' working... However, after each 
answer to my posting, I get more confused. Simon Peyton-Jones took all of my 
hope to get it working, because ghc doesn't like universal quantified but 
uniquely idetified types (at least, this is my understanding of his email). 
Now you have a working 'add' typelevel program. And the most confusing part 
for me is, that my fibonacci number program works, even though it makes use 
of the not working version of add.


So, I'm really looking forward to your version!

Ciao,
 Dirk
 





tir.tgz
Description: application/compressed-tar
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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:
 


You raise a vexed question, which has been discussed a lot.  Should this
typecheck?

class C a b | a -> b
instance C Int Bool

f :: forall a. C Int a => a -> a
f x = x

GHC rejects the type signature for f, because we can see that 'a' *must
be* Bool, so it's a bit misleading to universally quantify it.
   



Ok, maybe this is a reasonable choice. But why does the attached program work? 
ghci presents a unique type for the universal quantified function 'eight':


*Add> :t eight
eight :: Succ (Succ (Succ (Succ (Succ (Succ (Succ (Succ Zero)))

Best regards,
 Dirk

 


Simon

| -Original Message-
| From: [EMAIL PROTECTED]

[mailto:glasgow-haskell-users-

| [EMAIL PROTECTED] On Behalf Of Dirk Reckmann
| Sent: 21 July 2005 10:30
| To: glasgow-haskell-users@haskell.org
| Subject: Functional Dependencies
|
| Hello everybody!
|
| I wanted to have some fun with functional dependencies (see
| http://www.cs.chalmers.se/~hallgren/Papers/wm01.html), and tried some
| examples from this paper as well as some own experiments. The idea is

to use

| the type checker for computations by "abuse" of type classes with

functional

| dependencies.
|
| The example in the attached file is taken from the above paper. Due to

the

| functional dependencies, I expected the type of seven to be uniquely
| determined to be (Succ (Succ (Succ ...))), i. e. seven, but ghc

(version 6.4)

| gives me following error message:
|
| Add.hs:14:0:
| Couldn't match the rigid variable `a' against `Succ s'
|   `a' is bound by the type signature for `seven'
|   Expected type: Succ s
|   Inferred type: a
| When using functional dependencies to combine
|   Add (Succ n) m (Succ s), arising from the instance declaration

at

| Add.hs:11:0
|   Add (Succ (Succ (Succ Zero))) (Succ (Succ (Succ (Succ Zero

a,

| arising from the type signature for `seven' at Add.hs:13:0-77
| When generalising the type(s) for `seven'
|
| However, using the definition of Add to define Fibonacci numbers does

work,

| and a similar function declaration can be used to compute numbers by

the type

| checker.
|
| The same definition of Add works in Hugs...
|
| So, is this a bug in ghc, or am I doing something wrong?
|
| Thanks in advance,
|   Dirk Reckmann
   




{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

module Add where

data Zero
data Succ n

class Add n m s | n m -> s

instance Add Zero m m
instance Add n m s => Add (Succ n) m (Succ s)

class Fib n f | n -> f

instance Fib Zero (Succ Zero)
instance Fib (Succ Zero) (Succ Zero)
instance (Fib n fib_n,
 Fib (Succ n) fib_s_n,
 Add fib_n fib_s_n sum
) => Fib (Succ (Succ n)) sum

eight :: Fib (Succ (Succ (Succ (Succ (Succ Zero) n => n
eight = undefined
   




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
   



___
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
Yes, thats exactly what I mean. Can I switch the compiler to use with a
command line switch? ICC is compatible with GCC and can use the same
libraries. The main advantage is the automatic vectorisation of loops,
to use SSE / MMX.

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 is it possible to get /GHC/ to use /ICC/?  Otherwise I
> don't understand the question.


___
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 is it possible to get /GHC/ to use /ICC/?  Otherwise I
> don't understand the question.
>
>>Keean.
>>___
>>Glasgow-haskell-users mailing list
>>Glasgow-haskell-users@haskell.org
>>http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>
>>  
>>
>

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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: 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 
different, but I was
wondering if the fact that it has recently been shown that 
Hindley/Milner does not
have principal typings has any meaning here?

Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 v'',Datasource' v' v'' v)
>=> Datasource (JoinedDS l r) k v where
>dsread (JoinedDS l r) k =  dsread' (dsread l k) (dsread r k)
>
>class Datasource' l r v | l r -> v where
>dsread' :: l -> r -> v
>instance Datasource' TNothing TNothing TNothing where
>dsread' _ _ = TNothing
>instance Datasource' (TJust l) TNothing (TJust l) where
>dsread' t _ = t
>instance Datasource' TNothing (TJust r) (TJust r) where
>dsread' _ t = t
>instance Datasource' (TJust l) (TJust r) TNothing where
>dsread' _ _ = TNothing
Now all you need to do is arrange for individual datasources to
return (TJust v) if that combination of source and key exist and
TNothing if they dont. Something like:
>instance Datasource Source1 Key1 (TJust Value1)
>instance Datasource Source1 Key2 TNothing
>
>instance Datasource Source2 Key1 TNothing
>instance Datasource Source2 Key2 (TJust Value2)
This is a simple implementation, using TypeEq, you can generically
reject with TNothing all datasource instances not specifically defined.
   Keean.
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 refl;
   r <- readIORef 
refr; 
   (z,l,r,v) <- _dsread' (l,r) k;
   writeIORef refl l;
   writeIORef refr r;
   return (JoinedDS refl refr, v);
 }

class Datasource' z l r k v | l r k -> v where
 _dsread'  :: (l,r) -> k -> IO (z,l,r,Maybe v)
 _dswrite' :: (l,r) -> k -> v -> IO (z,l,r)
instance Datasource l k v => Datasource' HTrue  l r k v where
 _dsread' (l,r) k = do { (l,v) <- _dsread l k;
 return (hTrue, l, r, v);
   }
instance Datasource r k v => Datasource' HFalse l r k v where
 _dsread' (l,r) k = do { (r,v) <- _dsread r k;
 return (hFalse, l, r, v);
   }
This compiles.
I cannot, however, include type z in the fundep of Datasource', since 
this conflicts with Datasource ds k v | ds k -> v. Furthermore, I do 
not understand how the key and value types of my right datasource (r k 
v) is bound to the instance of Datasource (JoinedDS l r) k v, since in 
the premisse (Datasource l k' v', TypeEq k k' z, Datasource' z l r k 
v), nothing is said about Datasource r k'' v''. However, I could be 
wrong in this, since Datasource r k v is in the premisse of instance 
Datasource r k v => Datsource' HFalse l r k v.

However, my problem is, that when I use this code:
do {joined <- createJoinedDS' x y;
 (joined,(v::Maybe Int)) <- _dsread joined (2.0::Float);
}
{- | Easy constructor -}
createJoinedDS :: (IORef left) -> (IORef right) -> JoinedDS left right
createJoinedDS left right = JoinedDS left right
createJoinedDS' :: left -> right -> IO (JoinedDS left right)
createJoinedDS' l r = do { left <- newIORef l;
  right <- newIORef r;
  return (createJoinedDS left right);
}
the compiler will complain:
 Could not deduce (Datasource' z1 l r k v)
 from the context (Datasource (JoinedDS l r) k v,
   Datasource l k' v',
   TypeEq k k' z,
   Datasource' z l r k v)
 arising from use of `_dsread''
It seems to be the case that it cannot decide on the type of z.
Would you know how to solve this?
Regards,
Robert
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 fundep for Datasource should now be:
class Datasource s k v | s -> k v where ...

I see But the cool thing was, that my datasources were generic, in 
the sence that they could store multiple k's and v's. Now, they would 
be unique for the actual storage mechanism used, meaning, for example, 
that I could only read values from 1 table, if I'd instantiate the 
datasource for a database coupling.

Currently, I use the Boilerplate approach to make it possible to store 
multiple types in one datasource, for example:

data MyKeyVal = IntXString Int String
| FloatXInt  Float Int
deriving (Eq, Ord, Show)
Furthermore, I generate an instance of KeyHasValue, to tell my 
framework which keys are valid for a datasource, for example:

instance KeyHasValue MyKeyVal Int String where
constructor = IntXString
instance KeyHasValue MyKeyVal Float Int where
constructor = FloatXInt
I have an instance
instance (..., KeyHasValue a k v) =>
Datasource [a] k v where ...
This way, I can read Ints from a [MyKeyVal], and get a String, and 
read Floats, and get an Int. If I would have a fundep
class Datasource s k v | s -> k v where ...

this wouldn't be possible anymore, I guess?
Regards,
Robert
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 refl;
   r <- readIORef 
refr; 
   (z,l,r,v) <- _dsread' (l,r) k;
   writeIORef refl l;
   writeIORef refr r;
   return (JoinedDS refl refr, v);
 }

   _dsread (JoinedDS l r) k = _dsread' (typeEq (undefined::k') k) l r k
class Datasource' z l r k v | l r k -> v where

class Datasource' z l r k v | z l r k -> v where
 _dsread'  :: (l,r) -> k -> IO (z,l,r,Maybe v)
 _dswrite' :: (l,r) -> k -> v -> IO (z,l,r)
instance Datasource l k v => Datasource' HTrue  l r k v where
 _dsread' (l,r) k = do { (l,v) <- _dsread l k;
 return (hTrue, l, r, v);

The type says the return type of Datasource' is v where v is the type 
resturned from _dsread so:

  _dsread' _ (l,r) k = _dsread l k
The types are determined by the instance... (I don't understand why you 
are trying to return
hTrue

   _dsread :: s -> k -> v
and for Datasource'
   _dsread :: z -> l -> r -> k -> v
   }
instance Datasource r k v => Datasource' HFalse l r k v where
 _dsread' (l,r) k = do { (r,v) <- _dsread r k;
 return (hFalse, l, r, v);
   }
This compiles.
I cannot, however, include type z in the fundep of Datasource', since 
this conflicts with Datasource ds k v | ds k -> v. Furthermore, I do 
not understand how the key and value types of my right datasource (r 
k v) is bound to the instance of Datasource (JoinedDS l r) k v, since 
in the premisse (Datasource l k' v', TypeEq k k' z, Datasource' z l r 
k v), nothing is said about Datasource r k'' v''. However, I could be 
wrong in this, since Datasource r k v is in the premisse of instance 
Datasource r k v => Datsource' HFalse l r k v.

However, my problem is, that when I use this code:
do {joined <- createJoinedDS' x y;
 (joined,(v::Maybe Int)) <- _dsread joined (2.0::Float);
}
{- | Easy constructor -}
createJoinedDS :: (IORef left) -> (IORef right) -> JoinedDS left right
createJoinedDS left right = JoinedDS left right
createJoinedDS' :: left -> right -> IO (JoinedDS left right)
createJoinedDS' l r = do { left <- newIORef l;
  right <- newIORef r;
  return (createJoinedDS left right);
}
the compiler will complain:
 Could not deduce (Datasource' z1 l r k v)
 from the context (Datasource (JoinedDS l r) k v,
   Datasource l k' v',
   TypeEq k k' z,
   Datasource' z l r k v)
 arising from use of `_dsread''
It seems to be the case that it cannot decide on the type of z.
See change above!
Also note type of fundep for Datasource should now be:
class Datasource s k v | s -> k v where ...
   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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;
 (joined,(v::Maybe Int)) <- _dsread joined (2.0::Float);
  }
Robert

Subject:
Re: Allowing duplicate instances in GHC 6.4
From:
Robert van Herk <[EMAIL PROTECTED]>
Date:
Thu, 31 Mar 2005 16:49:07 +0200
To:
glasgow-haskell-users@haskell.org
To:
glasgow-haskell-users@haskell.org
Return-Path:
<[EMAIL PROTECTED]>
X-Original-To:
[EMAIL PROTECTED]
Delivered-To:
[EMAIL PROTECTED]
Received:
from mail.students.cs.uu.nl (localhost.localdomain [127.0.0.1]) by 
mail.students.cs.uu.nl (Postfix) with ESMTP id 85339225D8C for 
<[EMAIL PROTECTED]>; Thu, 31 Mar 2005 16:54:12 +0200 (CEST)
Received:
from mail.cs.uu.nl (dusk.cs.uu.nl [131.211.80.10]) by 
mail.students.cs.uu.nl (Postfix) with ESMTP id 68C95225D84 for 
<[EMAIL PROTECTED]>; Thu, 31 Mar 2005 16:54:12 +0200 (CEST)
Received:
by mail.cs.uu.nl (Postfix) id EF0D9A35E2; Thu, 31 Mar 2005 16:54:11 
+0200 (CEST)
Delivered-To:
[EMAIL PROTECTED]
Received:
from mail.cs.uu.nl (localhost.localdomain [127.0.0.1]) by 
mail.cs.uu.nl (Postfix) with ESMTP id D9C06A35F7; Thu, 31 Mar 2005 
16:54:11 +0200 (CEST)
Received:
from www.haskell.org (bugs.haskell.org [128.36.229.215]) by 
mail.cs.uu.nl (Postfix) with ESMTP id 99FA2A35E2; Thu, 31 Mar 2005 
16:54:11 +0200 (CEST)
Received:
from haskell.cs.yale.edu (localhost.localdomain [127.0.0.1]) by 
www.haskell.org (Postfix) with ESMTP id 666A436825E; Thu, 31 Mar 2005 
09:36:48 -0500 (EST)
X-Original-To:
glasgow-haskell-users@haskell.org
Delivered-To:
glasgow-haskell-users@haskell.org
Received:
from mail.cs.uu.nl (dusk.cs.uu.nl [131.211.80.10]) by www.haskell.org 
(Postfix) with ESMTP id 3A87D368106 for 
; Thu, 31 Mar 2005 09:36:45 -0500 
(EST)
Received:
from mail.cs.uu.nl (localhost.localdomain [127.0.0.1]) by 
mail.cs.uu.nl (Postfix) with ESMTP id 16C67A35F7; Thu, 31 Mar 2005 
16:54:05 +0200 (CEST)
Received:
from [131.211.84.110] (mckroket.labs.cs.uu.nl [131.211.84.110]) by 
mail.cs.uu.nl (Postfix) with ESMTP id 0635AA35E2; Thu, 31 Mar 2005 
16:54:05 +0200 (CEST)
Message-ID:
<[EMAIL PROTECTED]>
User-Agent:
Mozilla Thunderbird 1.0 (Macintosh/20041206)
X-Accept-Language:
en-us, en
MIME-Version:
1.0
References:
<[EMAIL PROTECTED]> <[EMAIL PROTECTED]> 
<[EMAIL PROTECTED]> <[EMAIL PROTECTED]> 
<[EMAIL PROTECTED]> <[EMAIL PROTECTED]>
In-Reply-To:
<[EMAIL PROTECTED]>
Content-Type:
text/plain; charset=ISO-8859-1; format=flowed
Content-Transfer-Encoding:
7bit
X-AV-Checked:
ClamAV using ClamSMTP at cs.uu.nl
X-BeenThere:
glasgow-haskell-users@haskell.org
X-Mailman-Version:
2.1.5
Precedence:
list
List-Id:
The Glasgow Haskell Users Mailing List 

List-Unsubscribe:
<http://www.haskell.org/mailman/listinfo/glasgow-haskell-users>, 
<mailto:[EMAIL PROTECTED]>
List-Archive:
<http://www.haskell.org//pipermail/glasgow-haskell-users>
List-Post:
<mailto:glasgow-haskell-users@haskell.org>
List-Help:
<mailto:[EMAIL PROTECTED]>
List-Subscribe:
<http://www.haskell.org/mailman/listinfo/glasgow-haskell-users>, 
<mailto:[EMAIL PROTECTED]>
Sender:
[EMAIL PROTECTED]
Errors-To:
[EMAIL PROTECTED]
X-AV-Checked:
ClamAV using ClamSMTP at cs.uu.nl
X-AV-Checked:
ClamAV using ClamSMTP at students.cs.uu.nl
X-Spam-Checker-Version:
SpamAssassin 3.0.2-hvl (2004-11-16) on dawn.students.cs.uu.nl
X-Spam-Status:
No, score=-0.7 required=7.0 tests=AWL autolearn=ham version=3.0.2-hvl

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 refl;
   r <- readIORef 
refr; 
   (z,l,r,v) <- _dsread' (l,r) k;
   writeIORef refl l;
   writeIORef refr r;
   return (JoinedDS refl refr, v);
 }

class Datasource' z l r k v | l r k -> v where
class Datasource' z l r k v | z l r k -> v where
 _dsread'  :: (l,r) -> k -> IO (z,l,r,Maybe v)
 _dswrite' :: (l,r) -> k -> v -> IO (z,l,r)
instance Datasource l k v => Datasource' HTrue  l r k v where
 _dsread' (l,r) k = do { (l,v) <- _dsread l k;
 return (hTrue, l, r, v);
   }
instance Datasource r k v => Datasource' HFalse l r k v where
 _dsread'

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' happened, GHC version 6.3):
>app_match: unbound tpl s{tv a2M9}
>
>Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
Any idea how to track down the cause of this?
   Keean.
Simon Marlow wrote:
On 29 March 2005 08:59, Johannes Waldmann wrote:
 

I am trying to bring a larger heap of code
(http://141.57.11.163/auto/ ) into 6.4 land (because of wonder
stories about faster compilation, faster execution, Data.Map, and so
on ...) 
Here are a few observations and questions
that may be useful to others as well.

* what is the situation with ghc-6.4 for sparc/solaris?
  I don't see a binary package in the download area.
  I started to build from source - can this be successful?
  (The rest of this report refers to i386/linux)
   

There are some outstanding issues on Sparc/Solaris that I didn't get
around to investigating before the release.  One of them is a random
crash, so you should probably consider 6.4 to be broken on Sparc/Solaris
for the time being (it might be related to gcc version though: 6.2.x
might be just as broken with recent gcc versions).  I'm keen to get more
data points, if you have the time & inclination to test it.
We could really do with a Sparc/GHC guru to take up the mantle of
maintaining the Sparc port - it's kind of hard for us to do it without
the hardware locally, and I'm no Sparc expert.
 

* Cabal is very nice! - The only thing that was confusing me
  is that I have to list all modules in the *.cabal file:
  if I don't, it still happily builds and installs the package
  but it cannot be used, giving linker errors. Couldn't this be
  checked earlier? Or better, couldn't it infer the needed
  hidden modules? Anyway I can generate the module list by a shell
  script but that does not feel right. - How do I build and install
  a profiling version of a package, how does Cabal support this?
   

The module list: yes, I think this is something the Cabal team would
like to automate in the future.  There's no way to build profiled
packages at the moment, as far as I'm aware.  I agree it's an important
feature, though.
 

* I don't see "dramatic" improvements in execution times -
  are there some magic ghc options I missed? I used -O -fvia-C.
  Still, executables are maybe 2 .. 5 % smaller and faster than they
  were with 6.2 - and compilation without -O is really fast.
   

I don't know where this rumour of dramatic improvements in execution
time comes from :-)  Our testing shows modest improvements in most
programs, with some programs going slower.  The focus of 6.4 wasn't
really on performance, but we hope to merge performance improvements
back into future 6.4 releases.
Cheers,
	Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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

As both datasources have the same key and value types, you then 
choose which 'v' to return at the value level.

Nono, the datasources I have implemented are a type safe means to 
extract (key,value) pairs from a data store. The idea is that this 
way, in a type safe fashion, e.g. database access can be abstract.

I use HaskellDB as the database access layer, and then define a 
datasource instance for any given database, so that the user does not 
need to think about the details of the actual database access: he can 
just read and write from the datasource, and the datasource will make 
sure the actual queries will be executed.

My idea now was that if I have 2 databases, and I construct 
datasources for them, it would be really cool if I was able to unite 
them, so that the programmer in the end could talk two 1 datasource, 
that allowed for accessing the 2 databases at one entry point. This 
was what I was making the JoinedDS for.

So, suppose I have 2 datasources for two different databases. One may 
have keys:
data KeysOfDS1 = KDB1_Table1 Int
   |  KDB1_Table2 Int

and values
data ValuesOfDS1 = VDB1_Table1 (Int,Int,String)
   | VDB2_Table2 (Int,Int,String)
and the other one:
data KeysOfDS2 = KDB2_Table1 String
   |  KDB2_Table2 String
data ValuesOfDS2 = VDB2_Table1 (String, Float)
   | VDB2_Table2 (String, Float, Int)
Now, these datastructures correspond to the actual tables in the 
database. My toolset will generate datasources for these types, thus 
we have instances:

instance Datasource Database1 KeysOfDS1 ValuesOfDS1
instance Datasource Database2 KeysOfDS2 ValuesOfDS2
and the cool thing would be, to combine these two datasources at a 
higher level in my datasources graph, so that I would have 1 
datasource that found out by itself which actual datasource to use, thus:

x::JoinedDS
x = JoinedDS  db1 db2 -- where dbx is a datasource Databasex KeysOfDSx 
ValuesOfDSx

Now, I would want the user to be able to read both KeysOfDS1 (which 
would yield a ValuesOfDS1) as well as KeysOfDS2 (which would yield a 
ValuesOfDS2) from x.

Herefore, I need the instances mentioned before:
instance (Datasource l k v) => Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) => Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)
But this, thus, yields duplicate instance errors, which I don't like :-).
Robert
P.S. Sorry for any typos, I am enjoying a rather nice bottle of wine :-).
Thats because they overlap in 'k'. However you can change the fundep:
>class Datasource s k v | s -> k v
>instance Datasource DB1 K1 V1
>instance Datasource DB2 K2 V2
>instance (Datasource l k' v',TypeEq k k' z,Datasource' z l r k v) => 
Datasource (JoinedDS l r) k v where
>
>class Datasource' z l r k v | z l r -> k v
>instance Datasource l k v => Datasource' TTrue l r k v
>instance Datasource r k v => Datasource' TFalse l r k v

Here I have used TypeEq from the HList library to determine if the type 
parameter k is the same type as the k' from datasource l. This lets k 
determine which instance from the other class gets used.

   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 value types, you then choose 
which 'v' to return at the value level.

I am not sure whether you intended Datasources to contain heterogeneous 
key or value types, and whether the loolup is supposed to be value or 
type driven. My original answer assumed a single Datasource contains 
values of different types, selected by the type of the key...

   Keean.

Robert van Herk wrote:
Yes, but this is not what I want. I want to be able to give a key that 
either the left or the right data source would take, and then return 
the appropriate value. Thus: if I pass it a key that would normally go 
into l, I want the value l returns me to be returned, and if I pass it 
the key that would normally go into r, I want to return the value r 
returns me.

The datasource class has a function dsread :: ds -> k -> (ds, v) -- 
read may have a side effect
Thus I want want to do something like:
instance (Datasource l k v) => Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) => Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)

It would be perfectly okay to me when the compiler would complain if 
the key and value that go into l and r are the same, but for any 
useful purpose I can think of (e.g. glueing two database couplings 
together, since I also made a Datasource instance for database 
access), this will not happen and the duplicate instances should not 
really occur, since the context of the instances makes sure only 1 
will be possible.

However, GHC only looks at the RHS (thus: Datasource (JoinedDS l r) k 
v) and then decides that both instances are the same.

So, my question was: how to overcome this.
Thanks,
Robert

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource 
allows the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) => Datasource (JoinedDS left right) k 
v where
...

instance (Datasource right k v) => Datasource (JoinedDS left right) k 
v where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of 
(key,value) pairs, so the duplicate instances will not occur and when 
they do, this will be by mistake. Hence, the two premisses in the 
instance declaration will never be fulfilled both at the same time 
and I do not want a duplicate instance error here.

Is there a  solution to this problem?
To resolve overlap the HEAD of the instance must be different... Might 
I suggest:

-- as value depends on source and key, requires functional dependancy
class Datasource s k v | s k -> v ...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,Datasource r k v2) => Datasource (JoinedDS 
l r) k (v1,v2) ...

Now a joined datasource resturns a pair of values instead of a single 
value.

 
Further to this to get the exact behaviour you want, if a datasource can 
return the result using a type lifted maybe on a lookup failure then:

>class Datasource s k v | s k -> v ...
>data JoinedDS l r = JoinedDS l r
>instance (Datasource l k v1,
>Datasource r k v2,
>JoinDS v1 v2 v) => Datasource (JoinedDS l r) k v
>
>class Fail
>data This_should_never_happen
>
>data TNothing = TNothing
>data TJust a = TJust a
>
>class JoinDS l r t | l r -> t
>instance JoinDS TNothing TNothing TNothing
>instance JoinDS TNothing (TJust v) (TJust v)
>instance JoinDS (TJust u) TNothing (TJust u)
>instance Fail This_should_never_happen => JoinDS (TJust u) (TJust v) 
TNothing

Now you datasources just need to return the type "TJust v" on success 
and TNothing on failure.

   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource 
allows the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) => Datasource (JoinedDS left right) k v 
where
...

instance (Datasource right k v) => Datasource (JoinedDS left right) k 
v where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of 
(key,value) pairs, so the duplicate instances will not occur and when 
they do, this will be by mistake. Hence, the two premisses in the 
instance declaration will never be fulfilled both at the same time and 
I do not want a duplicate instance error here.

Is there a  solution to this problem?
To resolve overlap the HEAD of the instance must be different... Might I 
suggest:

-- as value depends on source and key, requires functional dependancy
class Datasource s k v | s k -> v ...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,Datasource r k v2) => Datasource (JoinedDS l 
r) k (v1,v2) ...

Now a joined datasource resturns a pair of values instead of a single value.
   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 
-momit-leaf-frame-pointer -ftracer -fno-crossjumping -mfpmath=sse,387 
-ffast-math -fsched-spec-load -fprefetch-loop-arrays 
-maccumulate-outgoing-args -fmove-all-movables
-freduce-all-givs"

   Keean.
Alexandre wrote:
As I heard, 6.4 version of the Haskell using C-- backend and make lots 
of the resulting code perfomance (programs executed faster).
If so, does any test/comparison with other languages available?

Thank you in advance,
Regards,
/Alexandre.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 automatically.  Could you elaborate?
 

My mistake... It seems fine to call 'main' in a .hs file
which calls overlapping instances, so there appears to only
be an issue with interactive execution.
I guess this is not as serious as I thought, as runghc (which is
ghci that automatically calls Main.main right?) works fine.
   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 -f #-} works as expected,
only overlapping instances is affected.
I don't see why it requires a per-instance fix (although that would be 
nice).

If I start ghci with multiple source files:
ghci A.hs B.hs C.hs
we get:
*C>
as the prompt - in this case why not just let the options pragma's from 
'C.hs' be
in force in the interpreter. This fix is quick, and intuitive as the 
interpreter is telling
you what it thinks is the context.

Consider the situation where ghci is used as an embedded interpreter in 
another project. In the case where we do not know what options a given 
script may require.

The only other solution I can think of is to have a wrapper script:
   #!/bin/csh
   if (`grep '^{-# OPTIONS -fallow-overlapping-instances #-} $1` != "") 
then
   ghci_real -fallow-overlapping-instances $1
   else
   ghci_real $1
   endif

I suppose you could check all top level .hs files given on the command 
line for a more thorough check.

   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 pragmas not be in effect?
for example:
ghc -o test Main.hs
needs no flags and I can then run test with no flags (./test). But:
ghci Main.hs
Now all of a sudden you are telling me I need to provide command line
flags to get it to run (in the interpreter) but I do not need to if I use
the compiler... (remember this worked fine in 6.3 and 6.3 included the
new lazy instance overlap detection)
This seems very inconsistant to me... I really like the ability to put 
any flags code
might need into the source using the OPTIONS pragmas... but it seems to 
undermine
the usefulness of this if ghci ignores the flags.

Keean

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 documentation.
 

But I can also have just one top level module ...
Simon Marlow wrote:
   

I think GHC's behaviour is right here.  To use the flag settings from
the source module on the command-line would be wrong: for example,
when the module is compiled, its implementation (and therefore flag
settings) must be hidden. 

 

Requiring options on the command line exposes the implementation
I do not expect the GHCi user to be required to know which flags to
apply to get my code to run.
   

Why not?  You're providing a library which exports some instances.  If
overlapping instance resolution is required to resolve overloading in
code that uses the library, I want to know about it, and I don't want
the compiler to turn on overlapping instance resolution behind my back.
 

But what if it is an application and not a library... you definitely do 
not wantr to have to explain
in the user manual that ghci needs to be started with:

ghci -fglasgow-exts -fallow-overlapping-instances ...
Further more it is the _importing_ module that needs to have overlapping 
instances defined, therefore
there is absolutely no chance of them being turned on behind your back.

Importing a library should *not* affect how the code that imports it is
compiled, except in the ways you expect (bringing names and instances
into scope).
 

It would not... All I am saying is if the top level module in GHCi (the 
one named in the prompt)
has OPTIONS pagmas these should be in effect.

If you could specify overlapping on a per-instance basis, then that
would be a way around the problem.
 

This worked in all GHCi before 6.4 - so something has broken the (in mu 
opinion) correct
behavior. Was this a deliberate decision - or has something just changed 
without anyone
realising?

   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/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 are required.
If the code specifies "overlapping instances", I don't expext to have
to specify it on the command line as well.
Simon Marlow wrote:
I think GHC's behaviour is right here.  To use the flag settings from
the source module on the command-line would be wrong: for example, when
the module is compiled, its implementation (and therefore flag settings)
must be hidden.
 

Requiring options on the command line exposes the implementation
I do not expect the GHCi user to be required to know which flags to
apply to get my code to run.
Also, as Simon pointed out, there might be multiple modules in scope at
the prompt, so how do you resolve the flag settings if they're
contradictory?
 

Only the flags from the top level (the one named before the prompt)
would be in scope.
If I type:
ghci Test.hs
Then I would expect the options pragma in Test.hs to be in effect.
In general, flag settings affect the current source file only.  The flag
settings at the GHCi prompt are those given on the command line and from
:set - it's simple, no worrying about "where did that option come from?
I don't want overlapping instances!".
 

I really don't like GHCi users needing to know what flags they must
use to get code to work. There must be some way of code asserting
top level options.
If the options pragma cannot be used for this purpose I suggest there
should be another way for code to assert top level options of ghci... this
method should be in the source file so that extra options files are not
required...
Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-03-02 Thread Keean Schupke
Erm, what is the module context of GHCi? I thought ghci
used the context of the loaded module:
ghci Test.hs
*Test>
I though the 'Test' in the prompt indicated you were in the context of
the "Test" module. In which case the pragma at the top of the test
module should be in force?
   Keean.
Simon Peyton-Jones wrote:
Ah, yes.  In 6.2, overlap errors were checked and reported "eagerly" at
the instance declaration.  So
instance C Int a
instance C b Bool
was rejected.  Now it isn't.  Instead the program is only rejected if a
constraint arises that matches two instance decls, and neither is more
specific.  For example (C Int Bool)
But many constraints are fine e.g. C Int Char
However this does have the consequence that the overlapping-instance
flag must be on in the module that calls the function rather than the
one that defines the instances.   It'd be better if the info travelled
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@haskell.org
| Subject: Re: GHC 6.4 release candidates available
| 
| 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.
| 
| Simon Peyton-Jones wrote:
| 
| >Ralf
| >
| >You have a pragma "-fallow-overlapping-instances" in Test.hs, and
indeed
| >it is honoured when compiling Test.hs.  But it's not taken into
account
| >when compiling top-level expressions, or, indeed, if you were to
import
| >Test into another module.
| >
| >If you say ":set -falllow-overlapping-instances" it'll work fine.
| >
| >Now, maybe you'd like the flag to attach permanently to the
*instance*,
| >so that if an instance decl is compiled with
| >-fallow-overlapping-instances, then no complaint will ever be issued
for
| >its overlaps, even if it is imported into a module that doesn't have
| >-fallow-overlapping-instances.  That would make sense, I think, but
it's
| >not implemented and never has been.
| >
| >Simon
| >
| >| -Original Message-
| >| From: [EMAIL PROTECTED]
| >[mailto:glasgow-haskell-users-
| >| [EMAIL PROTECTED] On Behalf Of Ralf Lammel
| >| Sent: 02 March 2005 08:45
| >| To: glasgow-haskell-users@haskell.org
| >| Subject: RE: GHC 6.4 release candidates available
| >|
| >| I think this is an old bug,
| >| or at least I have seen it months back.
| >|
| >| The "overlapping instances" directive does not make it to the
| >top-level.
| >| See attached sample with the offending session.
| >|
| >| Thanks for fixing.
| >| Ralf
| >
| >___
| >Glasgow-haskell-users mailing list
| >Glasgow-haskell-users@haskell.org
| >http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
| >
| >
| 
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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.
Simon Peyton-Jones wrote:
Ralf
You have a pragma "-fallow-overlapping-instances" in Test.hs, and indeed
it is honoured when compiling Test.hs.  But it's not taken into account
when compiling top-level expressions, or, indeed, if you were to import
Test into another module.
If you say ":set -falllow-overlapping-instances" it'll work fine.
Now, maybe you'd like the flag to attach permanently to the *instance*,
so that if an instance decl is compiled with
-fallow-overlapping-instances, then no complaint will ever be issued for
its overlaps, even if it is imported into a module that doesn't have
-fallow-overlapping-instances.  That would make sense, I think, but it's
not implemented and never has been.  

Simon
| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Ralf Lammel
| Sent: 02 March 2005 08:45
| To: glasgow-haskell-users@haskell.org
| Subject: RE: GHC 6.4 release candidates available
| 
| I think this is an old bug,
| or at least I have seen it months back.
| 
| The "overlapping instances" directive does not make it to the
top-level.
| See attached sample with the offending session.
| 
| Thanks for fixing.
| Ralf

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 (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 those instances that use it from the XMLData constraint.
   Keean.
Simon David Foster wrote:
On Fri, 2005-02-18 at 02:18 +0100, Ralf Laemmel wrote:
 

Here I assume that you don't _really_ depend on ClassB to be a 
superclass of ClassA. (Why would you?)
  

Ok, here's what the real class head is (or was before I butchered it to
make it work);
class (Data (DictXMLData h) a, XMLNamespace a) => XMLData h a where
We want to do this so that it is unnecessary to store XML Namespaces in
the XMLData instances (which is supposed to be for only encoding). There
are two reasons why this is necessary;
* 1 - We have another class XSDType a, which gives types an XSD Type.
This also depends on the types having a namespace. If we don't have this
class dependency, we end up with repeated data.
* 2 - In various contexts, you will require a different namespace for a
particular element, but the same encoder. For example, when creating a
SOAP Envelope, the "int" data-type could have the SOAP Encoding
namespace or it could have the XSD Namespace. Further it may not have a
namespace at all, in which case the default instance (XMLNamespace a)
will take over. By taking the dependency out you bind a particular
namespace to an encoder.
For now, the various encoders for XSD data-types are in the XSD Module,
this means that any user that wants to encode an int or string must
import the XSD module, since we can't centralise the encoder.
 

This is a simpler recursion scheme in terrms of class/instance 
constraints.
  

Maybe, but sadly it doesn't achieve my goal. I could do Namespaces via a
hook, but that makes the construction and encoding of namespace tables
almost impossible.
Thanks,
-Si.
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 those instances that use it from the XMLData constraint.
   Keean.
Simon David Foster wrote:
On Fri, 2005-02-18 at 02:18 +0100, Ralf Laemmel wrote:
 

Here I assume that you don't _really_ depend on ClassB to be a 
superclass of ClassA. (Why would you?)
   

Ok, here's what the real class head is (or was before I butchered it to
make it work);
class (Data (DictXMLData h) a, XMLNamespace a) => XMLData h a where
We want to do this so that it is unnecessary to store XML Namespaces in
the XMLData instances (which is supposed to be for only encoding). There
are two reasons why this is necessary;
* 1 - We have another class XSDType a, which gives types an XSD Type.
This also depends on the types having a namespace. If we don't have this
class dependency, we end up with repeated data.
* 2 - In various contexts, you will require a different namespace for a
particular element, but the same encoder. For example, when creating a
SOAP Envelope, the "int" data-type could have the SOAP Encoding
namespace or it could have the XSD Namespace. Further it may not have a
namespace at all, in which case the default instance (XMLNamespace a)
will take over. By taking the dependency out you bind a particular
namespace to an encoder.
For now, the various encoders for XSD data-types are in the XSD Module,
this means that any user that wants to encode an int or string must
import the XSD module, since we can't centralise the encoder.
 

This is a simpler recursion scheme in terrms of class/instance constraints.
   

Maybe, but sadly it doesn't achieve my goal. I could do Namespaces via a
hook, but that makes the construction and encoding of namespace tables
almost impossible.
Thanks,
-Si.
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 just the monomorphism restriction at work?
This works fine:
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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:
-
main = do
  var <- newIORef (0::Int)
  let ?global_counter = var in f
   

f = do
  a <- get_unique
  putStr (showInt a "\n")
  b <- get_unique
  putStr (showInt b "\n")
  c <- get_unique
  putStr (showInt c "\n")
   

get_unique :: (?global_counter :: IORef Int) => IO Int
get_unique = readIORef ?global_counter
--
If "(?global_counter :: IORef Int)" were a class constraint the type 
signature
for 'f' could be derived automatically... but we get:

   Unbound implicit parameter (?global_counter::IORef a)
   arising from use of `get_unique' at Test.hs:17:13-22
Is this a bug? Is there some reason why this is not possible? (and if it 
is not possible
shouldn't the documentation be changed to reflect this)...

   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 degrees of strictness);
Special data-parallel language concepts weave an automatism into the
data structures they aim at.
But apparently, the programmer should know very well if this is the case,
and she may explicitly opt for speculative evaluation, or not. 
Explicit or
"implemented" (which means in a way automatic): Garbage collection in a
parallel system is able to detect unneeded results and will stop the
computation in this case.

I wait for the day the compiler does it all for us... One of the reasons 
for adopting
Haskell is the way functional languages parallel hardware implementations
(in VHDL recursion = registers ... and parameters = wires). With an 
imperative
language all the side effects get in the way (side-effects = memory 
access over
a bus).

It seems to me the compiler should sort out all the possible 
parallelisations, and
static dependancies, the RTS should deal with dynamic-dependancies and
speculative execution...

It would be nice if the compiler would also calculate a cost metric for 
funtions, so
that the RTS could make intelligent architecture dependant decisions on 
whether
to run a dependancy sequentially on the current CPU, or in parallel on 
another.

But of course to me the beauty is that not one like of source code 
should need
to be modified...

   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 evaluation to start ASAP, even if there is no
actual demand on its result.
I think this is not quite right... surely you don't want to run the function
(even in parallel) if there is _no_ demand on its result.
The compiler will know at compile time whether the result is required for
a lot of cases... the only ones that cause problems are where program flow
depends on IO actions. In which case you implement speculative execution
(like a modern CPU does) - if you don't know whether a function result
will be required and you have a free execution unit, you run the function.
If at a later time it becomes apparent the results of some running funtions
will not be required, you kill them, throw away the data, and free the
execution unit to do something more useful.
   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
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.
 

___
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
I suspect its becuse q needs to get the dictionary for 'm' from
somewhere... as it is recursive, p calls q calls p, so p must have
the dictionary for 'm' in its context... So this works:
module Main where
   p :: Monad m => m ()
   p = q >>= id
   q :: Monad m => m (m ())
   q = return p
  
   Keean.

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 change is in this line
}
Best regards,
Tomasz
 

___
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
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
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 definition of run is 
provided for 'm'

   Keean.

Ashley Yakeley wrote:
I suspect someone's come across this before, so maybe there's an 
explanation for it.

This does not compile:
module Bug where
{
   p :: IO ();
   p = q >>= id;
   q :: (Monad m) => m (IO ());
   q = return p;
}
Bug.hs:3:
   Mismatched contexts
   When matching the contexts of the signatures for
 p :: IO ()
 q :: forall m. (Monad m) => m (IO ())
   The signature contexts in a mutually recursive group should all be 
identical
   When generalising the type(s) for p, q

The code looks correct to me. Why must the signature contexts be 
identical in this case?

 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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.
Duncan Coutts wrote:
In message <[EMAIL PROTECTED]> "Serge D. Mechveliani"
<[EMAIL PROTECTED]> writes:
 

Dear Haskellers, dear GHC team,
Is a variable `_x' equivalent to `_' 
   

No, '_x' is a perfectly ordinary variable. The only special "dummy 
variable" (a
pattern that matches anything but does not bind a varialbe) is '_'.
 

Does really  Haskell  mean this? It this reasonable?
How to set self-commenting dummy variables? 
   

You can use them as dummy variables by never using them in an expression
context, only in pattern/binding context. As you noted they should be unique
withing each scope.
Duncan
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 = 
then the type variable 'a' should be in scope in .   At present in
GHC you have to write
	f (x :: [a]) = 
to bring 'a' into scope. 

I've fought against this because it seems funny for a 'forall' in a type
signature to bring a type variable into scope in perhaps-distant
function body, but it's just so convenient and "natural".  Furthermore,
as Martin Sulzmann points out, you might have type variables that are
mentioned only in the context of the type:
g :: Foo a b => [a] -> [a]
g = ...
GHC provides no way to bring 'b' into scope at the moment, and that
seems bad design.
If I do this, which I'm inclined to, it could break some programs,
because (with -fglasgow-exts) all type signatures will bring scoped type
variables into scope in their function body.  Here's an example that
will break
f :: [a] -> [a]
f x = my_id x
   where
   my_id :: a -> a
   my_id y = y
The type signature for my_id will become monomorphic, since 'a' is now
in scope, so the application (my_id x) will fail saying
	can't unify 'a' with '[a]'.  
In some ways that makes sense.  If you used 'b' instead in the defn of
my_id, it'd be fine, because my_id would get the type (forall b. b->b).
Fixing such breakages is easy.

So there it is.   Any one have strong opinions?  (This is in addition to
the existing mechanism for bringing scoped type variables into scope via
pattern type signatures, of course.)
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bug in touchForeignPtr?

2004-11-24 Thread Keean Schupke
Is that true... what about:
>module Main where
>
>import Control.Concurrent.MVar
>import System.Mem.Weak
>
>myFinalizer :: MVar () -> IO ()
>myFinalizer m = do
>putMVar m ()
>return ()
>
>createMyFinalizer :: IO (MVar (),Weak ())
>createMyFinalizer = do
>m <- newMVar ()
>w <- mkWeakPtr () (Just (myFinalizer m))
>return (m,w)
>
>main :: IO ()
>main = do
>   (m,_) <- createMyFinalizer
>   _ <- takeMVar m
>   return ()
   Keean
Duncan Coutts wrote:
On Tue, 2004-11-23 at 18:01 +0100, Peter Simons wrote:
 

Simon Marlow writes:
>>> Note that the GC only starts the finaliser thread. The
>>> program can still terminate before this thread has run
>>> to completion [...]
> If you want anything else, you can implement it.
How do I implement that particular feature? I don't see how
I could write a 'main' function that waits for the finalizer
thread having terminated.
   

For all normal threads you can wait for them by making them write to an
MVar when they finish and the main thread waits to read from the MVar
before finishing itself.
Of course for the finalizer thread you cannot do this since you did not
start it. However the fact that finalizers are run in a dedicated thread
is itself an implementation detail that you have no control over anyway.
Obviously from what Simon has said, you cannot solve the finalisers
problem just by running the finaliser thread to completion (or it'd be
done that way already!)
Duncan
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 for all
forked threads to finish before the RTS exits.
   Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 wondering if it were possible to 
determine
that type inferance had failed... like with:

   show (read x :: y)
Here y (the type of read x) has no type... and does not match _any_ 
instance apart
from 'x'... so would it not be possible to have an instance for "no type"?

perhaps:
   instance _|_ ...
Keean. 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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. With our semaphores
we are actually quite clever, in that the at_exit routine is set 
containing the
semaphore ID as a constant, so it should always be runnable...

What I am suggesting is that every effort should be made to clean up, 
just because
there are some circumstances (which should be rare) in which it cannot 
happen, does
not mean you shouldn't try...

   Keean
Glynn Clements wrote:
There isn't any way to *guarantee* that something is run upon
termination. The program may be terminated due to SIGKILL (e.g. due to
a system-wide lack of virtual memory). If you run out of stack, you
may not be able to call functions to perform clean-up.
 

Also, if the program crashes, handling the resulting SIGSEGV (etc) is
likely to be unreliable, as the memory containing the resource
references may have been trashed. Calling remove() on a filename which
might have been corrupted is inadvisable.
Also, at_exit() isn't standard. atexit() is ANSI C, but that is only
supposed to be called for normal termination (exit() or return from
main()), not for _exit() or fatal signals.
 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bug in touchForeignPtr?

2004-11-22 Thread Keean Schupke
Glynn Clements 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 process
created.
 

Right, which is why if you want to clean up temporary files, or
temporary semaphores the OS doesn't do it for you, and you
need to put some routine inplace to do it (using at_exit)... It
seems this is the only way to guarantee something gets run when
a program exits for whatever reason.
   Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 need rebooting eventually.

That's an OS task IMHO, not really the task of an RTS. Looks like you're
working on WinDoze... (sorry, couldn't resist :-)
Cheers,
   S.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 finalizers remain. What 
can be
done about loops I am not sure (where A refers to B which refers to A and
both have finalizers)...

The alternative would seem to be writing your finilizers such that they
first call the finalizers on any refered objects which haven't been 
finalized
yet (In the case of loops if we specify running the finalizers on any 
objects
refered to on which the finalizer has not been entered yet - it should work
too)

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.
   Keean.
Simon Marlow wrote:
The problem is that the runtime is running all outstanding finalizers at
the end of execution, without regard for GC dependencies like the ones
introduced by touchForeignPtr.
I've been planning to remove this automatic running of finalizers for
other reasons.   However, then you will get absolutely no guarantee that
your finalizer will ever run at all (indeed, the property isn't always
true right now, but it is usually true).
Let me share with you something that I've come to appreciate over the
last few years:
 Finalizers are almost always not the right thing.
Finalizers look terribly attractive, but often lead to a huge can of
worms - best avoided if at all possible.
Cheers,
	Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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.
   Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 the function):
data Test = Test (forall a . a)
test a = Test a
However this fails to compile with the following error:
   

The current implementation of rank-n polymorphism
(which is documented in the paper "Pratical type inference
for arbitrary-rank types") does not "guess" polymorphic
types for lambda-abstracted values.
In this situation, this means that the variable "a"
is assumed to have a monorphic type, which then cannot
be passed to "Test" as an argument.
Knowledge about polymorphism is passed down/inwards,
but not up/outwards.
This definition typechecks only if you add a type
signature:
test :: (forall a . a) -> Test
If you want to know the reasons, read the paper. It explains
the problems very well.
Cheers,
 Andres
 

___
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
 It is mentioned in the environment:
   test :: a -> Test (bound at Test.hs:9:0)
   a :: a (bound at Test.hs:9:5)
   In the first argument of `Test', namely `a'
   In the definition of `test': test a = Test a
I think this should only generate an error once the value of
'a' is known not to be undefined.
   Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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


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
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: deriving...

2004-10-17 Thread Keean Schupke
Okay so that does the deriving...  How are you deriving the constraints? 
(in the ghc code there is
some equaion expansion, where it finds the fixed point).

Still the main point was that it would be nice to seamlessly integrate 
this... Surely it wouldn't take much
to get the compiler to look 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 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 x = X x deriving MyClass
I saw the same suggestion earlier today on the Haskell list...
 

Check out Ulf Norell's IOHCC submission, his DeriveData.hs module does
this,
though I can't tell if it will work for parameterized types.
   

It doesn't. A version that does can be downloaded from
http://www.cs.chalmers.se/~ulfn/th/DeriveData.hs
/ Ulf
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 x = X x deriving MyClass
I saw the same suggestion earlier today on the Haskell list...
Keean.
Andre Pang wrote:
On 13/10/2004, at 10:02 AM, MR K P SCHUPKE wrote:
Okay, I see the Generic type class stuff does not support multi
parameter type classes. I guess I am stuck - any suggestions as to
how best do this?
I wish to be able to derive type level labels for datatypes, like
the following:
data Fred a = Fred a deriving TTypeable
generates the instance:
instance TTypeable a al => TTypeable (Fred a) (NCons (N3 (N4 (N5 
Nil))) (TCons al Nil))

If you are happy to live on the edge a bit (which you seem to be happy 
with, considering that you're playing with GHC CVS ;), Template 
Haskell might be one way to do it.  See "Template Haskell: A Report 
from the Field", a paper where Ian Lynagh does exactly what you're 
trying to do:

http://www.haskell.org/th/papers.html

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 like:
Sig id = Sig (Location name) (LHsDecl name)
what type is name? Presumably it can be a range of types, 
what are valid types for name? 

	Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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:

   print $ test (\_ -> [True]) [True]

it says no instance for (t -> [Bool), but if I add a type annotation all 
is Okay:

   print $ test ((\_ -> [True]) :: () -> [Bool]) [True]

Is this expected behavior? Finally, If I change the definition to:

   instance Test (a -> m b) z where
   test _ _ = "Third"
it now complains about it overlapping with both of the other 
definitions... Why does this overlap?

   Regards,
   Keean.


Simon Peyton-Jones wrote:

| I have been doing some work recently which involves classes with
| overlapping instances... for example
| 
| class Test x y where
| test :: x -> y
| 
| instance Test (a b) (c b) where
| test =
| 
| instance Test (a b) (a b) where
| test =
| 
| This gives an overlapping instance error - which cannot be avoided
with
| -fallow-overlapping-instances.
| However - it is fairly obvious that the first case 'a' cannot be
unified
| with 'c' or it would be a type error, therefore
| the cases do not overlap... Is this a bug in ghc, is it easily fixable
-
| or am I confused?

You are right.  They don't overlap.  The program below runs fine with
GHC 6.0.1, and prints
cam-02-unx:~/tmp$ ghc -fallow-overlapping-instances -fglasgow-exts
Foo.hs
cam-02-unx:~/tmp$ ./a.out
"Second"
"First"
Simon

=
module Main where
class Test x y where
   test :: x -> y -> String
instance Test (a b) (c b) where 
 test x y = "First"

instance Test (a b) (a b) where
 test x y = "Second"
main = do { print (test [True] [True]) ;
print (test [True] (Just True)) }


 



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Query regarding GHC handling of overlapping instances.

2003-09-09 Thread Keean Schupke
I have been doing some work recently which involves classes with 
overlapping instances... for example

class Test x y where
   test :: x -> y
instance Test (a b) (c b) where
   test =
instance Test (a b) (a b) where
   test =
This gives an overlapping instance error - which cannot be avoided with 
-fallow-overlapping-instances.
However - it is fairly obvious that the first case 'a' cannot be unified 
with 'c' or it would be a type error, therefore
the cases do not overlap... Is this a bug in ghc, is it easily fixable - 
or am I confused?

This leads on to my second point: A request for a new feature (if it 
cannot be done with existing features). I would like
to be able to specify class non-membership. Say we have orthogonal 
classes A and B, I can see situations where definitions like the 
following would be useful:

instance (A a,B a) => C a ...

instance (A a, (not B) a) => C a ...

perhaps the complete set of boolean operators would make sense for 
completeness allowing:

instance ((A a) and ((B a) or (C a))) => D a ...

Obviously functions defined in classes B and C would not be usable in 
the function definitions of D because
we are uncertain of membership of B and C individually.

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


RE: ghc-6.0 heap profiling broken.

2003-06-13 Thread Keean
It does not happen straight away... It seems to happen when 4 threads are
sparked
to do network IO... I guess I'll have to try to produce a small example that
causes it
to break...

Regards,
    Keean.

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] Behalf Of Simon
Marlow
Sent: 13 June 2003 10:12
To: Keean Schupke; Glasgow-haskell-users
Subject: RE: ghc-6.0 heap profiling broken.



> After compiling code with ghc-6.0 profiling support on, it
> appears that
> running the application with -prof produces an output file,
> but any -h?
> options for heap profiling causes a segmentation-fault under
> linux. The
> fault appearch to come in HeapCensus.

That's strange, I can't seem to repeat it here.

What flavour of Linux and which GHC distribution did you install?

Is anyone else having the same problem with heap profiling?

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


ghc-6.0 heap profiling broken.

2003-06-12 Thread Keean Schupke
After compiling code with ghc-6.0 profiling support on, it appears that 
running the application with -prof produces an output file, but any -h? 
options for heap profiling causes a segmentation-fault under linux. The 
fault appearch to come in HeapCensus.

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


Re: Dynamic Compilation

2003-06-12 Thread Keean Schupke
Whilst I Agree with you about Apache being widely useful, most websites 
fall into the category database backend, dynamic content in the middle 
and HTTP infront. Apache is a waste of disc space and memory, if all you 
want is Haskell Servlets (Think Java Servlets and Tomcat - a large 
number of major projects are done on tomcat which is a server written in 
Java, completely stand alone from Apache). Further to this HTTP is quite 
a simple protocol, and its implementation in Haskell quite easy - there 
is really no need for a complete implementation of the standard - you 
only really need put and get...

When using servlets there is no need for CGI or FastCGI, the server is 
written in Haskell, the Servlets are
written in Haskell, you use the ghci-linker to load up the pages - 
although for high demand services it is better
to compile the pages into the server for better speed. A record is used 
to parse the request to the servlet.

The setup we use - with real paying customers - is an implementation of 
HTTP in haskell - Authentication is
provided by a plug-in, and like most sites uses on-page login/password 
boxes, the server provides session management,
so the Servlet simply has to deal with page generation and parsing 
user-feedback. A database backend using ODBC
means we can change database without major code rewrites. Everything is 
in Haskell (apart from the DB) and this setup
will do 90% of the things you would ever want a dynamic web site to 
do... (The other 10% does not justify code bloat in
the server - for those 10% use different tools)

   Regards,
   Keean Schupke...
Peter Simons wrote:

Keean  writes:

> 	http://losser.st-lab.cs.uu.nl/mod_haskell/

Interesting!

> But, think of the advantages of a type-safe web-server, utilising GHC's
> light weight threads...
Well, yes, but the problem is that web server today must provide tons
of things to be suitable for production use. Authentication, CGI, even
FastCGI come to my mind, etc., etc. I don't think something like
Apache can be re-built from scratch very easily, so it's good that
Haskell support for it is available.
Peter

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Dynamic Compilation

2003-06-11 Thread Keean
A mod_haskell (using hugs) has been done here:

http://losser.st-lab.cs.uu.nl/mod_haskell/

But, think of the advantages of a type-safe web-server, utilising GHC's
light weight threads...

Regards,
    Keean Schupke.

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] Behalf Of Peter
Simons
Sent: 11 June 2003 18:01
To: [EMAIL PROTECTED]
Subject: Re: Dynamic Compilation


Carsten Schultz writes:

 > a web server written in Erlang that can compile [...] code embedded
 > in HTML files to produce dynamic pages

IMHO it should be possible to add a "mod_runhugs" module to Apache,
which implements exactly that except that it doesn't require any
compilation of code at all. As far as I know, Hugs does already have a
server mode where code can be sent via IPC for execution, doesn't it?

Something like this would certainly be useful, and if it's based on
Apache, many people could use without any trouble.

Peter

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Dynamic Compilation

2003-06-11 Thread Keean Schupke
We are using a web server written in Haskell in a production 
environment... It only serves dynamic pages - it is
a bit like Tomcat for Haskell... It uses the ghci linker interface to 
load object files... but does not compile automatically.
I think it sould be possible to embed ghc 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 a Haskell analog of
Yaws (yaws.hyber.org) possible?
For those who don't know Yaws: It is a web server written in Erlang
that can compile and load Erlang code embedded in HTML files to
produce dynamic pages.  I have played with it a bit, and it seems
useful to me, but I would prefer Haskell over Erlang.
Greetings,

Carsten

 



___
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
Well if its any help, I have now done extensive testing on a server that 
opens connections
using connectTo, and hGetContents - and without these two fixes, it 
dies, with them it seems
rock solid (ie make connection, randomly break connection - repeat for 
several hours, examine
sockets on server and there are no hanging sockets.) Without the 
finalizer fix there will be lots
of CLOSE_WAIT write handles, without the connectTo exception-handler you 
get the odd socket
of unknown type hanging about ... I have added the fixes by hand to a 
source copy of 5.04.3 on the
assumption 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 side as in previous versions... Once again this is a 
critical fix, 
as otherwise applications keep one
half of the connection open until they quit, or crash due to lack of 
resources.
   

Darn!  That fix is sitting in my tree uncommitted because I never got
around to testing it properly.  Sigh, I think I need a holiday :-(
/me wanders off looking a bit sheepish.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Handle finalizer fix missing too...

2003-03-13 Thread Keean Schupke
The fix for duplex handle finalizers ... where GHC.Handle has the 
finalizer attached to the read side
addMVarFinalizer read_side (handleFinalizer read_side), and it should be 
on the write side (as the read side points to the write side using 
haOther...)

Without this fix hGetContents leaks file handles...

   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 again this is a critical fix, 
as otherwise applications keep one
half of the connection open until they quit, or crash due to lack of 
resources.

   Keean.



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


fix missing from 5.04.3 ???

2003-03-12 Thread Keean Schupke
Previous 5.04 releases had an exception handler missing from connectTo 
that results in a socket leaking if socketToHandle fails for some reason 
(I cant remember the exact circumstances at the moment, but it causes a 
server to die - I think the leak is caused when the client closes the 
connection during the handshake - ie somebody presses stop on a web 
browser because of a slow connection after the handshake has just 
started) - I suggested a fix along the lines of:

connectTo hostname (Service serv) = do
   proto <- getProtocolNumber "tcp"
   port <- getServicePortNumber serv
   he <- getHostByName hostname
   sock <- socket AF_INET Stream proto
   (do
   connect sock (SockAddrInet port (hostAddress he))
   socketToHandle sock ReadWriteMode) `Control.Exception.catch` (\e 
-> do sClose sock; throw e)

   This seems to be missing from 5.04.3 - this fix is important for 
reliability 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


Re: MArray and runST

2003-02-13 Thread Keean Schupke
Ahh, I see, perhaps you could give me a clue as to why (or how) this 
works...
I have probably become a little over keen on using '$' as a general 
replacement for
braces '(' ')'  - the '$' was there because the actual wrapper function 
takes arguments and
it looks neater not to have too many nested braces. I thought this could 
be something to do
with runST enforcing strictness, but '$!' causes the same problem, only 
runST (wrapper x y z)
appears to work - if its not too much trouble, how does runSTs type 
enforce this, and why does
using '$' and '$!' cause type leakage?

   Regards,
   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
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 




___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



MArrayt and runST

2003-02-13 Thread Keean
I appreciate this may have been covered before, but i'm struggling to get
the types
right for the following functions:

firstly I have a function I want to be passed an MArray (so the function
itself is polymorphic and independant of the type of array used). This has a
type similar to:

fn1 :: MArray a Int m => a (Int,Int) Int -> m ()

now I want to produce a wrapper function to provide an MArray of a given
type, and
freeze the result into a non-mutable array, so I have a function like:

wrapper :: MArray (STUArray s) Int (ST s) => ST s (Array (Int,Int) Int)
wrapper = do
d <- newArray ((0,0),(10,10)) 0
fn1 d
unsafeFreeze d

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

where am I going wrong?

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 implementing if it's easy and you can
find the the time.  Or perhaps I am just doing things the wrong way?

The point is that I sometimes have something like the following situation

class ComplicatedClass x where
  simpleTitleFn :: x -> String
  muchMoreComplicatedTitleFn :: extra arguments -> x -> IO (WithError (Source blah blah blah String)
  
  muchMoreComplicatedTitleFn _ x = [ ... some expression involving simpleTitleFn ...]

The idea is that only muchMoreComplicatedTitleFn must always work; however instances may
choose to implement it directly, or implement the much simpler function simpleTitleFn
(if that does all they want).  

At the moment the situation is that someone who defines just "muchMoreComplicatedTitleFn"
will get an unnecessary warning message from the compiler about "No explicit method or
default method for simpleTitleFn".  I suggest instead introducing a new class of
optional method (for example, via a pragma {-# OPTIONAL_METHOD simpleTitleFn #-}) which
compiles exactly as normal except that (1) no warning is given for instances which don't
define it; (2) a warning is given whenever anyone outside the class declaration *uses*
simpleTitleFn.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 




___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: signal masks and garbage collection.

2003-01-10 Thread Keean
I am trying to block the SIGPIPE signal, I have used the Posix sigprocmask
call to set the signal to blocked. However the program sill bails out if the
client closes its socket. The exception handler appears to be called then
the program terminates. When I run the program in gdb, it gives a SIGPIPE
signal just after the thread swap happens... Heres the report from gdb:

Starting program: /local/home/keean/HServer/hserver
(no debugging symbols found)...(no debugging symbols found)...(no debugging
symbols found)...
(no debugging symbols found)...(no debugging symbols found)...(no debugging
symbols found)...
(no debugging symbols found)...[New Thread 16384 (LWP 23152)]
(no debugging symbols found)...(no debugging symbols found)...
(no debugging symbols found)...(no debugging symbols found)...(no debugging
symbols found)...
Server Start
serverMain
Connection from: "xxx.xxx.xxx.xxx":1054
caught thread exception
application finally
Connection from: "xxx.xxx.xxx.xxx":1055
caught thread exception
application finally
:
:
Connection from: "pc-80-192-247-253-cr.blueyonder.co.uk":1104
(no debugging symbols found)...(no debugging symbols found)...(no debugging
symbols found)...
Program received signal SIGPIPE, Broken pipe.
[Switching to Thread 16384 (LWP 23152)]
0x4015b8cd in sigprocmask () from /lib/libc.so.6

So there is a real thread, what I cant quite figure out is why it dies
in sigprocmask ()...

Regards,
Keean Schupke



-Original Message-
From: Wolfgang Thaller [mailto:[EMAIL PROTECTED]]
Sent: 10 January 2003 19:20
To: Keean Schupke
Subject: Re: signal masks and garbage collection.


Keean Schupke wrote:

> I have a problem with c_sigprocmask from the Posix library. This is
> supposed to set a signal mask for the process
> (but it appears it actually only sets it for the thread). I need some
> way of calling sigprocmask before the garbage
> collector thread is started so it inherits the same signal mask (or a
> way of setting the signal mask of the garbage collector
> whilst running). Any ideas?

The garbage collector in GHC doesn't currenlty run in a separate thread
- it is executed in the same thread as your haskell code (even if you
use the "threaded RTS"). Therefore there is no separate signal mask for
the garbage collector.
What are you trying to do?

Regards,
Wolfgang Thaller

___
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
I have a problem with c_sigprocmask from the Posix library. This is 
supposed to set a signal mask for the process
(but it appears it actually only sets it for the thread). I need some 
way of calling sigprocmask before the garbage
collector thread is started so it inherits the same signal mask (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: readping fd's and flushing buffers

2003-01-09 Thread Keean
A related problem... connections are refused when using accept if the
hostname doesn't resolve. Maybe something like this would help, unless there
is a better way?

accept sock = do
 ~(sock', (SockAddrInet port haddr)) <- Socket.accept sock
 (HostEntry peer _ _ _) <- ((getHostByAddr AF_INET haddr)
`Control.Exception.catch` (\_ ->
   return (HostEntry ((showHex ((haddr `shiftR` 24) .&. 0xff) . showChar '.'
. showHex ((haddr `shiftR` 16) .&. 0xff)
  . showChar '.' . showHex ((haddr `shiftR` 8) .&. 0xff) . showChar '.'
. showHex (haddr .&. 0xff)) "") [] AF_INET [])))
 handle <- socketToHandle sock' ReadWriteMode
 return (handle, peer, port)

Regards,
Keean Schupke.

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED]]On Behalf Of Simon
Marlow
Sent: 09 January 2003 13:18
To: Keean Schupke; [EMAIL PROTECTED]
Subject: RE: readping fd's and flushing buffers


> This may be related to the answer just given to do with
> finalizing the
> Handles, as I have a
> problem with sockets hanging around after a host name resolution has
> failed (using the simple socket
> library). Having looked at the code I would like to suggest the
> following change:
>
> connectTo hostname (PortNumber port) = do
> proto   <- getProtocolNumber "tcp"
> sock<- socket AF_INET Stream proto
> he <- getHostByName hostname
> connect sock (SockAddrInet port (hostAddress he))
> socketToHandle sock ReadWriteMode
>
> Should become:
>
> connectTo hostname (PortNumber port) = do
> proto   <- getProtocolNumber "tcp"
> sock<- socket AF_INET Stream proto
> (do
> he <- getHostByName hostname
> connect sock (SockAddrInet port (hostAddress he))
> socketToHandle sock ReadWriteMode) `Exception.catch`
> (\e -> do
> sClose sock;throw e)
>
> Is this a sensible change to make?

Yes, well spotted.  I'll add the exception handler.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: readping fd's and flushing buffers

2003-01-09 Thread Keean Schupke
This may be related to the answer just given to do with finalizing the 
Handles, as I have a
problem with sockets hanging around after a host name resolution has 
failed (using the simple socket
library). Having looked at the code I would like to suggest the 
following change:

connectTo hostname (PortNumber port) = do
   proto   <- getProtocolNumber "tcp"
   sock<- socket AF_INET Stream proto
   he <- getHostByName hostname
   connect sock (SockAddrInet port (hostAddress he))
   socketToHandle sock ReadWriteMode

Should become:

connectTo hostname (PortNumber port) = do
   proto   <- getProtocolNumber "tcp"
   sock<- socket AF_INET Stream proto
   (do
   he <- getHostByName hostname
   connect sock (SockAddrInet port (hostAddress he))
   socketToHandle sock ReadWriteMode) `Exception.catch` (\e -> do 
sClose sock;throw e)

Is this a sensible change to make?

   Regards,
   Keean Schupke.


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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:

   Actually this raises an interesting point - As far as I can see
you can do anything you can do with TRex, using a FiniteMap of
Dynamic. How is TRex different from this? Is TRex just syntactic
sugar for this kind of construct?
  


Read the paper (on Mark Jones publications page).

Trex is statically typed.

You could certainly get the effect of Haskell typeclasses using a
FiniteMap of Dynamic to store methods (this isn't too far from what
Smalltalk does) but it wouldn't be statically typed.  Trex uses
mechanisms close to those used to implement typeclasses to implement
extensible records.

--
Alastair

 




___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re : Extensible records in Haskell

2002-11-06 Thread Keean Schupke
Just a quick point, which I'm sure you realise, but static typing gives 
you guarantees about the runnability of
a program that dynamic typing breaks... You can do almost anything you 
would want to use dynamic types for
using a sufficently broad algebraic data type. For instance you could 
create 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:

>   > Hello, is there something like extensible records in ghc?

>Are you wanting something like Hugs' T-Rex or did you have something
>else in mind?


Hello,
For what I understand of T-Rex it is what I wait.

I need something that can allow to use records without declaring their 
type first and that can be extended by creating a new records with the 
same contents plus one or less one.

Best regards,
Nicolas

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: RTS interface followup...

2002-07-17 Thread Keean

Yup, -optl-u -optl Addr_Azh_con_info fixes it, and is better than putting
HSlang.o in the
compile as it will not automatically include the whole library in the
binary.

As for the slowdown, I will try and compare some code compiled with ghc-5.02
and I will
let you know if anything real is happening here...

Keean Schupke
Department of Electrical & Electronic Engineering,
Imperial College.

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED]]On Behalf Of Simon
Marlow
Sent: 17 July 2002 11:38
To: [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]
Subject: RE: RTS interface followup...


> rts_mkAddr is used by Linker.o in libHSrts.a (it looks like in the
> resolveObjs call - I in turn am calling this... (this was
> from doing an nm on the library)...

Hmm, yes the Linker does refer to it, just in case the dynamically
linked program requires it.  I think you should probably arrange that
the missing symbols get linked in from HSlang.o, something like:

ghc -package lang -optl-u -optl Addr_Azh_con_info

does that help?

> with regards to the threading, I was wondering if the default file
> buffering mode has changed, as text IO to the console seems slower
> (you can see characters 'printing' left to right, rather than just
> lines flying past)...

No, the default buffering has not changed.  Can you quantify the
slowdown, or provide an example?  Does it only happen when
--enable-threaded-rts is on?

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: RTS interface followup...

2002-07-17 Thread Keean

rts_mkAddr is used by Linker.o in libHSrts.a (it looks like in the
resolveObjs call - I in turn am calling this... (this was from doing an nm
on the library)...

with regards to the threading, I was wondering if the default file
buffering mode has changed, as text IO to the console seems slower
(you can see characters 'printing' left to right, rather than just
lines flying past)...

    Keean Schupke
Department of Electrical & Electronic Engineering,
Imperial College.

-Original Message-
From: Simon Marlow [mailto:[EMAIL PROTECTED]]
Sent: 17 July 2002 11:19
To: [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]
Subject: RE: RTS interface followup...



> The code (which is what I am assuming is where the error is 
> comming from) is
> lifted
> from Linker.lhs, namely (lookupSymbol :: CString -> IO (Ptr 
> a)) this is used
> in the
> following:
> 
>   hobj <- lookupSymbol c_objsym
>   case hobj of
>   o | o == nullPtr -> return Nothing
>   Ptr o -> case (addrToHValue# o) of
>   (# h #) -> return (Just h)
> 
> [I am not 100% certain this is where the error is comming 
> from - but its the only reference to an Addr I can find...]

There isn't a reference to Addr in the above code, only the primitive
type Addr# (which isn't deprecated).

> this compiles fine, however in the final link (i'm doing a 2 
> stage compile with -c to
> generate all the .o files then a link - using ghc) the 
> following error is generated:
> 
> .../ghc-5.04/libHSrts.a(RtsAPIDeprec.o): In function 'rts_mkAddr':
> RtsAPIDeprec.o(.text+0x14): undefined reference to 'Addr_Azh_con_info'

RtsAPIDeprec should only be linked in if something requires it - i.e. if
one of the symbols rts_getAddr or rts_mkAddr is used elsewhere.  Do you
have any code which uses one of those functions?

> ...same for rts_getAttr, with the addition of the symbol
> Addr_Azh_static_info
> which is also undefined...
> 
>   Hope this makes it a bit clearer. A second problem I 
> have just found - using
> a threaded runtime, my code now hangs after getting a connection on a
> socket, and forking
> a haskell-thread to handle it. The reply is not sent until another
> connection attempt
> occurs... where does the behavior of the threaded runtime 
> differ from the non-threaded?

I'm afraid I don't know about this one, I haven't done much testing of
the threaded RTS myself (due to lack of time and trying to get 5.04 out
of the door).

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: RTS interface followup...

2002-07-17 Thread Keean

The code (which is what I am assuming is where the error is comming from) is
lifted
from Linker.lhs, namely (lookupSymbol :: CString -> IO (Ptr a)) this is used
in the
following:

hobj <- lookupSymbol c_objsym
case hobj of
o | o == nullPtr -> return Nothing
Ptr o -> case (addrToHValue# o) of
(# h #) -> return (Just h)

[I am not 100% certain this is where the error is comming from - but its the
only
reference to an Addr I can find...]

this compiles fine, however in the final link (i'm doing a 2 stage compile
with -c to
generate all the .o files then a link - using ghc) the following error is
generated:

.../ghc-5.04/libHSrts.a(RtsAPIDeprec.o): In function 'rts_mkAddr':
RtsAPIDeprec.o(.text+0x14): undefined reference to 'Addr_Azh_con_info'

...same for rts_getAttr, with the addition of the symbol
Addr_Azh_static_info
which is also undefined...

Hope this makes it a bit clearer. A second problem I have just found -
using
a threaded runtime, my code now hangs after getting a connection on a
socket, and forking
a haskell-thread to handle it. The reply is not sent until another
connection attempt
occurs... where does the behavior of the threaded runtime differ from the
non-threaded?

Keean Schupke
Department of Electrical & Electronic Engineering,
Imperial College.

-Original Message-
From: Simon Marlow [mailto:[EMAIL PROTECTED]]
Sent: 17 July 2002 10:40
To: [EMAIL PROTECTED]; [EMAIL PROTECTED]
Subject: RE: RTS interface followup...


> Have got the rts stuff to compile by including
> .../ghc-5.04/HSlang.o on the
> compile command line. I think this means the linker is not
> including the
> object
> with defines Addr_Azh_con_info when it links the library (only objects
> actually
> referenced from an archive library get included in the final
> binary) however
> including
> the .o forces all the code in the library to be included. It
> looks like a
> problem with
> the arguments ghc passes to the linker, however passing -optl
> --undefined
> Addr_Azh_con_info
> (should force the linker to output the code containing the
> definiton) made
> no difference,
> so I'm a little confused by that.

I'm a bit hazy about this - I remember you were working on doing some
dynamic linking of Haskell code, but could you explain in more detail
exactly what it is you're doing, and at what point the error is
generated?

The Addr type is deprecated, so please don't use it if possible.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RTS interface followup...

2002-07-17 Thread Keean

Have got the rts stuff to compile by including .../ghc-5.04/HSlang.o on the
compile command line. I think this means the linker is not including the
object
with defines Addr_Azh_con_info when it links the library (only objects
actually
referenced from an archive library get included in the final binary) however
including
the .o forces all the code in the library to be included. It looks like a
problem with
the arguments ghc passes to the linker, however passing -optl --undefined
Addr_Azh_con_info
(should force the linker to output the code containing the definiton) made
no difference,
so I'm a little confused by that.

    Keean Schupke
Department of Electrical & Electronic Engineering,
Imperial College.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



new RTS interface problem with ghc-5.04

2002-07-16 Thread Keean

I have just moved to ghc-5.04 to try the threaded runtime, however
some code I have to do dynaminc module loading using the rts linker will not
compile, failing with:

RtsAPIDeprec.o undefined reference to Addr_Azh_con_info (in rts_mkAddr)

this symbol appears to be defined in libHSlang.a, and I have a -syslib lang
in the compile command... what's wrong here?

secondly, if this interface is deprecated, (I presume this is something to
do with the FFI?) where am I using rts_mkAddr and rts_getAddr, would that be
in addrToHValue, and if so what is the non-deprecated way of doing this?

    Keean Schupke
Department of Electrical & Electronic Engineering,
Imperial College.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



type classes / ghci

2002-07-10 Thread Keean

I have found what is either a problem in ghc/ghci or a problem in my
understanding...
either way if someone could point out whats wrong I would be very grateful.

I am experimenting with monad-transformers, and am tying to define a class
to allow a
run function to be overloaded. The program layers two monads on top of the
IO monad,
a state monad-transformer, and an error monad-transformer.

If I define a set of untyped functions:

unFC (FC x) = x -- run a forward composed monad
unBC (BC x) = x -- run a backward composed monad
unSTM (STM x) = x   -- run a monad composed with a State monad-transformer

I then used ghci to derive the type for these functions...

unFC :: forall m n a . (Monad m,Monad n) => FComp m n a -> n (m a)
unBC :: forall m n a . (Monad m,Monad n) => BComp m n a -> m (n a)
unSTM :: forall s m a . (Monad m) => StateT s m a -> s -> m (a,s)

the program still passes type checking with these types added.
next I defined a type class:

class Composed c where
run :: c

and some instances:

instance (Monad m,Monad n) => Composed (FComp m n a -> n (m a))
run = unFC

instance (Monad m,Monad n) => Composed (BComp m n a -> m (n a))
run = unBC

instance (Monad m) => Composed (StateT s m a -> s -> m (a,s))
run = unSTM

However when I compile now, replacing:
   unFC (unSTM test (0::Int))
with
   run (run test (0::Int))

I now get an error: no instances for (Composed (t -> IO t1),Composed (StateT
Int ErrorIO Int  -> Int -> t))


Regards,
Keean.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: Andy Gill's html library

2002-06-26 Thread Keean

I have an alternative HTML library if you are interested... it uses an
intermediate representation (a DOM style model) and defines the type
ShowDOM = DOM -> DOM , allowing efficent concatination using function
composition, finally a layer on top of this using the type
ShowDOM -> (a,ShowDOM), instanciating a Monad allows monadic composition of
html pages - there is also some static type checking done by creating the
types:

newtype HtmlFragment = HtmlFragment (ShowDOM -> (a,ShowDOM))
newtype HtmlTableFragment = HtmlTableFragment (ShowDOM -> (a,ShowDOM))
etc...

this allows you to compose HTML as in the following example

attrTable [MkAttribute ("cellspacing","0")] ( do
htmlTR (attrTD [MkAttribute ("colspan","2")] $ htmlText "Test Cell 1"))
htmlTR ( do
htmlTD (htmlText "Cell 2 (Left)")
htmlTD (htmlText "Cell 3 (Right)")))

If you (or anyone) are interested let me know ... 

Keean Schupke
Department of Electrical & Electronic Engineering
Imperial College - London.


-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED]]On Behalf Of Albert Lai
Sent: 26 June 2002 05:52
To: [EMAIL PROTECTED]
Subject: Re: Andy Gill's Html library


"Thomas L. Bevan" <[EMAIL PROTECTED]> writes:

> Can someone explain the reasoning behind using 
> a function to describe a Table rather than just a list of lists?

Just my feeling, but perhaps it is essentially the same reason why
ShowS is String -> String rather than String, so that concatenation
becomes efficient?
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Dynamic loading with GHCi Linker

2002-04-05 Thread Keean


[Firstly, appologies if this is a duplicate, my first mail did not appear on
the list.]

Summary so far: I want to dynamic load haskell code into a host haskell
application (plug-in style)

I have, as suggested, put together an interface for Linker.h, and written
some little wrapper
functions. I have a few questions though... (is there any documentation?)

What are the integer return values from loadObj/resolveObjs/unloadObj ?

What is the void* pointer returned from lookupSymbol - and how do I apply
it if its
a function. (my first guess was to import rts_apply)

Finally, when I load the module there are unresolved symbols - will it link
against
the main program? Is there any way to get it to do this? (I would like to
avoid
dynamic loading dependancies if the code is already used by the main
program)

Keean

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



GHC Dynamic Loading

2002-04-04 Thread Keean


I am trying to dynamically load a shared haskell module - and it almost
works... however as
soon as the grabage collector thread runs it frees/moves something and the
program falls over.
Presumably this means I need to use a StablePtr - however I have as yet been
unable to work out
what exactly is the cause. I was hoping somebody with some knowledge of th
einternals of GHC could
help me out...

The summary of what happens is:

using FFI to call libdl on linux:

- load module using dlopen (the library is compiled with -optl -shared 
and
the
loader is compiled with -rdynamic, so after loading all static 
symbols
should be resolved.)

- using dlsym to get a FunPtr to a module initialiser.

- passing a StablePtr to a (FiniteMap String (SomeFunction)) as well 
as a
dynamically exported
continuation function (ie a "main-loop") which takes the 
FiniteMap as an
argument to the
initialiser.

(now in the loaded module)

- de-reference FiniteMap StablePtr, and add a handler function and
string-identifier
using addToFM, then create a newStablePtr to the modified 
FiniteMap and
call the
dynamic imported main-loop fn with FiniteMap as argument.

- main loop calls back to module at a later time - dependant on string
identifier.

when I run this with +RTS -B it successfully loads, links and calls back 3
or 4 times, then goes 'beep'
and dies - I think in the garbage collector thread itself, or as soon as the
GC finishes. Any info that
would shed light on what is happening would be useful.

    Regards,
Keean Schupke.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users