ArrayRef-0.1.2: Unboxed references, dynamic arrays and moreSource codeContentsIndex
GHC.Unboxed
PortabilityGHC
Stabilityexperimental
MaintainerBulat Ziganshin <Bulat.Ziganshin@gmail.com>
Description

Unboxed values (simple datatypes that can be stored in ByteArrays, i.e. raw memory buffers allocated inside the Haskell heap)

Based on the idea of Oleg Kiselyov (see http:www.haskell.orgpipermailhaskell-cafe2004-July006400.html)

Synopsis
class Monad m => STorIO m s | m -> s where
mLift :: (State# s -> (#State# s, a#)) -> m a
type IOSpecific a = a RealWorld
type IOSpecific2 a = a RealWorld
type IOSpecific3 a = a RealWorld
data UVec a = UVec ByteArray#
data MUVec s a = MUVec (MutableByteArray# s)
allocUnboxedBytes :: (STorIO m s, Integral bytes, Unboxed a) => bytes -> m (MUVec s a)
unsafeFreezeUnboxed :: STorIO m s => MUVec s a -> m (UVec a)
unsafeThawUnboxed :: STorIO m s => UVec a -> m (MUVec s a)
freezeUnboxed :: STorIO m s => MUVec s a -> Int -> m (UVec a)
thawUnboxed :: STorIO m s => UVec a -> Int -> m (MUVec s a)
castUnboxed :: UVec a -> UVec b
castMUnboxed :: MUVec s a -> MUVec s b
fromI# :: Integral n => n -> Int#
memcpy :: MutableByteArray# RealWorld -> ByteArray# -> Int# -> IO ()
class Unboxed value where
readUnboxed :: (STorIO m s, Integral index) => MUVec s value -> index -> m value
writeUnboxed :: (STorIO m s, Integral index) => MUVec s value -> index -> value -> m ()
indexUnboxed :: Integral index => UVec value -> index -> value
sizeOfUnboxed :: value -> Int
Documentation
class Monad m => STorIO m s | m -> s whereSource
That's all we need to unify ST and IO operations!
Methods
mLift :: (State# s -> (#State# s, a#)) -> m aSource
show/hide Instances
STorIO IO RealWorld
STorIO (ST s) s
STorIO (ST s) s
type IOSpecific a = a RealWorldSource
Type functions which converts universal ST or IO types to IO-specific ones
type IOSpecific2 a = a RealWorldSource
type IOSpecific3 a = a RealWorldSource
data UVec a Source
Immutable and mutable byte vectors
Constructors
UVec ByteArray#
data MUVec s a Source
Constructors
MUVec (MutableByteArray# s)
allocUnboxedBytes :: (STorIO m s, Integral bytes, Unboxed a) => bytes -> m (MUVec s a)Source
Alloc the mutable byte vector
unsafeFreezeUnboxed :: STorIO m s => MUVec s a -> m (UVec a)Source
Mutable->immutable byte vector on-place conversion
unsafeThawUnboxed :: STorIO m s => UVec a -> m (MUVec s a)Source
Immutable->mutable byte vector on-place conversion
freezeUnboxed :: STorIO m s => MUVec s a -> Int -> m (UVec a)Source
Mutable->immutable byte vector conversion which takes a copy of contents
thawUnboxed :: STorIO m s => UVec a -> Int -> m (MUVec s a)Source
Immutable->mutable byte vector conversion which takes a copy of contents
castUnboxed :: UVec a -> UVec bSource
Recast immutable unboxed vector
castMUnboxed :: MUVec s a -> MUVec s bSource
Recast mutable unboxed vector
fromI# :: Integral n => n -> Int#Source
memcpy :: MutableByteArray# RealWorld -> ByteArray# -> Int# -> IO ()Source
class Unboxed value whereSource
Unboxed is like Storable, but values are stored in byte vectors (i.e. inside the Haskell heap)
Methods
readUnboxed :: (STorIO m s, Integral index) => MUVec s value -> index -> m valueSource
Read the value from mutable byte vector at given index
writeUnboxed :: (STorIO m s, Integral index) => MUVec s value -> index -> value -> m ()Source
Write the value to mutable byte vector at given index
indexUnboxed :: Integral index => UVec value -> index -> valueSource
Read the value from immutable byte vector at given index
sizeOfUnboxed :: value -> IntSource
How many bytes required to represent values of this type
show/hide Instances
Produced by Haddock version 2.1.0