{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Data.Primitive.Generic
( Align(..), Packed
, GenericPrim(..)
, offsetOf
) where
import Data.Semigroup
import Data.Functor.Identity
import Data.Functor.Const
import Data.Complex
import Data.Primitive.ByteArray.Unaligned
import Data.Primitive
import Data.Proxy
import Data.Kind (Type)
import Foreign.C
import Foreign.Ptr
import System.Posix.Types
import GHC.Generics
import GHC.Stable
import GHC.TypeLits
import GHC.Exts hiding (setByteArray#)
newtype Align (a :: Nat) t = Align t
deriving newtype (ByteArray# -> Int# -> Align a t
(ByteArray# -> Int# -> Align a t)
-> (forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, Align a t #))
-> (forall s.
MutableByteArray# s -> Int# -> Align a t -> State# s -> State# s)
-> PrimUnaligned (Align a t)
forall (a :: Nat) t.
PrimUnaligned t =>
ByteArray# -> Int# -> Align a t
forall (a :: Nat) t s.
PrimUnaligned t =>
MutableByteArray# s
-> Int# -> State# s -> (# State# s, Align a t #)
forall (a :: Nat) t s.
PrimUnaligned t =>
MutableByteArray# s -> Int# -> Align a t -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, Align a t #)
forall s.
MutableByteArray# s -> Int# -> Align a t -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: forall (a :: Nat) t.
PrimUnaligned t =>
ByteArray# -> Int# -> Align a t
indexUnalignedByteArray# :: ByteArray# -> Int# -> Align a t
$creadUnalignedByteArray# :: forall (a :: Nat) t s.
PrimUnaligned t =>
MutableByteArray# s
-> Int# -> State# s -> (# State# s, Align a t #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, Align a t #)
$cwriteUnalignedByteArray# :: forall (a :: Nat) t s.
PrimUnaligned t =>
MutableByteArray# s -> Int# -> Align a t -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Align a t -> State# s -> State# s
PrimUnaligned)
type Packed = Align 1
type family ValidAlign (n :: Nat) :: Constraint where
ValidAlign 0 = TypeError (Text "Alignment must be strictly possitive (> 0)")
ValidAlign _ = ()
newtype GenericPrim a = GenericPrim a
instance (ValidAlign a, KnownNat a, Prim t) => Prim (Align a t) where
alignmentOfType# :: Proxy (Align a t) -> Int#
alignmentOfType# Proxy (Align a t)
_ = Int#
align#
where !(I# Int#
align#) = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal @a Proxy a
forall {k} (t :: k). Proxy t
Proxy)
sizeOfType# :: Proxy (Align a t) -> Int#
sizeOfType# Proxy (Align a t)
_ = forall a. Prim a => Proxy a -> Int#
sizeOfType# @t Proxy t
forall {k} (t :: k). Proxy t
Proxy
indexByteArray# :: ByteArray# -> Int# -> Align a t
indexByteArray# ByteArray#
ba# Int#
idx# = t -> Align a t
forall (a :: Nat) t. t -> Align a t
Align (ByteArray# -> Int# -> t
forall a. Prim a => ByteArray# -> Int# -> a
indexByteArray# ByteArray#
ba# Int#
idx#)
readByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, Align a t #)
readByteArray# MutableByteArray# s
ba# Int#
idx# State# s
state# =
let !(# State# s
state'#, t
value #) = MutableByteArray# s -> Int# -> State# s -> (# State# s, t #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, t #)
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
readByteArray# MutableByteArray# s
ba# Int#
idx# State# s
state#
in (# State# s
state'#, t -> Align a t
forall (a :: Nat) t. t -> Align a t
Align t
value #)
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Align a t -> State# s -> State# s
writeByteArray# MutableByteArray# s
ba# Int#
idx# (Align t
value) = MutableByteArray# s -> Int# -> t -> State# s -> State# s
forall s. MutableByteArray# s -> Int# -> t -> State# s -> State# s
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
writeByteArray# MutableByteArray# s
ba# Int#
idx# t
value
indexOffAddr# :: Addr# -> Int# -> Align a t
indexOffAddr# Addr#
addr# Int#
idx# = t -> Align a t
forall (a :: Nat) t. t -> Align a t
Align (Addr# -> Int# -> t
forall a. Prim a => Addr# -> Int# -> a
indexOffAddr# Addr#
addr# Int#
idx#)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Align a t #)
readOffAddr# Addr#
addr# Int#
idx# State# s
state# =
let !(# State# s
state'#, t
value #) = Addr# -> Int# -> State# s -> (# State# s, t #)
forall s. Addr# -> Int# -> State# s -> (# State# s, t #)
forall a s.
Prim a =>
Addr# -> Int# -> State# s -> (# State# s, a #)
readOffAddr# Addr#
addr# Int#
idx# State# s
state#
in (# State# s
state'#, t -> Align a t
forall (a :: Nat) t. t -> Align a t
Align t
value #)
writeOffAddr# :: forall s. Addr# -> Int# -> Align a t -> State# s -> State# s
writeOffAddr# Addr#
addr# Int#
idx# (Align t
value) = Addr# -> Int# -> t -> State# s -> State# s
forall s. Addr# -> Int# -> t -> State# s -> State# s
forall a s. Prim a => Addr# -> Int# -> a -> State# s -> State# s
writeOffAddr# Addr#
addr# Int#
idx# t
value
instance (Generic a, DerivePrim (Rep a)) => PrimUnaligned (GenericPrim a) where
indexUnalignedByteArray# :: ByteArray# -> Int# -> GenericPrim a
indexUnalignedByteArray# ByteArray#
ba# Int#
offs# = a -> GenericPrim a
forall a. a -> GenericPrim a
GenericPrim (Rep a Any -> a
forall a x. Generic a => Rep a x -> a
forall x. Rep a x -> a
to (DeriveTree (Rep a) Any -> ByteArray# -> Int# -> Rep a Any
forall p. DeriveTree (Rep a) p -> ByteArray# -> Int# -> Rep a p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> ByteArray# -> Int# -> q p
implIndexUnalignedByteArray# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) ByteArray#
ba# Int#
offs#))
readUnalignedByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, GenericPrim a #)
readUnalignedByteArray# MutableByteArray# s
ba# Int#
offs# State# s
state# =
let !(# State# s
state'#, Rep a Any
value #) = DeriveTree (Rep a) Any
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, Rep a Any #)
forall p s.
DeriveTree (Rep a) p
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, Rep a p #)
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, q p #)
implReadUnalignedByteArray# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) MutableByteArray# s
ba# Int#
offs# State# s
state#
in (# State# s
state'#, a -> GenericPrim a
forall a. a -> GenericPrim a
GenericPrim (Rep a Any -> a
forall a x. Generic a => Rep a x -> a
forall x. Rep a x -> a
to Rep a Any
value) #)
writeUnalignedByteArray# :: forall s.
MutableByteArray# s
-> Int# -> GenericPrim a -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba# Int#
offs# (GenericPrim (a -> Rep a Any
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from -> Rep a Any
value)) = DeriveTree (Rep a) Any
-> MutableByteArray# s -> Int# -> Rep a Any -> State# s -> State# s
forall p s.
DeriveTree (Rep a) p
-> MutableByteArray# s -> Int# -> Rep a p -> State# s -> State# s
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> q p -> State# s -> State# s
implWriteUnalignedByteArray# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) MutableByteArray# s
ba# Int#
offs# Rep a Any
value
type family Or (a :: Bool) (b :: Bool) :: Bool where
Or False False = False
Or _ _ = True
type family HasOffsetOf t (s :: Symbol) :: Bool where
HasOffsetOf (f :*: g) s = Or (HasOffsetOf f s) (HasOffsetOf g s)
HasOffsetOf (M1 _ (MetaSel (Just s) _ _ _) _) s = True
HasOffsetOf (M1 _ _ f) s = HasOffsetOf f s
HasOffsetOf _ _ = False
type family Assert (s :: Symbol) (c :: Bool) :: Constraint where
Assert _ True = ()
Assert s False = TypeError (Text s)
type family Equal a b :: Bool where
Equal a a = True
Equal _ _ = False
class KnownBool (b :: Bool) where
boolVal :: Proxy b -> Bool
ifBool :: a -> a -> Proxy b -> a
instance KnownBool True where
boolVal :: Proxy 'True -> Bool
boolVal Proxy 'True
_ = Bool
True
ifBool :: forall a. a -> a -> Proxy 'True -> a
ifBool a
_ a
a Proxy 'True
_ = a
a
instance KnownBool False where
boolVal :: Proxy 'False -> Bool
boolVal Proxy 'False
_ = Bool
False
ifBool :: forall a. a -> a -> Proxy 'False -> a
ifBool a
a a
_ Proxy 'False
_ = a
a
instance (Generic a, DerivePrim (Rep a)) => Prim (GenericPrim a) where
sizeOfType# :: Proxy (GenericPrim a) -> Int#
sizeOfType# Proxy (GenericPrim a)
_ = forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structSize# @(Rep a) Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy
alignmentOfType# :: Proxy (GenericPrim a) -> Int#
alignmentOfType# Proxy (GenericPrim a)
_ = forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structAlign# @(Rep a) Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy
indexByteArray# :: ByteArray# -> Int# -> GenericPrim a
indexByteArray# ByteArray#
ba# Int#
idx# = a -> GenericPrim a
forall a. a -> GenericPrim a
GenericPrim (Rep a Any -> a
forall a x. Generic a => Rep a x -> a
forall x. Rep a x -> a
to (DeriveTree (Rep a) Any -> ByteArray# -> Int# -> Rep a Any
forall p. DeriveTree (Rep a) p -> ByteArray# -> Int# -> Rep a p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> ByteArray# -> Int# -> q p
implIndexUnalignedByteArray# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) ByteArray#
ba# (Int#
idx# Int# -> Int# -> Int#
*# forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structSize# @(Rep a) Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy)))
readByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, GenericPrim a #)
readByteArray# MutableByteArray# s
ba# Int#
idx# State# s
state# =
let !(# State# s
state'#, Rep a Any
value #) = DeriveTree (Rep a) Any
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, Rep a Any #)
forall p s.
DeriveTree (Rep a) p
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, Rep a p #)
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, q p #)
implReadUnalignedByteArray# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) MutableByteArray# s
ba# (Int#
idx# Int# -> Int# -> Int#
*# forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structSize# @(Rep a) Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy) State# s
state#
in (# State# s
state'#, a -> GenericPrim a
forall a. a -> GenericPrim a
GenericPrim (Rep a Any -> a
forall a x. Generic a => Rep a x -> a
forall x. Rep a x -> a
to Rep a Any
value) #)
writeByteArray# :: forall s.
MutableByteArray# s
-> Int# -> GenericPrim a -> State# s -> State# s
writeByteArray# MutableByteArray# s
ba# Int#
idx# (GenericPrim (a -> Rep a Any
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from -> Rep a Any
value)) = DeriveTree (Rep a) Any
-> MutableByteArray# s -> Int# -> Rep a Any -> State# s -> State# s
forall p s.
DeriveTree (Rep a) p
-> MutableByteArray# s -> Int# -> Rep a p -> State# s -> State# s
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> q p -> State# s -> State# s
implWriteUnalignedByteArray# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) MutableByteArray# s
ba# (Int#
idx# Int# -> Int# -> Int#
*# forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structSize# @(Rep a) Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy) Rep a Any
value
indexOffAddr# :: Addr# -> Int# -> GenericPrim a
indexOffAddr# Addr#
addr# Int#
idx# = a -> GenericPrim a
forall a. a -> GenericPrim a
GenericPrim (Rep a Any -> a
forall a x. Generic a => Rep a x -> a
forall x. Rep a x -> a
to (DeriveTree (Rep a) Any -> Addr# -> Rep a Any
forall p. DeriveTree (Rep a) p -> Addr# -> Rep a p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> Addr# -> q p
implIndexUnalignedOffAddr# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) (Addr#
addr# Addr# -> Int# -> Addr#
`plusAddr#` (Int#
idx# Int# -> Int# -> Int#
*# forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structSize# @(Rep a) Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy))))
readOffAddr# :: forall s.
Addr# -> Int# -> State# s -> (# State# s, GenericPrim a #)
readOffAddr# Addr#
addr# Int#
idx# State# s
state# =
let !(# State# s
state'#, Rep a Any
value #) = DeriveTree (Rep a) Any
-> Addr# -> State# s -> (# State# s, Rep a Any #)
forall p s.
DeriveTree (Rep a) p
-> Addr# -> State# s -> (# State# s, Rep a p #)
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p -> Addr# -> State# s -> (# State# s, q p #)
implReadUnalignedOffAddr# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) (Addr#
addr# Addr# -> Int# -> Addr#
`plusAddr#` (Int#
idx# Int# -> Int# -> Int#
*# forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structSize# @(Rep a) Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy)) State# s
state#
in (# State# s
state'#, a -> GenericPrim a
forall a. a -> GenericPrim a
GenericPrim (Rep a Any -> a
forall a x. Generic a => Rep a x -> a
forall x. Rep a x -> a
to Rep a Any
value) #)
writeOffAddr# :: forall s. Addr# -> Int# -> GenericPrim a -> State# s -> State# s
writeOffAddr# Addr#
addr# Int#
idx# (GenericPrim (a -> Rep a Any
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from -> Rep a Any
value)) = DeriveTree (Rep a) Any
-> Addr# -> Rep a Any -> State# s -> State# s
forall p s.
DeriveTree (Rep a) p -> Addr# -> Rep a p -> State# s -> State# s
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p -> Addr# -> q p -> State# s -> State# s
implWriteUnalignedOffAddr# (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep a)) (Addr#
addr# Addr# -> Int# -> Addr#
`plusAddr#` (Int#
idx# Int# -> Int# -> Int#
*# forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structSize# @(Rep a) Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy)) Rep a Any
value
alignTo# :: Int# -> Int# -> Int#
alignTo# :: Int# -> Int# -> Int#
alignTo# Int#
offs# Int#
base# = Int#
res#
where padded# :: Int#
padded# = Int#
offs# Int# -> Int# -> Int#
+# Int#
base# Int# -> Int# -> Int#
-# Int#
1#
res# :: Int#
res# = Int#
padded# Int# -> Int# -> Int#
-# (Int#
padded# Int# -> Int# -> Int#
`remInt#` Int#
base#)
class DerivePrim q where
type DeriveTree q :: Type -> Type
inOrder' :: (Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder :: (Int# -> (# Int#, Int# #) -> (# Int#, Int# #)) -> Int# -> (# DeriveTree q p, Int# #)
implIndexUnalignedByteArray# :: DeriveTree q p -> ByteArray# -> Int# -> q p
implReadUnalignedByteArray# :: DeriveTree q p -> MutableByteArray# s -> Int# -> State# s -> (# State# s, q p #)
implWriteUnalignedByteArray# :: DeriveTree q p -> MutableByteArray# s -> Int# -> q p -> State# s -> State# s
implIndexUnalignedOffAddr# :: DeriveTree q p -> Addr# -> q p
implReadUnalignedOffAddr# :: DeriveTree q p -> Addr# -> State# s -> (# State# s, q p #)
implWriteUnalignedOffAddr# :: DeriveTree q p -> Addr# -> q p -> State# s -> State# s
class OffsetOf t (s :: Symbol) where
offsetOf# :: t p -> Int#
getInt# :: t p -> Int#
instance OffsetOf V1 s where
offsetOf# :: forall (p :: k). V1 p -> Int#
offsetOf# V1 p
_ = Int#
-1#
getInt# :: forall (p :: k). V1 p -> Int#
getInt# V1 p
_ = Int#
-1#
instance OffsetOf U1 s where
offsetOf# :: forall (p :: k). U1 p -> Int#
offsetOf# U1 p
_ = Int#
-1#
getInt# :: forall (p :: k). U1 p -> Int#
getInt# U1 p
_ = Int#
-1#
instance (OffsetOf f s, OffsetOf g s, KnownBool (HasOffsetOf f s), KnownBool (HasOffsetOf g s)) => OffsetOf (f :*: g) s where
offsetOf# :: forall (p :: k). (:*:) f g p -> Int#
offsetOf# (f p
f :*: g p
g)
| forall (b :: Bool). KnownBool b => Proxy b -> Bool
boolVal @(HasOffsetOf f s) Proxy (HasOffsetOf f s)
forall {k} (t :: k). Proxy t
Proxy = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
offsetOf# @_ @s f p
f
| forall (b :: Bool). KnownBool b => Proxy b -> Bool
boolVal @(HasOffsetOf g s) Proxy (HasOffsetOf g s)
forall {k} (t :: k). Proxy t
Proxy = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
offsetOf# @_ @s g p
g
| Bool
otherwise = Int#
-1#
getInt# :: forall (p :: k). (:*:) f g p -> Int#
getInt# (:*:) f g p
_ = Int#
-1#
instance OffsetOf (K1 i Int) s where
offsetOf# :: forall (p :: k). K1 i Int p -> Int#
offsetOf# K1 i Int p
_ = Int#
-1#
getInt# :: forall (p :: k). K1 i Int p -> Int#
getInt# (K1 (I# Int#
offs#)) = Int#
offs#
instance OffsetOf c s => OffsetOf (M1 i (MetaSel (Just s') a b d) c) s where
offsetOf# :: forall (p :: k). M1 i ('MetaSel ('Just s') a b d) c p -> Int#
offsetOf# (M1 c p
c) = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
getInt# @_ @s c p
c
getInt# :: forall (p :: k). M1 i ('MetaSel ('Just s') a b d) c p -> Int#
getInt# (M1 c p
c) = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
getInt# @_ @s c p
c
instance OffsetOf c s => OffsetOf (M1 i (MetaSel Nothing a b d) c) s where
offsetOf# :: forall (p :: k). M1 i ('MetaSel 'Nothing a b d) c p -> Int#
offsetOf# (M1 c p
c) = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
offsetOf# @_ @s c p
c
getInt# :: forall (p :: k). M1 i ('MetaSel 'Nothing a b d) c p -> Int#
getInt# (M1 c p
c) = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
getInt# @_ @s c p
c
instance OffsetOf c s => OffsetOf (M1 i (MetaData a b d e) c) s where
offsetOf# :: forall (p :: k). M1 i ('MetaData a b d e) c p -> Int#
offsetOf# (M1 c p
c) = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
offsetOf# @_ @s c p
c
getInt# :: forall (p :: k). M1 i ('MetaData a b d e) c p -> Int#
getInt# (M1 c p
c) = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
getInt# @_ @s c p
c
instance OffsetOf c s => OffsetOf (M1 i (MetaCons a b e) c) s where
offsetOf# :: forall (p :: k). M1 i ('MetaCons a b e) c p -> Int#
offsetOf# (M1 c p
c) = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
offsetOf# @_ @s c p
c
getInt# :: forall (p :: k). M1 i ('MetaCons a b e) c p -> Int#
getInt# (M1 c p
c) = forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
getInt# @_ @s c p
c
offsetOf :: forall t s. (Generic t, DerivePrim (Rep t), OffsetOf (DeriveTree (Rep t)) s, Assert "Field does not exist" (HasOffsetOf (DeriveTree (Rep t)) s)) => Int
offsetOf :: forall t (s :: Symbol).
(Generic t, DerivePrim (Rep t), OffsetOf (DeriveTree (Rep t)) s,
Assert
"Field does not exist" (HasOffsetOf (DeriveTree (Rep t)) s)) =>
Int
offsetOf = Int# -> Int
I# (forall {k} (t :: k -> *) (s :: Symbol) (p :: k).
OffsetOf t s =>
t p -> Int#
forall (t :: * -> *) (s :: Symbol) p. OffsetOf t s => t p -> Int#
offsetOf# @_ @s (forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets @(Rep t)))
membOffsets :: forall q p. DerivePrim q => DeriveTree q p
membOffsets :: forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membOffsets = DeriveTree q p
tree
where (# DeriveTree q p
tree, Int#
_ #) = forall (q :: * -> *) p.
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree q p, Int# #)
inOrder @q Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
0#
fn :: Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
accum# (# Int#
align#, Int#
size# #) =
let offs# :: Int#
offs# = Int#
accum# Int# -> Int# -> Int#
`alignTo#` Int#
align#
in (# Int#
offs#, Int#
offs# Int# -> Int# -> Int#
+# Int#
size# #)
membAligns :: forall q p. DerivePrim q => DeriveTree q p
membAligns :: forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membAligns = DeriveTree q p
tree
where (# DeriveTree q p
tree, Int#
_ #) = forall (q :: * -> *) p.
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree q p, Int# #)
inOrder @q Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
0#
fn :: Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn (Int#
_ :: Int#) (# Int#
align# :: Int# , Int#
_ :: Int# #) =
(# Int#
align#, Int#
0# #)
membSizes :: forall q p. DerivePrim q => DeriveTree q p
membSizes :: forall (q :: * -> *) p. DerivePrim q => DeriveTree q p
membSizes = DeriveTree q p
tree
where (# DeriveTree q p
tree, Int#
_ #) = forall (q :: * -> *) p.
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree q p, Int# #)
inOrder @q Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
0#
fn :: Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn (Int#
_ :: Int#) (# Int#
_ :: Int# , Int#
size# :: Int# #) =
(# Int#
size#, Int#
0# #)
structSize# :: forall q. DerivePrim q => Proxy q -> Int#
structSize# :: forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structSize# Proxy q
p = forall (q :: * -> *).
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' @q Int# -> (# Int#, Int# #) -> Int#
fn Int#
0# Int# -> Int# -> Int#
`alignTo#` Proxy q -> Int#
forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structAlign# Proxy q
p
where fn :: Int# -> (# Int#, Int# #) -> Int#
fn Int#
offset# (# Int#
align#, Int#
size# #) = (Int#
offset# Int# -> Int# -> Int#
`alignTo#` Int#
align#) Int# -> Int# -> Int#
+# Int#
size#
structAlign# :: forall q. DerivePrim q => Proxy q -> Int#
structAlign# :: forall (q :: * -> *). DerivePrim q => Proxy q -> Int#
structAlign# Proxy q
_ = forall (q :: * -> *).
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' @q Int# -> (# Int#, Int# #) -> Int#
fn Int#
1#
where fn :: Int# -> (# Int#, Int# #) -> Int#
fn (Int# -> Int
I# -> Int
accum) (# Int# -> Int
I# -> Int
align, Int#
_ :: Int# #) =
let !(I# Int#
result#) = Int -> Int -> Int
forall a. Integral a => a -> a -> a
lcm Int
accum Int
align
in Int#
result#
instance DerivePrim V1 where
type DeriveTree V1 = V1
inOrder' :: (Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' Int# -> (# Int#, Int# #) -> Int#
_ Int#
a = Int#
a
inOrder :: forall p.
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree V1 p, Int# #)
inOrder Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
_ Int#
a = (# V1 p
DeriveTree V1 p
forall a. HasCallStack => a
undefined, Int#
a #)
implIndexUnalignedByteArray# :: forall p. DeriveTree V1 p -> ByteArray# -> Int# -> V1 p
implIndexUnalignedByteArray# DeriveTree V1 p
_ ByteArray#
_ Int#
_ = V1 p
forall a. HasCallStack => a
undefined
implReadUnalignedByteArray# :: forall p s.
DeriveTree V1 p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, V1 p #)
implReadUnalignedByteArray# DeriveTree V1 p
_ MutableByteArray# s
_ Int#
_ State# s
state# = (# State# s
state#, V1 p
forall a. HasCallStack => a
undefined #)
implWriteUnalignedByteArray# :: forall p s.
DeriveTree V1 p
-> MutableByteArray# s -> Int# -> V1 p -> State# s -> State# s
implWriteUnalignedByteArray# DeriveTree V1 p
_ MutableByteArray# s
_ Int#
_ V1 p
_ State# s
state# = State# s
state#
implIndexUnalignedOffAddr# :: forall p. DeriveTree V1 p -> Addr# -> V1 p
implIndexUnalignedOffAddr# DeriveTree V1 p
_ Addr#
_ = V1 p
forall a. HasCallStack => a
undefined
implReadUnalignedOffAddr# :: forall p s.
DeriveTree V1 p -> Addr# -> State# s -> (# State# s, V1 p #)
implReadUnalignedOffAddr# DeriveTree V1 p
_ Addr#
_ State# s
state# = (# State# s
state#, V1 p
forall a. HasCallStack => a
undefined #)
implWriteUnalignedOffAddr# :: forall p s.
DeriveTree V1 p -> Addr# -> V1 p -> State# s -> State# s
implWriteUnalignedOffAddr# DeriveTree V1 p
_ Addr#
_ V1 p
_ State# s
state# = State# s
state#
instance DerivePrim U1 where
type DeriveTree U1 = U1
inOrder' :: (Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' Int# -> (# Int#, Int# #) -> Int#
fn Int#
a = Int# -> (# Int#, Int# #) -> Int#
fn Int#
a (# Int#
1#, Int#
0# #)
inOrder :: forall p.
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree U1 p, Int# #)
inOrder Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
a = (# U1 p
DeriveTree U1 p
forall k (p :: k). U1 p
U1, Int#
a' #)
where !(# Int#
_, Int#
a' #) = Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
a (# Int#
1#, Int#
0# #)
implIndexUnalignedByteArray# :: forall p. DeriveTree U1 p -> ByteArray# -> Int# -> U1 p
implIndexUnalignedByteArray# DeriveTree U1 p
_ ByteArray#
_ Int#
_ = U1 p
forall k (p :: k). U1 p
U1
implReadUnalignedByteArray# :: forall p s.
DeriveTree U1 p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, U1 p #)
implReadUnalignedByteArray# DeriveTree U1 p
_ MutableByteArray# s
_ Int#
_ State# s
state# = (# State# s
state#, U1 p
forall k (p :: k). U1 p
U1 #)
implWriteUnalignedByteArray# :: forall p s.
DeriveTree U1 p
-> MutableByteArray# s -> Int# -> U1 p -> State# s -> State# s
implWriteUnalignedByteArray# DeriveTree U1 p
_ MutableByteArray# s
_ Int#
_ U1 p
_ State# s
state# = State# s
state#
implIndexUnalignedOffAddr# :: forall p. DeriveTree U1 p -> Addr# -> U1 p
implIndexUnalignedOffAddr# DeriveTree U1 p
_ Addr#
_ = U1 p
forall k (p :: k). U1 p
U1
implReadUnalignedOffAddr# :: forall p s.
DeriveTree U1 p -> Addr# -> State# s -> (# State# s, U1 p #)
implReadUnalignedOffAddr# DeriveTree U1 p
_ Addr#
_ State# s
state# = (# State# s
state#, U1 p
forall k (p :: k). U1 p
U1 #)
implWriteUnalignedOffAddr# :: forall p s.
DeriveTree U1 p -> Addr# -> U1 p -> State# s -> State# s
implWriteUnalignedOffAddr# DeriveTree U1 p
_ Addr#
_ U1 p
_ State# s
state# = State# s
state#
instance (DerivePrim f, DerivePrim g) => DerivePrim (f :*: g) where
type DeriveTree (f :*: g) = DeriveTree f :*: DeriveTree g
inOrder' :: (Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' Int# -> (# Int#, Int# #) -> Int#
fn Int#
a = forall (q :: * -> *).
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' @g Int# -> (# Int#, Int# #) -> Int#
fn (forall (q :: * -> *).
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' @f Int# -> (# Int#, Int# #) -> Int#
fn Int#
a)
inOrder :: forall p.
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree (f :*: g) p, Int# #)
inOrder Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
a = (# DeriveTree f p
f DeriveTree f p
-> DeriveTree g p -> (:*:) (DeriveTree f) (DeriveTree g) p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: DeriveTree g p
g, Int#
g# #)
where !(# DeriveTree f p
f, Int#
f# #) = forall (q :: * -> *) p.
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree q p, Int# #)
inOrder @f Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
a
!(# DeriveTree g p
g, Int#
g# #) = forall (q :: * -> *) p.
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree q p, Int# #)
inOrder @g Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
f#
implIndexUnalignedByteArray# :: forall p.
DeriveTree (f :*: g) p -> ByteArray# -> Int# -> (:*:) f g p
implIndexUnalignedByteArray# (DeriveTree f p
fi :*: DeriveTree g p
gi) ByteArray#
ba# Int#
baseOffs# =
DeriveTree f p -> ByteArray# -> Int# -> f p
forall p. DeriveTree f p -> ByteArray# -> Int# -> f p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> ByteArray# -> Int# -> q p
implIndexUnalignedByteArray# DeriveTree f p
fi ByteArray#
ba# Int#
baseOffs# f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*:
DeriveTree g p -> ByteArray# -> Int# -> g p
forall p. DeriveTree g p -> ByteArray# -> Int# -> g p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> ByteArray# -> Int# -> q p
implIndexUnalignedByteArray# DeriveTree g p
gi ByteArray#
ba# Int#
baseOffs#
implReadUnalignedByteArray# :: forall p s.
DeriveTree (f :*: g) p
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, (:*:) f g p #)
implReadUnalignedByteArray# (DeriveTree f p
fi :*: DeriveTree g p
gi) MutableByteArray# s
ba# Int#
baseOffs# State# s
state0# =
let !(# State# s
state1#, f p
f #) = forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, q p #)
implReadUnalignedByteArray# @f DeriveTree f p
fi MutableByteArray# s
ba# Int#
baseOffs# State# s
state0#
!(# State# s
state2#, g p
g #) = forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, q p #)
implReadUnalignedByteArray# @g DeriveTree g p
gi MutableByteArray# s
ba# Int#
baseOffs# State# s
state1#
in (# State# s
state2#, f p
f f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g p
g #)
implWriteUnalignedByteArray# :: forall p s.
DeriveTree (f :*: g) p
-> MutableByteArray# s
-> Int#
-> (:*:) f g p
-> State# s
-> State# s
implWriteUnalignedByteArray# (DeriveTree f p
fi :*: DeriveTree g p
gi) MutableByteArray# s
ba# Int#
baseOffs# (f p
f :*: g p
g) State# s
state# =
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> q p -> State# s -> State# s
implWriteUnalignedByteArray# @g DeriveTree g p
gi MutableByteArray# s
ba# Int#
baseOffs# g p
g (forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> q p -> State# s -> State# s
implWriteUnalignedByteArray# @f DeriveTree f p
fi MutableByteArray# s
ba# Int#
baseOffs# f p
f State# s
state#)
implIndexUnalignedOffAddr# :: forall p. DeriveTree (f :*: g) p -> Addr# -> (:*:) f g p
implIndexUnalignedOffAddr# (DeriveTree f p
fi :*: DeriveTree g p
gi) Addr#
addr# =
DeriveTree f p -> Addr# -> f p
forall p. DeriveTree f p -> Addr# -> f p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> Addr# -> q p
implIndexUnalignedOffAddr# DeriveTree f p
fi Addr#
addr# f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*:
DeriveTree g p -> Addr# -> g p
forall p. DeriveTree g p -> Addr# -> g p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> Addr# -> q p
implIndexUnalignedOffAddr# DeriveTree g p
gi Addr#
addr#
implReadUnalignedOffAddr# :: forall p s.
DeriveTree (f :*: g) p
-> Addr# -> State# s -> (# State# s, (:*:) f g p #)
implReadUnalignedOffAddr# (DeriveTree f p
fi :*: DeriveTree g p
gi) Addr#
addr# State# s
state0# =
let !(# State# s
state1#, f p
f #) = forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p -> Addr# -> State# s -> (# State# s, q p #)
implReadUnalignedOffAddr# @f DeriveTree f p
fi Addr#
addr# State# s
state0#
!(# State# s
state2#, g p
g #) = forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p -> Addr# -> State# s -> (# State# s, q p #)
implReadUnalignedOffAddr# @g DeriveTree g p
gi Addr#
addr# State# s
state1#
in (# State# s
state2#, f p
f f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g p
g #)
implWriteUnalignedOffAddr# :: forall p s.
DeriveTree (f :*: g) p
-> Addr# -> (:*:) f g p -> State# s -> State# s
implWriteUnalignedOffAddr# (DeriveTree f p
fi :*: DeriveTree g p
gi) Addr#
addr# (f p
f :*: g p
g) State# s
state# =
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p -> Addr# -> q p -> State# s -> State# s
implWriteUnalignedOffAddr# @g DeriveTree g p
gi Addr#
addr# g p
g (forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p -> Addr# -> q p -> State# s -> State# s
implWriteUnalignedOffAddr# @f DeriveTree f p
fi Addr#
addr# f p
f State# s
state#)
instance DerivePrim f => DerivePrim (M1 i t f) where
type DeriveTree (M1 i t f) = M1 i t (DeriveTree f)
inOrder' :: (Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' = forall (q :: * -> *).
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' @f
inOrder :: forall p.
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree (M1 i t f) p, Int# #)
inOrder Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
a = (# DeriveTree f p -> M1 i t (DeriveTree f) p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 DeriveTree f p
f, Int#
f# #)
where !(# DeriveTree f p
f, Int#
f# #) = forall (q :: * -> *) p.
DerivePrim q =>
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree q p, Int# #)
inOrder @f Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
a
implIndexUnalignedByteArray# :: forall p.
DeriveTree (M1 i t f) p -> ByteArray# -> Int# -> M1 i t f p
implIndexUnalignedByteArray# (M1 DeriveTree f p
fi) ByteArray#
ba# Int#
baseOffs# = f p -> M1 i t f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (DeriveTree f p -> ByteArray# -> Int# -> f p
forall p. DeriveTree f p -> ByteArray# -> Int# -> f p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> ByteArray# -> Int# -> q p
implIndexUnalignedByteArray# DeriveTree f p
fi ByteArray#
ba# Int#
baseOffs#)
implReadUnalignedByteArray# :: forall p s.
DeriveTree (M1 i t f) p
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, M1 i t f p #)
implReadUnalignedByteArray# (M1 DeriveTree f p
fi) MutableByteArray# s
ba# Int#
baseOffs# State# s
state# =
let !(# State# s
state'#, f p
value #) = DeriveTree f p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, f p #)
forall p s.
DeriveTree f p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, f p #)
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> State# s -> (# State# s, q p #)
implReadUnalignedByteArray# DeriveTree f p
fi MutableByteArray# s
ba# Int#
baseOffs# State# s
state#
in (# State# s
state'#, f p -> M1 i t f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 f p
value #)
implWriteUnalignedByteArray# :: forall p s.
DeriveTree (M1 i t f) p
-> MutableByteArray# s
-> Int#
-> M1 i t f p
-> State# s
-> State# s
implWriteUnalignedByteArray# (M1 DeriveTree f p
fi) MutableByteArray# s
ba# Int#
baseOffs# (M1 f p
value) =
DeriveTree f p
-> MutableByteArray# s -> Int# -> f p -> State# s -> State# s
forall p s.
DeriveTree f p
-> MutableByteArray# s -> Int# -> f p -> State# s -> State# s
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p
-> MutableByteArray# s -> Int# -> q p -> State# s -> State# s
implWriteUnalignedByteArray# DeriveTree f p
fi MutableByteArray# s
ba# Int#
baseOffs# f p
value
implIndexUnalignedOffAddr# :: forall p. DeriveTree (M1 i t f) p -> Addr# -> M1 i t f p
implIndexUnalignedOffAddr# (M1 DeriveTree f p
fi) Addr#
addr# = f p -> M1 i t f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (DeriveTree f p -> Addr# -> f p
forall p. DeriveTree f p -> Addr# -> f p
forall (q :: * -> *) p.
DerivePrim q =>
DeriveTree q p -> Addr# -> q p
implIndexUnalignedOffAddr# DeriveTree f p
fi Addr#
addr#)
implReadUnalignedOffAddr# :: forall p s.
DeriveTree (M1 i t f) p
-> Addr# -> State# s -> (# State# s, M1 i t f p #)
implReadUnalignedOffAddr# (M1 DeriveTree f p
fi) Addr#
addr# State# s
state# =
let !(# State# s
state'#, f p
value #) = DeriveTree f p -> Addr# -> State# s -> (# State# s, f p #)
forall p s.
DeriveTree f p -> Addr# -> State# s -> (# State# s, f p #)
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p -> Addr# -> State# s -> (# State# s, q p #)
implReadUnalignedOffAddr# DeriveTree f p
fi Addr#
addr# State# s
state#
in (# State# s
state'#, f p -> M1 i t f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 f p
value #)
implWriteUnalignedOffAddr# :: forall p s.
DeriveTree (M1 i t f) p
-> Addr# -> M1 i t f p -> State# s -> State# s
implWriteUnalignedOffAddr# (M1 DeriveTree f p
fi) Addr#
addr# (M1 f p
value) =
DeriveTree f p -> Addr# -> f p -> State# s -> State# s
forall p s. DeriveTree f p -> Addr# -> f p -> State# s -> State# s
forall (q :: * -> *) p s.
DerivePrim q =>
DeriveTree q p -> Addr# -> q p -> State# s -> State# s
implWriteUnalignedOffAddr# DeriveTree f p
fi Addr#
addr# f p
value
instance (Prim c, PrimUnaligned c) => DerivePrim (K1 i c) where
type DeriveTree (K1 i c) = K1 i Int
inOrder' :: (Int# -> (# Int#, Int# #) -> Int#) -> Int# -> Int#
inOrder' Int# -> (# Int#, Int# #) -> Int#
fn Int#
a = Int# -> (# Int#, Int# #) -> Int#
fn Int#
a (# forall a. Prim a => Proxy a -> Int#
alignmentOfType# @c Proxy c
forall {k} (t :: k). Proxy t
Proxy, forall a. Prim a => Proxy a -> Int#
sizeOfType# @c Proxy c
forall {k} (t :: k). Proxy t
Proxy #)
inOrder :: forall p.
(Int# -> (# Int#, Int# #) -> (# Int#, Int# #))
-> Int# -> (# DeriveTree (K1 i c) p, Int# #)
inOrder Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
a = (# Int -> K1 i Int p
forall k i c (p :: k). c -> K1 i c p
K1 Int
v, Int#
a' #)
where !(# Int# -> Int
I# -> Int
v, Int#
a' #) = Int# -> (# Int#, Int# #) -> (# Int#, Int# #)
fn Int#
a (# forall a. Prim a => Proxy a -> Int#
alignmentOfType# @c Proxy c
forall {k} (t :: k). Proxy t
Proxy, forall a. Prim a => Proxy a -> Int#
sizeOfType# @c Proxy c
forall {k} (t :: k). Proxy t
Proxy #)
implIndexUnalignedByteArray# :: forall p. DeriveTree (K1 i c) p -> ByteArray# -> Int# -> K1 i c p
implIndexUnalignedByteArray# (K1 (I# Int#
membOffs#)) ByteArray#
ba# Int#
baseOffs# = c -> K1 i c p
forall k i c (p :: k). c -> K1 i c p
K1 (ByteArray# -> Int# -> c
forall a. PrimUnaligned a => ByteArray# -> Int# -> a
indexUnalignedByteArray# ByteArray#
ba# (Int#
baseOffs# Int# -> Int# -> Int#
+# Int#
membOffs#))
implReadUnalignedByteArray# :: forall p s.
DeriveTree (K1 i c) p
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, K1 i c p #)
implReadUnalignedByteArray# (K1 (I# Int#
membOffs#)) MutableByteArray# s
ba# Int#
baseOffs# State# s
state# = (# State# s
state'#, c -> K1 i c p
forall k i c (p :: k). c -> K1 i c p
K1 c
value #)
where !(# State# s
state'#, c
value #) = MutableByteArray# s -> Int# -> State# s -> (# State# s, c #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, c #)
forall a s.
PrimUnaligned a =>
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
readUnalignedByteArray# MutableByteArray# s
ba# (Int#
baseOffs# Int# -> Int# -> Int#
+# Int#
membOffs#) State# s
state#
implWriteUnalignedByteArray# :: forall p s.
DeriveTree (K1 i c) p
-> MutableByteArray# s -> Int# -> K1 i c p -> State# s -> State# s
implWriteUnalignedByteArray# (K1 (I# Int#
membOffs#)) MutableByteArray# s
ba# Int#
baseOffs# (K1 c
value) =
MutableByteArray# s -> Int# -> c -> State# s -> State# s
forall s. MutableByteArray# s -> Int# -> c -> State# s -> State# s
forall a s.
PrimUnaligned a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba# (Int#
baseOffs# Int# -> Int# -> Int#
+# Int#
membOffs#) c
value
implIndexUnalignedOffAddr# :: forall p. DeriveTree (K1 i c) p -> Addr# -> K1 i c p
implIndexUnalignedOffAddr# (K1 (I# Int#
membOffs#)) Addr#
addr# = c -> K1 i c p
forall k i c (p :: k). c -> K1 i c p
K1 (Addr# -> Int# -> c
forall a. Prim a => Addr# -> Int# -> a
indexOffAddr# (Addr#
addr# Addr# -> Int# -> Addr#
`plusAddr#` Int#
membOffs#) Int#
0#)
implReadUnalignedOffAddr# :: forall p s.
DeriveTree (K1 i c) p
-> Addr# -> State# s -> (# State# s, K1 i c p #)
implReadUnalignedOffAddr# (K1 (I# Int#
membOffs#)) Addr#
addr# State# s
state# = (# State# s
state'#, c -> K1 i c p
forall k i c (p :: k). c -> K1 i c p
K1 c
value #)
where !(# State# s
state'#, c
value #) = Addr# -> Int# -> State# s -> (# State# s, c #)
forall s. Addr# -> Int# -> State# s -> (# State# s, c #)
forall a s.
Prim a =>
Addr# -> Int# -> State# s -> (# State# s, a #)
readOffAddr# (Addr#
addr# Addr# -> Int# -> Addr#
`plusAddr#` Int#
membOffs#) Int#
0# State# s
state#
implWriteUnalignedOffAddr# :: forall p s.
DeriveTree (K1 i c) p -> Addr# -> K1 i c p -> State# s -> State# s
implWriteUnalignedOffAddr# (K1 (I# Int#
membOffs#)) Addr#
addr# (K1 c
value) =
Addr# -> Int# -> c -> State# s -> State# s
forall s. Addr# -> Int# -> c -> State# s -> State# s
forall a s. Prim a => Addr# -> Int# -> a -> State# s -> State# s
writeOffAddr# (Addr#
addr# Addr# -> Int# -> Addr#
`plusAddr#` Int#
membOffs#) Int#
0# c
value
instance PrimUnaligned (StablePtr a) where
indexUnalignedByteArray# :: ByteArray# -> Int# -> StablePtr a
indexUnalignedByteArray# ByteArray#
ba# Int#
offset# = StablePtr# a -> StablePtr a
forall a. StablePtr# a -> StablePtr a
StablePtr (ByteArray# -> Int# -> StablePtr# a
forall a. ByteArray# -> Int# -> StablePtr# a
indexWord8ArrayAsStablePtr# ByteArray#
ba# Int#
offset#)
readUnalignedByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr a #)
readUnalignedByteArray# MutableByteArray# s
ba# Int#
offset# State# s
state# =
let !(# State# s
state'#, StablePtr# a
ptr# #) = MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr# a #)
forall d a.
MutableByteArray# d
-> Int# -> State# d -> (# State# d, StablePtr# a #)
readWord8ArrayAsStablePtr# MutableByteArray# s
ba# Int#
offset# State# s
state#
in (# State# s
state'#, StablePtr# a -> StablePtr a
forall a. StablePtr# a -> StablePtr a
StablePtr StablePtr# a
ptr# #)
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> StablePtr a -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba# Int#
offset# (StablePtr StablePtr# a
ptr#) = MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
forall d a.
MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
writeWord8ArrayAsStablePtr# MutableByteArray# s
ba# Int#
offset# StablePtr# a
ptr#
instance PrimUnaligned (FunPtr a) where
indexUnalignedByteArray# :: ByteArray# -> Int# -> FunPtr a
indexUnalignedByteArray# ByteArray#
ba# Int#
offset# = Addr# -> FunPtr a
forall a. Addr# -> FunPtr a
FunPtr (ByteArray# -> Int# -> Addr#
indexWord8ArrayAsAddr# ByteArray#
ba# Int#
offset#)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FunPtr a #)
readUnalignedByteArray# MutableByteArray# s
ba# Int#
offset# State# s
state# =
let !(# State# s
state'#, Addr#
ptr# #) = MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
readWord8ArrayAsAddr# MutableByteArray# s
ba# Int#
offset# State# s
state#
in (# State# s
state'#, Addr# -> FunPtr a
forall a. Addr# -> FunPtr a
FunPtr Addr#
ptr# #)
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> FunPtr a -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba# Int#
offset# (FunPtr Addr#
ptr#) = MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
writeWord8ArrayAsAddr# MutableByteArray# s
ba# Int#
offset# Addr#
ptr#
instance (Prim a, PrimUnaligned a) => PrimUnaligned (Complex a) where
indexUnalignedByteArray# :: ByteArray# -> Int# -> Complex a
indexUnalignedByteArray# ByteArray#
ba# Int#
offset# =
ByteArray# -> Int# -> a
forall a. PrimUnaligned a => ByteArray# -> Int# -> a
indexUnalignedByteArray# ByteArray#
ba# Int#
offset# a -> a -> Complex a
forall a. a -> a -> Complex a
:+
ByteArray# -> Int# -> a
forall a. PrimUnaligned a => ByteArray# -> Int# -> a
indexUnalignedByteArray# ByteArray#
ba# (Int#
offset# Int# -> Int# -> Int#
+# forall a. Prim a => Proxy a -> Int#
sizeOfType# @a Proxy a
forall {k} (t :: k). Proxy t
Proxy)
readUnalignedByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, Complex a #)
readUnalignedByteArray# MutableByteArray# s
ba# Int#
offset# State# s
state0# =
let !(# State# s
state1#, a
a #) = MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
forall a s.
PrimUnaligned a =>
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
readUnalignedByteArray# MutableByteArray# s
ba# Int#
offset# State# s
state0#
!(# State# s
state2#, a
b #) = MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
forall a s.
PrimUnaligned a =>
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
readUnalignedByteArray# MutableByteArray# s
ba# (Int#
offset# Int# -> Int# -> Int#
+# forall a. Prim a => Proxy a -> Int#
sizeOfType# @a Proxy a
forall {k} (t :: k). Proxy t
Proxy) State# s
state1#
in (# State# s
state2#, a
a a -> a -> Complex a
forall a. a -> a -> Complex a
:+ a
b #)
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Complex a -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba# Int#
offset# (a
a :+ a
b) State# s
state# =
MutableByteArray# s -> Int# -> a -> State# s -> State# s
forall s. MutableByteArray# s -> Int# -> a -> State# s -> State# s
forall a s.
PrimUnaligned a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba# (Int#
offset# Int# -> Int# -> Int#
+# forall a. Prim a => Proxy a -> Int#
sizeOfType# @a Proxy a
forall {k} (t :: k). Proxy t
Proxy) a
b (MutableByteArray# s -> Int# -> a -> State# s -> State# s
forall s. MutableByteArray# s -> Int# -> a -> State# s -> State# s
forall a s.
PrimUnaligned a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba# Int#
offset# a
a State# s
state#)
deriving newtype instance PrimUnaligned CBool
deriving newtype instance PrimUnaligned CClock
deriving newtype instance PrimUnaligned CFloat
deriving newtype instance PrimUnaligned CIntMax
deriving newtype instance PrimUnaligned CUIntMax
deriving newtype instance PrimUnaligned CIntPtr
deriving newtype instance PrimUnaligned CUIntPtr
deriving newtype instance PrimUnaligned CPtrdiff
deriving newtype instance PrimUnaligned CUSeconds
deriving newtype instance PrimUnaligned CSUSeconds
deriving newtype instance PrimUnaligned CSigAtomic
deriving newtype instance PrimUnaligned CSize
deriving newtype instance PrimUnaligned CTime
deriving newtype instance PrimUnaligned CUChar
deriving newtype instance PrimUnaligned CUShort
deriving newtype instance PrimUnaligned CWchar
deriving newtype instance PrimUnaligned IntPtr
deriving newtype instance PrimUnaligned WordPtr
deriving newtype instance PrimUnaligned CBlkCnt
deriving newtype instance PrimUnaligned CBlkSize
deriving newtype instance PrimUnaligned CCc
deriving newtype instance PrimUnaligned CClockId
deriving newtype instance PrimUnaligned CFsBlkCnt
deriving newtype instance PrimUnaligned CFsFilCnt
deriving newtype instance PrimUnaligned CGid
deriving newtype instance PrimUnaligned CId
deriving newtype instance PrimUnaligned CKey
deriving newtype instance PrimUnaligned CNlink
deriving newtype instance PrimUnaligned CRLim
deriving newtype instance PrimUnaligned CSpeed
deriving newtype instance PrimUnaligned CTcflag
deriving newtype instance PrimUnaligned CTimer
deriving newtype instance PrimUnaligned CUid
deriving newtype instance PrimUnaligned a => PrimUnaligned (Identity a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (Down a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (First a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (Last a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (Max a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (Min a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (Dual a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (Product a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (Sum a)
deriving newtype instance PrimUnaligned a => PrimUnaligned (Const a b)