[Haskell-cafe] Top Level etc.

Ashley Yakeley ashley at semantic.org
Wed Jan 19 06:52:00 EST 2005


In article <41EE22BE.80302 at imperial.ac.uk>,
 Keean Schupke <k.schupke at imperial.ac.uk> wrote:

> Do you think implicit parameters could replace 
> top-level-things-with-identity?
> 
> I hadn't really thought of it before (and I don't use implicit 
> parameters much).

Yes, but I think people are clamouring for 
top-level-things-with-identity because they don't like implicit 
parameters. Not me, though.

I have been musing on the connection between data-types, modules, 
classes, and implicit parameters, and wondering if there might be some 
grand scheme to tie it all together. For instance, a module is very 
similar to class with no type parameters and all members defined. You'll 
notice that class members have different declared types inside and 
outside the class:

class C a where
   foo :: a -> a -- inside

foo :: (C a) => a -> a -- outside


Perhaps one could have top-level implicit parameters (or top-level 
contexts in general):

module (?myvar :: IORef Int) => Random where

  random :: IO Int -- inside
  random = do
    i <- readIORef ?myvar
    ...
    writeIORef i'
    return i'


module (?myvar :: IORef Int) => MyMain where
  import Random

  -- random :: IO Int -- also inside

  mymain :: IO ()
  mymain = do
    ...
    i <- random
    ...


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

-- 
Ashley Yakeley, Seattle WA



More information about the Haskell-Cafe mailing list