[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.
 
 The main difference from implicit parameters would be that
 thread-local variables would be restricted to the IO monad.

These two paragraphs sound _heavily_ contradictory to me. The point of
implicit parameters (fluids or just parameters in Scheme) is that
they provide a controlled form of dynamic scoping without introducing
any stateful mess. Implicit parameters are useful in plain purely
functional code just to make certain values customizable without forcing
them to be propagated explicitely everywhere even though default values
are ok most of the time. Restricting them to the IO monad would severely
undermine their purpose.

Now, I wonder whether we really really really need to track implicit
parameters in the type system. After all, exceptions, too, introduce a
certain amount of impurity yet they work just fine in pure code. 
Couldn't the same kind of semantic trickery that was used in the
imprecise exceptions paper also be applied to Scheme-style parameter
objects?


Lauri
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


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,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[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 parameters at runtime.  It works perfectly well for 
the OS example you give, for example.



Interesting. What would that look like in code?


No concrete plans yet.  There have been proposals for thread-local 
variables in the past on this list and haskell-cafe, and other languages 
have similar features (eg. Scheme's support for dynamic scoping).  Doing 
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.


The main difference from implicit parameters would be that thread-local 
variables would be restricted to the IO monad.


Cheers,
Simon
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[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 simplify programs
  but they make reasoning about them much harder.

Feh. Implicit parameters are often exactly what you want. You just have 
to make sure to provide type signatures (-Wall -Werror can help here).


In fact it would be useful to allow implicit parameters and other type 
context at the top level of a module:


  forall m. (Monad m,?getCPUTime :: m Integer) = module MyModule where
timeFunction :: forall a. m a - m (Integer,a)
timeFunction ma = do
  t0 - ?getCPUTime
  a - ma
  t1 - ?getCPUTime
  return (t1 - t0,a)

This is just syntactic sugar that gives this:

  timeFunction :: forall m a. (Monad m,?getCPUTime :: m Integer) =
 m a - m (Integer,a)

In a future Haskell Operating System, this is how system functions could 
be provided to application code. This would make secure sandboxes easy 
to set up, for instance.


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 perfectly well for 
the OS example you give, for example.


Cheers,
Simon
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


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


[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 perfectly well for 
the OS example you give, for example.


Interesting. What would that look like in code?

--
Ashley Yakeley

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] RE: Implicit parameters:

2005-02-04 Thread Simon Peyton-Jones
| Sent: 19 January 2005 14:42
| 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'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
woggle y = ?x + y

GHC's current rules say that 'foo' is monomorphic, so we get
foo :: Int
but we also get an unbound top-level constraint (?x::Int).  GHC emits a
message like:
 Unbound implicit parameter (?x::Int)
 arising from use of `woggle' at ...

The point is that THERE IS NO WAY FOR THIS CONSTRAINT TO GET BOUND,
because we don't have a top-level binding form for implicit parameters.
So it's stupid for 'foo' to be monomorphic.

The situation is a bit different for class constraints:

   module Main where
main = print fooC

fooC = woggleC 3

woggleC :: Num a = a - a
wogglec y = y+1

'fooC' is monomorphic, so we get foo :: a, with a top-level constraint
(Num a); and the defaulting mechanism fixes a=Integer, so all is well.
Even in the absence of monomorphism, we might get some other use of
'fooC' in the module which fixes fooC's type.  So it's *not* stupid for
foo to be monomorphic.


Possible conclusions

A) Emit an error message at the definition of foo, saying that it needs
a type signature.

B) Change the rule so that we always generalise over the implicit
parameters of *top-level* definitions, even in definitions that fall
under the MR.

C) Change the rule so that we always generalise over implicit
parameters, whether top-level or nested.

I'll do (A) for now, I think, since it improves the error message. 

For those that care, there are quite extensive notes about
generalisation and implicit parameters in GHC's source code, here:
http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/typecheck
/TcSimplify.lhs?rev=1.144
(search for Notes on implicit parameters).  Interestingly, the notes
argue for (C), but that's not what is currently implemented in GHC, for
reasons I don't remember.  Perhaps compatibility with other
implementations.


Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Keean Schupke
| Sent: 19 January 2005 14:42
| To: glasgow-haskell-users@haskell.org
| Subject: Implicit parameters:
| 
| 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
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[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 polymorphic-friendly?

-- 
Ashley Yakeley, Seattle WA

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


Re: [Haskell] Re: Implicit parameters redux

2004-01-29 Thread Ben Rudiak-Gould
On Thu, 29 Jan 2004, Ashley Yakeley wrote:

  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 polymorphic-friendly?

Well, there can be type variables there too.

The issue is that there needs to be a source of fresh names for
newly-created state threads, and the simplest solution I could think of
was to return an existentially-quantified %foo s. It's supposed to work
along the lines of a (Num a, Num b) context, where the type checker
doesn't merge the constraints because it can't prove they're equal, even
though it also can't prove they aren't. It's not clear that 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 implicit
parameter instead of its name, and decree that merging happens by name and
type.

-- Ben

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