{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE EmptyDataDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-dodgy-exports #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
{-# OPTIONS_GHC -Wno-name-shadowing #-}
module Capnp.Gen.Capnp.Schema where
import qualified Capnp.Repr as R
import qualified Capnp.Repr.Parsed as RP
import qualified Capnp.Basics as Basics
import qualified GHC.OverloadedLabels as OL
import qualified Capnp.GenHelpers as GH
import qualified Capnp.Classes as C
import qualified GHC.Generics as Generics
import qualified Prelude as Std_
import qualified Data.Word as Std_
import qualified Data.Int as Std_
import Prelude ((<$>), (<*>), (>>=))
data Node 
type instance (R.ReprFor Node) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node) where
    typeId :: Word64
typeId  = Word64
16610026722781537303
instance (C.TypedStruct Node) where
    numStructWords :: Word16
numStructWords  = Word16
5
    numStructPtrs :: Word16
numStructPtrs  = Word16
6
instance (C.Allocate Node) where
    type AllocHint Node = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node -> Message ('Mut s) -> m (Raw Node ('Mut s))
new AllocHint Node
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node (C.Parsed Node))
instance (C.AllocateList Node) where
    type ListAllocHint Node = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node
-> Message ('Mut s) -> m (Raw (List Node) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node (C.Parsed Node))
data instance C.Parsed Node
    = Node 
        {Parsed Node -> Parsed Word64
id :: (RP.Parsed Std_.Word64)
        ,Parsed Node -> Parsed Text
displayName :: (RP.Parsed Basics.Text)
        ,Parsed Node -> Parsed Word32
displayNamePrefixLength :: (RP.Parsed Std_.Word32)
        ,Parsed Node -> Parsed Word64
scopeId :: (RP.Parsed Std_.Word64)
        ,Parsed Node -> Parsed (List Node'NestedNode)
nestedNodes :: (RP.Parsed (R.List Node'NestedNode))
        ,Parsed Node -> Parsed (List Annotation)
annotations :: (RP.Parsed (R.List Annotation))
        ,Parsed Node -> Parsed (List Node'Parameter)
parameters :: (RP.Parsed (R.List Node'Parameter))
        ,Parsed Node -> Parsed Bool
isGeneric :: (RP.Parsed Std_.Bool)
        ,Parsed Node -> Parsed (Which Node)
union' :: (C.Parsed (GH.Which Node))}
    deriving(forall x. Rep (Parsed Node) x -> Parsed Node
forall x. Parsed Node -> Rep (Parsed Node) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node) x -> Parsed Node
$cfrom :: forall x. Parsed Node -> Rep (Parsed Node) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node))
deriving instance (Std_.Eq (C.Parsed Node))
instance (C.Parse Node (C.Parsed Node)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node 'Const -> m (Parsed Node)
parse Raw Node 'Const
raw_ = (Parsed Word64
-> Parsed Text
-> Parsed Word32
-> Parsed Word64
-> Parsed (List Node'NestedNode)
-> Parsed (List Annotation)
-> Parsed (List Node'Parameter)
-> Parsed Bool
-> Parsed (Which Node)
-> Parsed Node
Node forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "id" a => a
#id Raw Node 'Const
raw_)
                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "displayName" a => a
#displayName Raw Node 'Const
raw_)
                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "displayNamePrefixLength" a => a
#displayNamePrefixLength Raw Node 'Const
raw_)
                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "scopeId" a => a
#scopeId Raw Node 'Const
raw_)
                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "nestedNodes" a => a
#nestedNodes Raw Node 'Const
raw_)
                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "annotations" a => a
#annotations Raw Node 'Const
raw_)
                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "parameters" a => a
#parameters Raw Node 'Const
raw_)
                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "isGeneric" a => a
#isGeneric Raw Node 'Const
raw_)
                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Node 'Const
raw_)))
instance (C.Marshal Node (C.Parsed Node)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node ('Mut s) -> Parsed Node -> m ()
marshalInto Raw Node ('Mut s)
raw_ Node{Parsed (Which Node)
Parsed Bool
Parsed Word32
Parsed Word64
Parsed (List Annotation)
Parsed (List Node'NestedNode)
Parsed (List Node'Parameter)
Parsed Text
union' :: Parsed (Which Node)
isGeneric :: Parsed Bool
parameters :: Parsed (List Node'Parameter)
annotations :: Parsed (List Annotation)
nestedNodes :: Parsed (List Node'NestedNode)
scopeId :: Parsed Word64
displayNamePrefixLength :: Parsed Word32
displayName :: Parsed Text
id :: Parsed Word64
$sel:union':Node :: Parsed Node -> Parsed (Which Node)
$sel:isGeneric:Node :: Parsed Node -> Parsed Bool
$sel:parameters:Node :: Parsed Node -> Parsed (List Node'Parameter)
$sel:annotations:Node :: Parsed Node -> Parsed (List Annotation)
$sel:nestedNodes:Node :: Parsed Node -> Parsed (List Node'NestedNode)
$sel:scopeId:Node :: Parsed Node -> Parsed Word64
$sel:displayNamePrefixLength:Node :: Parsed Node -> Parsed Word32
$sel:displayName:Node :: Parsed Node -> Parsed Text
$sel:id:Node :: Parsed Node -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "id" a => a
#id Parsed Word64
id Raw Node ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "displayName" a => a
#displayName Parsed Text
displayName Raw Node ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "displayNamePrefixLength" a => a
#displayNamePrefixLength Parsed Word32
displayNamePrefixLength Raw Node ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "scopeId" a => a
#scopeId Parsed Word64
scopeId Raw Node ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "nestedNodes" a => a
#nestedNodes Parsed (List Node'NestedNode)
nestedNodes Raw Node ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "annotations" a => a
#annotations Parsed (List Annotation)
annotations Raw Node ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "parameters" a => a
#parameters Parsed (List Node'Parameter)
parameters Raw Node ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "isGeneric" a => a
#isGeneric Parsed Bool
isGeneric Raw Node ('Mut s)
raw_)
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Node ('Mut s)
raw_) Parsed (Which Node)
union')
        )
instance (GH.HasUnion Node) where
    unionField :: Field 'Slot Node Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
32 Word16
1 BitCount
16 Word64
0)
    data RawWhich Node mut_
        = RW_Node'file (R.Raw () mut_)
        | RW_Node'struct (R.Raw Node'struct mut_)
        | RW_Node'enum (R.Raw Node'enum mut_)
        | RW_Node'interface (R.Raw Node'interface mut_)
        | RW_Node'const (R.Raw Node'const mut_)
        | RW_Node'annotation (R.Raw Node'annotation mut_)
        | RW_Node'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16 -> Raw Node mut -> m (RawWhich Node mut)
internalWhich Word16
tag_ Raw Node mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Node mut_
RW_Node'file forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "file" a => a
#file Raw Node mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability).
Raw Node'struct mut_ -> RawWhich Node mut_
RW_Node'struct forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "struct" a => a
#struct Raw Node mut
struct_))
        Word16
2 ->
            (forall (mut_ :: Mutability).
Raw Node'enum mut_ -> RawWhich Node mut_
RW_Node'enum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "enum" a => a
#enum Raw Node mut
struct_))
        Word16
3 ->
            (forall (mut_ :: Mutability).
Raw Node'interface mut_ -> RawWhich Node mut_
RW_Node'interface forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "interface" a => a
#interface Raw Node mut
struct_))
        Word16
4 ->
            (forall (mut_ :: Mutability).
Raw Node'const mut_ -> RawWhich Node mut_
RW_Node'const forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "const" a => a
#const Raw Node mut
struct_))
        Word16
5 ->
            (forall (mut_ :: Mutability).
Raw Node'annotation mut_ -> RawWhich Node mut_
RW_Node'annotation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "annotation" a => a
#annotation Raw Node mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability). Word16 -> RawWhich Node mut_
RW_Node'unknown' Word16
tag_))
    data Which Node
instance (GH.HasVariant "file" GH.Slot Node ()) where
    variantByLabel :: Variant 'Slot Node ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
0)
instance (GH.HasVariant "struct" GH.Group Node Node'struct) where
    variantByLabel :: Variant 'Group Node Node'struct
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
1)
instance (GH.HasVariant "enum" GH.Group Node Node'enum) where
    variantByLabel :: Variant 'Group Node Node'enum
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
2)
instance (GH.HasVariant "interface" GH.Group Node Node'interface) where
    variantByLabel :: Variant 'Group Node Node'interface
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
3)
instance (GH.HasVariant "const" GH.Group Node Node'const) where
    variantByLabel :: Variant 'Group Node Node'const
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
4)
instance (GH.HasVariant "annotation" GH.Group Node Node'annotation) where
    variantByLabel :: Variant 'Group Node Node'annotation
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
5)
data instance C.Parsed (GH.Which Node)
    = Node'file 
    | Node'struct (RP.Parsed Node'struct)
    | Node'enum (RP.Parsed Node'enum)
    | Node'interface (RP.Parsed Node'interface)
    | Node'const (RP.Parsed Node'const)
    | Node'annotation (RP.Parsed Node'annotation)
    | Node'unknown' Std_.Word16
    deriving(forall x. Rep (Parsed (Which Node)) x -> Parsed (Which Node)
forall x. Parsed (Which Node) -> Rep (Parsed (Which Node)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed (Which Node)) x -> Parsed (Which Node)
$cfrom :: forall x. Parsed (Which Node) -> Rep (Parsed (Which Node)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Node)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Node)))
instance (C.Parse (GH.Which Node) (C.Parsed (GH.Which Node))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Node) 'Const -> m (Parsed (Which Node))
parse Raw (Which Node) 'Const
raw_ = (do
        RawWhich Node 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Node) 'Const
raw_)
        case RawWhich Node 'Const
rawWhich_ of
            (RW_Node'file Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Node)
Node'file)
            (RW_Node'struct Raw Node'struct 'Const
rawArg_) ->
                (Parsed Node'struct -> Parsed (Which Node)
Node'struct forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Node'struct 'Const
rawArg_))
            (RW_Node'enum Raw Node'enum 'Const
rawArg_) ->
                (Parsed Node'enum -> Parsed (Which Node)
Node'enum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Node'enum 'Const
rawArg_))
            (RW_Node'interface Raw Node'interface 'Const
rawArg_) ->
                (Parsed Node'interface -> Parsed (Which Node)
Node'interface forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Node'interface 'Const
rawArg_))
            (RW_Node'const Raw Node'const 'Const
rawArg_) ->
                (Parsed Node'const -> Parsed (Which Node)
Node'const forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Node'const 'Const
rawArg_))
            (RW_Node'annotation Raw Node'annotation 'Const
rawArg_) ->
                (Parsed Node'annotation -> Parsed (Which Node)
Node'annotation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Node'annotation 'Const
rawArg_))
            (RW_Node'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Node)
Node'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Node) (C.Parsed (GH.Which Node))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Node) ('Mut s) -> Parsed (Which Node) -> m ()
marshalInto Raw (Which Node) ('Mut s)
raw_ Parsed (Which Node)
parsed_ = case Parsed (Which Node)
parsed_ of
        (Parsed (Which Node)
R:ParsedWhich
Node'file) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "file" a => a
#file () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Node) ('Mut s)
raw_))
        (Node'struct Parsed Node'struct
arg_) ->
            (do
                Raw Node'struct ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "struct" a => a
#struct (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Node) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Node'struct ('Mut s)
rawGroup_ Parsed Node'struct
arg_)
                )
        (Node'enum Parsed Node'enum
arg_) ->
            (do
                Raw Node'enum ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "enum" a => a
#enum (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Node) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Node'enum ('Mut s)
rawGroup_ Parsed Node'enum
arg_)
                )
        (Node'interface Parsed Node'interface
arg_) ->
            (do
                Raw Node'interface ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "interface" a => a
#interface (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Node) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Node'interface ('Mut s)
rawGroup_ Parsed Node'interface
arg_)
                )
        (Node'const Parsed Node'const
arg_) ->
            (do
                Raw Node'const ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "const" a => a
#const (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Node) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Node'const ('Mut s)
rawGroup_ Parsed Node'const
arg_)
                )
        (Node'annotation Parsed Node'annotation
arg_) ->
            (do
                Raw Node'annotation ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "annotation" a => a
#annotation (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Node) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Node'annotation ('Mut s)
rawGroup_ Parsed Node'annotation
arg_)
                )
        (Node'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Node) ('Mut s)
raw_))
instance (GH.HasField "id" GH.Slot Node Std_.Word64) where
    fieldByLabel :: Field 'Slot Node Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
64 Word64
0)
instance (GH.HasField "displayName" GH.Slot Node Basics.Text) where
    fieldByLabel :: Field 'Slot Node Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "displayNamePrefixLength" GH.Slot Node Std_.Word32) where
    fieldByLabel :: Field 'Slot Node Word32
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
32 Word64
0)
instance (GH.HasField "scopeId" GH.Slot Node Std_.Word64) where
    fieldByLabel :: Field 'Slot Node Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
2 BitCount
64 Word64
0)
instance (GH.HasField "nestedNodes" GH.Slot Node (R.List Node'NestedNode)) where
    fieldByLabel :: Field 'Slot Node (List Node'NestedNode)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
1)
instance (GH.HasField "annotations" GH.Slot Node (R.List Annotation)) where
    fieldByLabel :: Field 'Slot Node (List Annotation)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
2)
instance (GH.HasField "parameters" GH.Slot Node (R.List Node'Parameter)) where
    fieldByLabel :: Field 'Slot Node (List Node'Parameter)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
5)
instance (GH.HasField "isGeneric" GH.Slot Node Std_.Bool) where
    fieldByLabel :: Field 'Slot Node Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
32 Word16
4 BitCount
1 Word64
0)
data Node'struct 
type instance (R.ReprFor Node'struct) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'struct) where
    typeId :: Word64
typeId  = Word64
11430331134483579957
instance (C.TypedStruct Node'struct) where
    numStructWords :: Word16
numStructWords  = Word16
5
    numStructPtrs :: Word16
numStructPtrs  = Word16
6
instance (C.Allocate Node'struct) where
    type AllocHint Node'struct = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'struct
-> Message ('Mut s) -> m (Raw Node'struct ('Mut s))
new AllocHint Node'struct
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'struct (C.Parsed Node'struct))
instance (C.AllocateList Node'struct) where
    type ListAllocHint Node'struct = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'struct
-> Message ('Mut s) -> m (Raw (List Node'struct) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'struct (C.Parsed Node'struct))
data instance C.Parsed Node'struct
    = Node'struct' 
        {Parsed Node'struct -> Parsed Word16
dataWordCount :: (RP.Parsed Std_.Word16)
        ,Parsed Node'struct -> Parsed Word16
pointerCount :: (RP.Parsed Std_.Word16)
        ,Parsed Node'struct -> Parsed ElementSize
preferredListEncoding :: (RP.Parsed ElementSize)
        ,Parsed Node'struct -> Parsed Bool
isGroup :: (RP.Parsed Std_.Bool)
        ,Parsed Node'struct -> Parsed Word16
discriminantCount :: (RP.Parsed Std_.Word16)
        ,Parsed Node'struct -> Parsed Word32
discriminantOffset :: (RP.Parsed Std_.Word32)
        ,Parsed Node'struct -> Parsed (List Field)
fields :: (RP.Parsed (R.List Field))}
    deriving(forall x. Rep (Parsed Node'struct) x -> Parsed Node'struct
forall x. Parsed Node'struct -> Rep (Parsed Node'struct) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node'struct) x -> Parsed Node'struct
$cfrom :: forall x. Parsed Node'struct -> Rep (Parsed Node'struct) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'struct))
deriving instance (Std_.Eq (C.Parsed Node'struct))
instance (C.Parse Node'struct (C.Parsed Node'struct)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'struct 'Const -> m (Parsed Node'struct)
parse Raw Node'struct 'Const
raw_ = (Parsed Word16
-> Parsed Word16
-> Parsed ElementSize
-> Parsed Bool
-> Parsed Word16
-> Parsed Word32
-> Parsed (List Field)
-> Parsed Node'struct
Node'struct' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "dataWordCount" a => a
#dataWordCount Raw Node'struct 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "pointerCount" a => a
#pointerCount Raw Node'struct 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "preferredListEncoding" a => a
#preferredListEncoding Raw Node'struct 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "isGroup" a => a
#isGroup Raw Node'struct 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "discriminantCount" a => a
#discriminantCount Raw Node'struct 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "discriminantOffset" a => a
#discriminantOffset Raw Node'struct 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "fields" a => a
#fields Raw Node'struct 'Const
raw_))
instance (C.Marshal Node'struct (C.Parsed Node'struct)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'struct ('Mut s) -> Parsed Node'struct -> m ()
marshalInto Raw Node'struct ('Mut s)
raw_ Node'struct'{Parsed Bool
Parsed Word16
Parsed Word32
Parsed (List Field)
Parsed ElementSize
fields :: Parsed (List Field)
discriminantOffset :: Parsed Word32
discriminantCount :: Parsed Word16
isGroup :: Parsed Bool
preferredListEncoding :: Parsed ElementSize
pointerCount :: Parsed Word16
dataWordCount :: Parsed Word16
$sel:fields:Node'struct' :: Parsed Node'struct -> Parsed (List Field)
$sel:discriminantOffset:Node'struct' :: Parsed Node'struct -> Parsed Word32
$sel:discriminantCount:Node'struct' :: Parsed Node'struct -> Parsed Word16
$sel:isGroup:Node'struct' :: Parsed Node'struct -> Parsed Bool
$sel:preferredListEncoding:Node'struct' :: Parsed Node'struct -> Parsed ElementSize
$sel:pointerCount:Node'struct' :: Parsed Node'struct -> Parsed Word16
$sel:dataWordCount:Node'struct' :: Parsed Node'struct -> Parsed Word16
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "dataWordCount" a => a
#dataWordCount Parsed Word16
dataWordCount Raw Node'struct ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "pointerCount" a => a
#pointerCount Parsed Word16
pointerCount Raw Node'struct ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "preferredListEncoding" a => a
#preferredListEncoding Parsed ElementSize
preferredListEncoding Raw Node'struct ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "isGroup" a => a
#isGroup Parsed Bool
isGroup Raw Node'struct ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "discriminantCount" a => a
#discriminantCount Parsed Word16
discriminantCount Raw Node'struct ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "discriminantOffset" a => a
#discriminantOffset Parsed Word32
discriminantOffset Raw Node'struct ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "fields" a => a
#fields Parsed (List Field)
fields Raw Node'struct ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "dataWordCount" GH.Slot Node'struct Std_.Word16) where
    fieldByLabel :: Field 'Slot Node'struct Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
48 Word16
1 BitCount
16 Word64
0)
instance (GH.HasField "pointerCount" GH.Slot Node'struct Std_.Word16) where
    fieldByLabel :: Field 'Slot Node'struct Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
3 BitCount
16 Word64
0)
instance (GH.HasField "preferredListEncoding" GH.Slot Node'struct ElementSize) where
    fieldByLabel :: Field 'Slot Node'struct ElementSize
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
3 BitCount
16 Word64
0)
instance (GH.HasField "isGroup" GH.Slot Node'struct Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'struct Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
32 Word16
3 BitCount
1 Word64
0)
instance (GH.HasField "discriminantCount" GH.Slot Node'struct Std_.Word16) where
    fieldByLabel :: Field 'Slot Node'struct Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
48 Word16
3 BitCount
16 Word64
0)
instance (GH.HasField "discriminantOffset" GH.Slot Node'struct Std_.Word32) where
    fieldByLabel :: Field 'Slot Node'struct Word32
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
4 BitCount
32 Word64
0)
instance (GH.HasField "fields" GH.Slot Node'struct (R.List Field)) where
    fieldByLabel :: Field 'Slot Node'struct (List Field)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
3)
data Node'enum 
type instance (R.ReprFor Node'enum) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'enum) where
    typeId :: Word64
typeId  = Word64
13063450714778629528
instance (C.TypedStruct Node'enum) where
    numStructWords :: Word16
numStructWords  = Word16
5
    numStructPtrs :: Word16
numStructPtrs  = Word16
6
instance (C.Allocate Node'enum) where
    type AllocHint Node'enum = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'enum
-> Message ('Mut s) -> m (Raw Node'enum ('Mut s))
new AllocHint Node'enum
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'enum (C.Parsed Node'enum))
instance (C.AllocateList Node'enum) where
    type ListAllocHint Node'enum = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'enum
-> Message ('Mut s) -> m (Raw (List Node'enum) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'enum (C.Parsed Node'enum))
data instance C.Parsed Node'enum
    = Node'enum' 
        {Parsed Node'enum -> Parsed (List Enumerant)
enumerants :: (RP.Parsed (R.List Enumerant))}
    deriving(forall x. Rep (Parsed Node'enum) x -> Parsed Node'enum
forall x. Parsed Node'enum -> Rep (Parsed Node'enum) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node'enum) x -> Parsed Node'enum
$cfrom :: forall x. Parsed Node'enum -> Rep (Parsed Node'enum) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'enum))
deriving instance (Std_.Eq (C.Parsed Node'enum))
instance (C.Parse Node'enum (C.Parsed Node'enum)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'enum 'Const -> m (Parsed Node'enum)
parse Raw Node'enum 'Const
raw_ = (Parsed (List Enumerant) -> Parsed Node'enum
Node'enum' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "enumerants" a => a
#enumerants Raw Node'enum 'Const
raw_))
instance (C.Marshal Node'enum (C.Parsed Node'enum)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'enum ('Mut s) -> Parsed Node'enum -> m ()
marshalInto Raw Node'enum ('Mut s)
raw_ Node'enum'{Parsed (List Enumerant)
enumerants :: Parsed (List Enumerant)
$sel:enumerants:Node'enum' :: Parsed Node'enum -> Parsed (List Enumerant)
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "enumerants" a => a
#enumerants Parsed (List Enumerant)
enumerants Raw Node'enum ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "enumerants" GH.Slot Node'enum (R.List Enumerant)) where
    fieldByLabel :: Field 'Slot Node'enum (List Enumerant)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
3)
data Node'interface 
type instance (R.ReprFor Node'interface) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'interface) where
    typeId :: Word64
typeId  = Word64
16728431493453586831
instance (C.TypedStruct Node'interface) where
    numStructWords :: Word16
numStructWords  = Word16
5
    numStructPtrs :: Word16
numStructPtrs  = Word16
6
instance (C.Allocate Node'interface) where
    type AllocHint Node'interface = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'interface
-> Message ('Mut s) -> m (Raw Node'interface ('Mut s))
new AllocHint Node'interface
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'interface (C.Parsed Node'interface))
instance (C.AllocateList Node'interface) where
    type ListAllocHint Node'interface = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'interface
-> Message ('Mut s) -> m (Raw (List Node'interface) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'interface (C.Parsed Node'interface))
data instance C.Parsed Node'interface
    = Node'interface' 
        {Parsed Node'interface -> Parsed (List Method)
methods :: (RP.Parsed (R.List Method))
        ,Parsed Node'interface -> Parsed (List Superclass)
superclasses :: (RP.Parsed (R.List Superclass))}
    deriving(forall x. Rep (Parsed Node'interface) x -> Parsed Node'interface
forall x. Parsed Node'interface -> Rep (Parsed Node'interface) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node'interface) x -> Parsed Node'interface
$cfrom :: forall x. Parsed Node'interface -> Rep (Parsed Node'interface) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'interface))
deriving instance (Std_.Eq (C.Parsed Node'interface))
instance (C.Parse Node'interface (C.Parsed Node'interface)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'interface 'Const -> m (Parsed Node'interface)
parse Raw Node'interface 'Const
raw_ = (Parsed (List Method)
-> Parsed (List Superclass) -> Parsed Node'interface
Node'interface' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "methods" a => a
#methods Raw Node'interface 'Const
raw_)
                                  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "superclasses" a => a
#superclasses Raw Node'interface 'Const
raw_))
instance (C.Marshal Node'interface (C.Parsed Node'interface)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'interface ('Mut s) -> Parsed Node'interface -> m ()
marshalInto Raw Node'interface ('Mut s)
raw_ Node'interface'{Parsed (List Method)
Parsed (List Superclass)
superclasses :: Parsed (List Superclass)
methods :: Parsed (List Method)
$sel:superclasses:Node'interface' :: Parsed Node'interface -> Parsed (List Superclass)
$sel:methods:Node'interface' :: Parsed Node'interface -> Parsed (List Method)
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "methods" a => a
#methods Parsed (List Method)
methods Raw Node'interface ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "superclasses" a => a
#superclasses Parsed (List Superclass)
superclasses Raw Node'interface ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "methods" GH.Slot Node'interface (R.List Method)) where
    fieldByLabel :: Field 'Slot Node'interface (List Method)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
3)
instance (GH.HasField "superclasses" GH.Slot Node'interface (R.List Superclass)) where
    fieldByLabel :: Field 'Slot Node'interface (List Superclass)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
4)
data Node'const 
type instance (R.ReprFor Node'const) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'const) where
    typeId :: Word64
typeId  = Word64
12793219851699983392
instance (C.TypedStruct Node'const) where
    numStructWords :: Word16
numStructWords  = Word16
5
    numStructPtrs :: Word16
numStructPtrs  = Word16
6
instance (C.Allocate Node'const) where
    type AllocHint Node'const = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'const
-> Message ('Mut s) -> m (Raw Node'const ('Mut s))
new AllocHint Node'const
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'const (C.Parsed Node'const))
instance (C.AllocateList Node'const) where
    type ListAllocHint Node'const = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'const
-> Message ('Mut s) -> m (Raw (List Node'const) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'const (C.Parsed Node'const))
data instance C.Parsed Node'const
    = Node'const' 
        {Parsed Node'const -> Parsed Type
type_ :: (RP.Parsed Type)
        ,Parsed Node'const -> Parsed Value
value :: (RP.Parsed Value)}
    deriving(forall x. Rep (Parsed Node'const) x -> Parsed Node'const
forall x. Parsed Node'const -> Rep (Parsed Node'const) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node'const) x -> Parsed Node'const
$cfrom :: forall x. Parsed Node'const -> Rep (Parsed Node'const) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'const))
deriving instance (Std_.Eq (C.Parsed Node'const))
instance (C.Parse Node'const (C.Parsed Node'const)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'const 'Const -> m (Parsed Node'const)
parse Raw Node'const 'Const
raw_ = (Parsed Type -> Parsed Value -> Parsed Node'const
Node'const' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "type_" a => a
#type_ Raw Node'const 'Const
raw_)
                              forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "value" a => a
#value Raw Node'const 'Const
raw_))
instance (C.Marshal Node'const (C.Parsed Node'const)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'const ('Mut s) -> Parsed Node'const -> m ()
marshalInto Raw Node'const ('Mut s)
raw_ Node'const'{Parsed Value
Parsed Type
value :: Parsed Value
type_ :: Parsed Type
$sel:value:Node'const' :: Parsed Node'const -> Parsed Value
$sel:type_:Node'const' :: Parsed Node'const -> Parsed Type
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "type_" a => a
#type_ Parsed Type
type_ Raw Node'const ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "value" a => a
#value Parsed Value
value Raw Node'const ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "type_" GH.Slot Node'const Type) where
    fieldByLabel :: Field 'Slot Node'const Type
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
3)
instance (GH.HasField "value" GH.Slot Node'const Value) where
    fieldByLabel :: Field 'Slot Node'const Value
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
4)
data Node'annotation 
type instance (R.ReprFor Node'annotation) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'annotation) where
    typeId :: Word64
typeId  = Word64
17011813041836786320
instance (C.TypedStruct Node'annotation) where
    numStructWords :: Word16
numStructWords  = Word16
5
    numStructPtrs :: Word16
numStructPtrs  = Word16
6
instance (C.Allocate Node'annotation) where
    type AllocHint Node'annotation = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'annotation
-> Message ('Mut s) -> m (Raw Node'annotation ('Mut s))
new AllocHint Node'annotation
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'annotation (C.Parsed Node'annotation))
instance (C.AllocateList Node'annotation) where
    type ListAllocHint Node'annotation = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'annotation
-> Message ('Mut s) -> m (Raw (List Node'annotation) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'annotation (C.Parsed Node'annotation))
data instance C.Parsed Node'annotation
    = Node'annotation' 
        {Parsed Node'annotation -> Parsed Type
type_ :: (RP.Parsed Type)
        ,Parsed Node'annotation -> Parsed Bool
targetsFile :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsConst :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsEnum :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsEnumerant :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsStruct :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsField :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsUnion :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsGroup :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsInterface :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsMethod :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsParam :: (RP.Parsed Std_.Bool)
        ,Parsed Node'annotation -> Parsed Bool
targetsAnnotation :: (RP.Parsed Std_.Bool)}
    deriving(forall x. Rep (Parsed Node'annotation) x -> Parsed Node'annotation
forall x. Parsed Node'annotation -> Rep (Parsed Node'annotation) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node'annotation) x -> Parsed Node'annotation
$cfrom :: forall x. Parsed Node'annotation -> Rep (Parsed Node'annotation) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'annotation))
deriving instance (Std_.Eq (C.Parsed Node'annotation))
instance (C.Parse Node'annotation (C.Parsed Node'annotation)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'annotation 'Const -> m (Parsed Node'annotation)
parse Raw Node'annotation 'Const
raw_ = (Parsed Type
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Bool
-> Parsed Node'annotation
Node'annotation' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "type_" a => a
#type_ Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsFile" a => a
#targetsFile Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsConst" a => a
#targetsConst Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsEnum" a => a
#targetsEnum Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsEnumerant" a => a
#targetsEnumerant Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsStruct" a => a
#targetsStruct Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsField" a => a
#targetsField Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsUnion" a => a
#targetsUnion Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsGroup" a => a
#targetsGroup Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsInterface" a => a
#targetsInterface Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsMethod" a => a
#targetsMethod Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsParam" a => a
#targetsParam Raw Node'annotation 'Const
raw_)
                                   forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "targetsAnnotation" a => a
#targetsAnnotation Raw Node'annotation 'Const
raw_))
instance (C.Marshal Node'annotation (C.Parsed Node'annotation)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'annotation ('Mut s) -> Parsed Node'annotation -> m ()
marshalInto Raw Node'annotation ('Mut s)
raw_ Node'annotation'{Parsed Bool
Parsed Type
targetsAnnotation :: Parsed Bool
targetsParam :: Parsed Bool
targetsMethod :: Parsed Bool
targetsInterface :: Parsed Bool
targetsGroup :: Parsed Bool
targetsUnion :: Parsed Bool
targetsField :: Parsed Bool
targetsStruct :: Parsed Bool
targetsEnumerant :: Parsed Bool
targetsEnum :: Parsed Bool
targetsConst :: Parsed Bool
targetsFile :: Parsed Bool
type_ :: Parsed Type
$sel:targetsAnnotation:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsParam:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsMethod:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsInterface:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsGroup:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsUnion:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsField:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsStruct:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsEnumerant:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsEnum:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsConst:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:targetsFile:Node'annotation' :: Parsed Node'annotation -> Parsed Bool
$sel:type_:Node'annotation' :: Parsed Node'annotation -> Parsed Type
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "type_" a => a
#type_ Parsed Type
type_ Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsFile" a => a
#targetsFile Parsed Bool
targetsFile Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsConst" a => a
#targetsConst Parsed Bool
targetsConst Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsEnum" a => a
#targetsEnum Parsed Bool
targetsEnum Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsEnumerant" a => a
#targetsEnumerant Parsed Bool
targetsEnumerant Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsStruct" a => a
#targetsStruct Parsed Bool
targetsStruct Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsField" a => a
#targetsField Parsed Bool
targetsField Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsUnion" a => a
#targetsUnion Parsed Bool
targetsUnion Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsGroup" a => a
#targetsGroup Parsed Bool
targetsGroup Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsInterface" a => a
#targetsInterface Parsed Bool
targetsInterface Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsMethod" a => a
#targetsMethod Parsed Bool
targetsMethod Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsParam" a => a
#targetsParam Parsed Bool
targetsParam Raw Node'annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "targetsAnnotation" a => a
#targetsAnnotation Parsed Bool
targetsAnnotation Raw Node'annotation ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "type_" GH.Slot Node'annotation Type) where
    fieldByLabel :: Field 'Slot Node'annotation Type
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
3)
instance (GH.HasField "targetsFile" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
48 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsConst" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
49 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsEnum" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
50 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsEnumerant" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
51 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsStruct" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
52 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsField" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
53 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsUnion" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
54 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsGroup" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
55 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsInterface" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
56 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsMethod" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
57 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsParam" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
58 Word16
1 BitCount
1 Word64
0)
instance (GH.HasField "targetsAnnotation" GH.Slot Node'annotation Std_.Bool) where
    fieldByLabel :: Field 'Slot Node'annotation Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
59 Word16
1 BitCount
1 Word64
0)
data Node'Parameter 
type instance (R.ReprFor Node'Parameter) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'Parameter) where
    typeId :: Word64
typeId  = Word64
13353766412138554289
instance (C.TypedStruct Node'Parameter) where
    numStructWords :: Word16
numStructWords  = Word16
0
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Node'Parameter) where
    type AllocHint Node'Parameter = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'Parameter
-> Message ('Mut s) -> m (Raw Node'Parameter ('Mut s))
new AllocHint Node'Parameter
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'Parameter (C.Parsed Node'Parameter))
instance (C.AllocateList Node'Parameter) where
    type ListAllocHint Node'Parameter = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'Parameter
-> Message ('Mut s) -> m (Raw (List Node'Parameter) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'Parameter (C.Parsed Node'Parameter))
data instance C.Parsed Node'Parameter
    = Node'Parameter 
        {Parsed Node'Parameter -> Parsed Text
name :: (RP.Parsed Basics.Text)}
    deriving(forall x. Rep (Parsed Node'Parameter) x -> Parsed Node'Parameter
forall x. Parsed Node'Parameter -> Rep (Parsed Node'Parameter) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node'Parameter) x -> Parsed Node'Parameter
$cfrom :: forall x. Parsed Node'Parameter -> Rep (Parsed Node'Parameter) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'Parameter))
deriving instance (Std_.Eq (C.Parsed Node'Parameter))
instance (C.Parse Node'Parameter (C.Parsed Node'Parameter)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'Parameter 'Const -> m (Parsed Node'Parameter)
parse Raw Node'Parameter 'Const
raw_ = (Parsed Text -> Parsed Node'Parameter
Node'Parameter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "name" a => a
#name Raw Node'Parameter 'Const
raw_))
instance (C.Marshal Node'Parameter (C.Parsed Node'Parameter)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'Parameter ('Mut s) -> Parsed Node'Parameter -> m ()
marshalInto Raw Node'Parameter ('Mut s)
raw_ Node'Parameter{Parsed Text
name :: Parsed Text
$sel:name:Node'Parameter :: Parsed Node'Parameter -> Parsed Text
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "name" a => a
#name Parsed Text
name Raw Node'Parameter ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "name" GH.Slot Node'Parameter Basics.Text) where
    fieldByLabel :: Field 'Slot Node'Parameter Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
data Node'NestedNode 
type instance (R.ReprFor Node'NestedNode) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'NestedNode) where
    typeId :: Word64
typeId  = Word64
16050641862814319170
instance (C.TypedStruct Node'NestedNode) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Node'NestedNode) where
    type AllocHint Node'NestedNode = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'NestedNode
-> Message ('Mut s) -> m (Raw Node'NestedNode ('Mut s))
new AllocHint Node'NestedNode
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'NestedNode (C.Parsed Node'NestedNode))
instance (C.AllocateList Node'NestedNode) where
    type ListAllocHint Node'NestedNode = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'NestedNode
-> Message ('Mut s) -> m (Raw (List Node'NestedNode) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'NestedNode (C.Parsed Node'NestedNode))
data instance C.Parsed Node'NestedNode
    = Node'NestedNode 
        {Parsed Node'NestedNode -> Parsed Text
name :: (RP.Parsed Basics.Text)
        ,Parsed Node'NestedNode -> Parsed Word64
id :: (RP.Parsed Std_.Word64)}
    deriving(forall x. Rep (Parsed Node'NestedNode) x -> Parsed Node'NestedNode
forall x. Parsed Node'NestedNode -> Rep (Parsed Node'NestedNode) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node'NestedNode) x -> Parsed Node'NestedNode
$cfrom :: forall x. Parsed Node'NestedNode -> Rep (Parsed Node'NestedNode) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'NestedNode))
deriving instance (Std_.Eq (C.Parsed Node'NestedNode))
instance (C.Parse Node'NestedNode (C.Parsed Node'NestedNode)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'NestedNode 'Const -> m (Parsed Node'NestedNode)
parse Raw Node'NestedNode 'Const
raw_ = (Parsed Text -> Parsed Word64 -> Parsed Node'NestedNode
Node'NestedNode forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "name" a => a
#name Raw Node'NestedNode 'Const
raw_)
                                  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "id" a => a
#id Raw Node'NestedNode 'Const
raw_))
instance (C.Marshal Node'NestedNode (C.Parsed Node'NestedNode)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'NestedNode ('Mut s) -> Parsed Node'NestedNode -> m ()
marshalInto Raw Node'NestedNode ('Mut s)
raw_ Node'NestedNode{Parsed Word64
Parsed Text
id :: Parsed Word64
name :: Parsed Text
$sel:id:Node'NestedNode :: Parsed Node'NestedNode -> Parsed Word64
$sel:name:Node'NestedNode :: Parsed Node'NestedNode -> Parsed Text
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "name" a => a
#name Parsed Text
name Raw Node'NestedNode ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "id" a => a
#id Parsed Word64
id Raw Node'NestedNode ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "name" GH.Slot Node'NestedNode Basics.Text) where
    fieldByLabel :: Field 'Slot Node'NestedNode Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "id" GH.Slot Node'NestedNode Std_.Word64) where
    fieldByLabel :: Field 'Slot Node'NestedNode Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
64 Word64
0)
data Node'SourceInfo 
type instance (R.ReprFor Node'SourceInfo) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'SourceInfo) where
    typeId :: Word64
typeId  = Word64
17549997658772559790
instance (C.TypedStruct Node'SourceInfo) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
2
instance (C.Allocate Node'SourceInfo) where
    type AllocHint Node'SourceInfo = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'SourceInfo
-> Message ('Mut s) -> m (Raw Node'SourceInfo ('Mut s))
new AllocHint Node'SourceInfo
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'SourceInfo (C.Parsed Node'SourceInfo))
instance (C.AllocateList Node'SourceInfo) where
    type ListAllocHint Node'SourceInfo = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'SourceInfo
-> Message ('Mut s) -> m (Raw (List Node'SourceInfo) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'SourceInfo (C.Parsed Node'SourceInfo))
data instance C.Parsed Node'SourceInfo
    = Node'SourceInfo 
        {Parsed Node'SourceInfo -> Parsed Word64
id :: (RP.Parsed Std_.Word64)
        ,Parsed Node'SourceInfo -> Parsed Text
docComment :: (RP.Parsed Basics.Text)
        ,Parsed Node'SourceInfo -> Parsed (List Node'SourceInfo'Member)
members :: (RP.Parsed (R.List Node'SourceInfo'Member))}
    deriving(forall x. Rep (Parsed Node'SourceInfo) x -> Parsed Node'SourceInfo
forall x. Parsed Node'SourceInfo -> Rep (Parsed Node'SourceInfo) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Node'SourceInfo) x -> Parsed Node'SourceInfo
$cfrom :: forall x. Parsed Node'SourceInfo -> Rep (Parsed Node'SourceInfo) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'SourceInfo))
deriving instance (Std_.Eq (C.Parsed Node'SourceInfo))
instance (C.Parse Node'SourceInfo (C.Parsed Node'SourceInfo)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'SourceInfo 'Const -> m (Parsed Node'SourceInfo)
parse Raw Node'SourceInfo 'Const
raw_ = (Parsed Word64
-> Parsed Text
-> Parsed (List Node'SourceInfo'Member)
-> Parsed Node'SourceInfo
Node'SourceInfo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "id" a => a
#id Raw Node'SourceInfo 'Const
raw_)
                                  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "docComment" a => a
#docComment Raw Node'SourceInfo 'Const
raw_)
                                  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "members" a => a
#members Raw Node'SourceInfo 'Const
raw_))
instance (C.Marshal Node'SourceInfo (C.Parsed Node'SourceInfo)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'SourceInfo ('Mut s) -> Parsed Node'SourceInfo -> m ()
marshalInto Raw Node'SourceInfo ('Mut s)
raw_ Node'SourceInfo{Parsed Word64
Parsed (List Node'SourceInfo'Member)
Parsed Text
members :: Parsed (List Node'SourceInfo'Member)
docComment :: Parsed Text
id :: Parsed Word64
$sel:members:Node'SourceInfo :: Parsed Node'SourceInfo -> Parsed (List Node'SourceInfo'Member)
$sel:docComment:Node'SourceInfo :: Parsed Node'SourceInfo -> Parsed Text
$sel:id:Node'SourceInfo :: Parsed Node'SourceInfo -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "id" a => a
#id Parsed Word64
id Raw Node'SourceInfo ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "docComment" a => a
#docComment Parsed Text
docComment Raw Node'SourceInfo ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "members" a => a
#members Parsed (List Node'SourceInfo'Member)
members Raw Node'SourceInfo ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "id" GH.Slot Node'SourceInfo Std_.Word64) where
    fieldByLabel :: Field 'Slot Node'SourceInfo Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
64 Word64
0)
instance (GH.HasField "docComment" GH.Slot Node'SourceInfo Basics.Text) where
    fieldByLabel :: Field 'Slot Node'SourceInfo Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "members" GH.Slot Node'SourceInfo (R.List Node'SourceInfo'Member)) where
    fieldByLabel :: Field 'Slot Node'SourceInfo (List Node'SourceInfo'Member)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
1)
data Node'SourceInfo'Member 
type instance (R.ReprFor Node'SourceInfo'Member) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Node'SourceInfo'Member) where
    typeId :: Word64
typeId  = Word64
14031686161526562722
instance (C.TypedStruct Node'SourceInfo'Member) where
    numStructWords :: Word16
numStructWords  = Word16
0
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Node'SourceInfo'Member) where
    type AllocHint Node'SourceInfo'Member = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Node'SourceInfo'Member
-> Message ('Mut s) -> m (Raw Node'SourceInfo'Member ('Mut s))
new AllocHint Node'SourceInfo'Member
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Node'SourceInfo'Member (C.Parsed Node'SourceInfo'Member))
instance (C.AllocateList Node'SourceInfo'Member) where
    type ListAllocHint Node'SourceInfo'Member = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Node'SourceInfo'Member
-> Message ('Mut s)
-> m (Raw (List Node'SourceInfo'Member) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Node'SourceInfo'Member (C.Parsed Node'SourceInfo'Member))
data instance C.Parsed Node'SourceInfo'Member
    = Node'SourceInfo'Member 
        {Parsed Node'SourceInfo'Member -> Parsed Text
docComment :: (RP.Parsed Basics.Text)}
    deriving(forall x.
Rep (Parsed Node'SourceInfo'Member) x
-> Parsed Node'SourceInfo'Member
forall x.
Parsed Node'SourceInfo'Member
-> Rep (Parsed Node'SourceInfo'Member) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed Node'SourceInfo'Member) x
-> Parsed Node'SourceInfo'Member
$cfrom :: forall x.
Parsed Node'SourceInfo'Member
-> Rep (Parsed Node'SourceInfo'Member) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Node'SourceInfo'Member))
deriving instance (Std_.Eq (C.Parsed Node'SourceInfo'Member))
instance (C.Parse Node'SourceInfo'Member (C.Parsed Node'SourceInfo'Member)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Node'SourceInfo'Member 'Const
-> m (Parsed Node'SourceInfo'Member)
parse Raw Node'SourceInfo'Member 'Const
raw_ = (Parsed Text -> Parsed Node'SourceInfo'Member
Node'SourceInfo'Member forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "docComment" a => a
#docComment Raw Node'SourceInfo'Member 'Const
raw_))
instance (C.Marshal Node'SourceInfo'Member (C.Parsed Node'SourceInfo'Member)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Node'SourceInfo'Member ('Mut s)
-> Parsed Node'SourceInfo'Member -> m ()
marshalInto Raw Node'SourceInfo'Member ('Mut s)
raw_ Node'SourceInfo'Member{Parsed Text
docComment :: Parsed Text
$sel:docComment:Node'SourceInfo'Member :: Parsed Node'SourceInfo'Member -> Parsed Text
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "docComment" a => a
#docComment Parsed Text
docComment Raw Node'SourceInfo'Member ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "docComment" GH.Slot Node'SourceInfo'Member Basics.Text) where
    fieldByLabel :: Field 'Slot Node'SourceInfo'Member Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
data Field 
type instance (R.ReprFor Field) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Field) where
    typeId :: Word64
typeId  = Word64
11145653318641710175
instance (C.TypedStruct Field) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
4
instance (C.Allocate Field) where
    type AllocHint Field = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Field -> Message ('Mut s) -> m (Raw Field ('Mut s))
new AllocHint Field
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Field (C.Parsed Field))
instance (C.AllocateList Field) where
    type ListAllocHint Field = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Field
-> Message ('Mut s) -> m (Raw (List Field) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Field (C.Parsed Field))
data instance C.Parsed Field
    = Field 
        {Parsed Field -> Parsed Text
name :: (RP.Parsed Basics.Text)
        ,Parsed Field -> Parsed Word16
codeOrder :: (RP.Parsed Std_.Word16)
        ,Parsed Field -> Parsed (List Annotation)
annotations :: (RP.Parsed (R.List Annotation))
        ,Parsed Field -> Parsed Word16
discriminantValue :: (RP.Parsed Std_.Word16)
        ,Parsed Field -> Parsed Field'ordinal
ordinal :: (RP.Parsed Field'ordinal)
        ,Parsed Field -> Parsed (Which Field)
union' :: (C.Parsed (GH.Which Field))}
    deriving(forall x. Rep (Parsed Field) x -> Parsed Field
forall x. Parsed Field -> Rep (Parsed Field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Field) x -> Parsed Field
$cfrom :: forall x. Parsed Field -> Rep (Parsed Field) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Field))
deriving instance (Std_.Eq (C.Parsed Field))
instance (C.Parse Field (C.Parsed Field)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Field 'Const -> m (Parsed Field)
parse Raw Field 'Const
raw_ = (Parsed Text
-> Parsed Word16
-> Parsed (List Annotation)
-> Parsed Word16
-> Parsed Field'ordinal
-> Parsed (Which Field)
-> Parsed Field
Field forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "name" a => a
#name Raw Field 'Const
raw_)
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "codeOrder" a => a
#codeOrder Raw Field 'Const
raw_)
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "annotations" a => a
#annotations Raw Field 'Const
raw_)
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "discriminantValue" a => a
#discriminantValue Raw Field 'Const
raw_)
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "ordinal" a => a
#ordinal Raw Field 'Const
raw_)
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Field 'Const
raw_)))
instance (C.Marshal Field (C.Parsed Field)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Field ('Mut s) -> Parsed Field -> m ()
marshalInto Raw Field ('Mut s)
raw_ Field{Parsed (Which Field)
Parsed Word16
Parsed (List Annotation)
Parsed Text
Parsed Field'ordinal
union' :: Parsed (Which Field)
ordinal :: Parsed Field'ordinal
discriminantValue :: Parsed Word16
annotations :: Parsed (List Annotation)
codeOrder :: Parsed Word16
name :: Parsed Text
$sel:union':Field :: Parsed Field -> Parsed (Which Field)
$sel:ordinal:Field :: Parsed Field -> Parsed Field'ordinal
$sel:discriminantValue:Field :: Parsed Field -> Parsed Word16
$sel:annotations:Field :: Parsed Field -> Parsed (List Annotation)
$sel:codeOrder:Field :: Parsed Field -> Parsed Word16
$sel:name:Field :: Parsed Field -> Parsed Text
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "name" a => a
#name Parsed Text
name Raw Field ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "codeOrder" a => a
#codeOrder Parsed Word16
codeOrder Raw Field ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "annotations" a => a
#annotations Parsed (List Annotation)
annotations Raw Field ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "discriminantValue" a => a
#discriminantValue Parsed Word16
discriminantValue Raw Field ('Mut s)
raw_)
        (do
            Raw Field'ordinal ('Mut s)
group_ <- (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Field k a b -> Raw a mut -> m (Raw b mut)
GH.readField forall a. IsLabel "ordinal" a => a
#ordinal Raw Field ('Mut s)
raw_)
            (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Field'ordinal ('Mut s)
group_ Parsed Field'ordinal
ordinal)
            )
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Field ('Mut s)
raw_) Parsed (Which Field)
union')
        )
instance (GH.HasUnion Field) where
    unionField :: Field 'Slot Field Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
16 Word64
0)
    data RawWhich Field mut_
        = RW_Field'slot (R.Raw Field'slot mut_)
        | RW_Field'group (R.Raw Field'group mut_)
        | RW_Field'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16 -> Raw Field mut -> m (RawWhich Field mut)
internalWhich Word16
tag_ Raw Field mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability).
Raw Field'slot mut_ -> RawWhich Field mut_
RW_Field'slot forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "slot" a => a
#slot Raw Field mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability).
Raw Field'group mut_ -> RawWhich Field mut_
RW_Field'group forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "group" a => a
#group Raw Field mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability). Word16 -> RawWhich Field mut_
RW_Field'unknown' Word16
tag_))
    data Which Field
instance (GH.HasVariant "slot" GH.Group Field Field'slot) where
    variantByLabel :: Variant 'Group Field Field'slot
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
0)
instance (GH.HasVariant "group" GH.Group Field Field'group) where
    variantByLabel :: Variant 'Group Field Field'group
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
1)
data instance C.Parsed (GH.Which Field)
    = Field'slot (RP.Parsed Field'slot)
    | Field'group (RP.Parsed Field'group)
    | Field'unknown' Std_.Word16
    deriving(forall x. Rep (Parsed (Which Field)) x -> Parsed (Which Field)
forall x. Parsed (Which Field) -> Rep (Parsed (Which Field)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed (Which Field)) x -> Parsed (Which Field)
$cfrom :: forall x. Parsed (Which Field) -> Rep (Parsed (Which Field)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Field)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Field)))
instance (C.Parse (GH.Which Field) (C.Parsed (GH.Which Field))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Field) 'Const -> m (Parsed (Which Field))
parse Raw (Which Field) 'Const
raw_ = (do
        RawWhich Field 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Field) 'Const
raw_)
        case RawWhich Field 'Const
rawWhich_ of
            (RW_Field'slot Raw Field'slot 'Const
rawArg_) ->
                (Parsed Field'slot -> Parsed (Which Field)
Field'slot forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Field'slot 'Const
rawArg_))
            (RW_Field'group Raw Field'group 'Const
rawArg_) ->
                (Parsed Field'group -> Parsed (Which Field)
Field'group forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Field'group 'Const
rawArg_))
            (RW_Field'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Field)
Field'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Field) (C.Parsed (GH.Which Field))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Field) ('Mut s) -> Parsed (Which Field) -> m ()
marshalInto Raw (Which Field) ('Mut s)
raw_ Parsed (Which Field)
parsed_ = case Parsed (Which Field)
parsed_ of
        (Field'slot Parsed Field'slot
arg_) ->
            (do
                Raw Field'slot ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "slot" a => a
#slot (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Field) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Field'slot ('Mut s)
rawGroup_ Parsed Field'slot
arg_)
                )
        (Field'group Parsed Field'group
arg_) ->
            (do
                Raw Field'group ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "group" a => a
#group (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Field) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Field'group ('Mut s)
rawGroup_ Parsed Field'group
arg_)
                )
        (Field'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Field) ('Mut s)
raw_))
instance (GH.HasField "name" GH.Slot Field Basics.Text) where
    fieldByLabel :: Field 'Slot Field Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "codeOrder" GH.Slot Field Std_.Word16) where
    fieldByLabel :: Field 'Slot Field Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
16 Word64
0)
instance (GH.HasField "annotations" GH.Slot Field (R.List Annotation)) where
    fieldByLabel :: Field 'Slot Field (List Annotation)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
1)
instance (GH.HasField "discriminantValue" GH.Slot Field Std_.Word16) where
    fieldByLabel :: Field 'Slot Field Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
0 BitCount
16 Word64
65535)
instance (GH.HasField "ordinal" GH.Group Field Field'ordinal) where
    fieldByLabel :: Field 'Group Field Field'ordinal
fieldByLabel  = forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField
data Field'slot 
type instance (R.ReprFor Field'slot) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Field'slot) where
    typeId :: Word64
typeId  = Word64
14133145859926553711
instance (C.TypedStruct Field'slot) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
4
instance (C.Allocate Field'slot) where
    type AllocHint Field'slot = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Field'slot
-> Message ('Mut s) -> m (Raw Field'slot ('Mut s))
new AllocHint Field'slot
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Field'slot (C.Parsed Field'slot))
instance (C.AllocateList Field'slot) where
    type ListAllocHint Field'slot = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Field'slot
-> Message ('Mut s) -> m (Raw (List Field'slot) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Field'slot (C.Parsed Field'slot))
data instance C.Parsed Field'slot
    = Field'slot' 
        {Parsed Field'slot -> Parsed Word32
offset :: (RP.Parsed Std_.Word32)
        ,Parsed Field'slot -> Parsed Type
type_ :: (RP.Parsed Type)
        ,Parsed Field'slot -> Parsed Value
defaultValue :: (RP.Parsed Value)
        ,Parsed Field'slot -> Parsed Bool
hadExplicitDefault :: (RP.Parsed Std_.Bool)}
    deriving(forall x. Rep (Parsed Field'slot) x -> Parsed Field'slot
forall x. Parsed Field'slot -> Rep (Parsed Field'slot) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Field'slot) x -> Parsed Field'slot
$cfrom :: forall x. Parsed Field'slot -> Rep (Parsed Field'slot) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Field'slot))
deriving instance (Std_.Eq (C.Parsed Field'slot))
instance (C.Parse Field'slot (C.Parsed Field'slot)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Field'slot 'Const -> m (Parsed Field'slot)
parse Raw Field'slot 'Const
raw_ = (Parsed Word32
-> Parsed Type -> Parsed Value -> Parsed Bool -> Parsed Field'slot
Field'slot' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "offset" a => a
#offset Raw Field'slot 'Const
raw_)
                              forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "type_" a => a
#type_ Raw Field'slot 'Const
raw_)
                              forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "defaultValue" a => a
#defaultValue Raw Field'slot 'Const
raw_)
                              forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "hadExplicitDefault" a => a
#hadExplicitDefault Raw Field'slot 'Const
raw_))
instance (C.Marshal Field'slot (C.Parsed Field'slot)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Field'slot ('Mut s) -> Parsed Field'slot -> m ()
marshalInto Raw Field'slot ('Mut s)
raw_ Field'slot'{Parsed Bool
Parsed Word32
Parsed Value
Parsed Type
hadExplicitDefault :: Parsed Bool
defaultValue :: Parsed Value
type_ :: Parsed Type
offset :: Parsed Word32
$sel:hadExplicitDefault:Field'slot' :: Parsed Field'slot -> Parsed Bool
$sel:defaultValue:Field'slot' :: Parsed Field'slot -> Parsed Value
$sel:type_:Field'slot' :: Parsed Field'slot -> Parsed Type
$sel:offset:Field'slot' :: Parsed Field'slot -> Parsed Word32
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "offset" a => a
#offset Parsed Word32
offset Raw Field'slot ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "type_" a => a
#type_ Parsed Type
type_ Raw Field'slot ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "defaultValue" a => a
#defaultValue Parsed Value
defaultValue Raw Field'slot ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "hadExplicitDefault" a => a
#hadExplicitDefault Parsed Bool
hadExplicitDefault Raw Field'slot ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "offset" GH.Slot Field'slot Std_.Word32) where
    fieldByLabel :: Field 'Slot Field'slot Word32
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
32 Word16
0 BitCount
32 Word64
0)
instance (GH.HasField "type_" GH.Slot Field'slot Type) where
    fieldByLabel :: Field 'Slot Field'slot Type
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
2)
instance (GH.HasField "defaultValue" GH.Slot Field'slot Value) where
    fieldByLabel :: Field 'Slot Field'slot Value
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
3)
instance (GH.HasField "hadExplicitDefault" GH.Slot Field'slot Std_.Bool) where
    fieldByLabel :: Field 'Slot Field'slot Bool
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
2 BitCount
1 Word64
0)
data Field'group 
type instance (R.ReprFor Field'group) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Field'group) where
    typeId :: Word64
typeId  = Word64
14626792032033250577
instance (C.TypedStruct Field'group) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
4
instance (C.Allocate Field'group) where
    type AllocHint Field'group = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Field'group
-> Message ('Mut s) -> m (Raw Field'group ('Mut s))
new AllocHint Field'group
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Field'group (C.Parsed Field'group))
instance (C.AllocateList Field'group) where
    type ListAllocHint Field'group = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Field'group
-> Message ('Mut s) -> m (Raw (List Field'group) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Field'group (C.Parsed Field'group))
data instance C.Parsed Field'group
    = Field'group' 
        {Parsed Field'group -> Parsed Word64
typeId :: (RP.Parsed Std_.Word64)}
    deriving(forall x. Rep (Parsed Field'group) x -> Parsed Field'group
forall x. Parsed Field'group -> Rep (Parsed Field'group) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Field'group) x -> Parsed Field'group
$cfrom :: forall x. Parsed Field'group -> Rep (Parsed Field'group) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Field'group))
deriving instance (Std_.Eq (C.Parsed Field'group))
instance (C.Parse Field'group (C.Parsed Field'group)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Field'group 'Const -> m (Parsed Field'group)
parse Raw Field'group 'Const
raw_ = (Parsed Word64 -> Parsed Field'group
Field'group' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "typeId" a => a
#typeId Raw Field'group 'Const
raw_))
instance (C.Marshal Field'group (C.Parsed Field'group)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Field'group ('Mut s) -> Parsed Field'group -> m ()
marshalInto Raw Field'group ('Mut s)
raw_ Field'group'{Parsed Word64
typeId :: Parsed Word64
$sel:typeId:Field'group' :: Parsed Field'group -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "typeId" a => a
#typeId Parsed Word64
typeId Raw Field'group ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "typeId" GH.Slot Field'group Std_.Word64) where
    fieldByLabel :: Field 'Slot Field'group Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
2 BitCount
64 Word64
0)
data Field'ordinal 
type instance (R.ReprFor Field'ordinal) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Field'ordinal) where
    typeId :: Word64
typeId  = Word64
13515537513213004774
instance (C.TypedStruct Field'ordinal) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
4
instance (C.Allocate Field'ordinal) where
    type AllocHint Field'ordinal = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Field'ordinal
-> Message ('Mut s) -> m (Raw Field'ordinal ('Mut s))
new AllocHint Field'ordinal
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Field'ordinal (C.Parsed Field'ordinal))
instance (C.AllocateList Field'ordinal) where
    type ListAllocHint Field'ordinal = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Field'ordinal
-> Message ('Mut s) -> m (Raw (List Field'ordinal) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Field'ordinal (C.Parsed Field'ordinal))
data instance C.Parsed Field'ordinal
    = Field'ordinal' 
        {Parsed Field'ordinal -> Parsed (Which Field'ordinal)
union' :: (C.Parsed (GH.Which Field'ordinal))}
    deriving(forall x. Rep (Parsed Field'ordinal) x -> Parsed Field'ordinal
forall x. Parsed Field'ordinal -> Rep (Parsed Field'ordinal) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Field'ordinal) x -> Parsed Field'ordinal
$cfrom :: forall x. Parsed Field'ordinal -> Rep (Parsed Field'ordinal) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Field'ordinal))
deriving instance (Std_.Eq (C.Parsed Field'ordinal))
instance (C.Parse Field'ordinal (C.Parsed Field'ordinal)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Field'ordinal 'Const -> m (Parsed Field'ordinal)
parse Raw Field'ordinal 'Const
raw_ = (Parsed (Which Field'ordinal) -> Parsed Field'ordinal
Field'ordinal' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Field'ordinal 'Const
raw_)))
instance (C.Marshal Field'ordinal (C.Parsed Field'ordinal)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Field'ordinal ('Mut s) -> Parsed Field'ordinal -> m ()
marshalInto Raw Field'ordinal ('Mut s)
raw_ Field'ordinal'{Parsed (Which Field'ordinal)
union' :: Parsed (Which Field'ordinal)
$sel:union':Field'ordinal' :: Parsed Field'ordinal -> Parsed (Which Field'ordinal)
..} = (do
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Field'ordinal ('Mut s)
raw_) Parsed (Which Field'ordinal)
union')
        )
instance (GH.HasUnion Field'ordinal) where
    unionField :: Field 'Slot Field'ordinal Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
1 BitCount
16 Word64
0)
    data RawWhich Field'ordinal mut_
        = RW_Field'ordinal'implicit (R.Raw () mut_)
        | RW_Field'ordinal'explicit (R.Raw Std_.Word16 mut_)
        | RW_Field'ordinal'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16 -> Raw Field'ordinal mut -> m (RawWhich Field'ordinal mut)
internalWhich Word16
tag_ Raw Field'ordinal mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability).
Raw () mut_ -> RawWhich Field'ordinal mut_
RW_Field'ordinal'implicit forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "implicit" a => a
#implicit Raw Field'ordinal mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability).
Raw Word16 mut_ -> RawWhich Field'ordinal mut_
RW_Field'ordinal'explicit forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "explicit" a => a
#explicit Raw Field'ordinal mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability). Word16 -> RawWhich Field'ordinal mut_
RW_Field'ordinal'unknown' Word16
tag_))
    data Which Field'ordinal
instance (GH.HasVariant "implicit" GH.Slot Field'ordinal ()) where
    variantByLabel :: Variant 'Slot Field'ordinal ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
0)
instance (GH.HasVariant "explicit" GH.Slot Field'ordinal Std_.Word16) where
    variantByLabel :: Variant 'Slot Field'ordinal Word16
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
32 Word16
1 BitCount
16 Word64
0) Word16
1)
data instance C.Parsed (GH.Which Field'ordinal)
    = Field'ordinal'implicit 
    | Field'ordinal'explicit (RP.Parsed Std_.Word16)
    | Field'ordinal'unknown' Std_.Word16
    deriving(forall x.
Rep (Parsed (Which Field'ordinal)) x
-> Parsed (Which Field'ordinal)
forall x.
Parsed (Which Field'ordinal)
-> Rep (Parsed (Which Field'ordinal)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed (Which Field'ordinal)) x
-> Parsed (Which Field'ordinal)
$cfrom :: forall x.
Parsed (Which Field'ordinal)
-> Rep (Parsed (Which Field'ordinal)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Field'ordinal)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Field'ordinal)))
instance (C.Parse (GH.Which Field'ordinal) (C.Parsed (GH.Which Field'ordinal))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Field'ordinal) 'Const
-> m (Parsed (Which Field'ordinal))
parse Raw (Which Field'ordinal) 'Const
raw_ = (do
        RawWhich Field'ordinal 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Field'ordinal) 'Const
raw_)
        case RawWhich Field'ordinal 'Const
rawWhich_ of
            (RW_Field'ordinal'implicit Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Field'ordinal)
Field'ordinal'implicit)
            (RW_Field'ordinal'explicit Raw Word16 'Const
rawArg_) ->
                (Parsed Word16 -> Parsed (Which Field'ordinal)
Field'ordinal'explicit forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Word16 'Const
rawArg_))
            (RW_Field'ordinal'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Field'ordinal)
Field'ordinal'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Field'ordinal) (C.Parsed (GH.Which Field'ordinal))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Field'ordinal) ('Mut s)
-> Parsed (Which Field'ordinal) -> m ()
marshalInto Raw (Which Field'ordinal) ('Mut s)
raw_ Parsed (Which Field'ordinal)
parsed_ = case Parsed (Which Field'ordinal)
parsed_ of
        (Parsed (Which Field'ordinal)
R:ParsedWhich3
Field'ordinal'implicit) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "implicit" a => a
#implicit () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Field'ordinal) ('Mut s)
raw_))
        (Field'ordinal'explicit Parsed Word16
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "explicit" a => a
#explicit Parsed Word16
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Field'ordinal) ('Mut s)
raw_))
        (Field'ordinal'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Field'ordinal) ('Mut s)
raw_))
field'noDiscriminant :: Std_.Word16
field'noDiscriminant :: Word16
field'noDiscriminant  = (forall a. IsWord a => Word64 -> a
C.fromWord Word64
65535)
data Enumerant 
type instance (R.ReprFor Enumerant) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Enumerant) where
    typeId :: Word64
typeId  = Word64
10919677598968879693
instance (C.TypedStruct Enumerant) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
2
instance (C.Allocate Enumerant) where
    type AllocHint Enumerant = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Enumerant
-> Message ('Mut s) -> m (Raw Enumerant ('Mut s))
new AllocHint Enumerant
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Enumerant (C.Parsed Enumerant))
instance (C.AllocateList Enumerant) where
    type ListAllocHint Enumerant = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Enumerant
-> Message ('Mut s) -> m (Raw (List Enumerant) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Enumerant (C.Parsed Enumerant))
data instance C.Parsed Enumerant
    = Enumerant 
        {Parsed Enumerant -> Parsed Text
name :: (RP.Parsed Basics.Text)
        ,Parsed Enumerant -> Parsed Word16
codeOrder :: (RP.Parsed Std_.Word16)
        ,Parsed Enumerant -> Parsed (List Annotation)
annotations :: (RP.Parsed (R.List Annotation))}
    deriving(forall x. Rep (Parsed Enumerant) x -> Parsed Enumerant
forall x. Parsed Enumerant -> Rep (Parsed Enumerant) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Enumerant) x -> Parsed Enumerant
$cfrom :: forall x. Parsed Enumerant -> Rep (Parsed Enumerant) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Enumerant))
deriving instance (Std_.Eq (C.Parsed Enumerant))
instance (C.Parse Enumerant (C.Parsed Enumerant)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Enumerant 'Const -> m (Parsed Enumerant)
parse Raw Enumerant 'Const
raw_ = (Parsed Text
-> Parsed Word16 -> Parsed (List Annotation) -> Parsed Enumerant
Enumerant forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "name" a => a
#name Raw Enumerant 'Const
raw_)
                            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "codeOrder" a => a
#codeOrder Raw Enumerant 'Const
raw_)
                            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "annotations" a => a
#annotations Raw Enumerant 'Const
raw_))
instance (C.Marshal Enumerant (C.Parsed Enumerant)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Enumerant ('Mut s) -> Parsed Enumerant -> m ()
marshalInto Raw Enumerant ('Mut s)
raw_ Enumerant{Parsed Word16
Parsed (List Annotation)
Parsed Text
annotations :: Parsed (List Annotation)
codeOrder :: Parsed Word16
name :: Parsed Text
$sel:annotations:Enumerant :: Parsed Enumerant -> Parsed (List Annotation)
$sel:codeOrder:Enumerant :: Parsed Enumerant -> Parsed Word16
$sel:name:Enumerant :: Parsed Enumerant -> Parsed Text
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "name" a => a
#name Parsed Text
name Raw Enumerant ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "codeOrder" a => a
#codeOrder Parsed Word16
codeOrder Raw Enumerant ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "annotations" a => a
#annotations Parsed (List Annotation)
annotations Raw Enumerant ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "name" GH.Slot Enumerant Basics.Text) where
    fieldByLabel :: Field 'Slot Enumerant Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "codeOrder" GH.Slot Enumerant Std_.Word16) where
    fieldByLabel :: Field 'Slot Enumerant Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
16 Word64
0)
instance (GH.HasField "annotations" GH.Slot Enumerant (R.List Annotation)) where
    fieldByLabel :: Field 'Slot Enumerant (List Annotation)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
1)
data Superclass 
type instance (R.ReprFor Superclass) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Superclass) where
    typeId :: Word64
typeId  = Word64
12220001500510083064
instance (C.TypedStruct Superclass) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Superclass) where
    type AllocHint Superclass = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Superclass
-> Message ('Mut s) -> m (Raw Superclass ('Mut s))
new AllocHint Superclass
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Superclass (C.Parsed Superclass))
instance (C.AllocateList Superclass) where
    type ListAllocHint Superclass = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Superclass
-> Message ('Mut s) -> m (Raw (List Superclass) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Superclass (C.Parsed Superclass))
data instance C.Parsed Superclass
    = Superclass 
        {Parsed Superclass -> Parsed Word64
id :: (RP.Parsed Std_.Word64)
        ,Parsed Superclass -> Parsed Brand
brand :: (RP.Parsed Brand)}
    deriving(forall x. Rep (Parsed Superclass) x -> Parsed Superclass
forall x. Parsed Superclass -> Rep (Parsed Superclass) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Superclass) x -> Parsed Superclass
$cfrom :: forall x. Parsed Superclass -> Rep (Parsed Superclass) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Superclass))
deriving instance (Std_.Eq (C.Parsed Superclass))
instance (C.Parse Superclass (C.Parsed Superclass)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Superclass 'Const -> m (Parsed Superclass)
parse Raw Superclass 'Const
raw_ = (Parsed Word64 -> Parsed Brand -> Parsed Superclass
Superclass forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "id" a => a
#id Raw Superclass 'Const
raw_)
                             forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "brand" a => a
#brand Raw Superclass 'Const
raw_))
instance (C.Marshal Superclass (C.Parsed Superclass)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Superclass ('Mut s) -> Parsed Superclass -> m ()
marshalInto Raw Superclass ('Mut s)
raw_ Superclass{Parsed Word64
Parsed Brand
brand :: Parsed Brand
id :: Parsed Word64
$sel:brand:Superclass :: Parsed Superclass -> Parsed Brand
$sel:id:Superclass :: Parsed Superclass -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "id" a => a
#id Parsed Word64
id Raw Superclass ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "brand" a => a
#brand Parsed Brand
brand Raw Superclass ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "id" GH.Slot Superclass Std_.Word64) where
    fieldByLabel :: Field 'Slot Superclass Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
64 Word64
0)
instance (GH.HasField "brand" GH.Slot Superclass Brand) where
    fieldByLabel :: Field 'Slot Superclass Brand
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
data Method 
type instance (R.ReprFor Method) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Method) where
    typeId :: Word64
typeId  = Word64
10736806783679155584
instance (C.TypedStruct Method) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
5
instance (C.Allocate Method) where
    type AllocHint Method = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Method -> Message ('Mut s) -> m (Raw Method ('Mut s))
new AllocHint Method
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Method (C.Parsed Method))
instance (C.AllocateList Method) where
    type ListAllocHint Method = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Method
-> Message ('Mut s) -> m (Raw (List Method) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Method (C.Parsed Method))
data instance C.Parsed Method
    = Method 
        {Parsed Method -> Parsed Text
name :: (RP.Parsed Basics.Text)
        ,Parsed Method -> Parsed Word16
codeOrder :: (RP.Parsed Std_.Word16)
        ,Parsed Method -> Parsed Word64
paramStructType :: (RP.Parsed Std_.Word64)
        ,Parsed Method -> Parsed Word64
resultStructType :: (RP.Parsed Std_.Word64)
        ,Parsed Method -> Parsed (List Annotation)
annotations :: (RP.Parsed (R.List Annotation))
        ,Parsed Method -> Parsed Brand
paramBrand :: (RP.Parsed Brand)
        ,Parsed Method -> Parsed Brand
resultBrand :: (RP.Parsed Brand)
        ,Parsed Method -> Parsed (List Node'Parameter)
implicitParameters :: (RP.Parsed (R.List Node'Parameter))}
    deriving(forall x. Rep (Parsed Method) x -> Parsed Method
forall x. Parsed Method -> Rep (Parsed Method) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Method) x -> Parsed Method
$cfrom :: forall x. Parsed Method -> Rep (Parsed Method) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Method))
deriving instance (Std_.Eq (C.Parsed Method))
instance (C.Parse Method (C.Parsed Method)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Method 'Const -> m (Parsed Method)
parse Raw Method 'Const
raw_ = (Parsed Text
-> Parsed Word16
-> Parsed Word64
-> Parsed Word64
-> Parsed (List Annotation)
-> Parsed Brand
-> Parsed Brand
-> Parsed (List Node'Parameter)
-> Parsed Method
Method forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "name" a => a
#name Raw Method 'Const
raw_)
                         forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "codeOrder" a => a
#codeOrder Raw Method 'Const
raw_)
                         forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "paramStructType" a => a
#paramStructType Raw Method 'Const
raw_)
                         forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "resultStructType" a => a
#resultStructType Raw Method 'Const
raw_)
                         forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "annotations" a => a
#annotations Raw Method 'Const
raw_)
                         forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "paramBrand" a => a
#paramBrand Raw Method 'Const
raw_)
                         forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "resultBrand" a => a
#resultBrand Raw Method 'Const
raw_)
                         forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "implicitParameters" a => a
#implicitParameters Raw Method 'Const
raw_))
instance (C.Marshal Method (C.Parsed Method)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Method ('Mut s) -> Parsed Method -> m ()
marshalInto Raw Method ('Mut s)
raw_ Method{Parsed Word16
Parsed Word64
Parsed (List Annotation)
Parsed (List Node'Parameter)
Parsed Text
Parsed Brand
implicitParameters :: Parsed (List Node'Parameter)
resultBrand :: Parsed Brand
paramBrand :: Parsed Brand
annotations :: Parsed (List Annotation)
resultStructType :: Parsed Word64
paramStructType :: Parsed Word64
codeOrder :: Parsed Word16
name :: Parsed Text
$sel:implicitParameters:Method :: Parsed Method -> Parsed (List Node'Parameter)
$sel:resultBrand:Method :: Parsed Method -> Parsed Brand
$sel:paramBrand:Method :: Parsed Method -> Parsed Brand
$sel:annotations:Method :: Parsed Method -> Parsed (List Annotation)
$sel:resultStructType:Method :: Parsed Method -> Parsed Word64
$sel:paramStructType:Method :: Parsed Method -> Parsed Word64
$sel:codeOrder:Method :: Parsed Method -> Parsed Word16
$sel:name:Method :: Parsed Method -> Parsed Text
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "name" a => a
#name Parsed Text
name Raw Method ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "codeOrder" a => a
#codeOrder Parsed Word16
codeOrder Raw Method ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "paramStructType" a => a
#paramStructType Parsed Word64
paramStructType Raw Method ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "resultStructType" a => a
#resultStructType Parsed Word64
resultStructType Raw Method ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "annotations" a => a
#annotations Parsed (List Annotation)
annotations Raw Method ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "paramBrand" a => a
#paramBrand Parsed Brand
paramBrand Raw Method ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "resultBrand" a => a
#resultBrand Parsed Brand
resultBrand Raw Method ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "implicitParameters" a => a
#implicitParameters Parsed (List Node'Parameter)
implicitParameters Raw Method ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "name" GH.Slot Method Basics.Text) where
    fieldByLabel :: Field 'Slot Method Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "codeOrder" GH.Slot Method Std_.Word16) where
    fieldByLabel :: Field 'Slot Method Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
16 Word64
0)
instance (GH.HasField "paramStructType" GH.Slot Method Std_.Word64) where
    fieldByLabel :: Field 'Slot Method Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
64 Word64
0)
instance (GH.HasField "resultStructType" GH.Slot Method Std_.Word64) where
    fieldByLabel :: Field 'Slot Method Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
2 BitCount
64 Word64
0)
instance (GH.HasField "annotations" GH.Slot Method (R.List Annotation)) where
    fieldByLabel :: Field 'Slot Method (List Annotation)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
1)
instance (GH.HasField "paramBrand" GH.Slot Method Brand) where
    fieldByLabel :: Field 'Slot Method Brand
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
2)
instance (GH.HasField "resultBrand" GH.Slot Method Brand) where
    fieldByLabel :: Field 'Slot Method Brand
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
3)
instance (GH.HasField "implicitParameters" GH.Slot Method (R.List Node'Parameter)) where
    fieldByLabel :: Field 'Slot Method (List Node'Parameter)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
4)
data Type 
type instance (R.ReprFor Type) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type) where
    typeId :: Word64
typeId  = Word64
15020482145304562784
instance (C.TypedStruct Type) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type) where
    type AllocHint Type = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type -> Message ('Mut s) -> m (Raw Type ('Mut s))
new AllocHint Type
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type (C.Parsed Type))
instance (C.AllocateList Type) where
    type ListAllocHint Type = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type
-> Message ('Mut s) -> m (Raw (List Type) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type (C.Parsed Type))
data instance C.Parsed Type
    = Type 
        {Parsed Type -> Parsed (Which Type)
union' :: (C.Parsed (GH.Which Type))}
    deriving(forall x. Rep (Parsed Type) x -> Parsed Type
forall x. Parsed Type -> Rep (Parsed Type) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Type) x -> Parsed Type
$cfrom :: forall x. Parsed Type -> Rep (Parsed Type) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type))
deriving instance (Std_.Eq (C.Parsed Type))
instance (C.Parse Type (C.Parsed Type)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type 'Const -> m (Parsed Type)
parse Raw Type 'Const
raw_ = (Parsed (Which Type) -> Parsed Type
Type forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Type 'Const
raw_)))
instance (C.Marshal Type (C.Parsed Type)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type ('Mut s) -> Parsed Type -> m ()
marshalInto Raw Type ('Mut s)
raw_ Type{Parsed (Which Type)
union' :: Parsed (Which Type)
$sel:union':Type :: Parsed Type -> Parsed (Which Type)
..} = (do
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Type ('Mut s)
raw_) Parsed (Which Type)
union')
        )
instance (GH.HasUnion Type) where
    unionField :: Field 'Slot Type Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
16 Word64
0)
    data RawWhich Type mut_
        = RW_Type'void (R.Raw () mut_)
        | RW_Type'bool (R.Raw () mut_)
        | RW_Type'int8 (R.Raw () mut_)
        | RW_Type'int16 (R.Raw () mut_)
        | RW_Type'int32 (R.Raw () mut_)
        | RW_Type'int64 (R.Raw () mut_)
        | RW_Type'uint8 (R.Raw () mut_)
        | RW_Type'uint16 (R.Raw () mut_)
        | RW_Type'uint32 (R.Raw () mut_)
        | RW_Type'uint64 (R.Raw () mut_)
        | RW_Type'float32 (R.Raw () mut_)
        | RW_Type'float64 (R.Raw () mut_)
        | RW_Type'text (R.Raw () mut_)
        | RW_Type'data_ (R.Raw () mut_)
        | RW_Type'list (R.Raw Type'list mut_)
        | RW_Type'enum (R.Raw Type'enum mut_)
        | RW_Type'struct (R.Raw Type'struct mut_)
        | RW_Type'interface (R.Raw Type'interface mut_)
        | RW_Type'anyPointer (R.Raw Type'anyPointer mut_)
        | RW_Type'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16 -> Raw Type mut -> m (RawWhich Type mut)
internalWhich Word16
tag_ Raw Type mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'void forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "void" a => a
#void Raw Type mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "bool" a => a
#bool Raw Type mut
struct_))
        Word16
2 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'int8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "int8" a => a
#int8 Raw Type mut
struct_))
        Word16
3 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'int16 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "int16" a => a
#int16 Raw Type mut
struct_))
        Word16
4 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'int32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "int32" a => a
#int32 Raw Type mut
struct_))
        Word16
5 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'int64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "int64" a => a
#int64 Raw Type mut
struct_))
        Word16
6 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'uint8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "uint8" a => a
#uint8 Raw Type mut
struct_))
        Word16
7 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'uint16 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "uint16" a => a
#uint16 Raw Type mut
struct_))
        Word16
8 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'uint32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "uint32" a => a
#uint32 Raw Type mut
struct_))
        Word16
9 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'uint64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "uint64" a => a
#uint64 Raw Type mut
struct_))
        Word16
10 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'float32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "float32" a => a
#float32 Raw Type mut
struct_))
        Word16
11 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'float64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "float64" a => a
#float64 Raw Type mut
struct_))
        Word16
12 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'text forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "text" a => a
#text Raw Type mut
struct_))
        Word16
13 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Type mut_
RW_Type'data_ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "data_" a => a
#data_ Raw Type mut
struct_))
        Word16
14 ->
            (forall (mut_ :: Mutability).
Raw Type'list mut_ -> RawWhich Type mut_
RW_Type'list forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "list" a => a
#list Raw Type mut
struct_))
        Word16
15 ->
            (forall (mut_ :: Mutability).
Raw Type'enum mut_ -> RawWhich Type mut_
RW_Type'enum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "enum" a => a
#enum Raw Type mut
struct_))
        Word16
16 ->
            (forall (mut_ :: Mutability).
Raw Type'struct mut_ -> RawWhich Type mut_
RW_Type'struct forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "struct" a => a
#struct Raw Type mut
struct_))
        Word16
17 ->
            (forall (mut_ :: Mutability).
Raw Type'interface mut_ -> RawWhich Type mut_
RW_Type'interface forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "interface" a => a
#interface Raw Type mut
struct_))
        Word16
18 ->
            (forall (mut_ :: Mutability).
Raw Type'anyPointer mut_ -> RawWhich Type mut_
RW_Type'anyPointer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "anyPointer" a => a
#anyPointer Raw Type mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability). Word16 -> RawWhich Type mut_
RW_Type'unknown' Word16
tag_))
    data Which Type
instance (GH.HasVariant "void" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
0)
instance (GH.HasVariant "bool" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
1)
instance (GH.HasVariant "int8" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
2)
instance (GH.HasVariant "int16" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
3)
instance (GH.HasVariant "int32" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
4)
instance (GH.HasVariant "int64" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
5)
instance (GH.HasVariant "uint8" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
6)
instance (GH.HasVariant "uint16" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
7)
instance (GH.HasVariant "uint32" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
8)
instance (GH.HasVariant "uint64" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
9)
instance (GH.HasVariant "float32" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
10)
instance (GH.HasVariant "float64" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
11)
instance (GH.HasVariant "text" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
12)
instance (GH.HasVariant "data_" GH.Slot Type ()) where
    variantByLabel :: Variant 'Slot Type ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
13)
instance (GH.HasVariant "list" GH.Group Type Type'list) where
    variantByLabel :: Variant 'Group Type Type'list
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
14)
instance (GH.HasVariant "enum" GH.Group Type Type'enum) where
    variantByLabel :: Variant 'Group Type Type'enum
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
15)
instance (GH.HasVariant "struct" GH.Group Type Type'struct) where
    variantByLabel :: Variant 'Group Type Type'struct
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
16)
instance (GH.HasVariant "interface" GH.Group Type Type'interface) where
    variantByLabel :: Variant 'Group Type Type'interface
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
17)
instance (GH.HasVariant "anyPointer" GH.Group Type Type'anyPointer) where
    variantByLabel :: Variant 'Group Type Type'anyPointer
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
18)
data instance C.Parsed (GH.Which Type)
    = Type'void 
    | Type'bool 
    | Type'int8 
    | Type'int16 
    | Type'int32 
    | Type'int64 
    | Type'uint8 
    | Type'uint16 
    | Type'uint32 
    | Type'uint64 
    | Type'float32 
    | Type'float64 
    | Type'text 
    | Type'data_ 
    | Type'list (RP.Parsed Type'list)
    | Type'enum (RP.Parsed Type'enum)
    | Type'struct (RP.Parsed Type'struct)
    | Type'interface (RP.Parsed Type'interface)
    | Type'anyPointer (RP.Parsed Type'anyPointer)
    | Type'unknown' Std_.Word16
    deriving(forall x. Rep (Parsed (Which Type)) x -> Parsed (Which Type)
forall x. Parsed (Which Type) -> Rep (Parsed (Which Type)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed (Which Type)) x -> Parsed (Which Type)
$cfrom :: forall x. Parsed (Which Type) -> Rep (Parsed (Which Type)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Type)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Type)))
instance (C.Parse (GH.Which Type) (C.Parsed (GH.Which Type))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Type) 'Const -> m (Parsed (Which Type))
parse Raw (Which Type) 'Const
raw_ = (do
        RawWhich Type 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Type) 'Const
raw_)
        case RawWhich Type 'Const
rawWhich_ of
            (RW_Type'void Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'void)
            (RW_Type'bool Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'bool)
            (RW_Type'int8 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'int8)
            (RW_Type'int16 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'int16)
            (RW_Type'int32 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'int32)
            (RW_Type'int64 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'int64)
            (RW_Type'uint8 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'uint8)
            (RW_Type'uint16 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'uint16)
            (RW_Type'uint32 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'uint32)
            (RW_Type'uint64 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'uint64)
            (RW_Type'float32 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'float32)
            (RW_Type'float64 Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'float64)
            (RW_Type'text Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'text)
            (RW_Type'data_ Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type)
Type'data_)
            (RW_Type'list Raw Type'list 'Const
rawArg_) ->
                (Parsed Type'list -> Parsed (Which Type)
Type'list forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type'list 'Const
rawArg_))
            (RW_Type'enum Raw Type'enum 'Const
rawArg_) ->
                (Parsed Type'enum -> Parsed (Which Type)
Type'enum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type'enum 'Const
rawArg_))
            (RW_Type'struct Raw Type'struct 'Const
rawArg_) ->
                (Parsed Type'struct -> Parsed (Which Type)
Type'struct forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type'struct 'Const
rawArg_))
            (RW_Type'interface Raw Type'interface 'Const
rawArg_) ->
                (Parsed Type'interface -> Parsed (Which Type)
Type'interface forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type'interface 'Const
rawArg_))
            (RW_Type'anyPointer Raw Type'anyPointer 'Const
rawArg_) ->
                (Parsed Type'anyPointer -> Parsed (Which Type)
Type'anyPointer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type'anyPointer 'Const
rawArg_))
            (RW_Type'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Type)
Type'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Type) (C.Parsed (GH.Which Type))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Type) ('Mut s) -> Parsed (Which Type) -> m ()
marshalInto Raw (Which Type) ('Mut s)
raw_ Parsed (Which Type)
parsed_ = case Parsed (Which Type)
parsed_ of
        (Parsed (Which Type)
R:ParsedWhich5
Type'void) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "void" a => a
#void () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'bool) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "bool" a => a
#bool () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'int8) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "int8" a => a
#int8 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'int16) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "int16" a => a
#int16 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'int32) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "int32" a => a
#int32 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'int64) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "int64" a => a
#int64 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'uint8) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "uint8" a => a
#uint8 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'uint16) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "uint16" a => a
#uint16 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'uint32) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "uint32" a => a
#uint32 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'uint64) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "uint64" a => a
#uint64 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'float32) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "float32" a => a
#float32 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'float64) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "float64" a => a
#float64 () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'text) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "text" a => a
#text () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Parsed (Which Type)
R:ParsedWhich5
Type'data_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "data_" a => a
#data_ () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
        (Type'list Parsed Type'list
arg_) ->
            (do
                Raw Type'list ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "list" a => a
#list (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Type'list ('Mut s)
rawGroup_ Parsed Type'list
arg_)
                )
        (Type'enum Parsed Type'enum
arg_) ->
            (do
                Raw Type'enum ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "enum" a => a
#enum (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Type'enum ('Mut s)
rawGroup_ Parsed Type'enum
arg_)
                )
        (Type'struct Parsed Type'struct
arg_) ->
            (do
                Raw Type'struct ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "struct" a => a
#struct (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Type'struct ('Mut s)
rawGroup_ Parsed Type'struct
arg_)
                )
        (Type'interface Parsed Type'interface
arg_) ->
            (do
                Raw Type'interface ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "interface" a => a
#interface (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Type'interface ('Mut s)
rawGroup_ Parsed Type'interface
arg_)
                )
        (Type'anyPointer Parsed Type'anyPointer
arg_) ->
            (do
                Raw Type'anyPointer ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "anyPointer" a => a
#anyPointer (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Type'anyPointer ('Mut s)
rawGroup_ Parsed Type'anyPointer
arg_)
                )
        (Type'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type) ('Mut s)
raw_))
data Type'list 
type instance (R.ReprFor Type'list) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type'list) where
    typeId :: Word64
typeId  = Word64
9792858745991129751
instance (C.TypedStruct Type'list) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type'list) where
    type AllocHint Type'list = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type'list
-> Message ('Mut s) -> m (Raw Type'list ('Mut s))
new AllocHint Type'list
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type'list (C.Parsed Type'list))
instance (C.AllocateList Type'list) where
    type ListAllocHint Type'list = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type'list
-> Message ('Mut s) -> m (Raw (List Type'list) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type'list (C.Parsed Type'list))
data instance C.Parsed Type'list
    = Type'list' 
        {Parsed Type'list -> Parsed Type
elementType :: (RP.Parsed Type)}
    deriving(forall x. Rep (Parsed Type'list) x -> Parsed Type'list
forall x. Parsed Type'list -> Rep (Parsed Type'list) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Type'list) x -> Parsed Type'list
$cfrom :: forall x. Parsed Type'list -> Rep (Parsed Type'list) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type'list))
deriving instance (Std_.Eq (C.Parsed Type'list))
instance (C.Parse Type'list (C.Parsed Type'list)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type'list 'Const -> m (Parsed Type'list)
parse Raw Type'list 'Const
raw_ = (Parsed Type -> Parsed Type'list
Type'list' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "elementType" a => a
#elementType Raw Type'list 'Const
raw_))
instance (C.Marshal Type'list (C.Parsed Type'list)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type'list ('Mut s) -> Parsed Type'list -> m ()
marshalInto Raw Type'list ('Mut s)
raw_ Type'list'{Parsed Type
elementType :: Parsed Type
$sel:elementType:Type'list' :: Parsed Type'list -> Parsed Type
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "elementType" a => a
#elementType Parsed Type
elementType Raw Type'list ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "elementType" GH.Slot Type'list Type) where
    fieldByLabel :: Field 'Slot Type'list Type
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
data Type'enum 
type instance (R.ReprFor Type'enum) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type'enum) where
    typeId :: Word64
typeId  = Word64
11389172934837766057
instance (C.TypedStruct Type'enum) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type'enum) where
    type AllocHint Type'enum = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type'enum
-> Message ('Mut s) -> m (Raw Type'enum ('Mut s))
new AllocHint Type'enum
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type'enum (C.Parsed Type'enum))
instance (C.AllocateList Type'enum) where
    type ListAllocHint Type'enum = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type'enum
-> Message ('Mut s) -> m (Raw (List Type'enum) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type'enum (C.Parsed Type'enum))
data instance C.Parsed Type'enum
    = Type'enum' 
        {Parsed Type'enum -> Parsed Word64
typeId :: (RP.Parsed Std_.Word64)
        ,Parsed Type'enum -> Parsed Brand
brand :: (RP.Parsed Brand)}
    deriving(forall x. Rep (Parsed Type'enum) x -> Parsed Type'enum
forall x. Parsed Type'enum -> Rep (Parsed Type'enum) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Type'enum) x -> Parsed Type'enum
$cfrom :: forall x. Parsed Type'enum -> Rep (Parsed Type'enum) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type'enum))
deriving instance (Std_.Eq (C.Parsed Type'enum))
instance (C.Parse Type'enum (C.Parsed Type'enum)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type'enum 'Const -> m (Parsed Type'enum)
parse Raw Type'enum 'Const
raw_ = (Parsed Word64 -> Parsed Brand -> Parsed Type'enum
Type'enum' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "typeId" a => a
#typeId Raw Type'enum 'Const
raw_)
                             forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "brand" a => a
#brand Raw Type'enum 'Const
raw_))
instance (C.Marshal Type'enum (C.Parsed Type'enum)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type'enum ('Mut s) -> Parsed Type'enum -> m ()
marshalInto Raw Type'enum ('Mut s)
raw_ Type'enum'{Parsed Word64
Parsed Brand
brand :: Parsed Brand
typeId :: Parsed Word64
$sel:brand:Type'enum' :: Parsed Type'enum -> Parsed Brand
$sel:typeId:Type'enum' :: Parsed Type'enum -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "typeId" a => a
#typeId Parsed Word64
typeId Raw Type'enum ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "brand" a => a
#brand Parsed Brand
brand Raw Type'enum ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "typeId" GH.Slot Type'enum Std_.Word64) where
    fieldByLabel :: Field 'Slot Type'enum Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
64 Word64
0)
instance (GH.HasField "brand" GH.Slot Type'enum Brand) where
    fieldByLabel :: Field 'Slot Type'enum Brand
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
data Type'struct 
type instance (R.ReprFor Type'struct) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type'struct) where
    typeId :: Word64
typeId  = Word64
12410354185295152851
instance (C.TypedStruct Type'struct) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type'struct) where
    type AllocHint Type'struct = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type'struct
-> Message ('Mut s) -> m (Raw Type'struct ('Mut s))
new AllocHint Type'struct
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type'struct (C.Parsed Type'struct))
instance (C.AllocateList Type'struct) where
    type ListAllocHint Type'struct = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type'struct
-> Message ('Mut s) -> m (Raw (List Type'struct) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type'struct (C.Parsed Type'struct))
data instance C.Parsed Type'struct
    = Type'struct' 
        {Parsed Type'struct -> Parsed Word64
typeId :: (RP.Parsed Std_.Word64)
        ,Parsed Type'struct -> Parsed Brand
brand :: (RP.Parsed Brand)}
    deriving(forall x. Rep (Parsed Type'struct) x -> Parsed Type'struct
forall x. Parsed Type'struct -> Rep (Parsed Type'struct) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Type'struct) x -> Parsed Type'struct
$cfrom :: forall x. Parsed Type'struct -> Rep (Parsed Type'struct) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type'struct))
deriving instance (Std_.Eq (C.Parsed Type'struct))
instance (C.Parse Type'struct (C.Parsed Type'struct)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type'struct 'Const -> m (Parsed Type'struct)
parse Raw Type'struct 'Const
raw_ = (Parsed Word64 -> Parsed Brand -> Parsed Type'struct
Type'struct' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "typeId" a => a
#typeId Raw Type'struct 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "brand" a => a
#brand Raw Type'struct 'Const
raw_))
instance (C.Marshal Type'struct (C.Parsed Type'struct)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type'struct ('Mut s) -> Parsed Type'struct -> m ()
marshalInto Raw Type'struct ('Mut s)
raw_ Type'struct'{Parsed Word64
Parsed Brand
brand :: Parsed Brand
typeId :: Parsed Word64
$sel:brand:Type'struct' :: Parsed Type'struct -> Parsed Brand
$sel:typeId:Type'struct' :: Parsed Type'struct -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "typeId" a => a
#typeId Parsed Word64
typeId Raw Type'struct ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "brand" a => a
#brand Parsed Brand
brand Raw Type'struct ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "typeId" GH.Slot Type'struct Std_.Word64) where
    fieldByLabel :: Field 'Slot Type'struct Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
64 Word64
0)
instance (GH.HasField "brand" GH.Slot Type'struct Brand) where
    fieldByLabel :: Field 'Slot Type'struct Brand
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
data Type'interface 
type instance (R.ReprFor Type'interface) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type'interface) where
    typeId :: Word64
typeId  = Word64
17116997365232503999
instance (C.TypedStruct Type'interface) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type'interface) where
    type AllocHint Type'interface = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type'interface
-> Message ('Mut s) -> m (Raw Type'interface ('Mut s))
new AllocHint Type'interface
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type'interface (C.Parsed Type'interface))
instance (C.AllocateList Type'interface) where
    type ListAllocHint Type'interface = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type'interface
-> Message ('Mut s) -> m (Raw (List Type'interface) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type'interface (C.Parsed Type'interface))
data instance C.Parsed Type'interface
    = Type'interface' 
        {Parsed Type'interface -> Parsed Word64
typeId :: (RP.Parsed Std_.Word64)
        ,Parsed Type'interface -> Parsed Brand
brand :: (RP.Parsed Brand)}
    deriving(forall x. Rep (Parsed Type'interface) x -> Parsed Type'interface
forall x. Parsed Type'interface -> Rep (Parsed Type'interface) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Type'interface) x -> Parsed Type'interface
$cfrom :: forall x. Parsed Type'interface -> Rep (Parsed Type'interface) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type'interface))
deriving instance (Std_.Eq (C.Parsed Type'interface))
instance (C.Parse Type'interface (C.Parsed Type'interface)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type'interface 'Const -> m (Parsed Type'interface)
parse Raw Type'interface 'Const
raw_ = (Parsed Word64 -> Parsed Brand -> Parsed Type'interface
Type'interface' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "typeId" a => a
#typeId Raw Type'interface 'Const
raw_)
                                  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "brand" a => a
#brand Raw Type'interface 'Const
raw_))
instance (C.Marshal Type'interface (C.Parsed Type'interface)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type'interface ('Mut s) -> Parsed Type'interface -> m ()
marshalInto Raw Type'interface ('Mut s)
raw_ Type'interface'{Parsed Word64
Parsed Brand
brand :: Parsed Brand
typeId :: Parsed Word64
$sel:brand:Type'interface' :: Parsed Type'interface -> Parsed Brand
$sel:typeId:Type'interface' :: Parsed Type'interface -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "typeId" a => a
#typeId Parsed Word64
typeId Raw Type'interface ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "brand" a => a
#brand Parsed Brand
brand Raw Type'interface ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "typeId" GH.Slot Type'interface Std_.Word64) where
    fieldByLabel :: Field 'Slot Type'interface Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
64 Word64
0)
instance (GH.HasField "brand" GH.Slot Type'interface Brand) where
    fieldByLabel :: Field 'Slot Type'interface Brand
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
data Type'anyPointer 
type instance (R.ReprFor Type'anyPointer) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type'anyPointer) where
    typeId :: Word64
typeId  = Word64
14003731834718800369
instance (C.TypedStruct Type'anyPointer) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type'anyPointer) where
    type AllocHint Type'anyPointer = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type'anyPointer
-> Message ('Mut s) -> m (Raw Type'anyPointer ('Mut s))
new AllocHint Type'anyPointer
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type'anyPointer (C.Parsed Type'anyPointer))
instance (C.AllocateList Type'anyPointer) where
    type ListAllocHint Type'anyPointer = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type'anyPointer
-> Message ('Mut s) -> m (Raw (List Type'anyPointer) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type'anyPointer (C.Parsed Type'anyPointer))
data instance C.Parsed Type'anyPointer
    = Type'anyPointer' 
        {Parsed Type'anyPointer -> Parsed (Which Type'anyPointer)
union' :: (C.Parsed (GH.Which Type'anyPointer))}
    deriving(forall x. Rep (Parsed Type'anyPointer) x -> Parsed Type'anyPointer
forall x. Parsed Type'anyPointer -> Rep (Parsed Type'anyPointer) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Type'anyPointer) x -> Parsed Type'anyPointer
$cfrom :: forall x. Parsed Type'anyPointer -> Rep (Parsed Type'anyPointer) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type'anyPointer))
deriving instance (Std_.Eq (C.Parsed Type'anyPointer))
instance (C.Parse Type'anyPointer (C.Parsed Type'anyPointer)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type'anyPointer 'Const -> m (Parsed Type'anyPointer)
parse Raw Type'anyPointer 'Const
raw_ = (Parsed (Which Type'anyPointer) -> Parsed Type'anyPointer
Type'anyPointer' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Type'anyPointer 'Const
raw_)))
instance (C.Marshal Type'anyPointer (C.Parsed Type'anyPointer)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type'anyPointer ('Mut s) -> Parsed Type'anyPointer -> m ()
marshalInto Raw Type'anyPointer ('Mut s)
raw_ Type'anyPointer'{Parsed (Which Type'anyPointer)
union' :: Parsed (Which Type'anyPointer)
$sel:union':Type'anyPointer' :: Parsed Type'anyPointer -> Parsed (Which Type'anyPointer)
..} = (do
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Type'anyPointer ('Mut s)
raw_) Parsed (Which Type'anyPointer)
union')
        )
instance (GH.HasUnion Type'anyPointer) where
    unionField :: Field 'Slot Type'anyPointer Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
16 Word64
0)
    data RawWhich Type'anyPointer mut_
        = RW_Type'anyPointer'unconstrained (R.Raw Type'anyPointer'unconstrained mut_)
        | RW_Type'anyPointer'parameter (R.Raw Type'anyPointer'parameter mut_)
        | RW_Type'anyPointer'implicitMethodParameter (R.Raw Type'anyPointer'implicitMethodParameter mut_)
        | RW_Type'anyPointer'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16
-> Raw Type'anyPointer mut -> m (RawWhich Type'anyPointer mut)
internalWhich Word16
tag_ Raw Type'anyPointer mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability).
Raw Type'anyPointer'unconstrained mut_
-> RawWhich Type'anyPointer mut_
RW_Type'anyPointer'unconstrained forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "unconstrained" a => a
#unconstrained Raw Type'anyPointer mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability).
Raw Type'anyPointer'parameter mut_ -> RawWhich Type'anyPointer mut_
RW_Type'anyPointer'parameter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "parameter" a => a
#parameter Raw Type'anyPointer mut
struct_))
        Word16
2 ->
            (forall (mut_ :: Mutability).
Raw Type'anyPointer'implicitMethodParameter mut_
-> RawWhich Type'anyPointer mut_
RW_Type'anyPointer'implicitMethodParameter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "implicitMethodParameter" a => a
#implicitMethodParameter Raw Type'anyPointer mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability).
Word16 -> RawWhich Type'anyPointer mut_
RW_Type'anyPointer'unknown' Word16
tag_))
    data Which Type'anyPointer
instance (GH.HasVariant "unconstrained" GH.Group Type'anyPointer Type'anyPointer'unconstrained) where
    variantByLabel :: Variant 'Group Type'anyPointer Type'anyPointer'unconstrained
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
0)
instance (GH.HasVariant "parameter" GH.Group Type'anyPointer Type'anyPointer'parameter) where
    variantByLabel :: Variant 'Group Type'anyPointer Type'anyPointer'parameter
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
1)
instance (GH.HasVariant "implicitMethodParameter" GH.Group Type'anyPointer Type'anyPointer'implicitMethodParameter) where
    variantByLabel :: Variant
  'Group Type'anyPointer Type'anyPointer'implicitMethodParameter
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Ptr ('Just 'Struct)) => Field 'Group a b
GH.groupField Word16
2)
data instance C.Parsed (GH.Which Type'anyPointer)
    = Type'anyPointer'unconstrained (RP.Parsed Type'anyPointer'unconstrained)
    | Type'anyPointer'parameter (RP.Parsed Type'anyPointer'parameter)
    | Type'anyPointer'implicitMethodParameter (RP.Parsed Type'anyPointer'implicitMethodParameter)
    | Type'anyPointer'unknown' Std_.Word16
    deriving(forall x.
Rep (Parsed (Which Type'anyPointer)) x
-> Parsed (Which Type'anyPointer)
forall x.
Parsed (Which Type'anyPointer)
-> Rep (Parsed (Which Type'anyPointer)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed (Which Type'anyPointer)) x
-> Parsed (Which Type'anyPointer)
$cfrom :: forall x.
Parsed (Which Type'anyPointer)
-> Rep (Parsed (Which Type'anyPointer)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Type'anyPointer)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Type'anyPointer)))
instance (C.Parse (GH.Which Type'anyPointer) (C.Parsed (GH.Which Type'anyPointer))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Type'anyPointer) 'Const
-> m (Parsed (Which Type'anyPointer))
parse Raw (Which Type'anyPointer) 'Const
raw_ = (do
        RawWhich Type'anyPointer 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Type'anyPointer) 'Const
raw_)
        case RawWhich Type'anyPointer 'Const
rawWhich_ of
            (RW_Type'anyPointer'unconstrained Raw Type'anyPointer'unconstrained 'Const
rawArg_) ->
                (Parsed Type'anyPointer'unconstrained
-> Parsed (Which Type'anyPointer)
Type'anyPointer'unconstrained forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type'anyPointer'unconstrained 'Const
rawArg_))
            (RW_Type'anyPointer'parameter Raw Type'anyPointer'parameter 'Const
rawArg_) ->
                (Parsed Type'anyPointer'parameter -> Parsed (Which Type'anyPointer)
Type'anyPointer'parameter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type'anyPointer'parameter 'Const
rawArg_))
            (RW_Type'anyPointer'implicitMethodParameter Raw Type'anyPointer'implicitMethodParameter 'Const
rawArg_) ->
                (Parsed Type'anyPointer'implicitMethodParameter
-> Parsed (Which Type'anyPointer)
Type'anyPointer'implicitMethodParameter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type'anyPointer'implicitMethodParameter 'Const
rawArg_))
            (RW_Type'anyPointer'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Type'anyPointer)
Type'anyPointer'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Type'anyPointer) (C.Parsed (GH.Which Type'anyPointer))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Type'anyPointer) ('Mut s)
-> Parsed (Which Type'anyPointer) -> m ()
marshalInto Raw (Which Type'anyPointer) ('Mut s)
raw_ Parsed (Which Type'anyPointer)
parsed_ = case Parsed (Which Type'anyPointer)
parsed_ of
        (Type'anyPointer'unconstrained Parsed Type'anyPointer'unconstrained
arg_) ->
            (do
                Raw Type'anyPointer'unconstrained ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "unconstrained" a => a
#unconstrained (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Type'anyPointer'unconstrained ('Mut s)
rawGroup_ Parsed Type'anyPointer'unconstrained
arg_)
                )
        (Type'anyPointer'parameter Parsed Type'anyPointer'parameter
arg_) ->
            (do
                Raw Type'anyPointer'parameter ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "parameter" a => a
#parameter (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Type'anyPointer'parameter ('Mut s)
rawGroup_ Parsed Type'anyPointer'parameter
arg_)
                )
        (Type'anyPointer'implicitMethodParameter Parsed Type'anyPointer'implicitMethodParameter
arg_) ->
            (do
                Raw Type'anyPointer'implicitMethodParameter ('Mut s)
rawGroup_ <- (forall a b (m :: * -> *) s.
(HasUnion a, RWCtx m s) =>
Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
GH.initVariant forall a. IsLabel "implicitMethodParameter" a => a
#implicitMethodParameter (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer) ('Mut s)
raw_))
                (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto Raw Type'anyPointer'implicitMethodParameter ('Mut s)
rawGroup_ Parsed Type'anyPointer'implicitMethodParameter
arg_)
                )
        (Type'anyPointer'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer) ('Mut s)
raw_))
data Type'anyPointer'unconstrained 
type instance (R.ReprFor Type'anyPointer'unconstrained) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type'anyPointer'unconstrained) where
    typeId :: Word64
typeId  = Word64
10248890354574636630
instance (C.TypedStruct Type'anyPointer'unconstrained) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type'anyPointer'unconstrained) where
    type AllocHint Type'anyPointer'unconstrained = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type'anyPointer'unconstrained
-> Message ('Mut s)
-> m (Raw Type'anyPointer'unconstrained ('Mut s))
new AllocHint Type'anyPointer'unconstrained
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type'anyPointer'unconstrained (C.Parsed Type'anyPointer'unconstrained))
instance (C.AllocateList Type'anyPointer'unconstrained) where
    type ListAllocHint Type'anyPointer'unconstrained = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type'anyPointer'unconstrained
-> Message ('Mut s)
-> m (Raw (List Type'anyPointer'unconstrained) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type'anyPointer'unconstrained (C.Parsed Type'anyPointer'unconstrained))
data instance C.Parsed Type'anyPointer'unconstrained
    = Type'anyPointer'unconstrained' 
        {Parsed Type'anyPointer'unconstrained
-> Parsed (Which Type'anyPointer'unconstrained)
union' :: (C.Parsed (GH.Which Type'anyPointer'unconstrained))}
    deriving(forall x.
Rep (Parsed Type'anyPointer'unconstrained) x
-> Parsed Type'anyPointer'unconstrained
forall x.
Parsed Type'anyPointer'unconstrained
-> Rep (Parsed Type'anyPointer'unconstrained) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed Type'anyPointer'unconstrained) x
-> Parsed Type'anyPointer'unconstrained
$cfrom :: forall x.
Parsed Type'anyPointer'unconstrained
-> Rep (Parsed Type'anyPointer'unconstrained) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type'anyPointer'unconstrained))
deriving instance (Std_.Eq (C.Parsed Type'anyPointer'unconstrained))
instance (C.Parse Type'anyPointer'unconstrained (C.Parsed Type'anyPointer'unconstrained)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type'anyPointer'unconstrained 'Const
-> m (Parsed Type'anyPointer'unconstrained)
parse Raw Type'anyPointer'unconstrained 'Const
raw_ = (Parsed (Which Type'anyPointer'unconstrained)
-> Parsed Type'anyPointer'unconstrained
Type'anyPointer'unconstrained' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Type'anyPointer'unconstrained 'Const
raw_)))
instance (C.Marshal Type'anyPointer'unconstrained (C.Parsed Type'anyPointer'unconstrained)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type'anyPointer'unconstrained ('Mut s)
-> Parsed Type'anyPointer'unconstrained -> m ()
marshalInto Raw Type'anyPointer'unconstrained ('Mut s)
raw_ Type'anyPointer'unconstrained'{Parsed (Which Type'anyPointer'unconstrained)
union' :: Parsed (Which Type'anyPointer'unconstrained)
$sel:union':Type'anyPointer'unconstrained' :: Parsed Type'anyPointer'unconstrained
-> Parsed (Which Type'anyPointer'unconstrained)
..} = (do
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Type'anyPointer'unconstrained ('Mut s)
raw_) Parsed (Which Type'anyPointer'unconstrained)
union')
        )
instance (GH.HasUnion Type'anyPointer'unconstrained) where
    unionField :: Field 'Slot Type'anyPointer'unconstrained Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
1 BitCount
16 Word64
0)
    data RawWhich Type'anyPointer'unconstrained mut_
        = RW_Type'anyPointer'unconstrained'anyKind (R.Raw () mut_)
        | RW_Type'anyPointer'unconstrained'struct (R.Raw () mut_)
        | RW_Type'anyPointer'unconstrained'list (R.Raw () mut_)
        | RW_Type'anyPointer'unconstrained'capability (R.Raw () mut_)
        | RW_Type'anyPointer'unconstrained'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16
-> Raw Type'anyPointer'unconstrained mut
-> m (RawWhich Type'anyPointer'unconstrained mut)
internalWhich Word16
tag_ Raw Type'anyPointer'unconstrained mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability).
Raw () mut_ -> RawWhich Type'anyPointer'unconstrained mut_
RW_Type'anyPointer'unconstrained'anyKind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "anyKind" a => a
#anyKind Raw Type'anyPointer'unconstrained mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability).
Raw () mut_ -> RawWhich Type'anyPointer'unconstrained mut_
RW_Type'anyPointer'unconstrained'struct forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "struct" a => a
#struct Raw Type'anyPointer'unconstrained mut
struct_))
        Word16
2 ->
            (forall (mut_ :: Mutability).
Raw () mut_ -> RawWhich Type'anyPointer'unconstrained mut_
RW_Type'anyPointer'unconstrained'list forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "list" a => a
#list Raw Type'anyPointer'unconstrained mut
struct_))
        Word16
3 ->
            (forall (mut_ :: Mutability).
Raw () mut_ -> RawWhich Type'anyPointer'unconstrained mut_
RW_Type'anyPointer'unconstrained'capability forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "capability" a => a
#capability Raw Type'anyPointer'unconstrained mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability).
Word16 -> RawWhich Type'anyPointer'unconstrained mut_
RW_Type'anyPointer'unconstrained'unknown' Word16
tag_))
    data Which Type'anyPointer'unconstrained
instance (GH.HasVariant "anyKind" GH.Slot Type'anyPointer'unconstrained ()) where
    variantByLabel :: Variant 'Slot Type'anyPointer'unconstrained ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
0)
instance (GH.HasVariant "struct" GH.Slot Type'anyPointer'unconstrained ()) where
    variantByLabel :: Variant 'Slot Type'anyPointer'unconstrained ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
1)
instance (GH.HasVariant "list" GH.Slot Type'anyPointer'unconstrained ()) where
    variantByLabel :: Variant 'Slot Type'anyPointer'unconstrained ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
2)
instance (GH.HasVariant "capability" GH.Slot Type'anyPointer'unconstrained ()) where
    variantByLabel :: Variant 'Slot Type'anyPointer'unconstrained ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
3)
data instance C.Parsed (GH.Which Type'anyPointer'unconstrained)
    = Type'anyPointer'unconstrained'anyKind 
    | Type'anyPointer'unconstrained'struct 
    | Type'anyPointer'unconstrained'list 
    | Type'anyPointer'unconstrained'capability 
    | Type'anyPointer'unconstrained'unknown' Std_.Word16
    deriving(forall x.
Rep (Parsed (Which Type'anyPointer'unconstrained)) x
-> Parsed (Which Type'anyPointer'unconstrained)
forall x.
Parsed (Which Type'anyPointer'unconstrained)
-> Rep (Parsed (Which Type'anyPointer'unconstrained)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed (Which Type'anyPointer'unconstrained)) x
-> Parsed (Which Type'anyPointer'unconstrained)
$cfrom :: forall x.
Parsed (Which Type'anyPointer'unconstrained)
-> Rep (Parsed (Which Type'anyPointer'unconstrained)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Type'anyPointer'unconstrained)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Type'anyPointer'unconstrained)))
instance (C.Parse (GH.Which Type'anyPointer'unconstrained) (C.Parsed (GH.Which Type'anyPointer'unconstrained))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Type'anyPointer'unconstrained) 'Const
-> m (Parsed (Which Type'anyPointer'unconstrained))
parse Raw (Which Type'anyPointer'unconstrained) 'Const
raw_ = (do
        RawWhich Type'anyPointer'unconstrained 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Type'anyPointer'unconstrained) 'Const
raw_)
        case RawWhich Type'anyPointer'unconstrained 'Const
rawWhich_ of
            (RW_Type'anyPointer'unconstrained'anyKind Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type'anyPointer'unconstrained)
Type'anyPointer'unconstrained'anyKind)
            (RW_Type'anyPointer'unconstrained'struct Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type'anyPointer'unconstrained)
Type'anyPointer'unconstrained'struct)
            (RW_Type'anyPointer'unconstrained'list Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type'anyPointer'unconstrained)
Type'anyPointer'unconstrained'list)
            (RW_Type'anyPointer'unconstrained'capability Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Type'anyPointer'unconstrained)
Type'anyPointer'unconstrained'capability)
            (RW_Type'anyPointer'unconstrained'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Type'anyPointer'unconstrained)
Type'anyPointer'unconstrained'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Type'anyPointer'unconstrained) (C.Parsed (GH.Which Type'anyPointer'unconstrained))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Type'anyPointer'unconstrained) ('Mut s)
-> Parsed (Which Type'anyPointer'unconstrained) -> m ()
marshalInto Raw (Which Type'anyPointer'unconstrained) ('Mut s)
raw_ Parsed (Which Type'anyPointer'unconstrained)
parsed_ = case Parsed (Which Type'anyPointer'unconstrained)
parsed_ of
        (Parsed (Which Type'anyPointer'unconstrained)
R:ParsedWhich7
Type'anyPointer'unconstrained'anyKind) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "anyKind" a => a
#anyKind () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer'unconstrained) ('Mut s)
raw_))
        (Parsed (Which Type'anyPointer'unconstrained)
R:ParsedWhich7
Type'anyPointer'unconstrained'struct) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "struct" a => a
#struct () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer'unconstrained) ('Mut s)
raw_))
        (Parsed (Which Type'anyPointer'unconstrained)
R:ParsedWhich7
Type'anyPointer'unconstrained'list) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "list" a => a
#list () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer'unconstrained) ('Mut s)
raw_))
        (Parsed (Which Type'anyPointer'unconstrained)
R:ParsedWhich7
Type'anyPointer'unconstrained'capability) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "capability" a => a
#capability () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer'unconstrained) ('Mut s)
raw_))
        (Type'anyPointer'unconstrained'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Type'anyPointer'unconstrained) ('Mut s)
raw_))
data Type'anyPointer'parameter 
type instance (R.ReprFor Type'anyPointer'parameter) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type'anyPointer'parameter) where
    typeId :: Word64
typeId  = Word64
11372142272178113157
instance (C.TypedStruct Type'anyPointer'parameter) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type'anyPointer'parameter) where
    type AllocHint Type'anyPointer'parameter = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type'anyPointer'parameter
-> Message ('Mut s) -> m (Raw Type'anyPointer'parameter ('Mut s))
new AllocHint Type'anyPointer'parameter
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type'anyPointer'parameter (C.Parsed Type'anyPointer'parameter))
instance (C.AllocateList Type'anyPointer'parameter) where
    type ListAllocHint Type'anyPointer'parameter = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type'anyPointer'parameter
-> Message ('Mut s)
-> m (Raw (List Type'anyPointer'parameter) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type'anyPointer'parameter (C.Parsed Type'anyPointer'parameter))
data instance C.Parsed Type'anyPointer'parameter
    = Type'anyPointer'parameter' 
        {Parsed Type'anyPointer'parameter -> Parsed Word64
scopeId :: (RP.Parsed Std_.Word64)
        ,Parsed Type'anyPointer'parameter -> Parsed Word16
parameterIndex :: (RP.Parsed Std_.Word16)}
    deriving(forall x.
Rep (Parsed Type'anyPointer'parameter) x
-> Parsed Type'anyPointer'parameter
forall x.
Parsed Type'anyPointer'parameter
-> Rep (Parsed Type'anyPointer'parameter) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed Type'anyPointer'parameter) x
-> Parsed Type'anyPointer'parameter
$cfrom :: forall x.
Parsed Type'anyPointer'parameter
-> Rep (Parsed Type'anyPointer'parameter) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type'anyPointer'parameter))
deriving instance (Std_.Eq (C.Parsed Type'anyPointer'parameter))
instance (C.Parse Type'anyPointer'parameter (C.Parsed Type'anyPointer'parameter)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type'anyPointer'parameter 'Const
-> m (Parsed Type'anyPointer'parameter)
parse Raw Type'anyPointer'parameter 'Const
raw_ = (Parsed Word64 -> Parsed Word16 -> Parsed Type'anyPointer'parameter
Type'anyPointer'parameter' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "scopeId" a => a
#scopeId Raw Type'anyPointer'parameter 'Const
raw_)
                                             forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "parameterIndex" a => a
#parameterIndex Raw Type'anyPointer'parameter 'Const
raw_))
instance (C.Marshal Type'anyPointer'parameter (C.Parsed Type'anyPointer'parameter)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type'anyPointer'parameter ('Mut s)
-> Parsed Type'anyPointer'parameter -> m ()
marshalInto Raw Type'anyPointer'parameter ('Mut s)
raw_ Type'anyPointer'parameter'{Parsed Word16
Parsed Word64
parameterIndex :: Parsed Word16
scopeId :: Parsed Word64
$sel:parameterIndex:Type'anyPointer'parameter' :: Parsed Type'anyPointer'parameter -> Parsed Word16
$sel:scopeId:Type'anyPointer'parameter' :: Parsed Type'anyPointer'parameter -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "scopeId" a => a
#scopeId Parsed Word64
scopeId Raw Type'anyPointer'parameter ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "parameterIndex" a => a
#parameterIndex Parsed Word16
parameterIndex Raw Type'anyPointer'parameter ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "scopeId" GH.Slot Type'anyPointer'parameter Std_.Word64) where
    fieldByLabel :: Field 'Slot Type'anyPointer'parameter Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
2 BitCount
64 Word64
0)
instance (GH.HasField "parameterIndex" GH.Slot Type'anyPointer'parameter Std_.Word16) where
    fieldByLabel :: Field 'Slot Type'anyPointer'parameter Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
1 BitCount
16 Word64
0)
data Type'anyPointer'implicitMethodParameter 
type instance (R.ReprFor Type'anyPointer'implicitMethodParameter) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Type'anyPointer'implicitMethodParameter) where
    typeId :: Word64
typeId  = Word64
13470206089842057844
instance (C.TypedStruct Type'anyPointer'implicitMethodParameter) where
    numStructWords :: Word16
numStructWords  = Word16
3
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Type'anyPointer'implicitMethodParameter) where
    type AllocHint Type'anyPointer'implicitMethodParameter = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Type'anyPointer'implicitMethodParameter
-> Message ('Mut s)
-> m (Raw Type'anyPointer'implicitMethodParameter ('Mut s))
new AllocHint Type'anyPointer'implicitMethodParameter
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Type'anyPointer'implicitMethodParameter (C.Parsed Type'anyPointer'implicitMethodParameter))
instance (C.AllocateList Type'anyPointer'implicitMethodParameter) where
    type ListAllocHint Type'anyPointer'implicitMethodParameter = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Type'anyPointer'implicitMethodParameter
-> Message ('Mut s)
-> m (Raw (List Type'anyPointer'implicitMethodParameter) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Type'anyPointer'implicitMethodParameter (C.Parsed Type'anyPointer'implicitMethodParameter))
data instance C.Parsed Type'anyPointer'implicitMethodParameter
    = Type'anyPointer'implicitMethodParameter' 
        {Parsed Type'anyPointer'implicitMethodParameter -> Parsed Word16
parameterIndex :: (RP.Parsed Std_.Word16)}
    deriving(forall x.
Rep (Parsed Type'anyPointer'implicitMethodParameter) x
-> Parsed Type'anyPointer'implicitMethodParameter
forall x.
Parsed Type'anyPointer'implicitMethodParameter
-> Rep (Parsed Type'anyPointer'implicitMethodParameter) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed Type'anyPointer'implicitMethodParameter) x
-> Parsed Type'anyPointer'implicitMethodParameter
$cfrom :: forall x.
Parsed Type'anyPointer'implicitMethodParameter
-> Rep (Parsed Type'anyPointer'implicitMethodParameter) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Type'anyPointer'implicitMethodParameter))
deriving instance (Std_.Eq (C.Parsed Type'anyPointer'implicitMethodParameter))
instance (C.Parse Type'anyPointer'implicitMethodParameter (C.Parsed Type'anyPointer'implicitMethodParameter)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Type'anyPointer'implicitMethodParameter 'Const
-> m (Parsed Type'anyPointer'implicitMethodParameter)
parse Raw Type'anyPointer'implicitMethodParameter 'Const
raw_ = (Parsed Word16 -> Parsed Type'anyPointer'implicitMethodParameter
Type'anyPointer'implicitMethodParameter' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "parameterIndex" a => a
#parameterIndex Raw Type'anyPointer'implicitMethodParameter 'Const
raw_))
instance (C.Marshal Type'anyPointer'implicitMethodParameter (C.Parsed Type'anyPointer'implicitMethodParameter)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Type'anyPointer'implicitMethodParameter ('Mut s)
-> Parsed Type'anyPointer'implicitMethodParameter -> m ()
marshalInto Raw Type'anyPointer'implicitMethodParameter ('Mut s)
raw_ Type'anyPointer'implicitMethodParameter'{Parsed Word16
parameterIndex :: Parsed Word16
$sel:parameterIndex:Type'anyPointer'implicitMethodParameter' :: Parsed Type'anyPointer'implicitMethodParameter -> Parsed Word16
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "parameterIndex" a => a
#parameterIndex Parsed Word16
parameterIndex Raw Type'anyPointer'implicitMethodParameter ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "parameterIndex" GH.Slot Type'anyPointer'implicitMethodParameter Std_.Word16) where
    fieldByLabel :: Field 'Slot Type'anyPointer'implicitMethodParameter Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
1 BitCount
16 Word64
0)
data Brand 
type instance (R.ReprFor Brand) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Brand) where
    typeId :: Word64
typeId  = Word64
10391024731148337707
instance (C.TypedStruct Brand) where
    numStructWords :: Word16
numStructWords  = Word16
0
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Brand) where
    type AllocHint Brand = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Brand -> Message ('Mut s) -> m (Raw Brand ('Mut s))
new AllocHint Brand
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Brand (C.Parsed Brand))
instance (C.AllocateList Brand) where
    type ListAllocHint Brand = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Brand
-> Message ('Mut s) -> m (Raw (List Brand) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Brand (C.Parsed Brand))
data instance C.Parsed Brand
    = Brand 
        {Parsed Brand -> Parsed (List Brand'Scope)
scopes :: (RP.Parsed (R.List Brand'Scope))}
    deriving(forall x. Rep (Parsed Brand) x -> Parsed Brand
forall x. Parsed Brand -> Rep (Parsed Brand) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Brand) x -> Parsed Brand
$cfrom :: forall x. Parsed Brand -> Rep (Parsed Brand) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Brand))
deriving instance (Std_.Eq (C.Parsed Brand))
instance (C.Parse Brand (C.Parsed Brand)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Brand 'Const -> m (Parsed Brand)
parse Raw Brand 'Const
raw_ = (Parsed (List Brand'Scope) -> Parsed Brand
Brand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "scopes" a => a
#scopes Raw Brand 'Const
raw_))
instance (C.Marshal Brand (C.Parsed Brand)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Brand ('Mut s) -> Parsed Brand -> m ()
marshalInto Raw Brand ('Mut s)
raw_ Brand{Parsed (List Brand'Scope)
scopes :: Parsed (List Brand'Scope)
$sel:scopes:Brand :: Parsed Brand -> Parsed (List Brand'Scope)
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "scopes" a => a
#scopes Parsed (List Brand'Scope)
scopes Raw Brand ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "scopes" GH.Slot Brand (R.List Brand'Scope)) where
    fieldByLabel :: Field 'Slot Brand (List Brand'Scope)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
data Brand'Scope 
type instance (R.ReprFor Brand'Scope) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Brand'Scope) where
    typeId :: Word64
typeId  = Word64
12382423449155627977
instance (C.TypedStruct Brand'Scope) where
    numStructWords :: Word16
numStructWords  = Word16
2
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Brand'Scope) where
    type AllocHint Brand'Scope = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Brand'Scope
-> Message ('Mut s) -> m (Raw Brand'Scope ('Mut s))
new AllocHint Brand'Scope
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Brand'Scope (C.Parsed Brand'Scope))
instance (C.AllocateList Brand'Scope) where
    type ListAllocHint Brand'Scope = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Brand'Scope
-> Message ('Mut s) -> m (Raw (List Brand'Scope) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Brand'Scope (C.Parsed Brand'Scope))
data instance C.Parsed Brand'Scope
    = Brand'Scope 
        {Parsed Brand'Scope -> Parsed Word64
scopeId :: (RP.Parsed Std_.Word64)
        ,Parsed Brand'Scope -> Parsed (Which Brand'Scope)
union' :: (C.Parsed (GH.Which Brand'Scope))}
    deriving(forall x. Rep (Parsed Brand'Scope) x -> Parsed Brand'Scope
forall x. Parsed Brand'Scope -> Rep (Parsed Brand'Scope) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Brand'Scope) x -> Parsed Brand'Scope
$cfrom :: forall x. Parsed Brand'Scope -> Rep (Parsed Brand'Scope) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Brand'Scope))
deriving instance (Std_.Eq (C.Parsed Brand'Scope))
instance (C.Parse Brand'Scope (C.Parsed Brand'Scope)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Brand'Scope 'Const -> m (Parsed Brand'Scope)
parse Raw Brand'Scope 'Const
raw_ = (Parsed Word64 -> Parsed (Which Brand'Scope) -> Parsed Brand'Scope
Brand'Scope forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "scopeId" a => a
#scopeId Raw Brand'Scope 'Const
raw_)
                              forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Brand'Scope 'Const
raw_)))
instance (C.Marshal Brand'Scope (C.Parsed Brand'Scope)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Brand'Scope ('Mut s) -> Parsed Brand'Scope -> m ()
marshalInto Raw Brand'Scope ('Mut s)
raw_ Brand'Scope{Parsed (Which Brand'Scope)
Parsed Word64
union' :: Parsed (Which Brand'Scope)
scopeId :: Parsed Word64
$sel:union':Brand'Scope :: Parsed Brand'Scope -> Parsed (Which Brand'Scope)
$sel:scopeId:Brand'Scope :: Parsed Brand'Scope -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "scopeId" a => a
#scopeId Parsed Word64
scopeId Raw Brand'Scope ('Mut s)
raw_)
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Brand'Scope ('Mut s)
raw_) Parsed (Which Brand'Scope)
union')
        )
instance (GH.HasUnion Brand'Scope) where
    unionField :: Field 'Slot Brand'Scope Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
16 Word64
0)
    data RawWhich Brand'Scope mut_
        = RW_Brand'Scope'bind (R.Raw (R.List Brand'Binding) mut_)
        | RW_Brand'Scope'inherit (R.Raw () mut_)
        | RW_Brand'Scope'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16 -> Raw Brand'Scope mut -> m (RawWhich Brand'Scope mut)
internalWhich Word16
tag_ Raw Brand'Scope mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability).
Raw (List Brand'Binding) mut_ -> RawWhich Brand'Scope mut_
RW_Brand'Scope'bind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "bind" a => a
#bind Raw Brand'Scope mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability).
Raw () mut_ -> RawWhich Brand'Scope mut_
RW_Brand'Scope'inherit forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "inherit" a => a
#inherit Raw Brand'Scope mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability). Word16 -> RawWhich Brand'Scope mut_
RW_Brand'Scope'unknown' Word16
tag_))
    data Which Brand'Scope
instance (GH.HasVariant "bind" GH.Slot Brand'Scope (R.List Brand'Binding)) where
    variantByLabel :: Variant 'Slot Brand'Scope (List Brand'Binding)
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0) Word16
0)
instance (GH.HasVariant "inherit" GH.Slot Brand'Scope ()) where
    variantByLabel :: Variant 'Slot Brand'Scope ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
1)
data instance C.Parsed (GH.Which Brand'Scope)
    = Brand'Scope'bind (RP.Parsed (R.List Brand'Binding))
    | Brand'Scope'inherit 
    | Brand'Scope'unknown' Std_.Word16
    deriving(forall x.
Rep (Parsed (Which Brand'Scope)) x -> Parsed (Which Brand'Scope)
forall x.
Parsed (Which Brand'Scope) -> Rep (Parsed (Which Brand'Scope)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed (Which Brand'Scope)) x -> Parsed (Which Brand'Scope)
$cfrom :: forall x.
Parsed (Which Brand'Scope) -> Rep (Parsed (Which Brand'Scope)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Brand'Scope)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Brand'Scope)))
instance (C.Parse (GH.Which Brand'Scope) (C.Parsed (GH.Which Brand'Scope))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Brand'Scope) 'Const -> m (Parsed (Which Brand'Scope))
parse Raw (Which Brand'Scope) 'Const
raw_ = (do
        RawWhich Brand'Scope 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Brand'Scope) 'Const
raw_)
        case RawWhich Brand'Scope 'Const
rawWhich_ of
            (RW_Brand'Scope'bind Raw (List Brand'Binding) 'Const
rawArg_) ->
                (Parsed (List Brand'Binding) -> Parsed (Which Brand'Scope)
Brand'Scope'bind forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw (List Brand'Binding) 'Const
rawArg_))
            (RW_Brand'Scope'inherit Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Brand'Scope)
Brand'Scope'inherit)
            (RW_Brand'Scope'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Brand'Scope)
Brand'Scope'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Brand'Scope) (C.Parsed (GH.Which Brand'Scope))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Brand'Scope) ('Mut s)
-> Parsed (Which Brand'Scope) -> m ()
marshalInto Raw (Which Brand'Scope) ('Mut s)
raw_ Parsed (Which Brand'Scope)
parsed_ = case Parsed (Which Brand'Scope)
parsed_ of
        (Brand'Scope'bind Parsed (List Brand'Binding)
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "bind" a => a
#bind Parsed (List Brand'Binding)
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Brand'Scope) ('Mut s)
raw_))
        (Parsed (Which Brand'Scope)
R:ParsedWhich13
Brand'Scope'inherit) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "inherit" a => a
#inherit () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Brand'Scope) ('Mut s)
raw_))
        (Brand'Scope'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Brand'Scope) ('Mut s)
raw_))
instance (GH.HasField "scopeId" GH.Slot Brand'Scope Std_.Word64) where
    fieldByLabel :: Field 'Slot Brand'Scope Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
64 Word64
0)
data Brand'Binding 
type instance (R.ReprFor Brand'Binding) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Brand'Binding) where
    typeId :: Word64
typeId  = Word64
14439610327179913212
instance (C.TypedStruct Brand'Binding) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Brand'Binding) where
    type AllocHint Brand'Binding = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Brand'Binding
-> Message ('Mut s) -> m (Raw Brand'Binding ('Mut s))
new AllocHint Brand'Binding
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Brand'Binding (C.Parsed Brand'Binding))
instance (C.AllocateList Brand'Binding) where
    type ListAllocHint Brand'Binding = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Brand'Binding
-> Message ('Mut s) -> m (Raw (List Brand'Binding) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Brand'Binding (C.Parsed Brand'Binding))
data instance C.Parsed Brand'Binding
    = Brand'Binding 
        {Parsed Brand'Binding -> Parsed (Which Brand'Binding)
union' :: (C.Parsed (GH.Which Brand'Binding))}
    deriving(forall x. Rep (Parsed Brand'Binding) x -> Parsed Brand'Binding
forall x. Parsed Brand'Binding -> Rep (Parsed Brand'Binding) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Brand'Binding) x -> Parsed Brand'Binding
$cfrom :: forall x. Parsed Brand'Binding -> Rep (Parsed Brand'Binding) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Brand'Binding))
deriving instance (Std_.Eq (C.Parsed Brand'Binding))
instance (C.Parse Brand'Binding (C.Parsed Brand'Binding)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Brand'Binding 'Const -> m (Parsed Brand'Binding)
parse Raw Brand'Binding 'Const
raw_ = (Parsed (Which Brand'Binding) -> Parsed Brand'Binding
Brand'Binding forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Brand'Binding 'Const
raw_)))
instance (C.Marshal Brand'Binding (C.Parsed Brand'Binding)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Brand'Binding ('Mut s) -> Parsed Brand'Binding -> m ()
marshalInto Raw Brand'Binding ('Mut s)
raw_ Brand'Binding{Parsed (Which Brand'Binding)
union' :: Parsed (Which Brand'Binding)
$sel:union':Brand'Binding :: Parsed Brand'Binding -> Parsed (Which Brand'Binding)
..} = (do
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Brand'Binding ('Mut s)
raw_) Parsed (Which Brand'Binding)
union')
        )
instance (GH.HasUnion Brand'Binding) where
    unionField :: Field 'Slot Brand'Binding Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
16 Word64
0)
    data RawWhich Brand'Binding mut_
        = RW_Brand'Binding'unbound (R.Raw () mut_)
        | RW_Brand'Binding'type_ (R.Raw Type mut_)
        | RW_Brand'Binding'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16 -> Raw Brand'Binding mut -> m (RawWhich Brand'Binding mut)
internalWhich Word16
tag_ Raw Brand'Binding mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability).
Raw () mut_ -> RawWhich Brand'Binding mut_
RW_Brand'Binding'unbound forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "unbound" a => a
#unbound Raw Brand'Binding mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability).
Raw Type mut_ -> RawWhich Brand'Binding mut_
RW_Brand'Binding'type_ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "type_" a => a
#type_ Raw Brand'Binding mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability). Word16 -> RawWhich Brand'Binding mut_
RW_Brand'Binding'unknown' Word16
tag_))
    data Which Brand'Binding
instance (GH.HasVariant "unbound" GH.Slot Brand'Binding ()) where
    variantByLabel :: Variant 'Slot Brand'Binding ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
0)
instance (GH.HasVariant "type_" GH.Slot Brand'Binding Type) where
    variantByLabel :: Variant 'Slot Brand'Binding Type
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0) Word16
1)
data instance C.Parsed (GH.Which Brand'Binding)
    = Brand'Binding'unbound 
    | Brand'Binding'type_ (RP.Parsed Type)
    | Brand'Binding'unknown' Std_.Word16
    deriving(forall x.
Rep (Parsed (Which Brand'Binding)) x
-> Parsed (Which Brand'Binding)
forall x.
Parsed (Which Brand'Binding)
-> Rep (Parsed (Which Brand'Binding)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed (Which Brand'Binding)) x
-> Parsed (Which Brand'Binding)
$cfrom :: forall x.
Parsed (Which Brand'Binding)
-> Rep (Parsed (Which Brand'Binding)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Brand'Binding)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Brand'Binding)))
instance (C.Parse (GH.Which Brand'Binding) (C.Parsed (GH.Which Brand'Binding))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Brand'Binding) 'Const
-> m (Parsed (Which Brand'Binding))
parse Raw (Which Brand'Binding) 'Const
raw_ = (do
        RawWhich Brand'Binding 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Brand'Binding) 'Const
raw_)
        case RawWhich Brand'Binding 'Const
rawWhich_ of
            (RW_Brand'Binding'unbound Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Brand'Binding)
Brand'Binding'unbound)
            (RW_Brand'Binding'type_ Raw Type 'Const
rawArg_) ->
                (Parsed Type -> Parsed (Which Brand'Binding)
Brand'Binding'type_ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Type 'Const
rawArg_))
            (RW_Brand'Binding'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Brand'Binding)
Brand'Binding'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Brand'Binding) (C.Parsed (GH.Which Brand'Binding))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Brand'Binding) ('Mut s)
-> Parsed (Which Brand'Binding) -> m ()
marshalInto Raw (Which Brand'Binding) ('Mut s)
raw_ Parsed (Which Brand'Binding)
parsed_ = case Parsed (Which Brand'Binding)
parsed_ of
        (Parsed (Which Brand'Binding)
R:ParsedWhich11
Brand'Binding'unbound) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "unbound" a => a
#unbound () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Brand'Binding) ('Mut s)
raw_))
        (Brand'Binding'type_ Parsed Type
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "type_" a => a
#type_ Parsed Type
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Brand'Binding) ('Mut s)
raw_))
        (Brand'Binding'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Brand'Binding) ('Mut s)
raw_))
data Value 
type instance (R.ReprFor Value) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Value) where
    typeId :: Word64
typeId  = Word64
14853958794117909659
instance (C.TypedStruct Value) where
    numStructWords :: Word16
numStructWords  = Word16
2
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate Value) where
    type AllocHint Value = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Value -> Message ('Mut s) -> m (Raw Value ('Mut s))
new AllocHint Value
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Value (C.Parsed Value))
instance (C.AllocateList Value) where
    type ListAllocHint Value = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Value
-> Message ('Mut s) -> m (Raw (List Value) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Value (C.Parsed Value))
data instance C.Parsed Value
    = Value 
        {Parsed Value -> Parsed (Which Value)
union' :: (C.Parsed (GH.Which Value))}
    deriving(forall x. Rep (Parsed Value) x -> Parsed Value
forall x. Parsed Value -> Rep (Parsed Value) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Value) x -> Parsed Value
$cfrom :: forall x. Parsed Value -> Rep (Parsed Value) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Value))
deriving instance (Std_.Eq (C.Parsed Value))
instance (C.Parse Value (C.Parsed Value)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Value 'Const -> m (Parsed Value)
parse Raw Value 'Const
raw_ = (Parsed (Which Value) -> Parsed Value
Value forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Value 'Const
raw_)))
instance (C.Marshal Value (C.Parsed Value)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Value ('Mut s) -> Parsed Value -> m ()
marshalInto Raw Value ('Mut s)
raw_ Value{Parsed (Which Value)
union' :: Parsed (Which Value)
$sel:union':Value :: Parsed Value -> Parsed (Which Value)
..} = (do
        (forall t p (m :: * -> *) s.
(Marshal t p, RWCtx m s) =>
Raw t ('Mut s) -> p -> m ()
C.marshalInto (forall a (mut :: Mutability).
HasUnion a =>
Raw a mut -> Raw (Which a) mut
GH.structUnion Raw Value ('Mut s)
raw_) Parsed (Which Value)
union')
        )
instance (GH.HasUnion Value) where
    unionField :: Field 'Slot Value Word16
unionField  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
16 Word64
0)
    data RawWhich Value mut_
        = RW_Value'void (R.Raw () mut_)
        | RW_Value'bool (R.Raw Std_.Bool mut_)
        | RW_Value'int8 (R.Raw Std_.Int8 mut_)
        | RW_Value'int16 (R.Raw Std_.Int16 mut_)
        | RW_Value'int32 (R.Raw Std_.Int32 mut_)
        | RW_Value'int64 (R.Raw Std_.Int64 mut_)
        | RW_Value'uint8 (R.Raw Std_.Word8 mut_)
        | RW_Value'uint16 (R.Raw Std_.Word16 mut_)
        | RW_Value'uint32 (R.Raw Std_.Word32 mut_)
        | RW_Value'uint64 (R.Raw Std_.Word64 mut_)
        | RW_Value'float32 (R.Raw Std_.Float mut_)
        | RW_Value'float64 (R.Raw Std_.Double mut_)
        | RW_Value'text (R.Raw Basics.Text mut_)
        | RW_Value'data_ (R.Raw Basics.Data mut_)
        | RW_Value'list (R.Raw (Std_.Maybe Basics.AnyPointer) mut_)
        | RW_Value'enum (R.Raw Std_.Word16 mut_)
        | RW_Value'struct (R.Raw (Std_.Maybe Basics.AnyPointer) mut_)
        | RW_Value'interface (R.Raw () mut_)
        | RW_Value'anyPointer (R.Raw (Std_.Maybe Basics.AnyPointer) mut_)
        | RW_Value'unknown' Std_.Word16
    internalWhich :: forall (m :: * -> *) (mut :: Mutability).
ReadCtx m mut =>
Word16 -> Raw Value mut -> m (RawWhich Value mut)
internalWhich Word16
tag_ Raw Value mut
struct_ = case Word16
tag_ of
        Word16
0 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Value mut_
RW_Value'void forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "void" a => a
#void Raw Value mut
struct_))
        Word16
1 ->
            (forall (mut_ :: Mutability). Raw Bool mut_ -> RawWhich Value mut_
RW_Value'bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "bool" a => a
#bool Raw Value mut
struct_))
        Word16
2 ->
            (forall (mut_ :: Mutability). Raw Int8 mut_ -> RawWhich Value mut_
RW_Value'int8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "int8" a => a
#int8 Raw Value mut
struct_))
        Word16
3 ->
            (forall (mut_ :: Mutability). Raw Int16 mut_ -> RawWhich Value mut_
RW_Value'int16 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "int16" a => a
#int16 Raw Value mut
struct_))
        Word16
4 ->
            (forall (mut_ :: Mutability). Raw Int32 mut_ -> RawWhich Value mut_
RW_Value'int32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "int32" a => a
#int32 Raw Value mut
struct_))
        Word16
5 ->
            (forall (mut_ :: Mutability). Raw Int64 mut_ -> RawWhich Value mut_
RW_Value'int64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "int64" a => a
#int64 Raw Value mut
struct_))
        Word16
6 ->
            (forall (mut_ :: Mutability). Raw Word8 mut_ -> RawWhich Value mut_
RW_Value'uint8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "uint8" a => a
#uint8 Raw Value mut
struct_))
        Word16
7 ->
            (forall (mut_ :: Mutability). Raw Word16 mut_ -> RawWhich Value mut_
RW_Value'uint16 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "uint16" a => a
#uint16 Raw Value mut
struct_))
        Word16
8 ->
            (forall (mut_ :: Mutability). Raw Word32 mut_ -> RawWhich Value mut_
RW_Value'uint32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "uint32" a => a
#uint32 Raw Value mut
struct_))
        Word16
9 ->
            (forall (mut_ :: Mutability). Raw Word64 mut_ -> RawWhich Value mut_
RW_Value'uint64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "uint64" a => a
#uint64 Raw Value mut
struct_))
        Word16
10 ->
            (forall (mut_ :: Mutability). Raw Float mut_ -> RawWhich Value mut_
RW_Value'float32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "float32" a => a
#float32 Raw Value mut
struct_))
        Word16
11 ->
            (forall (mut_ :: Mutability). Raw Double mut_ -> RawWhich Value mut_
RW_Value'float64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "float64" a => a
#float64 Raw Value mut
struct_))
        Word16
12 ->
            (forall (mut_ :: Mutability). Raw Text mut_ -> RawWhich Value mut_
RW_Value'text forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "text" a => a
#text Raw Value mut
struct_))
        Word16
13 ->
            (forall (mut_ :: Mutability). Raw Data mut_ -> RawWhich Value mut_
RW_Value'data_ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "data_" a => a
#data_ Raw Value mut
struct_))
        Word16
14 ->
            (forall (mut_ :: Mutability).
Raw (Maybe AnyPointer) mut_ -> RawWhich Value mut_
RW_Value'list forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "list" a => a
#list Raw Value mut
struct_))
        Word16
15 ->
            (forall (mut_ :: Mutability). Raw Word16 mut_ -> RawWhich Value mut_
RW_Value'enum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "enum" a => a
#enum Raw Value mut
struct_))
        Word16
16 ->
            (forall (mut_ :: Mutability).
Raw (Maybe AnyPointer) mut_ -> RawWhich Value mut_
RW_Value'struct forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "struct" a => a
#struct Raw Value mut
struct_))
        Word16
17 ->
            (forall (mut_ :: Mutability). Raw () mut_ -> RawWhich Value mut_
RW_Value'interface forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "interface" a => a
#interface Raw Value mut
struct_))
        Word16
18 ->
            (forall (mut_ :: Mutability).
Raw (Maybe AnyPointer) mut_ -> RawWhich Value mut_
RW_Value'anyPointer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (k :: FieldKind) a b (mut :: Mutability) (m :: * -> *).
(IsStruct a, ReadCtx m mut) =>
Variant k a b -> Raw a mut -> m (Raw b mut)
GH.readVariant forall a. IsLabel "anyPointer" a => a
#anyPointer Raw Value mut
struct_))
        Word16
_ ->
            (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (forall (mut_ :: Mutability). Word16 -> RawWhich Value mut_
RW_Value'unknown' Word16
tag_))
    data Which Value
instance (GH.HasVariant "void" GH.Slot Value ()) where
    variantByLabel :: Variant 'Slot Value ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
0)
instance (GH.HasVariant "bool" GH.Slot Value Std_.Bool) where
    variantByLabel :: Variant 'Slot Value Bool
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
0 BitCount
1 Word64
0) Word16
1)
instance (GH.HasVariant "int8" GH.Slot Value Std_.Int8) where
    variantByLabel :: Variant 'Slot Value Int8
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
0 BitCount
8 Word64
0) Word16
2)
instance (GH.HasVariant "int16" GH.Slot Value Std_.Int16) where
    variantByLabel :: Variant 'Slot Value Int16
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
0 BitCount
16 Word64
0) Word16
3)
instance (GH.HasVariant "int32" GH.Slot Value Std_.Int32) where
    variantByLabel :: Variant 'Slot Value Int32
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
32 Word16
0 BitCount
32 Word64
0) Word16
4)
instance (GH.HasVariant "int64" GH.Slot Value Std_.Int64) where
    variantByLabel :: Variant 'Slot Value Int64
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
64 Word64
0) Word16
5)
instance (GH.HasVariant "uint8" GH.Slot Value Std_.Word8) where
    variantByLabel :: Variant 'Slot Value Word8
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
0 BitCount
8 Word64
0) Word16
6)
instance (GH.HasVariant "uint16" GH.Slot Value Std_.Word16) where
    variantByLabel :: Variant 'Slot Value Word16
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
0 BitCount
16 Word64
0) Word16
7)
instance (GH.HasVariant "uint32" GH.Slot Value Std_.Word32) where
    variantByLabel :: Variant 'Slot Value Word32
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
32 Word16
0 BitCount
32 Word64
0) Word16
8)
instance (GH.HasVariant "uint64" GH.Slot Value Std_.Word64) where
    variantByLabel :: Variant 'Slot Value Word64
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
64 Word64
0) Word16
9)
instance (GH.HasVariant "float32" GH.Slot Value Std_.Float) where
    variantByLabel :: Variant 'Slot Value Float
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
32 Word16
0 BitCount
32 Word64
0) Word16
10)
instance (GH.HasVariant "float64" GH.Slot Value Std_.Double) where
    variantByLabel :: Variant 'Slot Value Double
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
1 BitCount
64 Word64
0) Word16
11)
instance (GH.HasVariant "text" GH.Slot Value Basics.Text) where
    variantByLabel :: Variant 'Slot Value Text
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0) Word16
12)
instance (GH.HasVariant "data_" GH.Slot Value Basics.Data) where
    variantByLabel :: Variant 'Slot Value Data
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0) Word16
13)
instance (GH.HasVariant "list" GH.Slot Value (Std_.Maybe Basics.AnyPointer)) where
    variantByLabel :: Variant 'Slot Value (Maybe AnyPointer)
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0) Word16
14)
instance (GH.HasVariant "enum" GH.Slot Value Std_.Word16) where
    variantByLabel :: Variant 'Slot Value Word16
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
0 BitCount
16 Word64
0) Word16
15)
instance (GH.HasVariant "struct" GH.Slot Value (Std_.Maybe Basics.AnyPointer)) where
    variantByLabel :: Variant 'Slot Value (Maybe AnyPointer)
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0) Word16
16)
instance (GH.HasVariant "interface" GH.Slot Value ()) where
    variantByLabel :: Variant 'Slot Value ()
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant forall b a. (ReprFor b ~ 'Data 'Sz0) => Field 'Slot a b
GH.voidField Word16
17)
instance (GH.HasVariant "anyPointer" GH.Slot Value (Std_.Maybe Basics.AnyPointer)) where
    variantByLabel :: Variant 'Slot Value (Maybe AnyPointer)
variantByLabel  = (forall (k :: FieldKind) a b. Field k a b -> Word16 -> Variant k a b
GH.Variant (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0) Word16
18)
data instance C.Parsed (GH.Which Value)
    = Value'void 
    | Value'bool (RP.Parsed Std_.Bool)
    | Value'int8 (RP.Parsed Std_.Int8)
    | Value'int16 (RP.Parsed Std_.Int16)
    | Value'int32 (RP.Parsed Std_.Int32)
    | Value'int64 (RP.Parsed Std_.Int64)
    | Value'uint8 (RP.Parsed Std_.Word8)
    | Value'uint16 (RP.Parsed Std_.Word16)
    | Value'uint32 (RP.Parsed Std_.Word32)
    | Value'uint64 (RP.Parsed Std_.Word64)
    | Value'float32 (RP.Parsed Std_.Float)
    | Value'float64 (RP.Parsed Std_.Double)
    | Value'text (RP.Parsed Basics.Text)
    | Value'data_ (RP.Parsed Basics.Data)
    | Value'list (RP.Parsed (Std_.Maybe Basics.AnyPointer))
    | Value'enum (RP.Parsed Std_.Word16)
    | Value'struct (RP.Parsed (Std_.Maybe Basics.AnyPointer))
    | Value'interface 
    | Value'anyPointer (RP.Parsed (Std_.Maybe Basics.AnyPointer))
    | Value'unknown' Std_.Word16
    deriving(forall x. Rep (Parsed (Which Value)) x -> Parsed (Which Value)
forall x. Parsed (Which Value) -> Rep (Parsed (Which Value)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed (Which Value)) x -> Parsed (Which Value)
$cfrom :: forall x. Parsed (Which Value) -> Rep (Parsed (Which Value)) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed (GH.Which Value)))
deriving instance (Std_.Eq (C.Parsed (GH.Which Value)))
instance (C.Parse (GH.Which Value) (C.Parsed (GH.Which Value))) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw (Which Value) 'Const -> m (Parsed (Which Value))
parse Raw (Which Value) 'Const
raw_ = (do
        RawWhich Value 'Const
rawWhich_ <- (forall a (mut :: Mutability) (m :: * -> *).
(ReadCtx m mut, HasUnion a) =>
Raw (Which a) mut -> m (RawWhich a mut)
GH.unionWhich Raw (Which Value) 'Const
raw_)
        case RawWhich Value 'Const
rawWhich_ of
            (RW_Value'void Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Value)
Value'void)
            (RW_Value'bool Raw Bool 'Const
rawArg_) ->
                (Parsed Bool -> Parsed (Which Value)
Value'bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Bool 'Const
rawArg_))
            (RW_Value'int8 Raw Int8 'Const
rawArg_) ->
                (Parsed Int8 -> Parsed (Which Value)
Value'int8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Int8 'Const
rawArg_))
            (RW_Value'int16 Raw Int16 'Const
rawArg_) ->
                (Parsed Int16 -> Parsed (Which Value)
Value'int16 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Int16 'Const
rawArg_))
            (RW_Value'int32 Raw Int32 'Const
rawArg_) ->
                (Parsed Int32 -> Parsed (Which Value)
Value'int32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Int32 'Const
rawArg_))
            (RW_Value'int64 Raw Int64 'Const
rawArg_) ->
                (Parsed Int64 -> Parsed (Which Value)
Value'int64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Int64 'Const
rawArg_))
            (RW_Value'uint8 Raw Word8 'Const
rawArg_) ->
                (Parsed Word8 -> Parsed (Which Value)
Value'uint8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Word8 'Const
rawArg_))
            (RW_Value'uint16 Raw Word16 'Const
rawArg_) ->
                (Parsed Word16 -> Parsed (Which Value)
Value'uint16 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Word16 'Const
rawArg_))
            (RW_Value'uint32 Raw Word32 'Const
rawArg_) ->
                (Parsed Word32 -> Parsed (Which Value)
Value'uint32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Word32 'Const
rawArg_))
            (RW_Value'uint64 Raw Word64 'Const
rawArg_) ->
                (Parsed Word64 -> Parsed (Which Value)
Value'uint64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Word64 'Const
rawArg_))
            (RW_Value'float32 Raw Float 'Const
rawArg_) ->
                (Parsed Float -> Parsed (Which Value)
Value'float32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Float 'Const
rawArg_))
            (RW_Value'float64 Raw Double 'Const
rawArg_) ->
                (Parsed Double -> Parsed (Which Value)
Value'float64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Double 'Const
rawArg_))
            (RW_Value'text Raw Text 'Const
rawArg_) ->
                (Parsed Text -> Parsed (Which Value)
Value'text forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Text 'Const
rawArg_))
            (RW_Value'data_ Raw Data 'Const
rawArg_) ->
                (Parsed Data -> Parsed (Which Value)
Value'data_ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Data 'Const
rawArg_))
            (RW_Value'list Raw (Maybe AnyPointer) 'Const
rawArg_) ->
                (Parsed (Maybe AnyPointer) -> Parsed (Which Value)
Value'list forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw (Maybe AnyPointer) 'Const
rawArg_))
            (RW_Value'enum Raw Word16 'Const
rawArg_) ->
                (Parsed Word16 -> Parsed (Which Value)
Value'enum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw Word16 'Const
rawArg_))
            (RW_Value'struct Raw (Maybe AnyPointer) 'Const
rawArg_) ->
                (Parsed (Maybe AnyPointer) -> Parsed (Which Value)
Value'struct forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw (Maybe AnyPointer) 'Const
rawArg_))
            (RW_Value'interface Raw () 'Const
_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure Parsed (Which Value)
Value'interface)
            (RW_Value'anyPointer Raw (Maybe AnyPointer) 'Const
rawArg_) ->
                (Parsed (Maybe AnyPointer) -> Parsed (Which Value)
Value'anyPointer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall t p (m :: * -> *).
(Parse t p, ReadCtx m 'Const) =>
Raw t 'Const -> m p
C.parse Raw (Maybe AnyPointer) 'Const
rawArg_))
            (RW_Value'unknown' Word16
tag_) ->
                (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure (Word16 -> Parsed (Which Value)
Value'unknown' Word16
tag_))
        )
instance (C.Marshal (GH.Which Value) (C.Parsed (GH.Which Value))) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw (Which Value) ('Mut s) -> Parsed (Which Value) -> m ()
marshalInto Raw (Which Value) ('Mut s)
raw_ Parsed (Which Value)
parsed_ = case Parsed (Which Value)
parsed_ of
        (Parsed (Which Value)
R:ParsedWhich15
Value'void) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "void" a => a
#void () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'bool Parsed Bool
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "bool" a => a
#bool Parsed Bool
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'int8 Parsed Int8
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "int8" a => a
#int8 Parsed Int8
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'int16 Parsed Int16
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "int16" a => a
#int16 Parsed Int16
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'int32 Parsed Int32
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "int32" a => a
#int32 Parsed Int32
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'int64 Parsed Int64
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "int64" a => a
#int64 Parsed Int64
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'uint8 Parsed Word8
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "uint8" a => a
#uint8 Parsed Word8
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'uint16 Parsed Word16
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "uint16" a => a
#uint16 Parsed Word16
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'uint32 Parsed Word32
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "uint32" a => a
#uint32 Parsed Word32
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'uint64 Parsed Word64
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "uint64" a => a
#uint64 Parsed Word64
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'float32 Parsed Float
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "float32" a => a
#float32 Parsed Float
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'float64 Parsed Double
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "float64" a => a
#float64 Parsed Double
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'text Parsed Text
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "text" a => a
#text Parsed Text
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'data_ Parsed Data
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "data_" a => a
#data_ Parsed Data
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'list Parsed (Maybe AnyPointer)
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "list" a => a
#list Parsed (Maybe AnyPointer)
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'enum Parsed Word16
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "enum" a => a
#enum Parsed Word16
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'struct Parsed (Maybe AnyPointer)
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "struct" a => a
#struct Parsed (Maybe AnyPointer)
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Parsed (Which Value)
R:ParsedWhich15
Value'interface) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "interface" a => a
#interface () (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'anyPointer Parsed (Maybe AnyPointer)
arg_) ->
            (forall a b (m :: * -> *) s bp.
(HasUnion a, Parse b bp, RWCtx m s) =>
Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeVariant forall a. IsLabel "anyPointer" a => a
#anyPointer Parsed (Maybe AnyPointer)
arg_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
        (Value'unknown' Word16
tag_) ->
            (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. HasUnion a => Field 'Slot a Word16
GH.unionField Word16
tag_ (forall a (mut :: Mutability).
HasUnion a =>
Raw (Which a) mut -> Raw a mut
GH.unionStruct Raw (Which Value) ('Mut s)
raw_))
data Annotation 
type instance (R.ReprFor Annotation) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId Annotation) where
    typeId :: Word64
typeId  = Word64
17422339044421236034
instance (C.TypedStruct Annotation) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
2
instance (C.Allocate Annotation) where
    type AllocHint Annotation = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint Annotation
-> Message ('Mut s) -> m (Raw Annotation ('Mut s))
new AllocHint Annotation
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc Annotation (C.Parsed Annotation))
instance (C.AllocateList Annotation) where
    type ListAllocHint Annotation = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint Annotation
-> Message ('Mut s) -> m (Raw (List Annotation) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc Annotation (C.Parsed Annotation))
data instance C.Parsed Annotation
    = Annotation 
        {Parsed Annotation -> Parsed Word64
id :: (RP.Parsed Std_.Word64)
        ,Parsed Annotation -> Parsed Value
value :: (RP.Parsed Value)
        ,Parsed Annotation -> Parsed Brand
brand :: (RP.Parsed Brand)}
    deriving(forall x. Rep (Parsed Annotation) x -> Parsed Annotation
forall x. Parsed Annotation -> Rep (Parsed Annotation) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed Annotation) x -> Parsed Annotation
$cfrom :: forall x. Parsed Annotation -> Rep (Parsed Annotation) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed Annotation))
deriving instance (Std_.Eq (C.Parsed Annotation))
instance (C.Parse Annotation (C.Parsed Annotation)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw Annotation 'Const -> m (Parsed Annotation)
parse Raw Annotation 'Const
raw_ = (Parsed Word64 -> Parsed Value -> Parsed Brand -> Parsed Annotation
Annotation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "id" a => a
#id Raw Annotation 'Const
raw_)
                             forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "value" a => a
#value Raw Annotation 'Const
raw_)
                             forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "brand" a => a
#brand Raw Annotation 'Const
raw_))
instance (C.Marshal Annotation (C.Parsed Annotation)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw Annotation ('Mut s) -> Parsed Annotation -> m ()
marshalInto Raw Annotation ('Mut s)
raw_ Annotation{Parsed Word64
Parsed Value
Parsed Brand
brand :: Parsed Brand
value :: Parsed Value
id :: Parsed Word64
$sel:brand:Annotation :: Parsed Annotation -> Parsed Brand
$sel:value:Annotation :: Parsed Annotation -> Parsed Value
$sel:id:Annotation :: Parsed Annotation -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "id" a => a
#id Parsed Word64
id Raw Annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "value" a => a
#value Parsed Value
value Raw Annotation ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "brand" a => a
#brand Parsed Brand
brand Raw Annotation ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "id" GH.Slot Annotation Std_.Word64) where
    fieldByLabel :: Field 'Slot Annotation Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
64 Word64
0)
instance (GH.HasField "value" GH.Slot Annotation Value) where
    fieldByLabel :: Field 'Slot Annotation Value
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "brand" GH.Slot Annotation Brand) where
    fieldByLabel :: Field 'Slot Annotation Brand
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
1)
data ElementSize 
    = ElementSize'empty 
    | ElementSize'bit 
    | ElementSize'byte 
    | ElementSize'twoBytes 
    | ElementSize'fourBytes 
    | ElementSize'eightBytes 
    | ElementSize'pointer 
    | ElementSize'inlineComposite 
    | ElementSize'unknown' Std_.Word16
    deriving(ElementSize -> ElementSize -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementSize -> ElementSize -> Bool
$c/= :: ElementSize -> ElementSize -> Bool
== :: ElementSize -> ElementSize -> Bool
$c== :: ElementSize -> ElementSize -> Bool
Std_.Eq
            ,Int -> ElementSize -> ShowS
[ElementSize] -> ShowS
ElementSize -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ElementSize] -> ShowS
$cshowList :: [ElementSize] -> ShowS
show :: ElementSize -> String
$cshow :: ElementSize -> String
showsPrec :: Int -> ElementSize -> ShowS
$cshowsPrec :: Int -> ElementSize -> ShowS
Std_.Show
            ,forall x. Rep ElementSize x -> ElementSize
forall x. ElementSize -> Rep ElementSize x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ElementSize x -> ElementSize
$cfrom :: forall x. ElementSize -> Rep ElementSize x
Generics.Generic)
type instance (R.ReprFor ElementSize) = (R.Data R.Sz16)
instance (C.HasTypeId ElementSize) where
    typeId :: Word64
typeId  = Word64
15102134695616452902
instance (Std_.Enum ElementSize) where
    toEnum :: Int -> ElementSize
toEnum Int
n_ = case Int
n_ of
        Int
0 ->
            ElementSize
ElementSize'empty
        Int
1 ->
            ElementSize
ElementSize'bit
        Int
2 ->
            ElementSize
ElementSize'byte
        Int
3 ->
            ElementSize
ElementSize'twoBytes
        Int
4 ->
            ElementSize
ElementSize'fourBytes
        Int
5 ->
            ElementSize
ElementSize'eightBytes
        Int
6 ->
            ElementSize
ElementSize'pointer
        Int
7 ->
            ElementSize
ElementSize'inlineComposite
        Int
tag_ ->
            (Word16 -> ElementSize
ElementSize'unknown' (forall a b. (Integral a, Num b) => a -> b
Std_.fromIntegral Int
tag_))
    fromEnum :: ElementSize -> Int
fromEnum ElementSize
value_ = case ElementSize
value_ of
        (ElementSize
ElementSize'empty) ->
            Int
0
        (ElementSize
ElementSize'bit) ->
            Int
1
        (ElementSize
ElementSize'byte) ->
            Int
2
        (ElementSize
ElementSize'twoBytes) ->
            Int
3
        (ElementSize
ElementSize'fourBytes) ->
            Int
4
        (ElementSize
ElementSize'eightBytes) ->
            Int
5
        (ElementSize
ElementSize'pointer) ->
            Int
6
        (ElementSize
ElementSize'inlineComposite) ->
            Int
7
        (ElementSize'unknown' Word16
tag_) ->
            (forall a b. (Integral a, Num b) => a -> b
Std_.fromIntegral Word16
tag_)
instance (C.IsWord ElementSize) where
    fromWord :: Word64 -> ElementSize
fromWord Word64
w_ = (forall a. Enum a => Int -> a
Std_.toEnum (forall a b. (Integral a, Num b) => a -> b
Std_.fromIntegral Word64
w_))
    toWord :: ElementSize -> Word64
toWord ElementSize
v_ = (forall a b. (Integral a, Num b) => a -> b
Std_.fromIntegral (forall a. Enum a => a -> Int
Std_.fromEnum ElementSize
v_))
instance (C.Parse ElementSize ElementSize) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw ElementSize 'Const -> m ElementSize
parse  = forall a (m :: * -> *).
(ReprFor a ~ 'Data 'Sz16, Enum a, Applicative m) =>
Raw a 'Const -> m a
GH.parseEnum
    encode :: forall (m :: * -> *) s.
RWCtx m s =>
Message ('Mut s) -> ElementSize -> m (Raw ElementSize ('Mut s))
encode  = forall a (m :: * -> *) s.
(ReprFor a ~ 'Data 'Sz16, Enum a, RWCtx m s) =>
Message ('Mut s) -> a -> m (Raw a ('Mut s))
GH.encodeEnum
instance (C.AllocateList ElementSize) where
    type ListAllocHint ElementSize = Std_.Int
instance (C.EstimateListAlloc ElementSize ElementSize)
data CapnpVersion 
type instance (R.ReprFor CapnpVersion) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId CapnpVersion) where
    typeId :: Word64
typeId  = Word64
15590670654532458851
instance (C.TypedStruct CapnpVersion) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
0
instance (C.Allocate CapnpVersion) where
    type AllocHint CapnpVersion = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint CapnpVersion
-> Message ('Mut s) -> m (Raw CapnpVersion ('Mut s))
new AllocHint CapnpVersion
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc CapnpVersion (C.Parsed CapnpVersion))
instance (C.AllocateList CapnpVersion) where
    type ListAllocHint CapnpVersion = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint CapnpVersion
-> Message ('Mut s) -> m (Raw (List CapnpVersion) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc CapnpVersion (C.Parsed CapnpVersion))
data instance C.Parsed CapnpVersion
    = CapnpVersion 
        {Parsed CapnpVersion -> Parsed Word16
major :: (RP.Parsed Std_.Word16)
        ,Parsed CapnpVersion -> Parsed Word8
minor :: (RP.Parsed Std_.Word8)
        ,Parsed CapnpVersion -> Parsed Word8
micro :: (RP.Parsed Std_.Word8)}
    deriving(forall x. Rep (Parsed CapnpVersion) x -> Parsed CapnpVersion
forall x. Parsed CapnpVersion -> Rep (Parsed CapnpVersion) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Parsed CapnpVersion) x -> Parsed CapnpVersion
$cfrom :: forall x. Parsed CapnpVersion -> Rep (Parsed CapnpVersion) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed CapnpVersion))
deriving instance (Std_.Eq (C.Parsed CapnpVersion))
instance (C.Parse CapnpVersion (C.Parsed CapnpVersion)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw CapnpVersion 'Const -> m (Parsed CapnpVersion)
parse Raw CapnpVersion 'Const
raw_ = (Parsed Word16
-> Parsed Word8 -> Parsed Word8 -> Parsed CapnpVersion
CapnpVersion forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "major" a => a
#major Raw CapnpVersion 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "minor" a => a
#minor Raw CapnpVersion 'Const
raw_)
                               forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "micro" a => a
#micro Raw CapnpVersion 'Const
raw_))
instance (C.Marshal CapnpVersion (C.Parsed CapnpVersion)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw CapnpVersion ('Mut s) -> Parsed CapnpVersion -> m ()
marshalInto Raw CapnpVersion ('Mut s)
raw_ CapnpVersion{Parsed Word8
Parsed Word16
micro :: Parsed Word8
minor :: Parsed Word8
major :: Parsed Word16
$sel:micro:CapnpVersion :: Parsed CapnpVersion -> Parsed Word8
$sel:minor:CapnpVersion :: Parsed CapnpVersion -> Parsed Word8
$sel:major:CapnpVersion :: Parsed CapnpVersion -> Parsed Word16
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "major" a => a
#major Parsed Word16
major Raw CapnpVersion ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "minor" a => a
#minor Parsed Word8
minor Raw CapnpVersion ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "micro" a => a
#micro Parsed Word8
micro Raw CapnpVersion ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "major" GH.Slot CapnpVersion Std_.Word16) where
    fieldByLabel :: Field 'Slot CapnpVersion Word16
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
16 Word64
0)
instance (GH.HasField "minor" GH.Slot CapnpVersion Std_.Word8) where
    fieldByLabel :: Field 'Slot CapnpVersion Word8
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
16 Word16
0 BitCount
8 Word64
0)
instance (GH.HasField "micro" GH.Slot CapnpVersion Std_.Word8) where
    fieldByLabel :: Field 'Slot CapnpVersion Word8
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
24 Word16
0 BitCount
8 Word64
0)
data CodeGeneratorRequest 
type instance (R.ReprFor CodeGeneratorRequest) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId CodeGeneratorRequest) where
    typeId :: Word64
typeId  = Word64
13818529054586492878
instance (C.TypedStruct CodeGeneratorRequest) where
    numStructWords :: Word16
numStructWords  = Word16
0
    numStructPtrs :: Word16
numStructPtrs  = Word16
4
instance (C.Allocate CodeGeneratorRequest) where
    type AllocHint CodeGeneratorRequest = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint CodeGeneratorRequest
-> Message ('Mut s) -> m (Raw CodeGeneratorRequest ('Mut s))
new AllocHint CodeGeneratorRequest
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc CodeGeneratorRequest (C.Parsed CodeGeneratorRequest))
instance (C.AllocateList CodeGeneratorRequest) where
    type ListAllocHint CodeGeneratorRequest = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint CodeGeneratorRequest
-> Message ('Mut s) -> m (Raw (List CodeGeneratorRequest) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc CodeGeneratorRequest (C.Parsed CodeGeneratorRequest))
data instance C.Parsed CodeGeneratorRequest
    = CodeGeneratorRequest 
        {Parsed CodeGeneratorRequest -> Parsed (List Node)
nodes :: (RP.Parsed (R.List Node))
        ,Parsed CodeGeneratorRequest
-> Parsed (List CodeGeneratorRequest'RequestedFile)
requestedFiles :: (RP.Parsed (R.List CodeGeneratorRequest'RequestedFile))
        ,Parsed CodeGeneratorRequest -> Parsed CapnpVersion
capnpVersion :: (RP.Parsed CapnpVersion)
        ,Parsed CodeGeneratorRequest -> Parsed (List Node'SourceInfo)
sourceInfo :: (RP.Parsed (R.List Node'SourceInfo))}
    deriving(forall x.
Rep (Parsed CodeGeneratorRequest) x -> Parsed CodeGeneratorRequest
forall x.
Parsed CodeGeneratorRequest -> Rep (Parsed CodeGeneratorRequest) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed CodeGeneratorRequest) x -> Parsed CodeGeneratorRequest
$cfrom :: forall x.
Parsed CodeGeneratorRequest -> Rep (Parsed CodeGeneratorRequest) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed CodeGeneratorRequest))
deriving instance (Std_.Eq (C.Parsed CodeGeneratorRequest))
instance (C.Parse CodeGeneratorRequest (C.Parsed CodeGeneratorRequest)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw CodeGeneratorRequest 'Const -> m (Parsed CodeGeneratorRequest)
parse Raw CodeGeneratorRequest 'Const
raw_ = (Parsed (List Node)
-> Parsed (List CodeGeneratorRequest'RequestedFile)
-> Parsed CapnpVersion
-> Parsed (List Node'SourceInfo)
-> Parsed CodeGeneratorRequest
CodeGeneratorRequest forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "nodes" a => a
#nodes Raw CodeGeneratorRequest 'Const
raw_)
                                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "requestedFiles" a => a
#requestedFiles Raw CodeGeneratorRequest 'Const
raw_)
                                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "capnpVersion" a => a
#capnpVersion Raw CodeGeneratorRequest 'Const
raw_)
                                       forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "sourceInfo" a => a
#sourceInfo Raw CodeGeneratorRequest 'Const
raw_))
instance (C.Marshal CodeGeneratorRequest (C.Parsed CodeGeneratorRequest)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw CodeGeneratorRequest ('Mut s)
-> Parsed CodeGeneratorRequest -> m ()
marshalInto Raw CodeGeneratorRequest ('Mut s)
raw_ CodeGeneratorRequest{Parsed (List CodeGeneratorRequest'RequestedFile)
Parsed (List Node'SourceInfo)
Parsed (List Node)
Parsed CapnpVersion
sourceInfo :: Parsed (List Node'SourceInfo)
capnpVersion :: Parsed CapnpVersion
requestedFiles :: Parsed (List CodeGeneratorRequest'RequestedFile)
nodes :: Parsed (List Node)
$sel:sourceInfo:CodeGeneratorRequest :: Parsed CodeGeneratorRequest -> Parsed (List Node'SourceInfo)
$sel:capnpVersion:CodeGeneratorRequest :: Parsed CodeGeneratorRequest -> Parsed CapnpVersion
$sel:requestedFiles:CodeGeneratorRequest :: Parsed CodeGeneratorRequest
-> Parsed (List CodeGeneratorRequest'RequestedFile)
$sel:nodes:CodeGeneratorRequest :: Parsed CodeGeneratorRequest -> Parsed (List Node)
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "nodes" a => a
#nodes Parsed (List Node)
nodes Raw CodeGeneratorRequest ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "requestedFiles" a => a
#requestedFiles Parsed (List CodeGeneratorRequest'RequestedFile)
requestedFiles Raw CodeGeneratorRequest ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "capnpVersion" a => a
#capnpVersion Parsed CapnpVersion
capnpVersion Raw CodeGeneratorRequest ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "sourceInfo" a => a
#sourceInfo Parsed (List Node'SourceInfo)
sourceInfo Raw CodeGeneratorRequest ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "nodes" GH.Slot CodeGeneratorRequest (R.List Node)) where
    fieldByLabel :: Field 'Slot CodeGeneratorRequest (List Node)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "requestedFiles" GH.Slot CodeGeneratorRequest (R.List CodeGeneratorRequest'RequestedFile)) where
    fieldByLabel :: Field
  'Slot
  CodeGeneratorRequest
  (List CodeGeneratorRequest'RequestedFile)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
1)
instance (GH.HasField "capnpVersion" GH.Slot CodeGeneratorRequest CapnpVersion) where
    fieldByLabel :: Field 'Slot CodeGeneratorRequest CapnpVersion
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
2)
instance (GH.HasField "sourceInfo" GH.Slot CodeGeneratorRequest (R.List Node'SourceInfo)) where
    fieldByLabel :: Field 'Slot CodeGeneratorRequest (List Node'SourceInfo)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
3)
data CodeGeneratorRequest'RequestedFile 
type instance (R.ReprFor CodeGeneratorRequest'RequestedFile) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId CodeGeneratorRequest'RequestedFile) where
    typeId :: Word64
typeId  = Word64
14981803260258615394
instance (C.TypedStruct CodeGeneratorRequest'RequestedFile) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
2
instance (C.Allocate CodeGeneratorRequest'RequestedFile) where
    type AllocHint CodeGeneratorRequest'RequestedFile = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint CodeGeneratorRequest'RequestedFile
-> Message ('Mut s)
-> m (Raw CodeGeneratorRequest'RequestedFile ('Mut s))
new AllocHint CodeGeneratorRequest'RequestedFile
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc CodeGeneratorRequest'RequestedFile (C.Parsed CodeGeneratorRequest'RequestedFile))
instance (C.AllocateList CodeGeneratorRequest'RequestedFile) where
    type ListAllocHint CodeGeneratorRequest'RequestedFile = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint CodeGeneratorRequest'RequestedFile
-> Message ('Mut s)
-> m (Raw (List CodeGeneratorRequest'RequestedFile) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc CodeGeneratorRequest'RequestedFile (C.Parsed CodeGeneratorRequest'RequestedFile))
data instance C.Parsed CodeGeneratorRequest'RequestedFile
    = CodeGeneratorRequest'RequestedFile 
        {Parsed CodeGeneratorRequest'RequestedFile -> Parsed Word64
id :: (RP.Parsed Std_.Word64)
        ,Parsed CodeGeneratorRequest'RequestedFile -> Parsed Text
filename :: (RP.Parsed Basics.Text)
        ,Parsed CodeGeneratorRequest'RequestedFile
-> Parsed (List CodeGeneratorRequest'RequestedFile'Import)
imports :: (RP.Parsed (R.List CodeGeneratorRequest'RequestedFile'Import))}
    deriving(forall x.
Rep (Parsed CodeGeneratorRequest'RequestedFile) x
-> Parsed CodeGeneratorRequest'RequestedFile
forall x.
Parsed CodeGeneratorRequest'RequestedFile
-> Rep (Parsed CodeGeneratorRequest'RequestedFile) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed CodeGeneratorRequest'RequestedFile) x
-> Parsed CodeGeneratorRequest'RequestedFile
$cfrom :: forall x.
Parsed CodeGeneratorRequest'RequestedFile
-> Rep (Parsed CodeGeneratorRequest'RequestedFile) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed CodeGeneratorRequest'RequestedFile))
deriving instance (Std_.Eq (C.Parsed CodeGeneratorRequest'RequestedFile))
instance (C.Parse CodeGeneratorRequest'RequestedFile (C.Parsed CodeGeneratorRequest'RequestedFile)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw CodeGeneratorRequest'RequestedFile 'Const
-> m (Parsed CodeGeneratorRequest'RequestedFile)
parse Raw CodeGeneratorRequest'RequestedFile 'Const
raw_ = (Parsed Word64
-> Parsed Text
-> Parsed (List CodeGeneratorRequest'RequestedFile'Import)
-> Parsed CodeGeneratorRequest'RequestedFile
CodeGeneratorRequest'RequestedFile forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "id" a => a
#id Raw CodeGeneratorRequest'RequestedFile 'Const
raw_)
                                                     forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "filename" a => a
#filename Raw CodeGeneratorRequest'RequestedFile 'Const
raw_)
                                                     forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "imports" a => a
#imports Raw CodeGeneratorRequest'RequestedFile 'Const
raw_))
instance (C.Marshal CodeGeneratorRequest'RequestedFile (C.Parsed CodeGeneratorRequest'RequestedFile)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw CodeGeneratorRequest'RequestedFile ('Mut s)
-> Parsed CodeGeneratorRequest'RequestedFile -> m ()
marshalInto Raw CodeGeneratorRequest'RequestedFile ('Mut s)
raw_ CodeGeneratorRequest'RequestedFile{Parsed Word64
Parsed (List CodeGeneratorRequest'RequestedFile'Import)
Parsed Text
imports :: Parsed (List CodeGeneratorRequest'RequestedFile'Import)
filename :: Parsed Text
id :: Parsed Word64
$sel:imports:CodeGeneratorRequest'RequestedFile :: Parsed CodeGeneratorRequest'RequestedFile
-> Parsed (List CodeGeneratorRequest'RequestedFile'Import)
$sel:filename:CodeGeneratorRequest'RequestedFile :: Parsed CodeGeneratorRequest'RequestedFile -> Parsed Text
$sel:id:CodeGeneratorRequest'RequestedFile :: Parsed CodeGeneratorRequest'RequestedFile -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "id" a => a
#id Parsed Word64
id Raw CodeGeneratorRequest'RequestedFile ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "filename" a => a
#filename Parsed Text
filename Raw CodeGeneratorRequest'RequestedFile ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "imports" a => a
#imports Parsed (List CodeGeneratorRequest'RequestedFile'Import)
imports Raw CodeGeneratorRequest'RequestedFile ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "id" GH.Slot CodeGeneratorRequest'RequestedFile Std_.Word64) where
    fieldByLabel :: Field 'Slot CodeGeneratorRequest'RequestedFile Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
64 Word64
0)
instance (GH.HasField "filename" GH.Slot CodeGeneratorRequest'RequestedFile Basics.Text) where
    fieldByLabel :: Field 'Slot CodeGeneratorRequest'RequestedFile Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)
instance (GH.HasField "imports" GH.Slot CodeGeneratorRequest'RequestedFile (R.List CodeGeneratorRequest'RequestedFile'Import)) where
    fieldByLabel :: Field
  'Slot
  CodeGeneratorRequest'RequestedFile
  (List CodeGeneratorRequest'RequestedFile'Import)
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
1)
data CodeGeneratorRequest'RequestedFile'Import 
type instance (R.ReprFor CodeGeneratorRequest'RequestedFile'Import) = (R.Ptr (Std_.Just R.Struct))
instance (C.HasTypeId CodeGeneratorRequest'RequestedFile'Import) where
    typeId :: Word64
typeId  = Word64
12560611460656617445
instance (C.TypedStruct CodeGeneratorRequest'RequestedFile'Import) where
    numStructWords :: Word16
numStructWords  = Word16
1
    numStructPtrs :: Word16
numStructPtrs  = Word16
1
instance (C.Allocate CodeGeneratorRequest'RequestedFile'Import) where
    type AllocHint CodeGeneratorRequest'RequestedFile'Import = ()
    new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint CodeGeneratorRequest'RequestedFile'Import
-> Message ('Mut s)
-> m (Raw CodeGeneratorRequest'RequestedFile'Import ('Mut s))
new AllocHint CodeGeneratorRequest'RequestedFile'Import
_ = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Message ('Mut s) -> m (Raw a ('Mut s))
C.newTypedStruct
instance (C.EstimateAlloc CodeGeneratorRequest'RequestedFile'Import (C.Parsed CodeGeneratorRequest'RequestedFile'Import))
instance (C.AllocateList CodeGeneratorRequest'RequestedFile'Import) where
    type ListAllocHint CodeGeneratorRequest'RequestedFile'Import = Std_.Int
    newList :: forall (m :: * -> *) s.
RWCtx m s =>
ListAllocHint CodeGeneratorRequest'RequestedFile'Import
-> Message ('Mut s)
-> m (Raw
        (List CodeGeneratorRequest'RequestedFile'Import) ('Mut s))
newList  = forall a (m :: * -> *) s.
(TypedStruct a, RWCtx m s) =>
Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
C.newTypedStructList
instance (C.EstimateListAlloc CodeGeneratorRequest'RequestedFile'Import (C.Parsed CodeGeneratorRequest'RequestedFile'Import))
data instance C.Parsed CodeGeneratorRequest'RequestedFile'Import
    = CodeGeneratorRequest'RequestedFile'Import 
        {Parsed CodeGeneratorRequest'RequestedFile'Import -> Parsed Word64
id :: (RP.Parsed Std_.Word64)
        ,Parsed CodeGeneratorRequest'RequestedFile'Import -> Parsed Text
name :: (RP.Parsed Basics.Text)}
    deriving(forall x.
Rep (Parsed CodeGeneratorRequest'RequestedFile'Import) x
-> Parsed CodeGeneratorRequest'RequestedFile'Import
forall x.
Parsed CodeGeneratorRequest'RequestedFile'Import
-> Rep (Parsed CodeGeneratorRequest'RequestedFile'Import) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (Parsed CodeGeneratorRequest'RequestedFile'Import) x
-> Parsed CodeGeneratorRequest'RequestedFile'Import
$cfrom :: forall x.
Parsed CodeGeneratorRequest'RequestedFile'Import
-> Rep (Parsed CodeGeneratorRequest'RequestedFile'Import) x
Generics.Generic)
deriving instance (Std_.Show (C.Parsed CodeGeneratorRequest'RequestedFile'Import))
deriving instance (Std_.Eq (C.Parsed CodeGeneratorRequest'RequestedFile'Import))
instance (C.Parse CodeGeneratorRequest'RequestedFile'Import (C.Parsed CodeGeneratorRequest'RequestedFile'Import)) where
    parse :: forall (m :: * -> *).
ReadCtx m 'Const =>
Raw CodeGeneratorRequest'RequestedFile'Import 'Const
-> m (Parsed CodeGeneratorRequest'RequestedFile'Import)
parse Raw CodeGeneratorRequest'RequestedFile'Import 'Const
raw_ = (Parsed Word64
-> Parsed Text -> Parsed CodeGeneratorRequest'RequestedFile'Import
CodeGeneratorRequest'RequestedFile'Import forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "id" a => a
#id Raw CodeGeneratorRequest'RequestedFile'Import 'Const
raw_)
                                                            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b bp (m :: * -> *) (k :: FieldKind).
(IsStruct a, Parse b bp, ReadCtx m 'Const) =>
Field k a b -> Raw a 'Const -> m bp
GH.parseField forall a. IsLabel "name" a => a
#name Raw CodeGeneratorRequest'RequestedFile'Import 'Const
raw_))
instance (C.Marshal CodeGeneratorRequest'RequestedFile'Import (C.Parsed CodeGeneratorRequest'RequestedFile'Import)) where
    marshalInto :: forall (m :: * -> *) s.
RWCtx m s =>
Raw CodeGeneratorRequest'RequestedFile'Import ('Mut s)
-> Parsed CodeGeneratorRequest'RequestedFile'Import -> m ()
marshalInto Raw CodeGeneratorRequest'RequestedFile'Import ('Mut s)
raw_ CodeGeneratorRequest'RequestedFile'Import{Parsed Word64
Parsed Text
name :: Parsed Text
id :: Parsed Word64
$sel:name:CodeGeneratorRequest'RequestedFile'Import :: Parsed CodeGeneratorRequest'RequestedFile'Import -> Parsed Text
$sel:id:CodeGeneratorRequest'RequestedFile'Import :: Parsed CodeGeneratorRequest'RequestedFile'Import -> Parsed Word64
..} = (do
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "id" a => a
#id Parsed Word64
id Raw CodeGeneratorRequest'RequestedFile'Import ('Mut s)
raw_)
        (forall a b (m :: * -> *) s bp.
(IsStruct a, Parse b bp, RWCtx m s) =>
Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
GH.encodeField forall a. IsLabel "name" a => a
#name Parsed Text
name Raw CodeGeneratorRequest'RequestedFile'Import ('Mut s)
raw_)
        (forall (f :: * -> *) a. Applicative f => a -> f a
Std_.pure ())
        )
instance (GH.HasField "id" GH.Slot CodeGeneratorRequest'RequestedFile'Import Std_.Word64) where
    fieldByLabel :: Field 'Slot CodeGeneratorRequest'RequestedFile'Import Word64
fieldByLabel  = (forall b a (sz :: DataSz).
(ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) =>
BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
GH.dataField BitCount
0 Word16
0 BitCount
64 Word64
0)
instance (GH.HasField "name" GH.Slot CodeGeneratorRequest'RequestedFile'Import Basics.Text) where
    fieldByLabel :: Field 'Slot CodeGeneratorRequest'RequestedFile'Import Text
fieldByLabel  = (forall a b. IsPtr b => Word16 -> Field 'Slot a b
GH.ptrField Word16
0)