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 appropriate environment, for
> > instance with the database connection already properly initialized.
> > 
> > (*) One might even want to change the environment a little within each
> > thread, for instance so that errors get logged to a thread-specific
> > log file.
> 
> So we have the following:
> 1) the library is initialized and spawns worker thread Tw
> 2) application initializes the database connection and it
>is associated with the current thread Tc and all the children
>it will have (unless changed)
> 3) the application calls the library in Tc passing an IO action
>to it. The IO action refers to the TLS thinking it is in
>Tc where it is valid.
> 4) the library runs the callback code in Tw where the TLS state is
>invalid. This is even worse than a global variable in this case.

If you have threads, and you have something which needs to be
different among different threads, then it is hard for me to see how
thread-local variables could be worse than global variables in any
case at all.

> Of course one can argue that the application should first initialize
> the database handle. But if the app uses worker threads (spawned
> before library initialization) then things will break if a library
> uses TLS and callbacks and they end up running in threads created
> before the library initialization.

OK, sure. In certain situations you have to keep track of whether a
function to which you pass an action might be sending it off to be run
in a different thread. We've been over this. Perhaps users should be
warned in the documentation - and in the documentation for exceptions
as well. I really don't see that as a problem that would sneak up on
people, since if you're passing an action to a function, rather than
executing it yourself, then in most cases it should be clear to
programmers that the action will run in a different context if not a
different thread altogether. And if you want to force the context to
be the same, you wrap the action in something restoring that context,
just like you would have to do with your state transformer monad
stack.

Another way to write buggy code is to have it so bloated with extra
syntax - e.g. with monad conversions, or extra function parameters, as
you propose - that it becomes impossible to read and understand.

Frederik

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


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 be useful. E.g. marking graph nodes while
traversing them.

> The argument to newLVar is an initial value that is used at the start
> of each transaction.  Note that this means that the value in an LVar
> does not persist between transaction. I agree that this limits their
> use, but simplifies them immensely, and doesn't stand in the way their
> being useful for solving a bunch of problems.

I think that them "reverting" to the initial value is more useful
than persisting behavior.

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


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 already properly initialized.
> 
> (*) One might even want to change the environment a little within each
> thread, for instance so that errors get logged to a thread-specific
> log file.

So we have the following:
1) the library is initialized and spawns worker thread Tw
2) application initializes the database connection and it
   is associated with the current thread Tc and all the children
   it will have (unless changed)
3) the application calls the library in Tc passing an IO action
   to it. The IO action refers to the TLS thinking it is in
   Tc where it is valid.
4) the library runs the callback code in Tw where the TLS state is
   invalid. This is even worse than a global variable in this case.

Of course one can argue that the application should first initialize
the database handle. But if the app uses worker threads (spawned
before library initialization) then things will break if a library
uses TLS and callbacks and they end up running in threads created
before the library initialization.

- Einar Karttunen

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


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
a pool of worker threads that invisible to the application.


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.

I think you'd need an API like

   type LVar a -- "local" var
   newLVar :: a -> STM (LVar a)
   readLVar :: LVar a -> STM a
   writeLVar:: LVar a -> a -> STM ()

The argument to newLVar is an initial value that is used at the start
of each transaction.  Note that this means that the value in an LVar
does not persist between transaction. I agree that this limits their
use, but simplifies them immensely, and doesn't stand in the way their
being useful for solving a bunch of problems.

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


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 updates are not propagated.

As I said, please read my code. There are no "updates".

> What about a design with 10 worker threads taking requests
> from a "Chan (IO ())" and running them (this occurs in real code).
> To get things right they should use the TLS-context relevant
> to each "IO ()" rather than the thread.

I could see how either behavior might be desirable, see below. (*)

> (snip)
> Usually I just define one custom monad for the application which
> wraps the stack of monad transformers. Thus changing the monad stack
> does not affect the application code. A quite clean and efficient
> solution.

That does sound like a clean approach. However, I think that my
approach would be cleaner; and in any case I think that both
approaches should be available to the programmer.

> 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
> a pool of worker threads that invisible to the application. 
> Or the same with the role of the application and library reversed.

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 already properly initialized.

(*) One might even want to change the environment a little within each
thread, for instance so that errors get logged to a thread-specific
log file.

> Offering it up as a separate library should be ok as it would
> be very easy to spot and take extra care not to cause problems.

That's good to hear.

Regards,

Frederik

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


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 requests
from a "Chan (IO ())" and running them (this occurs in real code).
To get things right they should use the TLS-context relevant
to each "IO ()" rather than the thread.
 
> > Now if the action changes the thread local state then
> > it behaves differently. Do we really want that?
> 
> I'm not sure what you're suggesting. The API I proposed actually
> doesn't let users discover when their actions are running in
> sub-threads. (Can you write an example using that API?) However, even
> if it did, I don't see a problem. Do you think that we should get rid
> of 'myThreadId', for instance? I don't.

I do consider using myThreadId bad form for most purposes.
It is nice to have for debugging output - and occasionally
for sending other threads a handle for asynchronous exceptions,
but this can lead to problems when changing threading patterns.

Usually nice code does not care in which thread it is run.

 
> > Usually one can just add a monad that wraps IO/STM and provides the
> > variables one needs. This has the good side of making scoping
> > explicit.
> 
> That's easier said than done. Sometimes I take that route. But
> sometimes I don't want 5 different monads wrapping each other, each
> with its own 'lift' and 'catch' functions, making error messages
> indecipherable and code difficult to read and debug. Do you propose
> creating a special monad for file operations? For network operations? 
> No? Then I don't see why I should have to make a special monad for
> database operations. Or, if the answer was "yes", then fine: obfuscate
> your own code, but please don't ask me to do the same. Let's support
> both ways of doing things, and we can be different.

Usually I just define one custom monad for the application which
wraps the stack of monad transformers. Thus changing the monad stack
does not affect the application code. A quite clean and efficient
solution.

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
a pool of worker threads that invisible to the application. 
Or the same with the role of the application and library reversed.

Offering it up as a separate library should be ok as it would
be very easy to spot and take extra care not to cause problems.

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


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 IORefs there is no
> > way to get thread-local behavior. Furthermore, that one can make
> > certain things thread-local (e.g. with withArgs, withProgName) makes
> > the solution seem close at hand (although I can appreciate that it may
> > not be). Yet isn't it just a matter of making a Map with existentially
> > quantified values part of the state of each thread, just as the
> > program name and arguments are also part of that state?
> 
> Are thread local variables really a good idea in Haskell?

Yes.

> If variables are thread local how would this combinator work:

Do read the code I posted. Please note I'm not suggesting that *all*
variables be thread local, I was proposing a special data-type for
that.

> withTimeOut :: Int -> IO a -> IO a
> withTimeOut tout op = mdo
>   mv <- newEmptyMVar
>   wt <- forkIO $ do try op >>= tryPutMVar mv >> killThread kt
>   kt <- forkIO $ do threadDelay tout
> e <- tryPutMVar mv $ Left $ DynException $ toDyn 
> TimeOutException
> if e then killThread wt else return ()
>   either throw return =<< takeMVar mv
> 
> 
> Would it change the semantics of the action as it is run in a
> different thread (this is a must if there are potentially blocking FFI
> calls).

No, because the thread in which it runs inherits any thread-local
state from its parent.

> Now if the action changes the thread local state then
> it behaves differently. Do we really want that?

I'm not sure what you're suggesting. The API I proposed actually
doesn't let users discover when their actions are running in
sub-threads. (Can you write an example using that API?) However, even
if it did, I don't see a problem. Do you think that we should get rid
of 'myThreadId', for instance? I don't.

> Usually one can just add a monad that wraps IO/STM and provides the
> variables one needs. This has the good side of making scoping
> explicit.

That's easier said than done. Sometimes I take that route. But
sometimes I don't want 5 different monads wrapping each other, each
with its own 'lift' and 'catch' functions, making error messages
indecipherable and code difficult to read and debug. Do you propose
creating a special monad for file operations? For network operations? 
No? Then I don't see why I should have to make a special monad for
database operations. Or, if the answer was "yes", then fine: obfuscate
your own code, but please don't ask me to do the same. Let's support
both ways of doing things, and we can be different.

Frederik

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


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 one can make
> certain things thread-local (e.g. with withArgs, withProgName) makes
> the solution seem close at hand (although I can appreciate that it may
> not be). Yet isn't it just a matter of making a Map with existentially
> quantified values part of the state of each thread, just as the
> program name and arguments are also part of that state?

Are thread local variables really a good idea in Haskell?

If variables are thread local how would this combinator work:

withTimeOut :: Int -> IO a -> IO a
withTimeOut tout op = mdo
  mv <- newEmptyMVar
  wt <- forkIO $ do try op >>= tryPutMVar mv >> killThread kt
  kt <- forkIO $ do threadDelay tout
e <- tryPutMVar mv $ Left $ DynException $ toDyn 
TimeOutException
if e then killThread wt else return ()
  either throw return =<< takeMVar mv


Would it change the semantics of the action as it is run in a
different thread (this is a must if there are potentially blocking FFI
calls). Now if the action changes the thread local state then
it behaves differently. Do we really want that?

Usually one can just add a monad that wraps IO/STM and provides the
variables one needs. This has the good side of making scoping
explicit.

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


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

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 one can make
certain things thread-local (e.g. with withArgs, withProgName) makes
the solution seem close at hand (although I can appreciate that it may
not be). Yet isn't it just a matter of making a Map with existentially
quantified values part of the state of each thread, just as the
program name and arguments are also part of that state?


import qualified Data.Map as M 
import Data.Maybe 
import Data.Unique
import Data.IORef 
import Data.Typeable 
 
-- only these 2 must be implemented:
withParams :: ParamsMap -> IO () -> IO () 
getParams :: IO ParamsMap 
--

type ParamsMap = M.Map Unique Value

data Value = forall a . (Typeable a) => V a 
 
type IOParam a = IORef (Unique, a) 
 
newIOParam :: Typeable a => a -> IO (IOParam a) 
newIOParam def = do 
k <- newUnique 
newIORef (k,def) 
 
withIOParam :: Typeable a => IOParam a -> a -> IO () -> IO () 
withIOParam p value act = do 
(k,def) <- readIORef p 
m <- getParams 
withParams (M.insert k (V value) m) act 
 
getIOParam :: Typeable a => IOParam a -> IO a 
getIOParam p = do 
(k,def) <- readIORef p 
m <- getParams 
return $ fromMaybe def (M.lookup k m >>= (\ (V x) -> cast x)) 


Frederik

P.S. I sent a message about this a while back, when I was trying to
implement my own version using ThreadId (not really a good approach).

-- 
http://ofb.net/~frederik/
___
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-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


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


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


[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


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


[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: 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 these be unified in any useful way?

-- 
Ashley Yakeley, Seattle WA

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


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

In practice they don't conflict, because { ; } braces always follow a
keyword, while labeled-apps never do, and field labels never begin with ?,
while implicit-parameter labels always do.

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

Name conflicts do arise between explicit parameter labels and field
labels, which are probably best solved by requiring that they be distinct.
Field labels already can't be used in more than one data type, so it's not
much of an additional burden.

-- Ben


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


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

-- 
Ashley Yakeley, Seattle WA

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


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 a big one. The monomorphism
restriction (MR) was (barely) acceptable in Haskell 98 because at least the
final value returned by the program was not changed by this kludge kicking
in. But, as we point out in the paper, implicit parameters and the MR are
simply incompatible. One of them has to go.

As John Hughes intimated, this debate is part of a much larger issue as to
how Haskell handles type schemes versus types, and implicit parameters show
that type schemes can arise from causes other than polymorphism.

In the long term, should Haskell maintain a distinction between types and
type schemes? Between call-by-name and call-by-need? Should type schemes be
permitted everywhere? If so, should inference do it's best and simply report
when ambiguities arise? Etc. etc.

I think the time has come for us to address these types of questions from a
fundamental basis, not simply as fixes to the existing infrastructure.
Otherwise we'll never be able to budge from the sludge of the kludge...

John



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



Re: Implicit Parameters

2002-02-05 Thread John Hughes


On Monday 04 February 2002 02:25 am, John Hughes wrote:
> Not so fast! Proposing a "solution" means this is regarded as a "problem"!
> But what is to say that the first behaviour is "right" in any general
> sense?
>
> The important thing is that the language semantics is clear, and this is a
> semantic question.  The static semantics of Haskell *is* clear: recursive
> calls are monomorphic unless a type signature is given; this is the basis
> for understanding the behaviour above. 

I think part of the problem is that we've confused 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 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 polymorphic 
definition.

However, Koen's example suggests that maybe implicit parameters shouldn't 
necessarily play according to the rules of polymorphic types.  Perhaps 
implciit parameters should be a special kind of monomorphic type instead.  If 
this were the choice, then it's clear that they should be captured by 
recursive definitions.

Yes, if one asks in isolation whether implicit parameters should belong at the
type level or the type scheme level, then it might seem reasonable to make
either choice. but bear in mind that the type/type scheme distinction is also
tied in with type inference. Namely, inferred types cannot contain nested type
schemes, only declared types may do so. (GHC's recent extension beyond rank 2
types doesn't change this basic fact).

If implicit parameters were to be moved to the type level, then it should also
be possible to infer types containing them in nested positions. For example,

 f x = (x with ?y = 1) + 1

should receive the inferred type

 f :: (Num a, Num b) => (?y :: a => b) -> b

What happens to principality? Even if there are principal types, can type
inference still be done fast (feels like inference in the presence of
subtypes)? These are hard questions!

I would be AGAINST moving implicit parameters to the type level, without
solving the inference problem satisfactorily. That would give Haskell three
sorts of types:

 inferrable types (no implicit parameters in nested positions)
 declarable monomorphic types (nested implicit parameters)
 type schemes

(And now, of course, one may wonder what kind of monomorphism the M-R refers
to...). Two sorts of types is, in my view, already enough.

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



Re: Implicit Parameters

2002-02-04 Thread Jeffrey R. Lewis

On Monday 04 February 2002 02:25 am, John Hughes wrote:
> Not so fast! Proposing a "solution" means this is regarded as a "problem"!
> But what is to say that the first behaviour is "right" in any general
> sense?
>
> The important thing is that the language semantics is clear, and this is a
> semantic question.  The static semantics of Haskell *is* clear: recursive
> calls are monomorphic unless a type signature is given; this is the basis
> for understanding the behaviour above. 

I think part of the problem is that we've confused 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 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 polymorphic 
definition.

However, Koen's example suggests that maybe implicit parameters shouldn't 
necessarily play according to the rules of polymorphic types.  Perhaps 
implciit parameters should be a special kind of monomorphic type instead.  If 
this were the choice, then it's clear that they should be captured by 
recursive definitions.

> 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
> when a binding is monomorphic simpler? If not, it could be worse than the
> "problem" -- and the fact that it makes this one example behave as you want
> is no justification.

I agree that we should tread carefully ;-)

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



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 definitions without 
> a type signature]
>
> 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?

I think we overlooked it when the paper was written, but I reported this at 
the Haskell Implementers Meeting in Egmond.  At the time the only solution 
that occurred to me was to essentially do type inference twice - the first 
time to figure out what implicit parameters the definition depends on, and 
the second time with a weak signature provided that has those implicit 
parameters on board to get the effect of the user having provided the 
signature.  I believe you guys have looked at something like this as well.  
But I find that solution fairly unsatisfactory, and have been hoping 
something nicer will come along

I consider this to be a problem, but not enough of one that I've managed to 
spend time finding a solution ;-)

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



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 type definition would not cause this 
problem. Are implicit parameters not simply made explict
by the compiler?




-Original Message-
From: John Hughes [mailto:[EMAIL PROTECTED]]
Sent: 04 February 2002 10:26
To: [EMAIL PROTECTED]; [EMAIL PROTECTED]
Subject: Re: Implicit Parameters




    Suppose I have the following function definition:


      app :: (?ys :: [a]) => [a] -> [a]
      app xs =
        case ?ys of
      []  -> xs
      (y:ys') -> y : (app xs with ?ys = ys')


    This function appends its argument to its implicit argument,
    by recursively changing the implicit argument. For example:


      Hugs> app [1,2] with ?ys = [3,4]
      [3,4,1,2]


    So far so good! Now, since Haskell has type inference, we
    can leave out the type signature:


      -- app :: (?ys :: [a]) => [a] -> [a]
      app xs =
        case ?ys of
      []  -> xs
      (y:ys') -> y : (app xs with ?ys = ys')


    Let us check if it still works again:


      Hugs> app [1,2] with ?ys = [3,4]
      [3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,{Interrupted!}


    And, stunningly, it doesn't! Why doesn't this work?


    That is because type inference assumes that the body of
    `app' is monomorphic, i.e. has no context in its type.
    Therefore, the recursive call to app where ?ys is changed,
    had no effect at all.


    It works with the type signature there, because in order to
    implement type checking (note: not type inference) with
    polymorphic recursion demands to use the stated type in
    checking the body of the function.


    Mark Shields, Simon Peyton-Jones, and I, and also Jörgen
    Gustavsson have been discussing several modest solutions to
    this (we believe it is not needed to do full type inference
    that can deal with polymorphic recursion to solve this
    problem).


Not so fast! Proposing a "solution" means this is regarded as a "problem"! But
what is to say that the first behaviour is "right" in any general sense?


The important thing is that the language semantics is clear, and this is a
semantic question.  The static semantics of Haskell *is* clear: recursive
calls are monomorphic 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 when a
binding is monomorphic simpler? If not, it could be worse than the "problem"
-- and the fact that it makes this one example behave as you want is no
justification.


John


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





Re: Implicit Parameters

2002-02-04 Thread John Hughes


Suppose I have the following function definition:

  app :: (?ys :: [a]) => [a] -> [a]
  app xs =
case ?ys of
  []  -> xs
  (y:ys') -> y : (app xs with ?ys = ys')

This function appends its argument to its implicit argument,
by recursively changing the implicit argument. For example:

  Hugs> app [1,2] with ?ys = [3,4]
  [3,4,1,2]

So far so good! Now, since Haskell has type inference, we
can leave out the type signature:

  -- app :: (?ys :: [a]) => [a] -> [a]
  app xs =
case ?ys of
  []  -> xs
  (y:ys') -> y : (app xs with ?ys = ys')

Let us check if it still works again:

  Hugs> app [1,2] with ?ys = [3,4]
  [3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,{Interrupted!}

And, stunningly, it doesn't! Why doesn't this work?

That is because type inference assumes that the body of
`app' is monomorphic, i.e. has no context in its type.
Therefore, the recursive call to app where ?ys is changed,
had no effect at all.

It works with the type signature there, because in order to
implement type checking (note: not type inference) with
polymorphic recursion demands to use the stated type in
checking the body of the function.

Mark Shields, Simon Peyton-Jones, and I, and also Jörgen
Gustavsson have been discussing several modest solutions to
this (we believe it is not needed to do full type inference
that can deal with polymorphic recursion to solve this
problem).

Not so fast! Proposing a "solution" means this is regarded as a "problem"! But
what is to say that the first behaviour is "right" in any general sense?

The important thing is that the language semantics is clear, and this is a
semantic question.  The static semantics of Haskell *is* clear: recursive
calls are monomorphic 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 when a
binding is monomorphic simpler? If not, it could be worse than the "problem"
-- and the fact that it makes this one example behave as you want is no
justification.

John

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



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://www.cse.ogi.edu/~jlewis/

--Jeff


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