{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
module Network.DNS.Internal.Prim
( BA(..)
, MBA(..)
, unsafeFreezeByteArray
, newByteArray
, writeWord8Array
, writeWord8Array0
)
where
import GHC.Exts (ByteArray#, Int#, MutableByteArray#, newByteArray#,
unsafeFreezeByteArray#, writeWord8Array#, (+#))
import GHC.Int (Int(..))
import GHC.ST (ST(..))
import GHC.Word (Word8(..))
data BA = BA# ByteArray#
data MBA s = MBA# (MutableByteArray# s)
unsafeFreezeByteArray :: MBA s -> ST s (BA)
unsafeFreezeByteArray :: forall s. MBA s -> ST s BA
unsafeFreezeByteArray (MBA# MutableByteArray# s
mab) = STRep s BA -> ST s BA
forall s a. STRep s a -> ST s a
ST (STRep s BA -> ST s BA) -> STRep s BA -> ST s BA
forall a b. (a -> b) -> a -> b
$ \State# s
s1 -> case MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# s
mab State# s
s1 of
(# State# s
s2, ByteArray#
ba #) -> (# State# s
s2, ByteArray# -> BA
BA# ByteArray#
ba #)
newByteArray :: Int -> ST s (MBA s)
newByteArray :: forall s. Int -> ST s (MBA s)
newByteArray (I# Int#
l) = STRep s (MBA s) -> ST s (MBA s)
forall s a. STRep s a -> ST s a
ST (STRep s (MBA s) -> ST s (MBA s))
-> STRep s (MBA s) -> ST s (MBA s)
forall a b. (a -> b) -> a -> b
$ \State# s
s1 -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
l State# s
s1 of
(# State# s
s2, MutableByteArray# s
mba #) -> (# State# s
s2, MutableByteArray# s -> MBA s
forall s. MutableByteArray# s -> MBA s
MBA# MutableByteArray# s
mba #)
writeWord8Array :: MBA s -> Int# -> Word8 -> ST s ()
writeWord8Array :: forall s. MBA s -> Int# -> Word8 -> ST s ()
writeWord8Array (MBA# MutableByteArray# s
mab) Int#
i (W8# Word8#
w) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s -> (# MutableByteArray# s -> Int# -> Word8# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
writeWord8Array# MutableByteArray# s
mab Int#
i Word8#
w State# s
s, () #)
writeWord8Array0 :: MBA s -> Int# -> Word8 -> ST s ()
writeWord8Array0 :: forall s. MBA s -> Int# -> Word8 -> ST s ()
writeWord8Array0 MBA s
mba Int#
off Word8
w = MBA s -> Int# -> Word8 -> ST s ()
forall s. MBA s -> Int# -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int#
off Word8
w ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MBA s -> Int# -> Word8 -> ST s ()
forall s. MBA s -> Int# -> Word8 -> ST s ()
writeWord8Array MBA s
mba (Int#
off Int# -> Int# -> Int#
+# Int#
1#) Word8
0