[Haskell] Implicit Parameters
Ashley Yakeley
ashley at semantic.org
Mon Feb 27 15:31:51 EST 2006
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.
--
Ashley Yakeley
More information about the Haskell
mailing list