[Haskell] Implicit Parameters in Instance Declarations

2007-05-14 Thread Ashley Yakeley
Would horrible things happen if implicit parameters were allowed as contexts in instance declarations? instance (?limit :: Int) => Eq Thing where ... -- Ashley Yakeley ___ Haskell mailing list Haskell@haskell.org http://www.haskell.

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-31 Thread Frederik Eaton
On Mon, Jul 31, 2006 at 03:09:59PM +0300, Einar Karttunen wrote: > On 31.07 03:18, Frederik Eaton wrote: > > I don't think it's necessarily such a big deal. Presumably the library > > with the worker threads will have to be invoked somewhere. One should > > just make sure that it is invoked in the

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-31 Thread Einar Karttunen
On 31.07 14:03, Thomas Conway wrote: > This is why I believe transaction-local variables are a more useful concept. > You are garanteed that there is only one thread accessing them, and > they behave just like ordinary TVars except that each transaction has > its own copy. This seems like it could

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-31 Thread Einar Karttunen
On 31.07 03:18, Frederik Eaton wrote: > I don't think it's necessarily such a big deal. Presumably the library > with the worker threads will have to be invoked somewhere. One should > just make sure that it is invoked in the appropriate environment, for > instance with the database connection alre

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Thomas Conway
Hi All, On 7/31/06, Einar Karttunen wrote: My main objection to the TLS is that it looks like normal IO, but changing the thread that evaluates it can break things in ways that are hard to debug. E.g. we have an application that uses TLS and passes an IO action to a library that happens to use

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Frederik Eaton
On Mon, Jul 31, 2006 at 03:54:29AM +0300, Einar Karttunen wrote: > On 30.07 11:49, Frederik Eaton wrote: > > No, because the thread in which it runs inherits any thread-local > > state from its parent. > > So we have different threads modifying the thread-local state? > If it is a copy then update

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Einar Karttunen
On 30.07 11:49, Frederik Eaton wrote: > No, because the thread in which it runs inherits any thread-local > state from its parent. So we have different threads modifying the thread-local state? If it is a copy then updates are not propagated. What about a design with 10 worker threads taking req

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Frederik Eaton
On Sun, Jul 30, 2006 at 12:35:42PM +0300, Einar Karttunen wrote: > On 29.07 13:25, Frederik Eaton wrote: > > I think support for thread-local variables is something which is > > urgently needed. It's very frustrating that using concurrency in > > Haskell is so easy and nice, yet when it comes to IO

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Einar Karttunen
On 29.07 13:25, Frederik Eaton wrote: > I think support for thread-local variables is something which is > urgently needed. It's very frustrating that using concurrency in > Haskell is so easy and nice, yet when it comes to IORefs there is no > way to get thread-local behavior. Furthermore, that on

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-29 Thread Thomas Conway
I would also note that some form of transaction-local variable would also be really handy for STM usage. Tom ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-29 Thread Frederik Eaton
Hi, Sorry to bring up this thread from so long ago. On Wed, Mar 01, 2006 at 11:53:42AM +, Simon Marlow wrote: > Ashley Yakeley wrote: > >Simon Marlow wrote: > >>Simon & I have discussed doing some form of thread-local state, which > >>covers many uses of impli

Re: [Haskell] Re: Implicit Parameters

2006-03-02 Thread Bulat Ziganshin
Hello Lauri, Thursday, March 2, 2006, 3:25:31 PM, you wrote: LA> Now, I wonder whether we really really really need to track implicit LA> parameters in the type system. After all, exceptions, too, introduce a there is also another way - allow "partial function signatures" -- Best regards, Bul

[Haskell] Re: Implicit Parameters

2006-03-02 Thread Lauri Alanko
On Wed, Mar 01, 2006 at 11:53:42AM +, Simon Marlow wrote: > something along these lines is likely to be quite straightforward to > implement, won't require any changes to the type system, and gives you > a useful form of implicit parameters without any of the drawbacks.

[Haskell] Re: Implicit Parameters

2006-03-01 Thread Simon Marlow
Ashley Yakeley wrote: Simon Marlow wrote: Simon & I have discussed doing some form of thread-local state, which covers many uses of implicit parameters and is much preferable IMO. Thread-local state doesn't change your types, and it doesn't require passing any extra paramet

[Haskell] Re: Implicit Parameters

2006-02-28 Thread Ashley Yakeley
Simon Marlow wrote: Simon & I have discussed doing some form of thread-local state, which covers many uses of implicit parameters and is much preferable IMO. Thread-local state doesn't change your types, and it doesn't require passing any extra parameters at runtime. It works

Re: [Haskell] Re: Implicit Parameters

2006-02-28 Thread Bulat Ziganshin
Hello Simon, Tuesday, February 28, 2006, 5:40:35 PM, you wrote: SM> Simon & I have discussed doing some form of thread-local state, which this means new RTS primitives, like that used in IORef implementation? -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___

[Haskell] Re: Implicit Parameters

2006-02-28 Thread Simon Marlow
Ashley Yakeley wrote: Ben Rudiak-Gould wrote: I'd advise against using implicit parameters, because (as you've seen) it's hard to reason about when they'll get passed to functions. And Johannes Waldmann wrote: > Implicit parameters are *evil*. They seem to simpli

Re: [Haskell] Implicit Parameters

2006-02-27 Thread Robert Dockins
On Feb 27, 2006, at 3:31 PM, Ashley Yakeley wrote: Ben Rudiak-Gould wrote: I'd advise against using implicit parameters, because (as you've seen) it's hard to reason about when they'll get passed to functions. And Johannes Waldmann wrote: > Implicit parameters a

[Haskell] Implicit Parameters

2006-02-27 Thread Ashley Yakeley
Ben Rudiak-Gould wrote: I'd advise against using implicit parameters, because (as you've seen) it's hard to reason about when they'll get passed to functions. And Johannes Waldmann wrote: > Implicit parameters are *evil*. They seem to simplify programs > but they make

[Haskell] Re: "strange" behavior of Implicit Parameters

2006-02-27 Thread Ben Rudiak-Gould
I'd advise against using implicit parameters, because (as you've seen) it's hard to reason about when they'll get passed to functions. Another example: http://www.haskell.org/pipermail/haskell-cafe/2005-January/008571.html -- Ben ___

RE: [Haskell] "strange" behavior of Implicit Parameters

2006-02-27 Thread Simon Peyton-Jones
] On Behalf Of Eike Scholz | Sent: 27 February 2006 00:14 | To: haskell@haskell.org | Subject: [Haskell] "strange" behavior of Implicit Parameters | | Hi, | | I have just a short question, about the semantics of Implicit parameters | on GHC 6.4. | | Given the following code: | | > (???)

[Haskell] "strange" behavior of Implicit Parameters

2006-02-26 Thread Eike Scholz
Hi, I have just a short question, about the semantics of Implicit parameters on GHC 6.4. Given the following code: > (???) x f > = let ?foo = 1337 > in f x > fun :: (?foo::Int,Show x) => x -> String > fun x = "x = "++(show x)++"; ?foo = &qu

[Haskell] linear implicit parameters

2005-03-02 Thread Immanuel Litzroth
Has anybody got a good example of how to use linear implicit parameters? I seem to be unable to understand the description in the ghc manual and I couldn't find a paper on the web. Immanuel *** I can, I can

[Haskell] RE: Implicit parameters:

2005-02-04 Thread Simon Peyton-Jones
to reflect this)... Keean's program has made me realise (yet again) that implicit parameters are a bit different to class constraints. Consider module Main where main = let ?x = 5 in print foo foo = woggle 3 woggle :: (?x :: Int) => Int -> Int wog

Re: [Haskell] implicit parameters and the paper "prepose.pdf"

2004-11-20 Thread John Velman
Thanks to everyone who answered! I now have a copy. Best to all, John Velman ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] implicit parameters and the paper "prepose.pdf"

2004-11-20 Thread Dylan Thurston
On Sat, Nov 20, 2004 at 09:26:08AM -0800, John Velman wrote: > In a recent message to this list (msg15410) Oleg referenced a paper > comparing implicit parameters and implicit configurations with url > http://www.eecs.harvard.edu/~ccshan/prepose/prepose.pdf . I'd like to read > t

[Haskell] implicit parameters and the paper "prepose.pdf"

2004-11-20 Thread John Velman
In a recent message to this list (msg15410) Oleg referenced a paper comparing implicit parameters and implicit configurations with url http://www.eecs.harvard.edu/~ccshan/prepose/prepose.pdf . I'd like to read this, (and examine the companion literate haskell file prepose.lhs)

Re: [Haskell] Implicit parameters

2004-06-09 Thread Iavor S. Diatchki
more polymorphic then a schema) hope this helps, for details on the polymorphism & subtyping you may take a look at a number of papers over the past few years. there are some on simon pj's page i forget the exact title, but it is easy to find. -iavor Per Larsson wrote: When using

[Haskell] Implicit parameters

2004-06-09 Thread Per Larsson
When using implicit parameters I have noticed (at least for me) a rather puzzling behaviour with GHC and Hugs. Given the declarations data Env = Env {numlines :: Int, numcols :: Int} initEnv = Env {numlines = 0, numcols = 1} withEnv :: ((?env :: Env) => IO a) -> IO a withEnv io = le

Re: [Haskell] Re: Implicit parameters redux

2004-01-29 Thread Ben Rudiak-Gould
it's formally sound, though. Also, it would be nice if the type-class system could be implemented in terms of implicit parameters (plus sugar), and this extension would help with that. It might be possible to just parameterize the type of the implic

[Haskell] Re: Implicit parameters redux

2004-01-29 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > Another extension I proposed is that the "name" of an implicit return > value can include type parameters: thus %foo Int and %foo Char would be > treated as though they had different names. This bit doesn't seem very p

Re: [Haskell] Implicit parameters redux

2004-01-29 Thread Ben Rudiak-Gould
the user to supply a configuration file with names. So I encapsulate all this in a table of names and pass it to showExpr, and I get code like showExpr names (TheProcedure addr) = lookupProcedureName names addr But the rest of showExpr and showStatement get needlessly ugly, because they h

Re: [Haskell] Implicit parameters redux

2004-01-28 Thread David Sankel
Ben, Could you explain in an extremely dumbed-down way what this is? It would be great if there were examples of 1) Some common, simple, and useful code in Haskell. 2) Same code using Implicit Parameters with a discussion of how it is better. Thanks, David J. Sankel

[Haskell] Implicit parameters redux

2004-01-27 Thread Ben Rudiak-Gould
%y reversed, and also to ((123, %y = 99), %x = "foo") These implicit return values propagate upward through expressions in the same way that implicit parameters propagate downward. They can be "caught" at the root of an expression by matching against a similar syntax: case ex

Re: Implicit parameters, second draft

2003-08-14 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > The proposed notation seems to be almost the same as the existing > field-label notation semantically as well as syntactically, which suggests > that it wouldn't be a destabilizing addition. (See section 2.5.) Might th

Implicit parameters, second draft

2003-08-14 Thread Ben Rudiak-Gould
re I lay out my specific suggestions for changes to the existing implementations. 1. The new framework I will develop the idea of implicit parameters using a different approach from that of the original paper by Lewis et al. (hereafter "LSML"). In my approach implicit parameters wi

Re: The madness of implicit parameters: cured?

2003-08-11 Thread Ashley Yakeley
At 2003-08-04 22:33, Ben Rudiak-Gould wrote: >This illustrates what you pointed out earlier, that the >program's semantics can be changed by adding explicit type signatures >which include implicitly-parameterized parameters. But wasn't avoiding this a design goal of your proposal? >> If it is va

Re: Implicit parameters, second draft

2003-08-10 Thread Ben Rudiak-Gould
On Sat, 9 Aug 2003, Ashley Yakeley wrote: > I'm a bit worried about the use of curly braces. Currently they're used > to mark blocks when "layout" isn't used. Might this clash? > > IIRC braces are used after "do", "where", "let", "in" and "of" (probably > OK), and also for data structures with

Re: Implicit parameters, second draft

2003-08-09 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > 3.1. Changes which are easy to implement and seem to be clear wins ... > * Introduce the {?x = ...} syntax for implicit-parameter > application. (Should this be in section 3.3?) I'm a bit worried about the use of

Re: The madness of implicit parameters: cured?

2003-08-07 Thread Ben Rudiak-Gould
PROTECTED] -> ((\a -> ((a,[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = 2})) @x) If we next apply (\a -> ...) to @x, something interesting happens: we have to rename to avoid variable capture. I didn't realize this was ever necessary with implicit parameters. The renaming is impo

Re: The madness of implicit parameters: cured?

2003-08-06 Thread Ben Rudiak-Gould
rect. This is a different lambda calculus, with a different beta rule. You can see the same effect in the type inference rules for implicit parameters: If f has type Int -> String and ?x has type (?x :: Int) => Int, then f ?x has type (?x :: Int) => String, i.e. the implicit ?x parameter

Re: The madness of implicit parameters: cured?

2003-08-05 Thread Ben Rudiak-Gould
pes are ambiguous? Yes, it's effectively the same; that was the point. I'm not trying to create a new language extension, but an improved conceptual foundation for the existing extension. It's fine if I don't end up with quite the design I expected, as long as it coheres. Th

Re: The madness of implicit parameters: cured?

2003-08-05 Thread Ashley Yakeley
At 2003-08-04 18:19, Ben Rudiak-Gould wrote: >> ((\a -> ((a,[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = 2})) ([EMAIL PROTECTED] -> >> @x),[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = 1} > ^^^ >> (([EMAIL PROTECTED] -> @x,[EMAIL PROTECTED] -> @x) [EMAIL PROTECT

Re: The madness of implicit parameters: cured?

2003-08-04 Thread Ben Rudiak-Gould
On Mon, 4 Aug 2003, Ashley Yakeley wrote: > At 2003-08-04 20:00, Ben Rudiak-Gould wrote: > > >This is a different lambda calculus, with a different beta rule. You can > >see the same effect in the type inference rules for implicit parameters: > >If f has type Int ->

Re: The madness of implicit parameters: cured?

2003-08-04 Thread Ashley Yakeley
At 2003-08-04 20:00, Ben Rudiak-Gould wrote: >This is a different lambda calculus, with a different beta rule. You can >see the same effect in the type inference rules for implicit parameters: >If f has type Int -> String and ?x has type (?x :: Int) => Int, then f ?x >h

Re: The madness of implicit parameters: cured?

2003-08-04 Thread Ashley Yakeley
At 2003-08-04 18:19, Ben Rudiak-Gould wrote: > [EMAIL PROTECTED] -> ((\a -> ((a,[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = > 2})) @x) > >If we next apply (\a -> ...) to @x, something interesting happens: we >have to rename to avoid variable capture. I don't see why, isn't this much the s

Re: The madness of implicit parameters: cured?

2003-08-04 Thread Ashley Yakeley
At 2003-08-03 14:09, Ben Rudiak-Gould wrote: >This reduction is incorrect. Auto-lifted parameters on the RHS of an >application get lifted out I am interpreting this as "Auto-lifted parameters on the RHS of an application get lifted out before [EMAIL PROTECTED] 'beta'-reduction can be done". I

Re: The madness of implicit parameters: cured?

2003-08-04 Thread Ben Rudiak-Gould
Trouble for implicit parameter defaults: consider ?foo = 0 let x = ?foo in (x + ?foo) { ?foo = 1 } This evaluates to 1 when the monomorphism restriction is turned on, and 2 when it's off. This is no worse than the current behavior of implicit parameters even wi

Re: The madness of implicit parameters: cured?

2003-08-04 Thread Wolfgang Lux
Ben Rudiak-Gould wrote: [...] The final straw was: Prelude> let ?x = 1 in let g = ?x in let ?x = 2 in g 1 Prelude> let ?x = 1 in let g () = ?x in let ?x = 2 in g () 2 This is insanity. I can't possibly use a language feature which behaves in such a non-orthogonal way. Well, this i

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
On Sun, 3 Aug 2003, Derek Elkins wrote: > I kinda think someone mentioned this, perhaps even you. Or maybe I'm > thinking of something else. As I'm feeling too lazy to check the > archives, at the risk of saying something stupid or repeating something > said, you may want to look at named instan

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
On Sun, 3 Aug 2003, Ashley Yakeley wrote: > At 2003-08-03 14:09, Ben Rudiak-Gould wrote: > > g ([EMAIL PROTECTED] -> @x) => ([EMAIL PROTECTED] -> g { @x = @x } @x) > > Hmm... I assume you mean specifically this: > > g ([EMAIL PROTECTED] -> @x) > [EMAIL PROTECTED] -> (g { @x = @x } @x)

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ashley Yakeley
At 2003-08-03 14:09, Ben Rudiak-Gould wrote: >> ((let g = \_ _ -> [EMAIL PROTECTED] -> @x in ((g ([EMAIL PROTECTED] -> @x)) [EMAIL >> PROTECTED] = 2})) ([EMAIL PROTECTED] -> >> @x))[EMAIL PROTECTED] = 1} >> ((let g = \_ _ -> [EMAIL PROTECTED] -> @x in (g 2)) ([EMAIL PROTECTED] -> >> @x))[EMAI

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Derek Elkins
I kinda think someone mentioned this, perhaps even you. Or maybe I'm thinking of something else. As I'm feeling too lazy to check the archives, at the risk of saying something stupid or repeating something said, you may want to look at named instances (google should turn something up with a littl

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
I just noticed something interesting. Consider f #name = g where g #name = "hello" This apparently has type (#name :: a) -> (#name :: b) -> String. Should the two #names be merged? Clearly not, because ordinary positional parameters never get merged, and named parameters are supposed to be th

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
27;s an error or it's exactly equivalent to "[]". My intuition is that this is a minor problem which would bite very rarely in practice, like "show []". And, let me emphasize again, it's safe: programs will not silently behave in an unexpected way because of this.

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > Now we have something almost the same as the current implicit-parameter > system, except that it behaves in a much safer and saner way. Hmm... you have this: [?x,?x] [EMAIL PROTECTED] -- OK [?x] [EMAIL PROTECTED] --

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Derek Elkins
On Sun, 3 Aug 2003 08:01:52 -0700 (PDT) Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > On Sat, 2 Aug 2003, Derek Elkins wrote: > > > Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > > > > > More recently, I've realized that I really don't underst

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
On Sat, 2 Aug 2003, Derek Elkins wrote: > Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > > > More recently, I've realized that I really don't understand implicit > > parameters at all. They seemed simple enough at first, but when I look > > at an expressio

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ashley Yakeley
ns in the two different cases. Ideally, GHC would complain about the ambiguity. IIRC with -fglasgow-exts turned on there are other cases when GHC infers the "wrong" type if you don't specify it. This is because with higher-order types, there isn't necessarily an inferable &quo

Re: The madness of implicit parameters: cured?

2003-08-02 Thread Derek Elkins
On Sat, 2 Aug 2003 00:45:07 -0700 (PDT) Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > When I first learned about implicit parameters I thought they were a > great idea. The honeymoon ended about the time I wrote some code of > the form"let ?foo = 123 in expr2", where e

The madness of implicit parameters: cured?

2003-08-02 Thread Ben Rudiak-Gould
When I first learned about implicit parameters I thought they were a great idea. The honeymoon ended about the time I wrote some code of the form "let ?foo = 123 in expr2", where expr2 used ?foo implicitly, and debugging eventually unearthed the fact that ?foo's implicit value was n

Re: Implicit Parameters

2002-02-05 Thread John Launchbury
> > My questiona are: Were the designers of the implicit > parameters paper aware of this problem when they wrote the > paper? If so, they probably did not think this was a big > problem. Do people in general think this is a problem? We certainly were aware. It is a problem, and

Re: Implicit Parameters

2002-02-05 Thread John Hughes
. It turned out to be very straightforward to add implicit parameters to Haskell by treating them as a special kind of qualified type, and thus they also play according to the rules of polymorphic types - i.e. you `capture' implicit parameters exactly when you generalize a p

Re: Implicit Parameters

2002-02-04 Thread Jeffrey R. Lewis
implicit parameterisation with polymorphism. Haskell has a two-level type system with monomorphic types at the bottom level, and polymorphic and qualified types at the second level. It turned out to be very straightforward to add implicit parameters to Haskell by treating them as a special ki

Re: Implicit Parameters

2002-02-04 Thread Jeffrey R. Lewis
On Monday 04 February 2002 01:58 am, Koen Claessen wrote: > Hi all, > > Now we are talking about implicit parameters, let us take up > the following problem with them on the Haskell mailing list > too. > > [implicit parameters are not propogated down recursive definiti

RE: Implicit Parameters

2002-02-04 Thread Chris Angus
Title: RE: Implicit Parameters I'm obviously missing something here. I dont understand what monomorphism has to do with the given example as the implicit parameter would be the same type [a] for some type a in each case. If we made the parameter explicit then removing the

Re: Implicit Parameters

2002-02-04 Thread John Hughes
rphic unless a type signature is given; this is the basis for understanding the behaviour above. When implicit parameters are used, it's very important to be aware whether a binding is monomorphic or not (can't resist plugging := again!). Will your "solution" make understanding whe

Implicit Parameters

2002-02-04 Thread Koen Claessen
Hi all, Now we are talking about implicit parameters, let us take up the following problem with them on the Haskell mailing list too. Suppose I have the following function definition: app :: (?ys :: [a]) => [a] -> [a] app xs = case ?ys of [] -> xs (y:ys'

Re: implicit-parameters paper

2001-04-24 Thread Jeffrey R. Lewis
"S.D.Mechveliani" wrote: > Simon P. Jones mentions some paper on implicit parameters > in his recent letter on "Implicit parameters and monomorphism." > > Please, where to find this paper? You can slurp one up from here: http://

implicit-parameters paper

2001-04-24 Thread S.D.Mechveliani
Simon P. Jones mentions some paper on implicit parameters in his recent letter on "Implicit parameters and monomorphism." Please, where to find this paper? - Serge Mechveliani [EMAIL PROTECTED] ___ Haskell mailing l