{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Bytes.Types
( Bytes (..)
, Bytes# (..)
, MutableBytes (..)
, UnmanagedBytes (..)
, BytesN (..)
, ByteArrayN (..)
) where
import Data.Bytes.Internal (Bytes (..))
import Data.Bytes.Internal.Show (showsSlice)
import Data.Primitive (ByteArray (..), MutableByteArray (..))
import Data.Primitive.Addr (Addr)
import Data.Proxy (Proxy (Proxy))
import GHC.Natural (naturalToInteger)
import GHC.TypeNats (KnownNat, Nat, natVal)
import Reps (Bytes# (..))
data BytesN (n :: Nat) = BytesN
{ forall (n :: Nat). BytesN n -> ByteArray
array :: {-# UNPACK #-} !ByteArray
, forall (n :: Nat). BytesN n -> Int
offset :: {-# UNPACK #-} !Int
}
instance (KnownNat n) => Show (BytesN n) where
showsPrec :: Int -> BytesN n -> ShowS
showsPrec Int
_ (BytesN ByteArray
arr Int
off) String
s =
let len :: Int
len = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Nat -> Integer
naturalToInteger (Proxy n -> Nat
forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal (Proxy n
forall {k} (t :: k). Proxy t
Proxy :: Proxy n)))
in ByteArray -> Int -> Int -> ShowS
showsSlice ByteArray
arr Int
off Int
len String
s
newtype ByteArrayN (n :: Nat) = ByteArrayN
{ forall (n :: Nat). ByteArrayN n -> ByteArray
array :: ByteArray
}
instance (KnownNat n) => Show (ByteArrayN n) where
showsPrec :: Int -> ByteArrayN n -> ShowS
showsPrec Int
_ (ByteArrayN ByteArray
arr) String
s =
let len :: Int
len = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Nat -> Integer
naturalToInteger (Proxy n -> Nat
forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal (Proxy n
forall {k} (t :: k). Proxy t
Proxy :: Proxy n)))
in ByteArray -> Int -> Int -> ShowS
showsSlice ByteArray
arr Int
0 Int
len String
s
data MutableBytes s = MutableBytes
{ forall s. MutableBytes s -> MutableByteArray s
array :: {-# UNPACK #-} !(MutableByteArray s)
, forall s. MutableBytes s -> Int
offset :: {-# UNPACK #-} !Int
, forall s. MutableBytes s -> Int
length :: {-# UNPACK #-} !Int
}
data UnmanagedBytes = UnmanagedBytes
{ UnmanagedBytes -> Addr
address :: {-# UNPACK #-} !Addr
, UnmanagedBytes -> Int
length :: {-# UNPACK #-} !Int
}