-- |-- Module : Data.Array.Byte-- Copyright : (c) Roman Leshchinskiy 2009-2012-- License : BSD-style---- Compatibility layer for-- <https://hackage.haskell.org/package/base/docs/Data-Array-Byte.html Data.Array.Byte>,-- providing boxed wrappers for `ByteArray#` and `MutableByteArray#`-- and relevant instances for GHC < 9.4. Include it into your Cabal file:---- > build-depends: base-- > if impl(ghc < 9.4)-- > build-depends: data-array-byte---- and then import "Data.Array.Byte" unconditionally.---- Originally derived from @primitive@ package.{-# LANGUAGE BangPatterns #-}{-# LANGUAGE CPP #-}{-# LANGUAGE MagicHash #-}{-# LANGUAGE TemplateHaskellQuotes #-}{-# LANGUAGE Trustworthy #-}{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE UnboxedTuples #-}{-# LANGUAGE UnliftedFFITypes #-}moduleData.Array.Byte(ByteArray (..),MutableByteArray (..),)whereimportData.Bits((.&.),unsafeShiftR)importData.Data(mkNoRepType,Data(..),Typeable)importqualifiedData.FoldableasFimportData.Semigroup(Semigroup(..))importGHC.Exts(ByteArray#,MutableByteArray#,sameMutableByteArray#,isTrue#,unsafeCoerce#,reallyUnsafePtrEquality#,copyByteArray#,writeWord8Array#,indexWord8Array#,sizeofByteArray#,unsafeFreezeByteArray#,newByteArray#,IsList(..),Int(..))importGHC.Show(intToDigit)importGHC.ST(ST(..),runST)importGHC.Word(Word8(..)) #if MIN_VERSION_base(4,11,0) importGHC.Exts(compareByteArrays#) #else importForeign.C.Types(CInt(..),CSize(..))importSystem.IO.Unsafe(unsafeDupablePerformIO) #endif importControl.DeepSeq(NFData(..))importGHC.Exts(Addr#,copyAddrToByteArray#)importLanguage.Haskell.TH.Syntax(Lift(..),Lit(..),Exp(..)) #if MIN_VERSION_template_haskell(2,17,0) importLanguage.Haskell.TH.Syntax(unsafeCodeCoerce) #elif MIN_VERSION_template_haskell(2,16,0) importLanguage.Haskell.TH.Syntax(unsafeTExpCoerce) #endif #if MIN_VERSION_template_haskell(2,16,0) importGHC.ForeignPtr(ForeignPtr(..),ForeignPtrContents(..))importGHC.Exts(newPinnedByteArray#,isByteArrayPinned#,byteArrayContents#)importLanguage.Haskell.TH.Syntax(Bytes(..)) #endif -- | Boxed wrapper for 'ByteArray#'.---- Since 'ByteArray#' is an unlifted type and not a member of kind 'Data.Kind.Type',-- things like @[ByteArray#]@ or @IO ByteArray#@ are ill-typed. To work around this-- inconvenience this module provides a standard boxed wrapper, inhabiting 'Data.Kind.Type'.-- Clients are expected to use 'ByteArray' in higher-level APIs,-- but wrap and unwrap 'ByteArray' internally as they please-- and use functions from "GHC.Exts".dataByteArray =ByteArray ByteArray#-- | Boxed wrapper for 'MutableByteArray#'.---- Since 'MutableByteArray#' is an unlifted type and not a member of kind 'Data.Kind.Type',-- things like @[MutableByteArray#]@ or @IO MutableByteArray#@ are ill-typed. To work around this-- inconvenience this module provides a standard boxed wrapper, inhabiting 'Data.Kind.Type'.-- Clients are expected to use 'MutableByteArray' in higher-level APIs,-- but wrap and unwrap 'MutableByteArray' internally as they please-- and use functions from "GHC.Exts".dataMutableByteArray s =MutableByteArray (MutableByteArray#s )-- | Create a new mutable byte array of the specified size in bytes.---- /Note:/ this function does not check if the input is non-negative.newByteArray ::Int->STs (MutableByteArray s ){-# INLINEnewByteArray #-}newByteArray :: forall s. Int -> ST s (MutableByteArray s) newByteArray (I#Int# n# )=forall s a. STRep s a -> ST s a ST(\State# s s# ->caseforall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newByteArray#Int# n# State# s s# of(#State# s s'# ,MutableByteArray# s arr# #)->(#State# s s'# ,forall s. MutableByteArray# s -> MutableByteArray s MutableByteArray MutableByteArray# s arr# #))-- | Convert a mutable byte array to an immutable one without copying. The-- array should not be modified after the conversion.unsafeFreezeByteArray ::MutableByteArray s ->STs ByteArray {-# INLINEunsafeFreezeByteArray #-}unsafeFreezeByteArray :: forall s. MutableByteArray s -> ST s ByteArray unsafeFreezeByteArray (MutableByteArray MutableByteArray# s arr# )=forall s a. STRep s a -> ST s a ST(\State# s s# ->caseforall d. MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) unsafeFreezeByteArray#MutableByteArray# s arr# State# s s# of(#State# s s'# ,ByteArray# arr'# #)->(#State# s s'# ,ByteArray# -> ByteArray ByteArray ByteArray# arr'# #))-- | Size of the byte array in bytes.sizeofByteArray ::ByteArray ->Int{-# INLINEsizeofByteArray #-}sizeofByteArray :: ByteArray -> Int sizeofByteArray (ByteArray ByteArray# arr# )=Int# -> Int I#(ByteArray# -> Int# sizeofByteArray#ByteArray# arr# )-- | Read byte at specific index.indexByteArray ::ByteArray ->Int->Word8{-# INLINEindexByteArray #-}indexByteArray :: ByteArray -> Int -> Word8 indexByteArray (ByteArray ByteArray# arr# )(I#Int# i# )=Word8# -> Word8 W8#(ByteArray# -> Int# -> Word8# indexWord8Array#ByteArray# arr# Int# i# )-- | Write byte at specific index.writeByteArray ::MutableByteArray s ->Int->Word8->STs (){-# INLINEwriteByteArray #-}writeByteArray :: forall s. MutableByteArray s -> Int -> Word8 -> ST s () writeByteArray (MutableByteArray MutableByteArray# s arr# )(I#Int# i# )(W8#Word8# x# )=forall s a. STRep s a -> ST s a ST(\State# s s# ->caseforall d. MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d writeWord8Array#MutableByteArray# s arr# Int# i# Word8# x# State# s s# ofState# s s'# ->(#State# s s'# ,()#))-- | Explode 'ByteArray' into a list of bytes.byteArrayToList ::ByteArray ->[Word8]{-# INLINEbyteArrayToList #-}byteArrayToList :: ByteArray -> [Word8] byteArrayToList ByteArray arr =Int -> [Word8] go Int 0wherego :: Int -> [Word8] go Int i |Int i forall a. Ord a => a -> a -> Bool <Int maxI =ByteArray -> Int -> Word8 indexByteArray ByteArray arr Int i forall a. a -> [a] -> [a] :Int -> [Word8] go (Int i forall a. Num a => a -> a -> a +Int 1)|Bool otherwise=[]maxI :: Int maxI =ByteArray -> Int sizeofByteArray ByteArray arr -- | Create a 'ByteArray' from a list of a known length. If the length-- of the list does not match the given length, this throws an exception.byteArrayFromListN ::Int->[Word8]->ByteArray byteArrayFromListN :: Int -> [Word8] -> ByteArray byteArrayFromListN Int n [Word8] ys =forall a. (forall s. ST s a) -> a runSTforall a b. (a -> b) -> a -> b $doMutableByteArray s marr <-forall s. Int -> ST s (MutableByteArray s) newByteArray Int n letgo :: Int -> [Word8] -> ST s () go !Int ix []=ifInt ix forall a. Eq a => a -> a -> Bool ==Int n thenforall (m :: * -> *) a. Monad m => a -> m a return()elseforall a. HasCallStack => [Char] -> a errorforall a b. (a -> b) -> a -> b $[Char] "Data.Array.Byte.byteArrayFromListN: list length less than specified size"go !Int ix (Word8 x :[Word8] xs )=ifInt ix forall a. Ord a => a -> a -> Bool <Int n thendoforall s. MutableByteArray s -> Int -> Word8 -> ST s () writeByteArray MutableByteArray s marr Int ix Word8 x Int -> [Word8] -> ST s () go (Int ix forall a. Num a => a -> a -> a +Int 1)[Word8] xs elseforall a. HasCallStack => [Char] -> a errorforall a b. (a -> b) -> a -> b $[Char] "Data.Array.Byte.byteArrayFromListN: list length greater than specified size"Int -> [Word8] -> ST s () go Int 0[Word8] ys forall s. MutableByteArray s -> ST s ByteArray unsafeFreezeByteArray MutableByteArray s marr -- | Copy a slice of an immutable byte array to a mutable byte array.---- /Note:/ this function does not do bounds or overlap checking.copyByteArray ::MutableByteArray s -- ^ destination array->Int-- ^ offset into destination array->ByteArray -- ^ source array->Int-- ^ offset into source array->Int-- ^ number of bytes to copy->STs (){-# INLINEcopyByteArray #-}copyByteArray :: forall s. MutableByteArray s -> Int -> ByteArray -> Int -> Int -> ST s () copyByteArray (MutableByteArray MutableByteArray# s dst# )(I#Int# doff# )(ByteArray ByteArray# src# )(I#Int# soff# )(I#Int# sz# )=forall s a. STRep s a -> ST s a ST(\State# s s# ->caseforall d. ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d copyByteArray#ByteArray# src# Int# soff# MutableByteArray# s dst# Int# doff# Int# sz# State# s s# ofState# s s'# ->(#State# s s'# ,()#))instanceDataByteArray wheretoConstr :: ByteArray -> Constr toConstrByteArray _=forall a. HasCallStack => [Char] -> a error[Char] "toConstr"gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteArray gunfoldforall b r. Data b => c (b -> r) -> c r _forall r. r -> c r _=forall a. HasCallStack => [Char] -> a error[Char] "gunfold"dataTypeOf :: ByteArray -> DataType dataTypeOfByteArray _=[Char] -> DataType mkNoRepType[Char] "Data.Array.Byte.ByteArray"instanceTypeables =>Data(MutableByteArray s )wheretoConstr :: MutableByteArray s -> Constr toConstr MutableByteArray s _=forall a. HasCallStack => [Char] -> a error[Char] "toConstr"gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MutableByteArray s) gunfold forall b r. Data b => c (b -> r) -> c r _forall r. r -> c r _=forall a. HasCallStack => [Char] -> a error[Char] "gunfold"dataTypeOf :: MutableByteArray s -> DataType dataTypeOf MutableByteArray s _=[Char] -> DataType mkNoRepType[Char] "Data.Array.Byte.MutableByteArray"instanceShowByteArray whereshowsPrec :: Int -> ByteArray -> ShowS showsPrecInt _ByteArray ba =[Char] -> ShowS showString[Char] "["forall b c a. (b -> c) -> (a -> b) -> a -> c .Int -> ShowS go Int 0whereshowW8 ::Word8->String->StringshowW8 :: Word8 -> ShowS showW8 !Word8 w [Char] s =Char '0'forall a. a -> [a] -> [a] :Char 'x'forall a. a -> [a] -> [a] :Int -> Char intToDigit(forall a b. (Integral a, Num b) => a -> b fromIntegral(forall a. Bits a => a -> Int -> a unsafeShiftRWord8 w Int 4))forall a. a -> [a] -> [a] :Int -> Char intToDigit(forall a b. (Integral a, Num b) => a -> b fromIntegral(Word8 w forall a. Bits a => a -> a -> a .&.Word8 0x0F))forall a. a -> [a] -> [a] :[Char] s go :: Int -> ShowS go Int i |Int i forall a. Ord a => a -> a -> Bool <ByteArray -> Int sizeofByteArray ByteArray ba =ShowS comma forall b c a. (b -> c) -> (a -> b) -> a -> c .Word8 -> ShowS showW8 (ByteArray -> Int -> Word8 indexByteArray ByteArray ba Int i ::Word8)forall b c a. (b -> c) -> (a -> b) -> a -> c .Int -> ShowS go (Int i forall a. Num a => a -> a -> a +Int 1)|Bool otherwise=Char -> ShowS showCharChar ']'wherecomma :: ShowS comma |Int i forall a. Eq a => a -> a -> Bool ==Int 0=forall a. a -> a id|Bool otherwise=[Char] -> ShowS showString[Char] ", "-- | Compare prefixes of given length.compareByteArraysFromBeginning ::ByteArray ->ByteArray ->Int->Ordering{-# INLINEcompareByteArraysFromBeginning #-} #if MIN_VERSION_base(4,11,0) compareByteArraysFromBeginning :: ByteArray -> ByteArray -> Int -> Ordering compareByteArraysFromBeginning (ByteArray ByteArray# ba1# )(ByteArray ByteArray# ba2# )(I#Int# n# )=forall a. Ord a => a -> a -> Ordering compare(Int# -> Int I#(ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# compareByteArrays#ByteArray# ba1# Int# 0#ByteArray# ba2# Int# 0#Int# n# ))Int 0 #else compareByteArraysFromBeginning(ByteArrayba1#)(ByteArrayba2#)(I#n#)=compare(fromCInt(unsafeDupablePerformIO(memcmpba1#ba2#n)))0wheren=fromIntegral(I#n#)::CSizefromCInt=fromIntegral::CInt->Intforeignimportccallunsafe"memcmp"memcmp::ByteArray#->ByteArray#->CSize->IOCInt #endif -- | Do two byte arrays share the same pointer?sameByteArray ::ByteArray#->ByteArray#->BoolsameByteArray :: ByteArray# -> ByteArray# -> Bool sameByteArray ByteArray# ba1 ByteArray# ba2 =caseforall a. a -> a -> Int# reallyUnsafePtrEquality#(unsafeCoerce# :: forall a b. a -> b unsafeCoerce#ByteArray# ba1 ::())(unsafeCoerce# :: forall a b. a -> b unsafeCoerce#ByteArray# ba2 ::())ofInt# r ->Int# -> Bool isTrue#Int# r instanceEqByteArray whereba1 :: ByteArray ba1 @(ByteArray ByteArray# ba1# )== :: ByteArray -> ByteArray -> Bool ==ba2 :: ByteArray ba2 @(ByteArray ByteArray# ba2# )|ByteArray# -> ByteArray# -> Bool sameByteArray ByteArray# ba1# ByteArray# ba2# =Bool True|Int n1 forall a. Eq a => a -> a -> Bool /=Int n2 =Bool False|Bool otherwise=ByteArray -> ByteArray -> Int -> Ordering compareByteArraysFromBeginning ByteArray ba1 ByteArray ba2 Int n1 forall a. Eq a => a -> a -> Bool ==Ordering EQwheren1 :: Int n1 =ByteArray -> Int sizeofByteArray ByteArray ba1 n2 :: Int n2 =ByteArray -> Int sizeofByteArray ByteArray ba2 instanceEq(MutableByteArray s )where== :: MutableByteArray s -> MutableByteArray s -> Bool (==)(MutableByteArray MutableByteArray# s arr# )(MutableByteArray MutableByteArray# s brr# )=Int# -> Bool isTrue#(forall d. MutableByteArray# d -> MutableByteArray# d -> Int# sameMutableByteArray#MutableByteArray# s arr# MutableByteArray# s brr# )-- | Non-lexicographic ordering. This compares the lengths of-- the byte arrays first and uses a lexicographic ordering if-- the lengths are equal. Subject to change between major versions.instanceOrdByteArray whereba1 :: ByteArray ba1 @(ByteArray ByteArray# ba1# )compare :: ByteArray -> ByteArray -> Ordering `compare` ba2 :: ByteArray ba2 @(ByteArray ByteArray# ba2# )|ByteArray# -> ByteArray# -> Bool sameByteArray ByteArray# ba1# ByteArray# ba2# =Ordering EQ|Int n1 forall a. Eq a => a -> a -> Bool /=Int n2 =Int n1 forall a. Ord a => a -> a -> Ordering `compare`Int n2 |Bool otherwise=ByteArray -> ByteArray -> Int -> Ordering compareByteArraysFromBeginning ByteArray ba1 ByteArray ba2 Int n1 wheren1 :: Int n1 =ByteArray -> Int sizeofByteArray ByteArray ba1 n2 :: Int n2 =ByteArray -> Int sizeofByteArray ByteArray ba2 -- The primop compareByteArrays# (invoked from 'compareByteArraysFromBeginning')-- performs a check for pointer equality as well. However, it-- is included here because it is likely better to check for pointer equality-- before checking for length equality. Getting the length requires deferencing-- the pointers, which could cause accesses to memory that is not in the cache.-- By contrast, a pointer equality check is always extremely cheap.-- | Append two byte arrays.appendByteArray ::ByteArray ->ByteArray ->ByteArray appendByteArray :: ByteArray -> ByteArray -> ByteArray appendByteArray ByteArray a ByteArray b =forall a. (forall s. ST s a) -> a runSTforall a b. (a -> b) -> a -> b $doMutableByteArray s marr <-forall s. Int -> ST s (MutableByteArray s) newByteArray (ByteArray -> Int sizeofByteArray ByteArray a forall a. Num a => a -> a -> a +ByteArray -> Int sizeofByteArray ByteArray b )forall s. MutableByteArray s -> Int -> ByteArray -> Int -> Int -> ST s () copyByteArray MutableByteArray s marr Int 0ByteArray a Int 0(ByteArray -> Int sizeofByteArray ByteArray a )forall s. MutableByteArray s -> Int -> ByteArray -> Int -> Int -> ST s () copyByteArray MutableByteArray s marr (ByteArray -> Int sizeofByteArray ByteArray a )ByteArray b Int 0(ByteArray -> Int sizeofByteArray ByteArray b )forall s. MutableByteArray s -> ST s ByteArray unsafeFreezeByteArray MutableByteArray s marr -- | Concatenate a list of 'ByteArray's.concatByteArray ::[ByteArray ]->ByteArray concatByteArray :: [ByteArray] -> ByteArray concatByteArray [ByteArray] arrs =forall a. (forall s. ST s a) -> a runSTforall a b. (a -> b) -> a -> b $doletlen :: Int len =[ByteArray] -> Int -> Int calcLength [ByteArray] arrs Int 0MutableByteArray s marr <-forall s. Int -> ST s (MutableByteArray s) newByteArray Int len forall s. MutableByteArray s -> Int -> [ByteArray] -> ST s () pasteByteArrays MutableByteArray s marr Int 0[ByteArray] arrs forall s. MutableByteArray s -> ST s ByteArray unsafeFreezeByteArray MutableByteArray s marr -- | Dump immutable 'ByteArray's into a mutable one, starting from a given offset.pasteByteArrays ::MutableByteArray s ->Int->[ByteArray ]->STs ()pasteByteArrays :: forall s. MutableByteArray s -> Int -> [ByteArray] -> ST s () pasteByteArrays !MutableByteArray s _!Int _[]=forall (m :: * -> *) a. Monad m => a -> m a return()pasteByteArrays !MutableByteArray s marr !Int ix (ByteArray x :[ByteArray] xs )=doforall s. MutableByteArray s -> Int -> ByteArray -> Int -> Int -> ST s () copyByteArray MutableByteArray s marr Int ix ByteArray x Int 0(ByteArray -> Int sizeofByteArray ByteArray x )forall s. MutableByteArray s -> Int -> [ByteArray] -> ST s () pasteByteArrays MutableByteArray s marr (Int ix forall a. Num a => a -> a -> a +ByteArray -> Int sizeofByteArray ByteArray x )[ByteArray] xs -- | Compute total length of 'ByteArray's, increased by accumulator.calcLength ::[ByteArray ]->Int->IntcalcLength :: [ByteArray] -> Int -> Int calcLength []!Int n =Int n calcLength (ByteArray x :[ByteArray] xs )!Int n =[ByteArray] -> Int -> Int calcLength [ByteArray] xs (ByteArray -> Int sizeofByteArray ByteArray x forall a. Num a => a -> a -> a +Int n )-- | An array of zero length.emptyByteArray ::ByteArray emptyByteArray :: ByteArray emptyByteArray =forall a. (forall s. ST s a) -> a runST(forall s. Int -> ST s (MutableByteArray s) newByteArray Int 0forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>=forall s. MutableByteArray s -> ST s ByteArray unsafeFreezeByteArray )-- | Replicate 'ByteArray' given number of times and concatenate all together.replicateByteArray ::Int->ByteArray ->ByteArray replicateByteArray :: Int -> ByteArray -> ByteArray replicateByteArray Int n ByteArray arr =forall a. (forall s. ST s a) -> a runSTforall a b. (a -> b) -> a -> b $doMutableByteArray s marr <-forall s. Int -> ST s (MutableByteArray s) newByteArray (Int n forall a. Num a => a -> a -> a *ByteArray -> Int sizeofByteArray ByteArray arr )letgo :: Int -> ST s () go Int i =ifInt i forall a. Ord a => a -> a -> Bool <Int n thendoforall s. MutableByteArray s -> Int -> ByteArray -> Int -> Int -> ST s () copyByteArray MutableByteArray s marr (Int i forall a. Num a => a -> a -> a *ByteArray -> Int sizeofByteArray ByteArray arr )ByteArray arr Int 0(ByteArray -> Int sizeofByteArray ByteArray arr )Int -> ST s () go (Int i forall a. Num a => a -> a -> a +Int 1)elseforall (m :: * -> *) a. Monad m => a -> m a return()Int -> ST s () go Int 0forall s. MutableByteArray s -> ST s ByteArray unsafeFreezeByteArray MutableByteArray s marr instanceSemigroupByteArray where<> :: ByteArray -> ByteArray -> ByteArray (<>)=ByteArray -> ByteArray -> ByteArray appendByteArray sconcat :: NonEmpty ByteArray -> ByteArray sconcat=forall a. Monoid a => [a] -> a mconcatforall b c a. (b -> c) -> (a -> b) -> a -> c .forall (t :: * -> *) a. Foldable t => t a -> [a] F.toListstimes :: forall b. Integral b => b -> ByteArray -> ByteArray stimesb i ByteArray arr |Integer itgr forall a. Ord a => a -> a -> Bool <Integer 1=ByteArray emptyByteArray |Integer itgr forall a. Ord a => a -> a -> Bool <=(forall a b. (Integral a, Num b) => a -> b fromIntegral(forall a. Bounded a => a maxBound::Int))=Int -> ByteArray -> ByteArray replicateByteArray (forall a b. (Integral a, Num b) => a -> b fromIntegralInteger itgr )ByteArray arr |Bool otherwise=forall a. HasCallStack => [Char] -> a error[Char] "Data.Array.Byte#stimes: cannot allocate the requested amount of memory"whereitgr :: Integer itgr =forall a. Integral a => a -> Integer toIntegerb i ::IntegerinstanceMonoidByteArray wheremempty :: ByteArray mempty=ByteArray emptyByteArray mappend :: ByteArray -> ByteArray -> ByteArray mappend=forall a. Semigroup a => a -> a -> a (<>)mconcat :: [ByteArray] -> ByteArray mconcat=[ByteArray] -> ByteArray concatByteArray instanceIsListByteArray wheretypeItemByteArray =Word8toList :: ByteArray -> [Item ByteArray] toList=ByteArray -> [Word8] byteArrayToList fromList :: [Item ByteArray] -> ByteArray fromList[Item ByteArray] xs =Int -> [Word8] -> ByteArray byteArrayFromListN (forall (t :: * -> *) a. Foldable t => t a -> Int length[Item ByteArray] xs )[Item ByteArray] xs fromListN :: Int -> [Item ByteArray] -> ByteArray fromListN=Int -> [Word8] -> ByteArray byteArrayFromListN instanceNFDataByteArray wherernf :: ByteArray -> () rnf(ByteArray ByteArray# _)=()instanceNFData(MutableByteArray s )wherernf :: MutableByteArray s -> () rnf (MutableByteArray MutableByteArray# s _)=()instanceLiftByteArray where #if MIN_VERSION_template_haskell(2,17,0) liftTyped :: forall (m :: * -> *). Quote m => ByteArray -> Code m ByteArray liftTyped=forall a (m :: * -> *). Quote m => m Exp -> Code m a unsafeCodeCoerceforall b c a. (b -> c) -> (a -> b) -> a -> c .forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp lift #elif MIN_VERSION_template_haskell(2,16,0) liftTyped=unsafeTExpCoerce.lift #endif #if MIN_VERSION_template_haskell(2,16,0) lift :: forall (m :: * -> *). Quote m => ByteArray -> m Exp lift(ByteArray ByteArray# b )=forall (m :: * -> *) a. Monad m => a -> m a return(Exp -> Exp -> Exp AppE(Exp -> Exp -> Exp AppE(Name -> Exp VarE'addrToByteArray)(Lit -> Exp LitE(Integer -> Lit IntegerL(forall a b. (Integral a, Num b) => a -> b fromIntegralInt len ))))(Lit -> Exp LitE(Bytes -> Lit BytesPrimL(ForeignPtr Word8 -> Word -> Word -> Bytes BytesForeignPtr Word8 ptr Word 0(forall a b. (Integral a, Num b) => a -> b fromIntegralInt len )))))wherelen# :: Int# len# =ByteArray# -> Int# sizeofByteArray#ByteArray# b len :: Int len =Int# -> Int I#Int# len# pb ::ByteArray#!(ByteArray ByteArray# pb )|Int# -> Bool isTrue#(ByteArray# -> Int# isByteArrayPinned#ByteArray# b )=ByteArray# -> ByteArray ByteArray ByteArray# b |Bool otherwise=forall a. (forall s. ST s a) -> a runSTforall a b. (a -> b) -> a -> b $forall s a. STRep s a -> ST s a STforall a b. (a -> b) -> a -> b $\State# s s ->caseforall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newPinnedByteArray#Int# len# State# s s of(#State# s s' ,MutableByteArray# s mb #)->caseforall d. ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d copyByteArray#ByteArray# b Int# 0#MutableByteArray# s mb Int# 0#Int# len# State# s s' ofState# s s'' ->caseforall d. MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) unsafeFreezeByteArray#MutableByteArray# s mb State# s s'' of(#State# s s''' ,ByteArray# ret #)->(#State# s s''' ,ByteArray# -> ByteArray ByteArray ByteArray# ret #)ptr ::ForeignPtrWord8ptr :: ForeignPtr Word8 ptr =forall a. Addr# -> ForeignPtrContents -> ForeignPtr a ForeignPtr(ByteArray# -> Addr# byteArrayContents#ByteArray# pb )(MutableByteArray# RealWorld -> ForeignPtrContents PlainPtr(unsafeCoerce# :: forall a b. a -> b unsafeCoerce#ByteArray# pb )) #else lift(ByteArrayb)=return(AppE(AppE(VarE'addrToByteArray)(LitE(IntegerL(fromIntegrallen))))(LitE(StringPrimL(toList(ByteArrayb)))))wherelen#=sizeofByteArray#blen=I#len# #endif addrToByteArray ::Int->Addr#->ByteArray addrToByteArray :: Int -> Addr# -> ByteArray addrToByteArray (I#Int# len )Addr# addr =forall a. (forall s. ST s a) -> a runSTforall a b. (a -> b) -> a -> b $forall s a. STRep s a -> ST s a STforall a b. (a -> b) -> a -> b $\State# s s ->caseforall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) newByteArray#Int# len State# s s of(#State# s s' ,MutableByteArray# s mb #)->caseforall d. Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d copyAddrToByteArray#Addr# addr MutableByteArray# s mb Int# 0#Int# len State# s s' ofState# s s'' ->caseforall d. MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) unsafeFreezeByteArray#MutableByteArray# s mb State# s s'' of(#State# s s''' ,ByteArray# ret #)->(#State# s s''' ,ByteArray# -> ByteArray ByteArray ByteArray# ret #)