Scoped data declarations

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)

On 6/23/06, Christophe Poucet
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 :)
I'm not sure I understand why this is something we need. Do you have any examples where this would be useful? /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Hello,
Well one specific example where this would be useful is for lambdabot and
similar systems. Additionally this could be useful for experimenting in any
interpreter such as hugs or ghci.
Regards
On 6/26/06, Sebastian Sylvan
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
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
On 6/23/06, Christophe Poucet
wrote: that 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 :)
I'm not sure I understand why this is something we need. Do you have any examples where this would be useful?
/S
-- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Here's a different example:
foo = let data Foo = Foo in [Foo, Foo]
Since unfolding let bindings is always sematically equivalent to the original expression this must be the same as
foo = [let data Foo = Foo, let data Foo = Foo]
How will you make that work? A, you could outlaw unfolding
'data', but then you would have to outlaw unfolding any expression
with an embedded 'data'. Very ugly. Or B, you can go for
structural equality on types. But that would be a radical departure
from Haskell. (BTW, this kind of example is the very reason Cayenne
has structural equality on types by default.)
I don't think local (scoped) type definitions mesh at all well
with the Haskell design. This work nicely now because type definitions
are only allowed at the top level, so they have a definition location.
Which means that name equality works.
-- Lennart
Quoting Christophe Poucet
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)
participants (3)
-
Christophe Poucet
-
lennart@augustsson.net
-
Sebastian Sylvan