{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Capnp.New.Accessors
( readField
, getField
, setField
, newField
, hasField
, encodeField
, parseField
, setVariant
, initVariant
, encodeVariant
, structWhich
, unionWhich
, structUnion
, unionStruct
) where
import qualified Capnp.Fields as F
import Capnp.Message (Mutability(..))
import qualified Capnp.New.Classes as C
import qualified Capnp.Repr as R
import Capnp.TraversalLimit (evalLimitT)
import qualified Capnp.Untyped as U
import Data.Bits
import Data.Maybe (fromJust, isJust)
import Data.Word
import GHC.Prim (coerce)
{-# INLINE readField #-}
readField
:: forall k a b mut m.
( R.IsStruct a
, U.ReadCtx m mut
)
=> F.Field k a b
-> R.Raw mut a
-> m (R.Raw mut b)
readField :: Field k a b -> Raw mut a -> m (Raw mut b)
readField (F.Field FieldLoc k (ReprFor b)
field) (R.Raw Untyped mut (ReprFor a)
struct) =
case FieldLoc k (ReprFor b)
field of
F.DataField F.DataFieldLoc{ BitCount
shift :: forall (sz :: DataSz). DataFieldLoc sz -> BitCount
shift :: BitCount
shift, Word16
index :: forall (sz :: DataSz). DataFieldLoc sz -> Word16
index :: Word16
index, Word64
mask :: forall (sz :: DataSz). DataFieldLoc sz -> Word64
mask :: Word64
mask, Word64
defaultValue :: forall (sz :: DataSz). DataFieldLoc sz -> Word64
defaultValue :: Word64
defaultValue } -> do
Word64
word <- Int -> Struct mut -> m Word64
forall (m :: * -> *) (msg :: Mutability).
ReadCtx m msg =>
Int -> Struct msg -> m Word64
U.getData (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
index) Struct mut
Untyped mut (ReprFor a)
struct
Raw mut b -> m (Raw mut b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Raw mut b -> m (Raw mut b)) -> Raw mut b -> m (Raw mut b)
forall a b. (a -> b) -> a -> b
$ Untyped mut (ReprFor b) -> Raw mut b
forall (mut :: Mutability) a. Untyped mut (ReprFor a) -> Raw mut a
R.Raw (Untyped mut (ReprFor b) -> Raw mut b)
-> Untyped mut (ReprFor b) -> Raw mut b
forall a b. (a -> b) -> a -> b
$ Word64 -> UntypedData a
forall a. IsWord a => Word64 -> a
C.fromWord (Word64 -> UntypedData a) -> Word64 -> UntypedData a
forall a b. (a -> b) -> a -> b
$ ((Word64
word Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
mask) Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` BitCount -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral BitCount
shift) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
`xor` Word64
defaultValue
F.PtrField Word16
index ->
Int -> Struct mut -> m (Maybe (Ptr mut))
forall (m :: * -> *) (msg :: Mutability).
ReadCtx m msg =>
Int -> Struct msg -> m (Maybe (Ptr msg))
U.getPtr (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
index) Struct mut
Untyped mut (ReprFor a)
struct m (Maybe (Ptr mut))
-> (Maybe (Ptr mut) -> m (Raw mut b)) -> m (Raw mut b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe (Ptr mut) -> m (Raw mut b)
forall (pr :: Maybe PtrRepr).
(ReprFor b ~ 'Ptr pr, IsPtrRepr pr) =>
Maybe (Ptr mut) -> m (Raw mut b)
readPtrField
FieldLoc k (ReprFor b)
F.GroupField ->
Raw mut b -> m (Raw mut b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Raw mut b -> m (Raw mut b)) -> Raw mut b -> m (Raw mut b)
forall a b. (a -> b) -> a -> b
$ Untyped mut (ReprFor b) -> Raw mut b
forall (mut :: Mutability) a. Untyped mut (ReprFor a) -> Raw mut a
R.Raw Untyped mut (ReprFor a)
Untyped mut (ReprFor b)
struct
FieldLoc k (ReprFor b)
F.VoidField ->
Raw mut b -> m (Raw mut b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Raw mut b -> m (Raw mut b)) -> Raw mut b -> m (Raw mut b)
forall a b. (a -> b) -> a -> b
$ Untyped mut (ReprFor b) -> Raw mut b
forall (mut :: Mutability) a. Untyped mut (ReprFor a) -> Raw mut a
R.Raw ()
where
readPtrField
:: forall pr.
( R.ReprFor b ~ 'R.Ptr pr
, R.IsPtrRepr pr
) => Maybe (U.Ptr mut) -> m (R.Raw mut b)
readPtrField :: Maybe (Ptr mut) -> m (Raw mut b)
readPtrField Maybe (Ptr mut)
ptr =
UntypedPtr mut pr -> Raw mut b
forall (mut :: Mutability) a. Untyped mut (ReprFor a) -> Raw mut a
R.Raw (UntypedPtr mut pr -> Raw mut b)
-> m (UntypedPtr mut pr) -> m (Raw mut b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr pr))
forall (r :: Maybe PtrRepr) (m :: * -> *) (mut :: Mutability).
(IsPtrRepr r, ReadCtx m mut) =>
Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr r))
R.fromPtr @pr (Struct mut -> Message mut
forall a (mut :: Mutability). HasMessage a mut => a -> Message mut
U.message Struct mut
Untyped mut (ReprFor a)
struct) Maybe (Ptr mut)
ptr
hasField ::
( U.ReadCtx m mut
, R.IsStruct a
, R.IsPtr b
) => F.Field 'F.Slot a b -> R.Raw mut a -> m Bool
hasField :: Field 'Slot a b -> Raw mut a -> m Bool
hasField (F.Field (F.PtrField Word16
index)) (R.Raw Untyped mut (ReprFor a)
struct) =
Maybe (Ptr mut) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (Ptr mut) -> Bool) -> m (Maybe (Ptr mut)) -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Struct mut -> m (Maybe (Ptr mut))
forall (m :: * -> *) (msg :: Mutability).
ReadCtx m msg =>
Int -> Struct msg -> m (Maybe (Ptr msg))
U.getPtr (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
index) Struct mut
Untyped mut (ReprFor a)
struct
{-# INLINE getField #-}
getField
:: ( R.IsStruct a
, R.ReprFor b ~ 'R.Data sz
, C.Parse b bp
)
=> F.Field 'F.Slot a b
-> R.Raw 'Const a
-> bp
getField :: Field 'Slot a b -> Raw 'Const a -> bp
getField Field 'Slot a b
field Raw 'Const a
struct =
Maybe bp -> bp
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe bp -> bp) -> Maybe bp -> bp
forall a b. (a -> b) -> a -> b
$ WordCount -> LimitT Maybe bp -> Maybe bp
forall (m :: * -> *) a.
MonadThrow m =>
WordCount -> LimitT m a -> m a
evalLimitT WordCount
forall a. Bounded a => a
maxBound (LimitT Maybe bp -> Maybe bp) -> LimitT Maybe bp -> Maybe bp
forall a b. (a -> b) -> a -> b
$
Field 'Slot a b -> Raw 'Const a -> LimitT Maybe (Raw 'Const b)
forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Field k a b -> Raw mut a -> m (Raw mut b)
readField Field 'Slot a b
field Raw 'Const a
struct LimitT Maybe (Raw 'Const b)
-> (Raw 'Const b -> LimitT Maybe bp) -> LimitT Maybe bp
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Raw 'Const b -> LimitT Maybe bp
forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw 'Const t -> m p
C.parse
{-# INLINE setField #-}
setField ::
forall a b m s.
( R.IsStruct a
, U.RWCtx m s
) => F.Field 'F.Slot a b -> R.Raw ('Mut s) b -> R.Raw ('Mut s) a -> m ()
setField :: Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
setField (F.Field FieldLoc 'Slot (ReprFor b)
field) (R.Raw Untyped ('Mut s) (ReprFor b)
value) (R.Raw Untyped ('Mut s) (ReprFor a)
struct) =
case FieldLoc 'Slot (ReprFor b)
field of
F.DataField DataFieldLoc a
fieldLoc ->
DataFieldLoc a -> m ()
forall (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
DataFieldLoc sz -> m ()
setDataField DataFieldLoc a
fieldLoc
F.PtrField Word16
index ->
Word16 -> UntypedPtr ('Mut s) a -> Struct ('Mut s) -> m ()
forall (pr :: Maybe PtrRepr).
(ReprFor b ~ 'Ptr pr, IsPtrRepr pr) =>
Word16 -> UntypedPtr ('Mut s) pr -> Struct ('Mut s) -> m ()
setPtrField Word16
index UntypedPtr ('Mut s) a
Untyped ('Mut s) (ReprFor b)
value Struct ('Mut s)
Untyped ('Mut s) (ReprFor a)
struct
FieldLoc 'Slot (ReprFor b)
F.VoidField ->
() -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
where
setPtrField
:: forall pr.
( R.ReprFor b ~ 'R.Ptr pr
, R.IsPtrRepr pr
) => Word16 -> R.UntypedPtr ('Mut s) pr -> U.Struct ('Mut s) -> m ()
setPtrField :: Word16 -> UntypedPtr ('Mut s) pr -> Struct ('Mut s) -> m ()
setPtrField Word16
index UntypedPtr ('Mut s) pr
value Struct ('Mut s)
struct =
Maybe (Ptr ('Mut s)) -> Int -> Struct ('Mut s) -> m ()
forall (m :: * -> *) s.
(ReadCtx m ('Mut s), WriteCtx m s) =>
Maybe (Ptr ('Mut s)) -> Int -> Struct ('Mut s) -> m ()
U.setPtr (Untyped ('Mut s) ('Ptr pr) -> Maybe (Ptr ('Mut s))
forall (r :: Maybe PtrRepr) (mut :: Mutability).
IsPtrRepr r =>
Untyped mut ('Ptr r) -> Maybe (Ptr mut)
R.toPtr @pr UntypedPtr ('Mut s) pr
Untyped ('Mut s) ('Ptr pr)
value) (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
index) Struct ('Mut s)
struct
setDataField
:: forall sz.
( R.ReprFor b ~ 'R.Data sz
, C.IsWord (R.UntypedData sz)
) => F.DataFieldLoc sz -> m ()
setDataField :: DataFieldLoc sz -> m ()
setDataField F.DataFieldLoc{ BitCount
shift :: BitCount
shift :: forall (sz :: DataSz). DataFieldLoc sz -> BitCount
shift, Word16
index :: Word16
index :: forall (sz :: DataSz). DataFieldLoc sz -> Word16
index, Word64
mask :: Word64
mask :: forall (sz :: DataSz). DataFieldLoc sz -> Word64
mask, Word64
defaultValue :: Word64
defaultValue :: forall (sz :: DataSz). DataFieldLoc sz -> Word64
defaultValue } = do
Word64
oldWord <- Int -> Struct ('Mut s) -> m Word64
forall (m :: * -> *) (msg :: Mutability).
ReadCtx m msg =>
Int -> Struct msg -> m Word64
U.getData (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
index) Struct ('Mut s)
Untyped ('Mut s) (ReprFor a)
struct
let valueWord :: Word64
valueWord = UntypedData sz -> Word64
forall a. IsWord a => a -> Word64
C.toWord UntypedData sz
Untyped ('Mut s) (ReprFor b)
value Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
`xor` Word64
defaultValue
newWord :: Word64
newWord = (Word64
oldWord Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64 -> Word64
forall a. Bits a => a -> a
complement Word64
mask)
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64
valueWord Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` BitCount -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral BitCount
shift)
Word64 -> Int -> Struct ('Mut s) -> m ()
forall (m :: * -> *) s.
(ReadCtx m ('Mut s), WriteCtx m s) =>
Word64 -> Int -> Struct ('Mut s) -> m ()
U.setData Word64
newWord (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
index) Struct ('Mut s)
Untyped ('Mut s) (ReprFor a)
struct
newField ::
forall a b m s.
( R.IsStruct a
, C.Allocate b
, U.RWCtx m s
) => F.Field 'F.Slot a b -> C.AllocHint b -> R.Raw ('Mut s) a -> m (R.Raw ('Mut s) b)
newField :: Field 'Slot a b
-> AllocHint b -> Raw ('Mut s) a -> m (Raw ('Mut s) b)
newField Field 'Slot a b
field AllocHint b
hint Raw ('Mut s) a
parent = do
Raw ('Mut s) b
value <- AllocHint b -> Message ('Mut s) -> m (Raw ('Mut s) b)
forall a (m :: * -> *) s.
(Allocate a, RWCtx m s) =>
AllocHint a -> Message ('Mut s) -> m (Raw ('Mut s) a)
C.new @b AllocHint b
hint (Raw ('Mut s) a -> Message ('Mut s)
forall a (mut :: Mutability). HasMessage a mut => a -> Message mut
U.message Raw ('Mut s) a
parent)
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
forall a b (m :: * -> *) s.
(IsStruct a, RWCtx m s) =>
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
setField Field 'Slot a b
field Raw ('Mut s) b
value Raw ('Mut s) a
parent
Raw ('Mut s) b -> m (Raw ('Mut s) b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Raw ('Mut s) b
value
encodeField ::
forall a b m s bp.
( R.IsStruct a
, C.Parse b bp
, U.RWCtx m s
) => F.Field 'F.Slot a b -> bp -> R.Raw ('Mut s) a -> m ()
encodeField :: Field 'Slot a b -> bp -> Raw ('Mut s) a -> m ()
encodeField Field 'Slot a b
field bp
parsed Raw ('Mut s) a
struct = do
Raw ('Mut s) b
encoded <- Message ('Mut s) -> bp -> m (Raw ('Mut s) b)
forall t p (m :: * -> *) s.
(Parse t p, RWCtx m s) =>
Message ('Mut s) -> p -> m (Raw ('Mut s) t)
C.encode (Raw ('Mut s) a -> Message ('Mut s)
forall a (mut :: Mutability). HasMessage a mut => a -> Message mut
U.message Raw ('Mut s) a
struct) bp
parsed
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
forall a b (m :: * -> *) s.
(IsStruct a, RWCtx m s) =>
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
setField Field 'Slot a b
field Raw ('Mut s) b
encoded Raw ('Mut s) a
struct
parseField ::
( R.IsStruct a
, C.Parse b bp
, U.ReadCtx m 'Const
) => F.Field k a b -> R.Raw 'Const a -> m bp
parseField :: Field k a b -> Raw 'Const a -> m bp
parseField Field k a b
field Raw 'Const a
raw =
Field k a b -> Raw 'Const a -> m (Raw 'Const b)
forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Field k a b -> Raw mut a -> m (Raw mut b)
readField Field k a b
field Raw 'Const a
raw m (Raw 'Const b) -> (Raw 'Const b -> m bp) -> m bp
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Raw 'Const b -> m bp
forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw 'Const t -> m p
C.parse
setVariant
:: forall a b m s.
( F.HasUnion a
, U.RWCtx m s
) => F.Variant 'F.Slot a b -> R.Raw ('Mut s) a -> R.Raw ('Mut s) b -> m ()
setVariant :: Variant 'Slot a b -> Raw ('Mut s) a -> Raw ('Mut s) b -> m ()
setVariant F.Variant{Field 'Slot a b
field :: forall (k :: FieldKind) a b. Variant k a b -> Field k a b
field :: Field 'Slot a b
field, Word16
tagValue :: forall (k :: FieldKind) a b. Variant k a b -> Word16
tagValue :: Word16
tagValue} Raw ('Mut s) a
struct Raw ('Mut s) b
value = do
Field 'Slot a Word16
-> Raw ('Mut s) Word16 -> Raw ('Mut s) a -> m ()
forall a b (m :: * -> *) s.
(IsStruct a, RWCtx m s) =>
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
setField (HasUnion a => Field 'Slot a Word16
forall a. HasUnion a => Field 'Slot a Word16
F.unionField @a) (Untyped ('Mut s) (ReprFor Word16) -> Raw ('Mut s) Word16
forall (mut :: Mutability) a. Untyped mut (ReprFor a) -> Raw mut a
R.Raw Word16
Untyped ('Mut s) (ReprFor Word16)
tagValue) Raw ('Mut s) a
struct
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
forall a b (m :: * -> *) s.
(IsStruct a, RWCtx m s) =>
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
setField Field 'Slot a b
field Raw ('Mut s) b
value Raw ('Mut s) a
struct
encodeVariant
:: forall a b m s bp.
( F.HasUnion a
, C.Parse b bp
, U.RWCtx m s
) => F.Variant 'F.Slot a b -> bp -> R.Raw ('Mut s) a -> m ()
encodeVariant :: Variant 'Slot a b -> bp -> Raw ('Mut s) a -> m ()
encodeVariant F.Variant{Field 'Slot a b
field :: Field 'Slot a b
field :: forall (k :: FieldKind) a b. Variant k a b -> Field k a b
field, Word16
tagValue :: Word16
tagValue :: forall (k :: FieldKind) a b. Variant k a b -> Word16
tagValue} bp
value Raw ('Mut s) a
struct = do
Field 'Slot a Word16
-> Raw ('Mut s) Word16 -> Raw ('Mut s) a -> m ()
forall a b (m :: * -> *) s.
(IsStruct a, RWCtx m s) =>
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
setField (HasUnion a => Field 'Slot a Word16
forall a. HasUnion a => Field 'Slot a Word16
F.unionField @a) (Untyped ('Mut s) (ReprFor Word16) -> Raw ('Mut s) Word16
forall (mut :: Mutability) a. Untyped mut (ReprFor a) -> Raw mut a
R.Raw Word16
Untyped ('Mut s) (ReprFor Word16)
tagValue) Raw ('Mut s) a
struct
Field 'Slot a b -> bp -> Raw ('Mut s) a -> m ()
forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw ('Mut s) a -> m ()
encodeField Field 'Slot a b
field bp
value Raw ('Mut s) a
struct
initVariant
:: forall a b m s. (F.HasUnion a, U.RWCtx m s)
=> F.Variant 'F.Group a b -> R.Raw ('Mut s) a -> m (R.Raw ('Mut s) b)
initVariant :: Variant 'Group a b -> Raw ('Mut s) a -> m (Raw ('Mut s) b)
initVariant F.Variant{Field 'Group a b
field :: Field 'Group a b
field :: forall (k :: FieldKind) a b. Variant k a b -> Field k a b
field, Word16
tagValue :: Word16
tagValue :: forall (k :: FieldKind) a b. Variant k a b -> Word16
tagValue} Raw ('Mut s) a
struct = do
Field 'Slot a Word16
-> Raw ('Mut s) Word16 -> Raw ('Mut s) a -> m ()
forall a b (m :: * -> *) s.
(IsStruct a, RWCtx m s) =>
Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m ()
setField (HasUnion a => Field 'Slot a Word16
forall a. HasUnion a => Field 'Slot a Word16
F.unionField @a) (Untyped ('Mut s) (ReprFor Word16) -> Raw ('Mut s) Word16
forall (mut :: Mutability) a. Untyped mut (ReprFor a) -> Raw mut a
R.Raw Word16
Untyped ('Mut s) (ReprFor Word16)
tagValue) Raw ('Mut s) a
struct
Field 'Group a b -> Raw ('Mut s) a -> m (Raw ('Mut s) b)
forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Field k a b -> Raw mut a -> m (Raw mut b)
readField Field 'Group a b
field Raw ('Mut s) a
struct
structUnion :: F.HasUnion a => R.Raw mut a -> R.Raw mut (F.Which a)
structUnion :: Raw mut a -> Raw mut (Which a)
structUnion = Raw mut a -> Raw mut (Which a)
coerce
unionStruct :: F.HasUnion a => R.Raw mut (F.Which a) -> R.Raw mut a
unionStruct :: Raw mut (Which a) -> Raw mut a
unionStruct = Raw mut (Which a) -> Raw mut a
coerce
structWhich :: forall a mut m. (U.ReadCtx m mut, F.HasUnion a) => R.Raw mut a -> m (F.RawWhich mut a)
structWhich :: Raw mut a -> m (RawWhich mut a)
structWhich Raw mut a
struct = do
R.Raw Untyped mut (ReprFor Word16)
tagValue <- Field 'Slot a Word16 -> Raw mut a -> m (Raw mut Word16)
forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Field k a b -> Raw mut a -> m (Raw mut b)
readField (HasUnion a => Field 'Slot a Word16
forall a. HasUnion a => Field 'Slot a Word16
F.unionField @a) Raw mut a
struct
Word16 -> Raw mut a -> m (RawWhich mut a)
forall a (m :: * -> *) (mut :: Mutability).
(HasUnion a, ReadCtx m mut) =>
Word16 -> Raw mut a -> m (RawWhich mut a)
F.internalWhich Word16
Untyped mut (ReprFor Word16)
tagValue Raw mut a
struct
unionWhich :: forall a mut m. (U.ReadCtx m mut, F.HasUnion a) => R.Raw mut (F.Which a) -> m (F.RawWhich mut a)
unionWhich :: Raw mut (Which a) -> m (RawWhich mut a)
unionWhich = Raw mut a -> m (RawWhich mut a)
forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw mut a -> m (RawWhich mut a)
structWhich (Raw mut a -> m (RawWhich mut a))
-> (Raw mut (Which a) -> Raw mut a)
-> Raw mut (Which a)
-> m (RawWhich mut a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Raw mut (Which a) -> Raw mut a
forall a (mut :: Mutability).
HasUnion a =>
Raw mut (Which a) -> Raw mut a
unionStruct