[Haskell-cafe] Scoped data declarations

Christophe Poucet christophe.poucet at gmail.com
Fri Jun 23 07:11:37 EDT 2006


Dear,

Yesterday, while discussing with Cale and SamB on I suddenly came up with
the crazy idea of scoped data declarations.  After some brief discussion to
check the validity, I finally came to the conclusion that they should be
feasible. In addition, I don't think that they would require a high amount
of changes in current compilers.

Basically if you have something like:

module Main where
foo = let data Foo = Foo deriving Show in Foo\
main :: IO ()
main = print foo

One can see this as having an extra hidden module that defines Foo but that
does not export it.  The only change that is then required is that while
compiling Foo, the hidden-ness of Foo must be removed.

For instance, if one were to load this into, say, ghci (this is fictive of
course):
# ghci Main.hs
> :t foo
foo :: Codeloc2.Foo

There were initially some objections to this, because it is no longer
feasible to actually write the type of the function foo.  But if one looks
at current GHC, this objection is already there:

module A(foo) where
data Foo = Foo deriving Show
foo = Foo

module Main where
import A
main = print foo

As Excedrin then pointed out, importing this Main into ghci, gives
foo :: Foo.Foo

And this notation can not be written in Main either, because Foo is hidden
in A.

Therefore, I would like to note that scoped data declarations are just like
hidden data-declarations with two extra requirements:
1) Generate source-location-based submodule names
2) Add an extra import rule for those hidden modules in the subexpressions
of where the data-declaration is being originally defined.

Comments are welcome, of course :)
Cheers!
Christophe (vincenz)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org//pipermail/haskell-cafe/attachments/20060623/a21df86d/attachment.htm


More information about the Haskell-Cafe mailing list