{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Data.Primitive.ByteArray.Extra where
import Data.Binary (Binary(..))
import Data.Primitive.ByteArray (ByteArray)
import GHC.Exts (IsList(..))
#if !MIN_VERSION_primitive(0,7,1)
import Control.DeepSeq (NFData(..))
#endif
#if !MIN_VERSION_primitive(0,8,0)
#define DEFINE_HASHABLE_BYTEARRAY
#elif !MIN_VERSION_hashable(1,4,1)
#define DEFINE_HASHABLE_BYTEARRAY
#elif !MIN_VERSION_hashable(1,4,2)
#if !MIN_VERSION_base(4,17,0)
#define DEFINE_HASHABLE_BYTEARRAY
#endif
#endif
#ifdef DEFINE_HASHABLE_BYTEARRAY
import Data.Hashable (Hashable(..))
#endif
#if !MIN_VERSION_primitive(0,7,1)
instance NFData ByteArray where
rnf x = x `seq` ()
#endif
instance Binary ByteArray where
get :: Get ByteArray
get = ([Word8] -> ByteArray) -> Get [Word8] -> Get ByteArray
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap [Word8] -> ByteArray
forall l. IsList l => [Item l] -> l
fromList Get [Word8]
forall t. Binary t => Get t
get
put :: ByteArray -> Put
put = [Word8] -> Put
forall t. Binary t => t -> Put
put ([Word8] -> Put) -> (ByteArray -> [Word8]) -> ByteArray -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> [Word8]
forall l. IsList l => l -> [Item l]
toList
#ifdef DEFINE_HASHABLE_BYTEARRAY
instance Hashable ByteArray where
hashWithSalt salt = hashWithSalt salt . toList
#endif