[Haskell-cafe] Top Level etc.

Jorge Adriano Aires jadrian at mat.uc.pt
Wed Jan 19 15:20:57 EST 2005


> Perhaps one could have top-level implicit parameters (or top-level
> contexts in general):
>
> module (?myvar :: IORef Int) => Random where

Hi!
I suggested something very similar to this some months ago, syntax and all. 
Nice to see I'm not the only one thinking along this lines.
http://www.mail-archive.com/haskell%40haskell.org/msg14884.html


> module Main where
>   import MyMain
>
>   -- mymain :: (?myvar :: IORef Int) => IO () -- outside
>
>   main = do
>      var <- newIORef 1   -- initialisers in the order you want
>      let ?myvar = var in mymain

By then I also suggest that maybe we could also bind the implicit on import,  
something like:

> module (?par :: Parameter) => A where 
> ...

> module B where
> import A                         -- simple, ?par unbound
> import qualified A as Ak where ?par = k -- ?par bound to k
> import qualified A as Am where ?par = m -- ?par bound to m

Seemed fine as long as the parameters didn't depend on the imported modules. 
But on hindsight, making an import depend on valued defined in the body of 
the module is probably quite clumsy, unfortunately (right?). Still, 

> import qualified A as Ak where ?par = 1
or 
> import qualified A as Ak where ?par = newIORef
or even 
> import C(k)
> import qualified A as Ak where ?par = k 

Doesn't sound that bad though. 

J.A.



More information about the Haskell-Cafe mailing list