{-# language BangPatterns #-} {-# language MagicHash #-} {-# language RankNTypes #-} {-# language TypeApplications #-} {-# language TypeFamilies #-} {-# language TypeInType #-} {-# language StandaloneKindSignatures #-} {-# language UnboxedTuples #-} module EmptyPrimArray ( emptyPrimArray# ) where import Data.Unlifted (PrimArray#(..)) import GHC.Exts (RuntimeRep,TYPE) import qualified GHC.Exts as Exts emptyPrimArray# :: forall (r :: RuntimeRep) (a :: TYPE r). (# #) -> PrimArray# a emptyPrimArray# :: forall a. (# #) -> PrimArray# a emptyPrimArray# (# #) _ = let !(# State# RealWorld _, ByteArray# z #) = (State# RealWorld -> (# State# RealWorld, ByteArray# #)) -> (# State# RealWorld, ByteArray# #) forall o. (State# RealWorld -> o) -> o Exts.runRW# (\State# RealWorld s -> case Int# -> State# RealWorld -> (# State# RealWorld, MutableByteArray# RealWorld #) forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) Exts.newByteArray# Int# 0# State# RealWorld s of (# State# RealWorld s', MutableByteArray# RealWorld x #) -> MutableByteArray# RealWorld -> State# RealWorld -> (# State# RealWorld, ByteArray# #) forall d. MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) Exts.unsafeFreezeByteArray# MutableByteArray# RealWorld x State# RealWorld s' ) in ByteArray# -> PrimArray# a forall a. ByteArray# -> PrimArray# a PrimArray# ByteArray# z