{-# 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 (MBA# mab) = ST $ \s1 -> case unsafeFreezeByteArray# mab s1 of (# s2, ba #) -> (# s2, BA# ba #) newByteArray :: Int -> ST s (MBA s) newByteArray (I# l) = ST $ \s1 -> case newByteArray# l s1 of (# s2, mba #) -> (# s2, MBA# mba #) writeWord8Array :: MBA s -> Int# -> Word8 -> ST s () writeWord8Array (MBA# mab) i (W8# w) = ST $ \s -> (# writeWord8Array# mab i w s, () #) -- | Variant that appends every byte with a 0. This is for embedding ASCII into UTF16 code units. writeWord8Array0 :: MBA s -> Int# -> Word8 -> ST s () writeWord8Array0 mba off w = writeWord8Array mba off w >> writeWord8Array mba (off +# 1#) 0