{- | Two flavours of array: mutable and immutable. All are boxed, lazy, and use zero-origin integers as indicies. -} {-# LANGUAGE MagicHash, UnboxedTuples #-} module Data.Array.Vanilla.Unsafe ( IArray (), MArray(), marray_new, marray_read, marray_write, marray_freeze, iarray_thaw, iarray_read ) where import GHC.Types import GHC.ST import GHC.Prim -- Oh noes!!! -- | The type of immutable arrays, with elements of type @x@. data IArray x = IArray (Array# x) {- | The type of mutable arrays, with elements of type @x@. These arrays live in the @ST@ monad, but you can use @stToIO@ to convert this to @IO@ if required. Two @MArray@s are equal as per @(==)@ if they are both the exact same array (i.e., the same block of RAM). Two seperate arrays which merely hold the same data are /not/ considered equal. (This fact could change at any second, after all.) -} data MArray s x = MArray (MutableArray# s x) instance Eq (MArray s x) where (MArray x#) == (MArray y#) = sameMutableArray# x# y# {- | Create a brand new @MArray@, of the specified size, with all elements set to the value provided. If the array size is @n@, valid indicies are from @0@ to @n-1@. -} marray_new :: Int -> x -> ST s (MArray s x) marray_new (I# i#) v0 = ST $ \s0# -> let (# s1#, a# #) = newArray# i# v0 s0# in (# s1#, MArray a# #) {- | Read from an @MArray@. /Unsafe/: No bounds checks. Indicies below @0@ or above @n-1@ will likely result in a program crash. -} marray_read :: MArray s x -> Int -> ST s x marray_read (MArray a#) (I# i#) = ST $ readArray# a# i# {- | Write to an @MArray@, replacing the element at the specified index. /Unsafe/: No bounds checks. Indicies below @0@ or above @n-1@ will likely result in a program crash (if you're lucky), or weird data corruption (if you're unlucky). -} marray_write :: MArray s x -> Int -> x -> ST s () marray_write (MArray a#) (I# i#) x = ST $ \s0# -> (# writeArray# a# i# x s0#, () #) {- | Create a new @IArray@ which refers to the same memory block as an existing @MArray@. /Unsafe/: Mutating the @MArray@ will cause the contents of the @IArray@ to mutate also, violating referential transparency. (Avoid this by explicitly copying the data before freezing.) -} marray_freeze :: MArray s x -> ST s (IArray x) marray_freeze (MArray a#) = ST $ \s0# -> let (# s1#, b# #) = unsafeFreezeArray# a# s0# in (# s1#, IArray b# #) {- | Create a new @MArray@ which refers to the same memory block as an existing @IArray@. /Unsafe/: Mutating the @MArray@ will cause the contents of the @IArray@ to mutate also, violating referential transparency. (Avoid this by explicitly copying the data after thawing and before mutating it.) -} iarray_thaw :: IArray x -> ST s (MArray s x) iarray_thaw (IArray a#) = ST $ \s0# -> let (# s1#, b# #) = unsafeThawArray# a# s0# in (# s1#, MArray b# #) {- | Read from an @IArray@. (Since @IArrays@ are immutable, this is a pure operation.) /Unsafe/: No bounds checks. Indicies below @0@ or above @n-1@ will likely result in a program crash. -} iarray_read :: IArray x -> Int -> x iarray_read (IArray a#) (I# i#) = let (# x #) = indexArray# a# i# in x