[Haskell] Re: Question for the haskell implementors: Arrays,
unsafePerformIO, runST
Simon Marlow
simonmarhaskell at gmail.com
Mon Feb 20 08:47:29 EST 2006
John Meacham wrote:
> So, I finally decided that jhc needs real arrays, but am running into an
> issue and was wondering how other compilers solve it, or if there is a
> general accepted way to do so.
>
> here is what I have so far
>
>> -- The opaque internal array type
>> data Array__ a
>>
>> -- the array transformer quasi-monad
>> newtype AT a = AT (Array__ -> Array__)
>>
>> seqAT__ :: AT a -> AT a -> AT a
>> seqAT__ (AT a1) (AT a2) = AT $ \a -> a2 (a1 a)
>>
>> doneAT__ :: AT a
>> doneAT__ = AT id
>>
>> newAT__ :: Int -> AT a -> Array__ a
>> newAT__ n (AT a1) = a1 (prim_newAT__ n)
>>
>> writeAT__ :: Int -> a -> AT a
>> writeAT__ i x = AT $ \a -> prim_writeAT__ i x a
>>
>> -- none of these routines have run-time checks
>> foreign import primitive "prim_newAT__" :: Int -> Array__
>> -- performs *update-in-place*
>> foreign import primitive "prim_writeAT__" :: Int -> a -> Array__ -> Array__
>> foreign import primitive "unsafeAt__" :: Array__ a -> Int -> a
>>
>> -- example use
>> newArray :: [a] -> Array__ a
>> newArray xs = newAT__ (length as) $ foldr assign doneAT (zip [0..] xs) where
>> assign (i,v) rs = writeAT__ i v `seqAT__` rs
>
>
> now, the problem occurs in newAT__
>
>> newAT__ :: Int -> AT a -> Array__ a
>> newAT__ n (AT a1) = a1 (prim_newAT__ n)
> ^ this gets floated out as a CAF.
In GHC, the primitive is this:
newArray# :: Int# -> a -> State# s -> (# State# s, MutArr# s a #)
that is, it takes a state and returns a new state. In order for calls
to newArray# to not be shared more than we want, we have to make sure
that the state argument to newArray# is never a constant visible to the
compiler. This entails, as you guessed, not inlining the definition of
unsafePerformIO or runST. See comments near the definition of runST in
libraries/base/GHC/ST.lhs for a description of exactly the problem you
describe.
Cheers,
Simon
More information about the Haskell
mailing list