[Haskell-cafe] [Haskell] Lexically scoped type variables

2004-11-26 Thread Martin Sulzmann
Hi,

let me answer your questions by comparing what's implemented in Chameleon.
(For details see
http://www.comp.nus.edu.sg/~sulzmann/chameleon/download/haskell.html#scoped)

   QUESTION 1 -
  
  In short, I'm considering adopting the Mondrian/Chameleon rule for GHC.
  There are two variations
  
1a) In the example, 'a' is only brought into scope in the
right hand side if there's an explicit 'forall' written by
  the programmer
1b) It's brought into scope even if the forall is implicit; e.g.
   f :: a - a
   f x = (x::a)
  
  I'm inclined to (1a). Coments?
  

Currently, Chameleon goes for 1b), i.e. foralls are implicit. I agree
that 1a) might help the programmer to immediately see which variables
are bound by the outer scope.

  
  - QUESTION 2 --
  
  [...]
  
  The alternatives I can see are
  
  2a) Make an arbitrary choice of (A) or (B); GHC currently chooses (B)
  2b) Decide that the scoped type variables arising from pattern
   bindings scope only over the right hand side, not over
   the body of the let
  2b) Get rid of result type signatures altogether; instead,
use choice (1a) or (1b), and use a separate type signature
  instead.
  
  Opinions?
  

Chameleon goes for 2c)

A Chameleon speciality is that we can write

f ::: a-a
f x = True

f ::: a-a states that f has type a-a for some a.

::: follows the same scoping rules as ::

Then, the following statement

let f (x::[a],ys) = rhs
in body

(I assume that x::[a] states here that x has type [a] for some a)

can be encoded as

let f ::: ([a],b)-c
f (x::[a],ys) = rhs
in body


The main motivation behind Chameleon's lexically scoped annotations
was to allow for programs such as

class Eval a b where eval::a-b
f :: Eval a (b,c) = a-b
f x = let g :: (b,c)
  g = eval x
  in fst g

As Josef pointed out, there are also examples where it might be useful
that some inner annotations refer to variable a from the outer annotation.

Martin
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] A puzzle and an annoying feature

2004-11-26 Thread Lennart Augustsson
Martin Sulzmann wrote:
[Discussion moved from Haskell to Haskell-Cafe]
Hi,
Regarding
- lazy overlap resolution aka unique instances
Well, if there's only instance which is not exported, then you can
use functional dependencies.
Assume
class C a
instance ... = C t
Internally, use
class C a | - a
instance ... = C t
 
But using functional dependencies feels like a sledge hammer,
and it is also not Haskell 98.
-- Lennart
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] A puzzle and an annoying feature

2004-11-26 Thread Martin Sulzmann
Lennart Augustsson writes:

  [...]
  
  But using functional dependencies feels like a sledge hammer,
  and it is also not Haskell 98.
  

Well, I'm simply saying that your proposed extension which is not
Haskell 98 can be expressed in terms of a known type class extension.

I agree that something weaker than FDs would be sufficient here.

Martin

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] A puzzle and an annoying feature

2004-11-26 Thread Keean Schupke
Martin Sulzmann wrote:
Well, if there's only instance which is not exported, then you can
use functional dependencies.
Assume
class C a
instance ... = C t
Internally, use
class C a | - a
instance ... = C t
 

The cases I was looking at had more than one instance, but thats
cool! (I didn't realise  - a was valid syntax without a LHS for the 
arrow.
Oleg has written quite a bit about using fundeps to close classes. Surely
you can export this as well - any attempt to add another instance will
conflict with the fundep (- a) which effectively says there can only be
one instance as all the LHS will overlap (all being the empty set)?


Furthermore, there seems to be an issue that has been overlooked so far.
- Providing sufficient type annotations
 

Well in the toy example, yes... but quite often this occurs where the
type is derived and extreemly complex - the whole point is you don't
really want to be type annotating every assignment. Also you may
really want polymorphism, you just have only one instance at the moment.
(duing development, or in a user extensible library)
   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] A puzzle and an annoying feature

2004-11-26 Thread Keean Schupke
Seeing as we are taling about type class extensions, can you see any 
problems
with the following...

class X x
instance Int
instance Float
instance x
Here we have overlapping instances... (bad), but if we look at the cases 
there
is one which will match 'x' but never any of the others... that is when the
overloading is unresolved... like in:

   show (read y)
suppose we replace X with
class X x y | x - y
instance Int Int
instance Float Float
instance x Int
What we mean is for 'x' to catch anything that does not match (not Int 
or Float)...
but this is broken because the programs meaning can change when extra 
instances
are added... But considering above, the 'unresolved condition' is 
included in x, as
well as all the overlapping cases... so is it safe to say:

class X x y | x - y
instance Int Int
instance Float Float
instance (_|_) Int
Where (_|_) is some symbol that represents no match is possible or a 
failure of
the overloading resolution... This _cannot_ overlap with the other 
instances, and
is distinct (the meaning does not change if instances are added)...

This could be used to force resolution in unresolvable cases (much like 
Integrals
default to Integer is ambiguous)...

Any thoughts?
   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Yet another IO initializer: Effectful declarations and an ACIO monad

2004-11-26 Thread Ian . Stark
On Fri, 26 Nov 2004, George Russell wrote:

 Ian Stark wrote (snipped):
   Way back in this thread, Koen Claessen mentioned the idea of a commutative
   version of the IO monad for handling things with identity.  That doesn't 
 quite
   do it, but I have a refinement that might.  The thing is to focus on IO
   computations that are:
  
a) central -- their effect commutes with every other IO action
b) affine  -- their effect is not directly observable, and can be 
 discarded.

 Unfortunately I have a number of examples where I use global variables with
 initialisation actions which cannot conceivably be proven to be central  
 affine
 by the compiler.  For example, where I want to call up an external program 
 (such
 as wish) which I will later use for doing graphics.

This indeed can't be proved central+affine, because it isn't.  So instead,
choose one of the following:

1 (Good) Indirection:

  declare gc - newIORef None; so that gc is a global variable holding a
  (Maybe GraphicsContext).  Initialise the contents in your main IO
  action; and then pull out the value any time you need to look at it.

  Yes, you need to explicitly initialise it; but you don't need then to
  pass the initialized handle all around your code.  The painful plumbing
  goes away.


2 (Neutral) As above, but write getGC :: IO GraphicsContext that looks in
  gc, and if there is None then calls out to wish, or whatever, to
  initialise it first.

  Sound, but getGC then hides some wildly varying behaviour.


3 (Evil) Give in to the dark side.  Have unsafeIOtoACIO, write a
  declaration using it, and hope that your compiler does the easy thing
  and executes all declarations at the start of the program.

  In fact not much worse than (2); only now the possible effect points
  have leapt from all uses of gc to all uses of IO.


 The Haskell libraries would run into a similar problem when they tried to
 open stdin/stdout/stderr.

But they don't open them, right?  The whole point of stdin/stdout/stderr
being fixed integers is that these handles are already opened when the
program starts.


 Or indeed when they tried to implement RandomGen, which I presume is
 going to want to get at the system clock to seed the random number
 generator.

Yes, the system StdGen really does have to get initialised.  But the
presumed readRandomNumberFromSystem() is ACIO if it's random (OK, so if
it's implemented by opening /dev/random, then this would have to be
wrapped in assertIOisACIO).

--
Ian Stark   http://www.ed.ac.uk/~stark
LFCS, School of Informatics, The University of Edinburgh, Scotland
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Yet another IO initializer: Effectful declarations and an ACIO monad

2004-11-26 Thread George Russell
[EMAIL PROTECTED] wrote:
(initialising by wish)
This indeed can't be proved central+affine, because it isn't.  So instead,
choose one of the following:
 1 (Good) Indirection:
   declare gc - newIORef None; so that gc is a global variable holding a
  (Maybe GraphicsContext).  Initialise the contents in your main IO
  action; and then pull out the value any time you need to look at it.

  Yes, you need to explicitly initialise it; but you don't need then to
  pass the initialized handle all around your code.  The painful plumbing
  goes away.
I think this is either unwieldy or inefficient. Imagine a large library
containing lots of these things which need to be initialised if used.  Then
I predict that one of two things will happen
(a) people will end up writing boilerplace code at the start of the main
action which does
   initialise1
   initialise2
   ... blah blah ...
(b) (more likely).  There will be a single initialisation function for the
library, which initialises everything, even the stuff you don't actually
want.
2 (Neutral) As above, but write getGC :: IO GraphicsContext that looks in
  gc, and if there is None then calls out to wish, or whatever, to
  initialise it first.
  Sound, but getGC then hides some wildly varying behaviour.
I think this is basically what my Data.GlobalVariables module does,
except that most of the work is done for you and you also get the
bonus of being able to create fresh worlds within your program (so
that two copies of main can be run concurrently, for example).


3 (Evil) Give in to the dark side.  Have unsafeIOtoACIO, write a
  declaration using it, and hope that your compiler does the easy thing
  and executes all declarations at the start of the program.
  In fact not much worse than (2); only now the possible effect points
  have leapt from all uses of gc to all uses of IO.
The real danger of unsafeIOtoACIO is that a compiler may well choose
to implement ACIO declarations by only initialising variables when
they are actually needed.  Thus possible effect points will not just
be all uses of IO, but everywhere in the program.
But they don't open them, right?  The whole point of stdin/stdout/stderr
being fixed integers is that these handles are already opened when the
program starts.
Surely not?  Haskell buffers have to be initialised and so on.
Yes, the system StdGen really does have to get initialised.  But the
presumed readRandomNumberFromSystem() is ACIO if it's random (OK, so if
it's implemented by opening /dev/random, then this would have to be
wrapped in assertIOisACIO).
So assertIOisACIO will have to exist, if only in an internal GHC module ...
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Real life examples

2004-11-26 Thread Keean Schupke
I've replied to the cafe, as per requests...
Peek and poke are instances of the Storable class, I can
re-implement storable, and provide the alternative definition
by giving ghc some -isomething arguments. I don't even
need to recompile your module, simply providing the alternate
Storable module at link time is sufficient.
So I restate my point, it _can_ be done in Haskell as it stands at
the moment, and yor proposal would break this.
   Keean.
Adrian Hey wrote:
On Friday 26 Nov 2004 11:39 am, Keean Schupke wrote:
 

Adrian Hey wrote:
   

Well it can be written in Haskell, but not using a module that was
specifically designed to prevent this.
 

Well, It can be written in Haskell as it stands at the moment...
   

No it can't. If I have a device driver that's accessing real hardware
(peeking and poking specific memory locations say), how are you going
to emulate that? You need to make peek and poke parameters of the
module.
That is certainly possible, but if the author of the driver module
didn't anticipate your emulation needs, you'd be stuck I think.
Regards
--
Adrian Hey
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-26 Thread Benjamin Franksen
[for the 4th time moving this discussion to cafe]

On Friday 26 November 2004 08:39, you wrote:
 Benjamin Franksen wrote (snipped):
   Doesn't that run contrary to Adrian Hey's oneShot example/requirement?

 Remind me again what Adrian Hey's oneShot example/requirement is ...

http://www.haskell.org//pipermail/haskell/2004-November/014766.html

 [...]
   Furthermore, I have great difficulty in understanding why different
   threads need different dictionaries. Could you explain why this is
   useful, or rather, more useful than a global single dictionary?

 Consider Data.Unique implemented over lots of processors.  If you had a
 single IORef managed by a single processor used to generate new unique
 identifiers, there is the danger that that processor will become a
 bottleneck for the whole system.  Much better to have a thread-local or
 processor-local IORef which generates new identifiers, which you then
 prepend with a processor tag.

I see. Note that currently there exists no Haskell implementation that is able 
to make use of multiple processors. See

http://research.microsoft.com/Users/simonpj/papers/conc-ffi/conc-ffi.ps

Having read

http://www.haskell.org//pipermail/haskell-cafe/2004-November/007666.html

again, as well as your comments above, I tend to agree that withEmptyDict may 
indeed be useful. However, the situations you describe are somewhat special. 
They can and should be handled by explicitly calling withEmptyDict.

I still can't see any reason why each single Haskell thread should have its 
own searate dictionary. Contrary, since it is common to use forkIO quite 
casually, and you expect your actions to do the same thing regardless of 
which thread calls them, this would be disastrous. IMO GlobalVariables.hs 
shouldn't be aware of threadIds at all.

   What non-standard libraries have I used (that you don't)?

 [...explanation...]

I see. Thanks for the explanation.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Yet another IO initializer: Effectful declarations and an ACIO monad

2004-11-26 Thread Jules Bean
On 26 Nov 2004, at 12:08, George Russell wrote:
  Yes, you need to explicitly initialise it; but you don't need then 
to
  pass the initialized handle all around your code.  The painful 
plumbing
  goes away.
I think this is either unwieldy or inefficient. Imagine a large library
containing lots of these things which need to be initialised if used.  
Then
I predict that one of two things will happen
(a) people will end up writing boilerplace code at the start of the 
main
action which does
   initialise1
   initialise2
   ... blah blah ...
(b) (more likely).  There will be a single initialisation function for 
the
library, which initialises everything, even the stuff you don't 
actually
want.

To me this seems perfectly fine. Ian's proposal gets us TWIs, which I 
can see the need for. Implicit initialisation (i.e. stateful 
initialisation functions happening non-deterministicly, like java 
static{} blocks or C++'s similar feature) is a can of worms I currently 
see no value in opening.

Jules
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-26 Thread Benjamin Franksen
On Friday 26 November 2004 14:12, Benjamin Franksen wrote:
 I still can't see any reason why each single Haskell thread should have its
 own searate dictionary. Contrary, since it is common to use forkIO quite
 casually, and you expect your actions to do the same thing regardless of
 which thread calls them, this would be disastrous. IMO GlobalVariables.hs
 shouldn't be aware of threadIds at all.

I think I misunderstood your proposal (GlobalVariables.hs). It seems to do 
what I would expect, if your version of forkIO is used. I thought by 
inheriting the dictionary you meant working on a new copy, but it does in 
fact mean using the same dictionary.

Sorry for the confusion.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Yet another IO initializer: Effectful declarations and an ACIO monad

2004-11-26 Thread Ian . Stark
On Fri, 26 Nov 2004, Jules Bean wrote:
On 26 Nov 2004, at 12:08, George Russell wrote:
  Yes, you need to explicitly initialise it; but you don't need then to
  pass the initialized handle all around your code.  The painful plumbing
  goes away.
I think this is either unwieldy or inefficient. Imagine a large library
containing lots of these things which need to be initialised if used.  Then
I predict that one of two things will happen
(a) people will end up writing boilerplace code at the start of the main
action which does
   initialise1
   initialise2
   ... blah blah ...
(b) (more likely).  There will be a single initialisation function for the
library, which initialises everything, even the stuff you don't 
actually
want.
To me this seems perfectly fine. Ian's proposal gets us TWIs, which I can see 
the need for. Implicit initialisation (i.e. stateful initialisation functions 
happening non-deterministicly, like java static{} blocks or C++'s similar 
feature) is a can of worms I currently see no value in opening.
It's true that ACIO only does some things: and that includes global 
variables initialized with values.  I think that's pretty useful; but 
it's true that we don't get initializing with arbitrary IO activity.

Even when you do want to open the can of worms, things are better: 
unsafePerformIO needs an accompanying NOINLINE pragma, whereas pushing 
things through assertIOisACIO will guarantee execution no more than once.

I.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Real life examples

2004-11-26 Thread Sven Panne
Keean Schupke wrote:
[...] I don't even need to recompile your module, simply providing
the alternate Storable module at link time is sufficient. [...]
[ Completely off-topic for this thread ] But this *won't* work in the
presence of cross-module inlining, e.g. when you are using GHC with
-O or -O2. And IMHO this aggressive inlining is a very good thing.
Haskell is not C. :-)
Cheers,
   S.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Real life examples

2004-11-26 Thread Keean Schupke
Hi,
Sven Panne wrote:
Keean Schupke wrote:
[...] I don't even need to recompile your module, simply providing
the alternate Storable module at link time is sufficient. [...]

[ Completely off-topic for this thread ] But this *won't* work in the
presence of cross-module inlining, e.g. when you are using GHC with
-O or -O2. And IMHO this aggressive inlining is a very good thing.
Haskell is not C. :-)
If a function is exported it cannot be inlined, can it? When I edit a module
I generally don't have to recompile my whole program even if I compile with
-O2... After all the fuss about certain type class extensions breaking 
separate
compilation it would be a bit odd if it was broken already?

   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Execution Contexts

2004-11-26 Thread Benjamin Franksen
I finally understood that George Russell's Library is not really about global 
variables. Rather it is about what I want to call 'execution contexts', which 
are -- as Marcin Kowalczyk observed -- a restricted form of dynamically 
scoped variables.

[NB: Another (maybe better) name would have been 'execution environment' but 
the name environment is too heavily associated with the related concept of 
process environment (the string to string map given to user processes as an 
implicit argument).]

An execution context is a mutable finite map from types to (monomorphic) 
values. Each IO action implicitly carries exactly one such map and by default 
passes it on to the actions that follow. A function is provided to 
(implicitly) create a new mapping and run a given IO action with the new 
mapping as its execution context, instead of the default one.

[NB: I also understand now why the library uses ThreadIds. This was obscure to 
me at first because in principle all this has nothing to do with concurrency 
(beside the requirement that accessing the context should be thread safe). 
ThreadIds are used simply because they are available as an index and nothing 
else is. Its just a hack.]

Seen this way, the whole thing smells very much of monads. Indeed, the monadic 
implementation is trivial. I attached a proof-of concept implementation, 
using George Russel's 'Dict' as an abstract data type in a separate module 
(copied verbatim from GlobalVariables.hs, see attached file Dict.hs). The 
idea: we define

type Context = MVar Dict

and introduce an eXtended version of the IO monad

type XIO a = StateT Context IO a

together with a small number of simple functions that implement the same 
interface as the original GlobalVariables.hs; no unsafe operations are used, 
everything is Haskell98 + Dynamics. Also ThreadIds do not appear and it is 
not necessary to change forkIO (apart from lifting it, of course). (code is 
in ExecutionContext.hs)

I modified George's test program so that it works with ExecutionContexts. The 
program is completely isomorphic to the original (and does the same, too ;). 
The only major difference is that all IO operations are lifted into the XIO 
monad. Again, almost everything is Haskell98, -fglasgow-exts is only needed 
to derive Typeable (which can also be done manually). (Code is in 
TestExecutionContext.hs)

The only task that remains to support this programming style so that it can be 
used practically, is to redefine IO as XIO in the kernel libraries. The 
annoying liftIOs everywhere (and the necessity to invent higher order lifts 
along the way) would be gone. I am almost sure that even the trick of 
indexing the dictionary via types (and thus the dependency on Data.Typeable 
and ghc extensions) can be avoided with a little more effort.

Ben
-- ---
-- The Dict type
-- ---
module Dict (
  Dict,
  emptyDict,
  lookupDict,
  addToDict,
  delFromDict
  ) where

import Data.Dynamic
import Data.Maybe

-- | Stores a set of elements with distinct types indexed by type
-- NB.  Needs to use a FiniteMap, when TypeRep's instance Ord.
newtype Dict = Dict [(TypeRep,Dynamic)]

-- | Dict with no elements.
emptyDict :: Dict
emptyDict = Dict []

-- | Retrieve an element from the dictionary, if one of that type exists.
lookupDict :: Typeable a = Dict - Maybe a
lookupDict (Dict list) =
   let
  -- construct a dummy value of the required type so we can get at its
  -- TypeRep.
  Just dummy = (Just undefined) `asTypeOf` aOpt

  -- get at the required result type.
  dynOpt = lookup (typeOf dummy) list 

  aOpt = case dynOpt of
 Nothing - Nothing
 Just dyn - 
Just (
   fromMaybe 
  (error Inconsistent type in Dict)
  (fromDynamic dyn)
   )
   in
  aOpt

-- | Add an element to the dictionary if possible, or return Nothing if it
-- isn't because one of that type already exists.
addToDict :: Typeable a = Dict - a - Maybe Dict
addToDict (Dict list) val =
   let
  typeRep = typeOf val
   in
  case lookup typeRep list of
 Just _ - Nothing
 Nothing - Just (Dict ((typeRep,toDyn val) : list))

-- | Delete an element from the dictionary, if one is in it, or return Nothing
-- if it isn't.
delFromDict :: Typeable a 
   = Dict 
   - a -- ^ this value is only interesting for its type, and isn't looked at.
   - Maybe Dict
delFromDict (Dict list) val =
   let
  typeRep = typeOf val

  dList [] = Nothing
  dList ((hd@(typeRep2,_)):list2) = 
 if typeRep == typeRep2
then
   Just list2
else
   fmap (hd:) (dList list2)
   in
  fmap Dict (dList list)
module ExecutionContext where

import Control.Concurrent
import Control.Monad
import Control.Monad.State
import Data.Typeable


[Haskell-cafe] Re: Lexically scoped type variables

2004-11-26 Thread oleg

Simon Peyton-Jones wrote:
 In GHC at present, a separate type signature introduces no scoping.  For
 example:
 f :: forall a. a - a
 f x = (x::a)
 would be rejected, because the type signature for 'f' does not make
 anything scope over the right-hand side, so (x::a) means (x::forall
 a.a), which is ill typed.

OTH, `f x = (x::a)' will be accepted if this definition appears in an
instance declaration, which mentions the type variable `a' somewhere
in its `signature'.
Incidentally, Hugs differs from GHC in that matter: Hugs considers type
variables in an instance declaration just like type variables in a
function signature -- having no effect on the local type variables.
One might say that Hugs is more consistent in that matter -- OTH, GHC
is more convenient, IMHO. 

The alternative
   1b) It's brought into scope even if the forall is implicit; e.g.
 f :: a - a
 f x = (x::a)

would seem therefore consistent with the existing behavior of GHC with
respect to `instance signatures'.


 2b) Get rid of result type signatures altogether; instead,
   use choice (1a) or (1b), and use a separate type signature

We can always emulate the result type signatures: that is, instead of
writing
foo a :: resType = body
we can write
foo a = result where result body
and use `asTypeOf` result wherever we need to refer to resType. Or we
can write
foo a = result where
  result = cid result
  cid (_::resType) = body
to reduce the result type signature to the argument type signature. 

OTH, I have personally used result type signatures on many occasions
and found them quite helpful. I would be grateful if there were a way
to keep them.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe