Top-level bindings for unlifted types

pepe mnislaih at gmail.com
Wed Nov 28 05:10:02 EST 2007


So what's the verdict w.r.t. unlifted things bound by the debugger?
Right now it's quite easy, for example:

> Prelude> :m +Data.IORef
> Prelude Data.IORef> p <- newIORef False
> Prelude Data.IORef> :p p
> p = GHC.IOBase.IORef (GHC.STRef.STRef (_t1::GHC.Prim.MutVar#  
> GHC.Prim.RealWorld Bool))
> Prelude Data.IORef> :t _t1
> _t1 :: GHC.Prim.MutVar# GHC.Prim.RealWorld Bool
>


Should we actively prevent this ?


On 13/11/2007, at 13:08, Simon Marlow wrote:

> Neil Mitchell wrote:
>
>> The following program:
>> -------------------------------------------
>> {-# OPTIONS_GHC -fglasgow-exts #-}
>> module Test() where
>> import GHC.Base
>> test = realWorld#
>> -----------------------------------------
>> gives the error message:
>>    Top-level bindings for unlifted types aren't allowed:
>>        { test = realWorld# }
>> Changing to test _ = realWorld# works fine.
>> The question is why are these bindings disallowed? Reading the
>> "Unboxed values as first class citizens" paper I can't see it listed
>> as a restriction.
>
> Let's consider unboxed values first.  They would have to be computed  
> at compile-time, and that means the value of every top-level  
> unlifted value needs to be visible in the interface file, for use in  
> other modules. Cycles are disallowed, of course.  Top-level unboxed  
> values would then behave just like #define constants, in fact.  This  
> is certainly possible, it would just add complexity to the compiler  
> in various places.
>
> Alternatively you could compute them at load-time, but then you'd  
> not only have to arrange to run the initialisers somehow, but also  
> worry about ordering and cycles.  And then there's the issue that a  
> top-level unboxed value would be represented by a pointer to the  
> value rather than the value itself, as is the case with normal  
> unboxed bindings.  This doesn't sound like a profitable direction.
>
> Top-level unlifted/boxed values would be useful, for example
>
>  x = case newMutVar# 0 realWorld# of (# s#, x# #) -> x#
>
> eliminating a layer of indirection compared to the usual  
> unsafePerformIO.newIORef.  These would also have to be computed at  
> either compile-time or load-time, but there's no difficulty with the  
> representation, because unlifted/boxed values are always represented  
> by pointers anyway.  This is related to static arrays, which we  
> don't have in GHC right now.  Conclusion: doable, but non-trivial.
>
> realWorld# is a special case, but really falls into the unboxed  
> category.
>
> Cheers,
> 	Simon
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



More information about the Glasgow-haskell-users mailing list