{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -Wno-unused-imports #-} {-# OPTIONS_GHC -Wno-dodgy-exports #-} {-# OPTIONS_GHC -Wno-unused-matches #-} {-# OPTIONS_GHC -Wno-orphans #-} module Capnp.Gen.Capnp.Compat.Json where import qualified Capnp.Message as Message import qualified Capnp.Untyped as Untyped import qualified Capnp.Basics as Basics import qualified Capnp.GenHelpers as GenHelpers import qualified Capnp.Classes as Classes import qualified GHC.Generics as Generics import qualified Capnp.Bits as Std_ import qualified Data.Maybe as Std_ import qualified Capnp.GenHelpers.ReExports.Data.ByteString as BS import qualified Prelude as Std_ import qualified Data.Word as Std_ import qualified Data.Int as Std_ import Prelude ((<$>), (<*>), (>>=)) newtype Value msg = Value'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Value msg)) where fromStruct :: Struct msg -> m (Value msg) fromStruct Struct msg struct = (Value msg -> m (Value msg) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure (Struct msg -> Value msg forall msg. Struct msg -> Value msg Value'newtype_ Struct msg struct)) instance (Classes.ToStruct msg (Value msg)) where toStruct :: Value msg -> Struct msg toStruct (Value'newtype_ Struct msg struct) = Struct msg struct instance (Untyped.HasMessage (Value msg)) where type InMessage (Value msg) = msg message :: Value msg -> InMessage (Value msg) message (Value'newtype_ Struct msg struct) = (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) instance (Untyped.MessageDefault (Value msg)) where messageDefault :: InMessage (Value msg) -> Value msg messageDefault InMessage (Value msg) msg = (Struct msg -> Value msg forall msg. Struct msg -> Value msg Value'newtype_ (InMessage (Struct msg) -> Struct msg forall a. MessageDefault a => InMessage a -> a Untyped.messageDefault InMessage (Struct msg) InMessage (Value msg) msg)) instance (Classes.FromPtr msg (Value msg)) where fromPtr :: msg -> Maybe (Ptr msg) -> m (Value msg) fromPtr msg msg Maybe (Ptr msg) ptr = (Struct msg -> Value msg forall msg. Struct msg -> Value msg Value'newtype_ (Struct msg -> Value msg) -> m (Struct msg) -> m (Value msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (Struct msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) instance (Classes.ToPtr s (Value (Message.MutMsg s))) where toPtr :: MutMsg s -> Value (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) toPtr MutMsg s msg (Value'newtype_ Struct (MutMsg s) struct) = (MutMsg s -> Struct (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr MutMsg s msg Struct (MutMsg s) struct) instance (Classes.Allocate s (Value (Message.MutMsg s))) where new :: MutMsg s -> m (Value (MutMsg s)) new MutMsg s msg = (Struct (MutMsg s) -> Value (MutMsg s) forall msg. Struct msg -> Value msg Value'newtype_ (Struct (MutMsg s) -> Value (MutMsg s)) -> m (Struct (MutMsg s)) -> m (Value (MutMsg s)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) Untyped.allocStruct MutMsg s msg Word16 2 Word16 1)) instance (Basics.ListElem msg (Value msg)) where newtype List msg (Value msg) = Value'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr :: msg -> Maybe (Ptr msg) -> m (List msg (Value msg)) listFromPtr msg msg Maybe (Ptr msg) ptr = (ListOf msg (Struct msg) -> List msg (Value msg) forall msg. ListOf msg (Struct msg) -> List msg (Value msg) Value'List_ (ListOf msg (Struct msg) -> List msg (Value msg)) -> m (ListOf msg (Struct msg)) -> m (List msg (Value msg)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (ListOf msg (Struct msg)) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) toUntypedList :: List msg (Value msg) -> List msg toUntypedList (Value'List_ l) = (ListOf msg (Struct msg) -> List msg forall msg. ListOf msg (Struct msg) -> List msg Untyped.ListStruct ListOf msg (Struct msg) l) length :: List msg (Value msg) -> Int length (Value'List_ l) = (ListOf msg (Struct msg) -> Int forall msg a. ListOf msg a -> Int Untyped.length ListOf msg (Struct msg) l) index :: Int -> List msg (Value msg) -> m (Value msg) index Int i (Value'List_ l) = (do Struct msg elt <- (Int -> ListOf msg (Struct msg) -> m (Struct msg) forall (m :: * -> *) msg a. ReadCtx m msg => Int -> ListOf msg a -> m a Untyped.index Int i ListOf msg (Struct msg) l) (Struct msg -> m (Value msg) forall msg a (m :: * -> *). (FromStruct msg a, ReadCtx m msg) => Struct msg -> m a Classes.fromStruct Struct msg elt) ) instance (Basics.MutListElem s (Value (Message.MutMsg s))) where setIndex :: Value (MutMsg s) -> Int -> List (MutMsg s) (Value (MutMsg s)) -> m () setIndex (Value'newtype_ Struct (MutMsg s) elt) Int i (Value'List_ l) = (Struct (MutMsg s) -> Int -> ListOf (MutMsg s) (Struct (MutMsg s)) -> m () forall (m :: * -> *) s a. RWCtx m s => a -> Int -> ListOf (MutMsg s) a -> m () Untyped.setIndex Struct (MutMsg s) elt Int i ListOf (MutMsg s) (Struct (MutMsg s)) l) newList :: MutMsg s -> Int -> m (List (MutMsg s) (Value (MutMsg s))) newList MutMsg s msg Int len = (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (Value (MutMsg s)) forall msg. ListOf msg (Struct msg) -> List msg (Value msg) Value'List_ (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (Value (MutMsg s))) -> m (ListOf (MutMsg s) (Struct (MutMsg s))) -> m (List (MutMsg s) (Value (MutMsg s))) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) Untyped.allocCompositeList MutMsg s msg Word16 2 Word16 1 Int len)) data Value' msg = Value'null | Value'boolean Std_.Bool | Value'number Std_.Double | Value'string (Basics.Text msg) | Value'array (Basics.List msg (Value msg)) | Value'object (Basics.List msg (Value'Field msg)) | Value'call (Value'Call msg) | Value'unknown' Std_.Word16 instance (Classes.FromStruct msg (Value' msg)) where fromStruct :: Struct msg -> m (Value' msg) fromStruct Struct msg struct = (do Word16 tag <- (Struct msg -> Int -> m Word16 forall (m :: * -> *) msg. ReadCtx m msg => Struct msg -> Int -> m Word16 GenHelpers.getTag Struct msg struct Int 0) case Word16 tag of Word16 0 -> (Value' msg -> m (Value' msg) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure Value' msg forall msg. Value' msg Value'null) Word16 1 -> (Bool -> Value' msg forall msg. Bool -> Value' msg Value'boolean (Bool -> Value' msg) -> m Bool -> m (Value' msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Struct msg -> Int -> Int -> Word64 -> m Bool forall (m :: * -> *) msg a. (ReadCtx m msg, IsWord a) => Struct msg -> Int -> Int -> Word64 -> m a GenHelpers.getWordField Struct msg struct Int 0 Int 16 Word64 0)) Word16 2 -> (Double -> Value' msg forall msg. Double -> Value' msg Value'number (Double -> Value' msg) -> m Double -> m (Value' msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Struct msg -> Int -> Int -> Word64 -> m Double forall (m :: * -> *) msg a. (ReadCtx m msg, IsWord a) => Struct msg -> Int -> Int -> Word64 -> m a GenHelpers.getWordField Struct msg struct Int 1 Int 0 Word64 0)) Word16 3 -> (Text msg -> Value' msg forall msg. Text msg -> Value' msg Value'string (Text msg -> Value' msg) -> m (Text msg) -> m (Value' msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (Text msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) )) Word16 4 -> (List msg (Value msg) -> Value' msg forall msg. List msg (Value msg) -> Value' msg Value'array (List msg (Value msg) -> Value' msg) -> m (List msg (Value msg)) -> m (Value' msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (List msg (Value msg)) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) )) Word16 5 -> (List msg (Value'Field msg) -> Value' msg forall msg. List msg (Value'Field msg) -> Value' msg Value'object (List msg (Value'Field msg) -> Value' msg) -> m (List msg (Value'Field msg)) -> m (Value' msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (List msg (Value'Field msg)) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) )) Word16 6 -> (Value'Call msg -> Value' msg forall msg. Value'Call msg -> Value' msg Value'call (Value'Call msg -> Value' msg) -> m (Value'Call msg) -> m (Value' msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (Value'Call msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) )) Word16 _ -> (Value' msg -> m (Value' msg) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure (Word16 -> Value' msg forall msg. Word16 -> Value' msg Value'unknown' (Word16 -> Word16 forall a b. (Integral a, Num b) => a -> b Std_.fromIntegral Word16 tag))) ) get_Value' :: ((Untyped.ReadCtx m msg) ,(Classes.FromStruct msg (Value' msg))) => (Value msg) -> (m (Value' msg)) get_Value' :: Value msg -> m (Value' msg) get_Value' (Value'newtype_ Struct msg struct) = (Struct msg -> m (Value' msg) forall msg a (m :: * -> *). (FromStruct msg a, ReadCtx m msg) => Struct msg -> m a Classes.fromStruct Struct msg struct) set_Value'null :: ((Untyped.RWCtx m s)) => (Value (Message.MutMsg s)) -> (m ()) set_Value'null :: Value (MutMsg s) -> m () set_Value'null (Value'newtype_ Struct (MutMsg s) struct) = (do (Struct (MutMsg s) -> Word16 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct (Word16 0 :: Std_.Word16) Int 0 Int 0 Word64 0) (() -> m () forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure ()) ) set_Value'boolean :: ((Untyped.RWCtx m s)) => (Value (Message.MutMsg s)) -> Std_.Bool -> (m ()) set_Value'boolean :: Value (MutMsg s) -> Bool -> m () set_Value'boolean (Value'newtype_ Struct (MutMsg s) struct) Bool value = (do (Struct (MutMsg s) -> Word16 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct (Word16 1 :: Std_.Word16) Int 0 Int 0 Word64 0) (Struct (MutMsg s) -> Word1 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct ((Word64 -> Word1 forall a b. (Integral a, Num b) => a -> b Std_.fromIntegral (Bool -> Word64 forall a. IsWord a => a -> Word64 Classes.toWord Bool value)) :: Std_.Word1) Int 0 Int 16 Word64 0) ) set_Value'number :: ((Untyped.RWCtx m s)) => (Value (Message.MutMsg s)) -> Std_.Double -> (m ()) set_Value'number :: Value (MutMsg s) -> Double -> m () set_Value'number (Value'newtype_ Struct (MutMsg s) struct) Double value = (do (Struct (MutMsg s) -> Word16 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct (Word16 2 :: Std_.Word16) Int 0 Int 0 Word64 0) (Struct (MutMsg s) -> Word64 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct ((Word64 -> Word64 forall a b. (Integral a, Num b) => a -> b Std_.fromIntegral (Double -> Word64 forall a. IsWord a => a -> Word64 Classes.toWord Double value)) :: Std_.Word64) Int 1 Int 0 Word64 0) ) set_Value'string :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.Text (Message.MutMsg s)))) => (Value (Message.MutMsg s)) -> (Basics.Text (Message.MutMsg s)) -> (m ()) set_Value'string :: Value (MutMsg s) -> Text (MutMsg s) -> m () set_Value'string (Value'newtype_ Struct (MutMsg s) struct) Text (MutMsg s) value = (do (Struct (MutMsg s) -> Word16 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct (Word16 3 :: Std_.Word16) Int 0 Int 0 Word64 0) (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> Text (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) Text (MutMsg s) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 0 Struct (MutMsg s) struct) ) ) set_Value'array :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.List (Message.MutMsg s) (Value (Message.MutMsg s))))) => (Value (Message.MutMsg s)) -> (Basics.List (Message.MutMsg s) (Value (Message.MutMsg s))) -> (m ()) set_Value'array :: Value (MutMsg s) -> List (MutMsg s) (Value (MutMsg s)) -> m () set_Value'array (Value'newtype_ Struct (MutMsg s) struct) List (MutMsg s) (Value (MutMsg s)) value = (do (Struct (MutMsg s) -> Word16 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct (Word16 4 :: Std_.Word16) Int 0 Int 0 Word64 0) (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> List (MutMsg s) (Value (MutMsg s)) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) List (MutMsg s) (Value (MutMsg s)) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 0 Struct (MutMsg s) struct) ) ) set_Value'object :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.List (Message.MutMsg s) (Value'Field (Message.MutMsg s))))) => (Value (Message.MutMsg s)) -> (Basics.List (Message.MutMsg s) (Value'Field (Message.MutMsg s))) -> (m ()) set_Value'object :: Value (MutMsg s) -> List (MutMsg s) (Value'Field (MutMsg s)) -> m () set_Value'object (Value'newtype_ Struct (MutMsg s) struct) List (MutMsg s) (Value'Field (MutMsg s)) value = (do (Struct (MutMsg s) -> Word16 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct (Word16 5 :: Std_.Word16) Int 0 Int 0 Word64 0) (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> List (MutMsg s) (Value'Field (MutMsg s)) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) List (MutMsg s) (Value'Field (MutMsg s)) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 0 Struct (MutMsg s) struct) ) ) set_Value'call :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Value'Call (Message.MutMsg s)))) => (Value (Message.MutMsg s)) -> (Value'Call (Message.MutMsg s)) -> (m ()) set_Value'call :: Value (MutMsg s) -> Value'Call (MutMsg s) -> m () set_Value'call (Value'newtype_ Struct (MutMsg s) struct) Value'Call (MutMsg s) value = (do (Struct (MutMsg s) -> Word16 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct (Word16 6 :: Std_.Word16) Int 0 Int 0 Word64 0) (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> Value'Call (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) Value'Call (MutMsg s) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 0 Struct (MutMsg s) struct) ) ) set_Value'unknown' :: ((Untyped.RWCtx m s)) => (Value (Message.MutMsg s)) -> Std_.Word16 -> (m ()) set_Value'unknown' :: Value (MutMsg s) -> Word16 -> m () set_Value'unknown' (Value'newtype_ Struct (MutMsg s) struct) Word16 value = (Struct (MutMsg s) -> Word16 -> Int -> Int -> Word64 -> m () forall (m :: * -> *) s a. (RWCtx m s, Bounded a, Integral a, IsWord a, Bits a) => Struct (MutMsg s) -> a -> Int -> Int -> Word64 -> m () GenHelpers.setWordField Struct (MutMsg s) struct ((Word64 -> Word16 forall a b. (Integral a, Num b) => a -> b Std_.fromIntegral (Word16 -> Word64 forall a. IsWord a => a -> Word64 Classes.toWord Word16 value)) :: Std_.Word16) Int 0 Int 0 Word64 0) newtype Value'Field msg = Value'Field'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Value'Field msg)) where fromStruct :: Struct msg -> m (Value'Field msg) fromStruct Struct msg struct = (Value'Field msg -> m (Value'Field msg) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure (Struct msg -> Value'Field msg forall msg. Struct msg -> Value'Field msg Value'Field'newtype_ Struct msg struct)) instance (Classes.ToStruct msg (Value'Field msg)) where toStruct :: Value'Field msg -> Struct msg toStruct (Value'Field'newtype_ Struct msg struct) = Struct msg struct instance (Untyped.HasMessage (Value'Field msg)) where type InMessage (Value'Field msg) = msg message :: Value'Field msg -> InMessage (Value'Field msg) message (Value'Field'newtype_ Struct msg struct) = (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) instance (Untyped.MessageDefault (Value'Field msg)) where messageDefault :: InMessage (Value'Field msg) -> Value'Field msg messageDefault InMessage (Value'Field msg) msg = (Struct msg -> Value'Field msg forall msg. Struct msg -> Value'Field msg Value'Field'newtype_ (InMessage (Struct msg) -> Struct msg forall a. MessageDefault a => InMessage a -> a Untyped.messageDefault InMessage (Struct msg) InMessage (Value'Field msg) msg)) instance (Classes.FromPtr msg (Value'Field msg)) where fromPtr :: msg -> Maybe (Ptr msg) -> m (Value'Field msg) fromPtr msg msg Maybe (Ptr msg) ptr = (Struct msg -> Value'Field msg forall msg. Struct msg -> Value'Field msg Value'Field'newtype_ (Struct msg -> Value'Field msg) -> m (Struct msg) -> m (Value'Field msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (Struct msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) instance (Classes.ToPtr s (Value'Field (Message.MutMsg s))) where toPtr :: MutMsg s -> Value'Field (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) toPtr MutMsg s msg (Value'Field'newtype_ Struct (MutMsg s) struct) = (MutMsg s -> Struct (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr MutMsg s msg Struct (MutMsg s) struct) instance (Classes.Allocate s (Value'Field (Message.MutMsg s))) where new :: MutMsg s -> m (Value'Field (MutMsg s)) new MutMsg s msg = (Struct (MutMsg s) -> Value'Field (MutMsg s) forall msg. Struct msg -> Value'Field msg Value'Field'newtype_ (Struct (MutMsg s) -> Value'Field (MutMsg s)) -> m (Struct (MutMsg s)) -> m (Value'Field (MutMsg s)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) Untyped.allocStruct MutMsg s msg Word16 0 Word16 2)) instance (Basics.ListElem msg (Value'Field msg)) where newtype List msg (Value'Field msg) = Value'Field'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr :: msg -> Maybe (Ptr msg) -> m (List msg (Value'Field msg)) listFromPtr msg msg Maybe (Ptr msg) ptr = (ListOf msg (Struct msg) -> List msg (Value'Field msg) forall msg. ListOf msg (Struct msg) -> List msg (Value'Field msg) Value'Field'List_ (ListOf msg (Struct msg) -> List msg (Value'Field msg)) -> m (ListOf msg (Struct msg)) -> m (List msg (Value'Field msg)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (ListOf msg (Struct msg)) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) toUntypedList :: List msg (Value'Field msg) -> List msg toUntypedList (Value'Field'List_ l) = (ListOf msg (Struct msg) -> List msg forall msg. ListOf msg (Struct msg) -> List msg Untyped.ListStruct ListOf msg (Struct msg) l) length :: List msg (Value'Field msg) -> Int length (Value'Field'List_ l) = (ListOf msg (Struct msg) -> Int forall msg a. ListOf msg a -> Int Untyped.length ListOf msg (Struct msg) l) index :: Int -> List msg (Value'Field msg) -> m (Value'Field msg) index Int i (Value'Field'List_ l) = (do Struct msg elt <- (Int -> ListOf msg (Struct msg) -> m (Struct msg) forall (m :: * -> *) msg a. ReadCtx m msg => Int -> ListOf msg a -> m a Untyped.index Int i ListOf msg (Struct msg) l) (Struct msg -> m (Value'Field msg) forall msg a (m :: * -> *). (FromStruct msg a, ReadCtx m msg) => Struct msg -> m a Classes.fromStruct Struct msg elt) ) instance (Basics.MutListElem s (Value'Field (Message.MutMsg s))) where setIndex :: Value'Field (MutMsg s) -> Int -> List (MutMsg s) (Value'Field (MutMsg s)) -> m () setIndex (Value'Field'newtype_ Struct (MutMsg s) elt) Int i (Value'Field'List_ l) = (Struct (MutMsg s) -> Int -> ListOf (MutMsg s) (Struct (MutMsg s)) -> m () forall (m :: * -> *) s a. RWCtx m s => a -> Int -> ListOf (MutMsg s) a -> m () Untyped.setIndex Struct (MutMsg s) elt Int i ListOf (MutMsg s) (Struct (MutMsg s)) l) newList :: MutMsg s -> Int -> m (List (MutMsg s) (Value'Field (MutMsg s))) newList MutMsg s msg Int len = (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (Value'Field (MutMsg s)) forall msg. ListOf msg (Struct msg) -> List msg (Value'Field msg) Value'Field'List_ (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (Value'Field (MutMsg s))) -> m (ListOf (MutMsg s) (Struct (MutMsg s))) -> m (List (MutMsg s) (Value'Field (MutMsg s))) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) Untyped.allocCompositeList MutMsg s msg Word16 0 Word16 2 Int len)) get_Value'Field'name :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Basics.Text msg))) => (Value'Field msg) -> (m (Basics.Text msg)) get_Value'Field'name :: Value'Field msg -> m (Text msg) get_Value'Field'name (Value'Field'newtype_ Struct msg struct) = (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (Text msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) ) set_Value'Field'name :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.Text (Message.MutMsg s)))) => (Value'Field (Message.MutMsg s)) -> (Basics.Text (Message.MutMsg s)) -> (m ()) set_Value'Field'name :: Value'Field (MutMsg s) -> Text (MutMsg s) -> m () set_Value'Field'name (Value'Field'newtype_ Struct (MutMsg s) struct) Text (MutMsg s) value = (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> Text (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) Text (MutMsg s) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 0 Struct (MutMsg s) struct) ) has_Value'Field'name :: ((Untyped.ReadCtx m msg)) => (Value'Field msg) -> (m Std_.Bool) has_Value'Field'name :: Value'Field msg -> m Bool has_Value'Field'name (Value'Field'newtype_ Struct msg struct) = (Maybe (Ptr msg) -> Bool forall a. Maybe a -> Bool Std_.isJust (Maybe (Ptr msg) -> Bool) -> m (Maybe (Ptr msg)) -> m Bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct)) new_Value'Field'name :: ((Untyped.RWCtx m s)) => Std_.Int -> (Value'Field (Message.MutMsg s)) -> (m (Basics.Text (Message.MutMsg s))) new_Value'Field'name :: Int -> Value'Field (MutMsg s) -> m (Text (MutMsg s)) new_Value'Field'name Int len Value'Field (MutMsg s) struct = (do Text (MutMsg s) result <- (MutMsg s -> Int -> m (Text (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Int -> m (Text (MutMsg s)) Basics.newText (Value'Field (MutMsg s) -> InMessage (Value'Field (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Value'Field (MutMsg s) struct) Int len) (Value'Field (MutMsg s) -> Text (MutMsg s) -> m () forall (m :: * -> *) s. (RWCtx m s, ToPtr s (Text (MutMsg s))) => Value'Field (MutMsg s) -> Text (MutMsg s) -> m () set_Value'Field'name Value'Field (MutMsg s) struct Text (MutMsg s) result) (Text (MutMsg s) -> m (Text (MutMsg s)) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure Text (MutMsg s) result) ) get_Value'Field'value :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Value msg))) => (Value'Field msg) -> (m (Value msg)) get_Value'Field'value :: Value'Field msg -> m (Value msg) get_Value'Field'value (Value'Field'newtype_ Struct msg struct) = (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 1 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (Value msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) ) set_Value'Field'value :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Value (Message.MutMsg s)))) => (Value'Field (Message.MutMsg s)) -> (Value (Message.MutMsg s)) -> (m ()) set_Value'Field'value :: Value'Field (MutMsg s) -> Value (MutMsg s) -> m () set_Value'Field'value (Value'Field'newtype_ Struct (MutMsg s) struct) Value (MutMsg s) value = (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> Value (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) Value (MutMsg s) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 1 Struct (MutMsg s) struct) ) has_Value'Field'value :: ((Untyped.ReadCtx m msg)) => (Value'Field msg) -> (m Std_.Bool) has_Value'Field'value :: Value'Field msg -> m Bool has_Value'Field'value (Value'Field'newtype_ Struct msg struct) = (Maybe (Ptr msg) -> Bool forall a. Maybe a -> Bool Std_.isJust (Maybe (Ptr msg) -> Bool) -> m (Maybe (Ptr msg)) -> m Bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 1 Struct msg struct)) new_Value'Field'value :: ((Untyped.RWCtx m s)) => (Value'Field (Message.MutMsg s)) -> (m (Value (Message.MutMsg s))) new_Value'Field'value :: Value'Field (MutMsg s) -> m (Value (MutMsg s)) new_Value'Field'value Value'Field (MutMsg s) struct = (do Value (MutMsg s) result <- (MutMsg s -> m (Value (MutMsg s)) forall s e (m :: * -> *). (Allocate s e, WriteCtx m s) => MutMsg s -> m e Classes.new (Value'Field (MutMsg s) -> InMessage (Value'Field (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Value'Field (MutMsg s) struct)) (Value'Field (MutMsg s) -> Value (MutMsg s) -> m () forall (m :: * -> *) s. (RWCtx m s, ToPtr s (Value (MutMsg s))) => Value'Field (MutMsg s) -> Value (MutMsg s) -> m () set_Value'Field'value Value'Field (MutMsg s) struct Value (MutMsg s) result) (Value (MutMsg s) -> m (Value (MutMsg s)) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure Value (MutMsg s) result) ) newtype Value'Call msg = Value'Call'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Value'Call msg)) where fromStruct :: Struct msg -> m (Value'Call msg) fromStruct Struct msg struct = (Value'Call msg -> m (Value'Call msg) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure (Struct msg -> Value'Call msg forall msg. Struct msg -> Value'Call msg Value'Call'newtype_ Struct msg struct)) instance (Classes.ToStruct msg (Value'Call msg)) where toStruct :: Value'Call msg -> Struct msg toStruct (Value'Call'newtype_ Struct msg struct) = Struct msg struct instance (Untyped.HasMessage (Value'Call msg)) where type InMessage (Value'Call msg) = msg message :: Value'Call msg -> InMessage (Value'Call msg) message (Value'Call'newtype_ Struct msg struct) = (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) instance (Untyped.MessageDefault (Value'Call msg)) where messageDefault :: InMessage (Value'Call msg) -> Value'Call msg messageDefault InMessage (Value'Call msg) msg = (Struct msg -> Value'Call msg forall msg. Struct msg -> Value'Call msg Value'Call'newtype_ (InMessage (Struct msg) -> Struct msg forall a. MessageDefault a => InMessage a -> a Untyped.messageDefault InMessage (Struct msg) InMessage (Value'Call msg) msg)) instance (Classes.FromPtr msg (Value'Call msg)) where fromPtr :: msg -> Maybe (Ptr msg) -> m (Value'Call msg) fromPtr msg msg Maybe (Ptr msg) ptr = (Struct msg -> Value'Call msg forall msg. Struct msg -> Value'Call msg Value'Call'newtype_ (Struct msg -> Value'Call msg) -> m (Struct msg) -> m (Value'Call msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (Struct msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) instance (Classes.ToPtr s (Value'Call (Message.MutMsg s))) where toPtr :: MutMsg s -> Value'Call (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) toPtr MutMsg s msg (Value'Call'newtype_ Struct (MutMsg s) struct) = (MutMsg s -> Struct (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr MutMsg s msg Struct (MutMsg s) struct) instance (Classes.Allocate s (Value'Call (Message.MutMsg s))) where new :: MutMsg s -> m (Value'Call (MutMsg s)) new MutMsg s msg = (Struct (MutMsg s) -> Value'Call (MutMsg s) forall msg. Struct msg -> Value'Call msg Value'Call'newtype_ (Struct (MutMsg s) -> Value'Call (MutMsg s)) -> m (Struct (MutMsg s)) -> m (Value'Call (MutMsg s)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) Untyped.allocStruct MutMsg s msg Word16 0 Word16 2)) instance (Basics.ListElem msg (Value'Call msg)) where newtype List msg (Value'Call msg) = Value'Call'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr :: msg -> Maybe (Ptr msg) -> m (List msg (Value'Call msg)) listFromPtr msg msg Maybe (Ptr msg) ptr = (ListOf msg (Struct msg) -> List msg (Value'Call msg) forall msg. ListOf msg (Struct msg) -> List msg (Value'Call msg) Value'Call'List_ (ListOf msg (Struct msg) -> List msg (Value'Call msg)) -> m (ListOf msg (Struct msg)) -> m (List msg (Value'Call msg)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (ListOf msg (Struct msg)) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) toUntypedList :: List msg (Value'Call msg) -> List msg toUntypedList (Value'Call'List_ l) = (ListOf msg (Struct msg) -> List msg forall msg. ListOf msg (Struct msg) -> List msg Untyped.ListStruct ListOf msg (Struct msg) l) length :: List msg (Value'Call msg) -> Int length (Value'Call'List_ l) = (ListOf msg (Struct msg) -> Int forall msg a. ListOf msg a -> Int Untyped.length ListOf msg (Struct msg) l) index :: Int -> List msg (Value'Call msg) -> m (Value'Call msg) index Int i (Value'Call'List_ l) = (do Struct msg elt <- (Int -> ListOf msg (Struct msg) -> m (Struct msg) forall (m :: * -> *) msg a. ReadCtx m msg => Int -> ListOf msg a -> m a Untyped.index Int i ListOf msg (Struct msg) l) (Struct msg -> m (Value'Call msg) forall msg a (m :: * -> *). (FromStruct msg a, ReadCtx m msg) => Struct msg -> m a Classes.fromStruct Struct msg elt) ) instance (Basics.MutListElem s (Value'Call (Message.MutMsg s))) where setIndex :: Value'Call (MutMsg s) -> Int -> List (MutMsg s) (Value'Call (MutMsg s)) -> m () setIndex (Value'Call'newtype_ Struct (MutMsg s) elt) Int i (Value'Call'List_ l) = (Struct (MutMsg s) -> Int -> ListOf (MutMsg s) (Struct (MutMsg s)) -> m () forall (m :: * -> *) s a. RWCtx m s => a -> Int -> ListOf (MutMsg s) a -> m () Untyped.setIndex Struct (MutMsg s) elt Int i ListOf (MutMsg s) (Struct (MutMsg s)) l) newList :: MutMsg s -> Int -> m (List (MutMsg s) (Value'Call (MutMsg s))) newList MutMsg s msg Int len = (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (Value'Call (MutMsg s)) forall msg. ListOf msg (Struct msg) -> List msg (Value'Call msg) Value'Call'List_ (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (Value'Call (MutMsg s))) -> m (ListOf (MutMsg s) (Struct (MutMsg s))) -> m (List (MutMsg s) (Value'Call (MutMsg s))) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) Untyped.allocCompositeList MutMsg s msg Word16 0 Word16 2 Int len)) get_Value'Call'function :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Basics.Text msg))) => (Value'Call msg) -> (m (Basics.Text msg)) get_Value'Call'function :: Value'Call msg -> m (Text msg) get_Value'Call'function (Value'Call'newtype_ Struct msg struct) = (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (Text msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) ) set_Value'Call'function :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.Text (Message.MutMsg s)))) => (Value'Call (Message.MutMsg s)) -> (Basics.Text (Message.MutMsg s)) -> (m ()) set_Value'Call'function :: Value'Call (MutMsg s) -> Text (MutMsg s) -> m () set_Value'Call'function (Value'Call'newtype_ Struct (MutMsg s) struct) Text (MutMsg s) value = (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> Text (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) Text (MutMsg s) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 0 Struct (MutMsg s) struct) ) has_Value'Call'function :: ((Untyped.ReadCtx m msg)) => (Value'Call msg) -> (m Std_.Bool) has_Value'Call'function :: Value'Call msg -> m Bool has_Value'Call'function (Value'Call'newtype_ Struct msg struct) = (Maybe (Ptr msg) -> Bool forall a. Maybe a -> Bool Std_.isJust (Maybe (Ptr msg) -> Bool) -> m (Maybe (Ptr msg)) -> m Bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct)) new_Value'Call'function :: ((Untyped.RWCtx m s)) => Std_.Int -> (Value'Call (Message.MutMsg s)) -> (m (Basics.Text (Message.MutMsg s))) new_Value'Call'function :: Int -> Value'Call (MutMsg s) -> m (Text (MutMsg s)) new_Value'Call'function Int len Value'Call (MutMsg s) struct = (do Text (MutMsg s) result <- (MutMsg s -> Int -> m (Text (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Int -> m (Text (MutMsg s)) Basics.newText (Value'Call (MutMsg s) -> InMessage (Value'Call (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Value'Call (MutMsg s) struct) Int len) (Value'Call (MutMsg s) -> Text (MutMsg s) -> m () forall (m :: * -> *) s. (RWCtx m s, ToPtr s (Text (MutMsg s))) => Value'Call (MutMsg s) -> Text (MutMsg s) -> m () set_Value'Call'function Value'Call (MutMsg s) struct Text (MutMsg s) result) (Text (MutMsg s) -> m (Text (MutMsg s)) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure Text (MutMsg s) result) ) get_Value'Call'params :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Basics.List msg (Value msg)))) => (Value'Call msg) -> (m (Basics.List msg (Value msg))) get_Value'Call'params :: Value'Call msg -> m (List msg (Value msg)) get_Value'Call'params (Value'Call'newtype_ Struct msg struct) = (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 1 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (List msg (Value msg)) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) ) set_Value'Call'params :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.List (Message.MutMsg s) (Value (Message.MutMsg s))))) => (Value'Call (Message.MutMsg s)) -> (Basics.List (Message.MutMsg s) (Value (Message.MutMsg s))) -> (m ()) set_Value'Call'params :: Value'Call (MutMsg s) -> List (MutMsg s) (Value (MutMsg s)) -> m () set_Value'Call'params (Value'Call'newtype_ Struct (MutMsg s) struct) List (MutMsg s) (Value (MutMsg s)) value = (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> List (MutMsg s) (Value (MutMsg s)) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) List (MutMsg s) (Value (MutMsg s)) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 1 Struct (MutMsg s) struct) ) has_Value'Call'params :: ((Untyped.ReadCtx m msg)) => (Value'Call msg) -> (m Std_.Bool) has_Value'Call'params :: Value'Call msg -> m Bool has_Value'Call'params (Value'Call'newtype_ Struct msg struct) = (Maybe (Ptr msg) -> Bool forall a. Maybe a -> Bool Std_.isJust (Maybe (Ptr msg) -> Bool) -> m (Maybe (Ptr msg)) -> m Bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 1 Struct msg struct)) new_Value'Call'params :: ((Untyped.RWCtx m s)) => Std_.Int -> (Value'Call (Message.MutMsg s)) -> (m (Basics.List (Message.MutMsg s) (Value (Message.MutMsg s)))) new_Value'Call'params :: Int -> Value'Call (MutMsg s) -> m (List (MutMsg s) (Value (MutMsg s))) new_Value'Call'params Int len Value'Call (MutMsg s) struct = (do List (MutMsg s) (Value (MutMsg s)) result <- (MutMsg s -> Int -> m (List (MutMsg s) (Value (MutMsg s))) forall s e (m :: * -> *). (MutListElem s e, WriteCtx m s) => MutMsg s -> Int -> m (List (MutMsg s) e) Classes.newList (Value'Call (MutMsg s) -> InMessage (Value'Call (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Value'Call (MutMsg s) struct) Int len) (Value'Call (MutMsg s) -> List (MutMsg s) (Value (MutMsg s)) -> m () forall (m :: * -> *) s. (RWCtx m s, ToPtr s (List (MutMsg s) (Value (MutMsg s)))) => Value'Call (MutMsg s) -> List (MutMsg s) (Value (MutMsg s)) -> m () set_Value'Call'params Value'Call (MutMsg s) struct List (MutMsg s) (Value (MutMsg s)) result) (List (MutMsg s) (Value (MutMsg s)) -> m (List (MutMsg s) (Value (MutMsg s))) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure List (MutMsg s) (Value (MutMsg s)) result) ) newtype FlattenOptions msg = FlattenOptions'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (FlattenOptions msg)) where fromStruct :: Struct msg -> m (FlattenOptions msg) fromStruct Struct msg struct = (FlattenOptions msg -> m (FlattenOptions msg) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure (Struct msg -> FlattenOptions msg forall msg. Struct msg -> FlattenOptions msg FlattenOptions'newtype_ Struct msg struct)) instance (Classes.ToStruct msg (FlattenOptions msg)) where toStruct :: FlattenOptions msg -> Struct msg toStruct (FlattenOptions'newtype_ Struct msg struct) = Struct msg struct instance (Untyped.HasMessage (FlattenOptions msg)) where type InMessage (FlattenOptions msg) = msg message :: FlattenOptions msg -> InMessage (FlattenOptions msg) message (FlattenOptions'newtype_ Struct msg struct) = (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) instance (Untyped.MessageDefault (FlattenOptions msg)) where messageDefault :: InMessage (FlattenOptions msg) -> FlattenOptions msg messageDefault InMessage (FlattenOptions msg) msg = (Struct msg -> FlattenOptions msg forall msg. Struct msg -> FlattenOptions msg FlattenOptions'newtype_ (InMessage (Struct msg) -> Struct msg forall a. MessageDefault a => InMessage a -> a Untyped.messageDefault InMessage (Struct msg) InMessage (FlattenOptions msg) msg)) instance (Classes.FromPtr msg (FlattenOptions msg)) where fromPtr :: msg -> Maybe (Ptr msg) -> m (FlattenOptions msg) fromPtr msg msg Maybe (Ptr msg) ptr = (Struct msg -> FlattenOptions msg forall msg. Struct msg -> FlattenOptions msg FlattenOptions'newtype_ (Struct msg -> FlattenOptions msg) -> m (Struct msg) -> m (FlattenOptions msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (Struct msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) instance (Classes.ToPtr s (FlattenOptions (Message.MutMsg s))) where toPtr :: MutMsg s -> FlattenOptions (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) toPtr MutMsg s msg (FlattenOptions'newtype_ Struct (MutMsg s) struct) = (MutMsg s -> Struct (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr MutMsg s msg Struct (MutMsg s) struct) instance (Classes.Allocate s (FlattenOptions (Message.MutMsg s))) where new :: MutMsg s -> m (FlattenOptions (MutMsg s)) new MutMsg s msg = (Struct (MutMsg s) -> FlattenOptions (MutMsg s) forall msg. Struct msg -> FlattenOptions msg FlattenOptions'newtype_ (Struct (MutMsg s) -> FlattenOptions (MutMsg s)) -> m (Struct (MutMsg s)) -> m (FlattenOptions (MutMsg s)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) Untyped.allocStruct MutMsg s msg Word16 0 Word16 1)) instance (Basics.ListElem msg (FlattenOptions msg)) where newtype List msg (FlattenOptions msg) = FlattenOptions'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr :: msg -> Maybe (Ptr msg) -> m (List msg (FlattenOptions msg)) listFromPtr msg msg Maybe (Ptr msg) ptr = (ListOf msg (Struct msg) -> List msg (FlattenOptions msg) forall msg. ListOf msg (Struct msg) -> List msg (FlattenOptions msg) FlattenOptions'List_ (ListOf msg (Struct msg) -> List msg (FlattenOptions msg)) -> m (ListOf msg (Struct msg)) -> m (List msg (FlattenOptions msg)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (ListOf msg (Struct msg)) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) toUntypedList :: List msg (FlattenOptions msg) -> List msg toUntypedList (FlattenOptions'List_ l) = (ListOf msg (Struct msg) -> List msg forall msg. ListOf msg (Struct msg) -> List msg Untyped.ListStruct ListOf msg (Struct msg) l) length :: List msg (FlattenOptions msg) -> Int length (FlattenOptions'List_ l) = (ListOf msg (Struct msg) -> Int forall msg a. ListOf msg a -> Int Untyped.length ListOf msg (Struct msg) l) index :: Int -> List msg (FlattenOptions msg) -> m (FlattenOptions msg) index Int i (FlattenOptions'List_ l) = (do Struct msg elt <- (Int -> ListOf msg (Struct msg) -> m (Struct msg) forall (m :: * -> *) msg a. ReadCtx m msg => Int -> ListOf msg a -> m a Untyped.index Int i ListOf msg (Struct msg) l) (Struct msg -> m (FlattenOptions msg) forall msg a (m :: * -> *). (FromStruct msg a, ReadCtx m msg) => Struct msg -> m a Classes.fromStruct Struct msg elt) ) instance (Basics.MutListElem s (FlattenOptions (Message.MutMsg s))) where setIndex :: FlattenOptions (MutMsg s) -> Int -> List (MutMsg s) (FlattenOptions (MutMsg s)) -> m () setIndex (FlattenOptions'newtype_ Struct (MutMsg s) elt) Int i (FlattenOptions'List_ l) = (Struct (MutMsg s) -> Int -> ListOf (MutMsg s) (Struct (MutMsg s)) -> m () forall (m :: * -> *) s a. RWCtx m s => a -> Int -> ListOf (MutMsg s) a -> m () Untyped.setIndex Struct (MutMsg s) elt Int i ListOf (MutMsg s) (Struct (MutMsg s)) l) newList :: MutMsg s -> Int -> m (List (MutMsg s) (FlattenOptions (MutMsg s))) newList MutMsg s msg Int len = (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (FlattenOptions (MutMsg s)) forall msg. ListOf msg (Struct msg) -> List msg (FlattenOptions msg) FlattenOptions'List_ (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (FlattenOptions (MutMsg s))) -> m (ListOf (MutMsg s) (Struct (MutMsg s))) -> m (List (MutMsg s) (FlattenOptions (MutMsg s))) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) Untyped.allocCompositeList MutMsg s msg Word16 0 Word16 1 Int len)) get_FlattenOptions'prefix :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Basics.Text msg))) => (FlattenOptions msg) -> (m (Basics.Text msg)) get_FlattenOptions'prefix :: FlattenOptions msg -> m (Text msg) get_FlattenOptions'prefix (FlattenOptions'newtype_ Struct msg struct) = (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (Text msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) ) set_FlattenOptions'prefix :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.Text (Message.MutMsg s)))) => (FlattenOptions (Message.MutMsg s)) -> (Basics.Text (Message.MutMsg s)) -> (m ()) set_FlattenOptions'prefix :: FlattenOptions (MutMsg s) -> Text (MutMsg s) -> m () set_FlattenOptions'prefix (FlattenOptions'newtype_ Struct (MutMsg s) struct) Text (MutMsg s) value = (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> Text (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) Text (MutMsg s) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 0 Struct (MutMsg s) struct) ) has_FlattenOptions'prefix :: ((Untyped.ReadCtx m msg)) => (FlattenOptions msg) -> (m Std_.Bool) has_FlattenOptions'prefix :: FlattenOptions msg -> m Bool has_FlattenOptions'prefix (FlattenOptions'newtype_ Struct msg struct) = (Maybe (Ptr msg) -> Bool forall a. Maybe a -> Bool Std_.isJust (Maybe (Ptr msg) -> Bool) -> m (Maybe (Ptr msg)) -> m Bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct)) new_FlattenOptions'prefix :: ((Untyped.RWCtx m s)) => Std_.Int -> (FlattenOptions (Message.MutMsg s)) -> (m (Basics.Text (Message.MutMsg s))) new_FlattenOptions'prefix :: Int -> FlattenOptions (MutMsg s) -> m (Text (MutMsg s)) new_FlattenOptions'prefix Int len FlattenOptions (MutMsg s) struct = (do Text (MutMsg s) result <- (MutMsg s -> Int -> m (Text (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Int -> m (Text (MutMsg s)) Basics.newText (FlattenOptions (MutMsg s) -> InMessage (FlattenOptions (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message FlattenOptions (MutMsg s) struct) Int len) (FlattenOptions (MutMsg s) -> Text (MutMsg s) -> m () forall (m :: * -> *) s. (RWCtx m s, ToPtr s (Text (MutMsg s))) => FlattenOptions (MutMsg s) -> Text (MutMsg s) -> m () set_FlattenOptions'prefix FlattenOptions (MutMsg s) struct Text (MutMsg s) result) (Text (MutMsg s) -> m (Text (MutMsg s)) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure Text (MutMsg s) result) ) newtype DiscriminatorOptions msg = DiscriminatorOptions'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (DiscriminatorOptions msg)) where fromStruct :: Struct msg -> m (DiscriminatorOptions msg) fromStruct Struct msg struct = (DiscriminatorOptions msg -> m (DiscriminatorOptions msg) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure (Struct msg -> DiscriminatorOptions msg forall msg. Struct msg -> DiscriminatorOptions msg DiscriminatorOptions'newtype_ Struct msg struct)) instance (Classes.ToStruct msg (DiscriminatorOptions msg)) where toStruct :: DiscriminatorOptions msg -> Struct msg toStruct (DiscriminatorOptions'newtype_ Struct msg struct) = Struct msg struct instance (Untyped.HasMessage (DiscriminatorOptions msg)) where type InMessage (DiscriminatorOptions msg) = msg message :: DiscriminatorOptions msg -> InMessage (DiscriminatorOptions msg) message (DiscriminatorOptions'newtype_ Struct msg struct) = (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) instance (Untyped.MessageDefault (DiscriminatorOptions msg)) where messageDefault :: InMessage (DiscriminatorOptions msg) -> DiscriminatorOptions msg messageDefault InMessage (DiscriminatorOptions msg) msg = (Struct msg -> DiscriminatorOptions msg forall msg. Struct msg -> DiscriminatorOptions msg DiscriminatorOptions'newtype_ (InMessage (Struct msg) -> Struct msg forall a. MessageDefault a => InMessage a -> a Untyped.messageDefault InMessage (Struct msg) InMessage (DiscriminatorOptions msg) msg)) instance (Classes.FromPtr msg (DiscriminatorOptions msg)) where fromPtr :: msg -> Maybe (Ptr msg) -> m (DiscriminatorOptions msg) fromPtr msg msg Maybe (Ptr msg) ptr = (Struct msg -> DiscriminatorOptions msg forall msg. Struct msg -> DiscriminatorOptions msg DiscriminatorOptions'newtype_ (Struct msg -> DiscriminatorOptions msg) -> m (Struct msg) -> m (DiscriminatorOptions msg) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (Struct msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) instance (Classes.ToPtr s (DiscriminatorOptions (Message.MutMsg s))) where toPtr :: MutMsg s -> DiscriminatorOptions (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) toPtr MutMsg s msg (DiscriminatorOptions'newtype_ Struct (MutMsg s) struct) = (MutMsg s -> Struct (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr MutMsg s msg Struct (MutMsg s) struct) instance (Classes.Allocate s (DiscriminatorOptions (Message.MutMsg s))) where new :: MutMsg s -> m (DiscriminatorOptions (MutMsg s)) new MutMsg s msg = (Struct (MutMsg s) -> DiscriminatorOptions (MutMsg s) forall msg. Struct msg -> DiscriminatorOptions msg DiscriminatorOptions'newtype_ (Struct (MutMsg s) -> DiscriminatorOptions (MutMsg s)) -> m (Struct (MutMsg s)) -> m (DiscriminatorOptions (MutMsg s)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) Untyped.allocStruct MutMsg s msg Word16 0 Word16 2)) instance (Basics.ListElem msg (DiscriminatorOptions msg)) where newtype List msg (DiscriminatorOptions msg) = DiscriminatorOptions'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr :: msg -> Maybe (Ptr msg) -> m (List msg (DiscriminatorOptions msg)) listFromPtr msg msg Maybe (Ptr msg) ptr = (ListOf msg (Struct msg) -> List msg (DiscriminatorOptions msg) forall msg. ListOf msg (Struct msg) -> List msg (DiscriminatorOptions msg) DiscriminatorOptions'List_ (ListOf msg (Struct msg) -> List msg (DiscriminatorOptions msg)) -> m (ListOf msg (Struct msg)) -> m (List msg (DiscriminatorOptions msg)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (msg -> Maybe (Ptr msg) -> m (ListOf msg (Struct msg)) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr msg msg Maybe (Ptr msg) ptr)) toUntypedList :: List msg (DiscriminatorOptions msg) -> List msg toUntypedList (DiscriminatorOptions'List_ l) = (ListOf msg (Struct msg) -> List msg forall msg. ListOf msg (Struct msg) -> List msg Untyped.ListStruct ListOf msg (Struct msg) l) length :: List msg (DiscriminatorOptions msg) -> Int length (DiscriminatorOptions'List_ l) = (ListOf msg (Struct msg) -> Int forall msg a. ListOf msg a -> Int Untyped.length ListOf msg (Struct msg) l) index :: Int -> List msg (DiscriminatorOptions msg) -> m (DiscriminatorOptions msg) index Int i (DiscriminatorOptions'List_ l) = (do Struct msg elt <- (Int -> ListOf msg (Struct msg) -> m (Struct msg) forall (m :: * -> *) msg a. ReadCtx m msg => Int -> ListOf msg a -> m a Untyped.index Int i ListOf msg (Struct msg) l) (Struct msg -> m (DiscriminatorOptions msg) forall msg a (m :: * -> *). (FromStruct msg a, ReadCtx m msg) => Struct msg -> m a Classes.fromStruct Struct msg elt) ) instance (Basics.MutListElem s (DiscriminatorOptions (Message.MutMsg s))) where setIndex :: DiscriminatorOptions (MutMsg s) -> Int -> List (MutMsg s) (DiscriminatorOptions (MutMsg s)) -> m () setIndex (DiscriminatorOptions'newtype_ Struct (MutMsg s) elt) Int i (DiscriminatorOptions'List_ l) = (Struct (MutMsg s) -> Int -> ListOf (MutMsg s) (Struct (MutMsg s)) -> m () forall (m :: * -> *) s a. RWCtx m s => a -> Int -> ListOf (MutMsg s) a -> m () Untyped.setIndex Struct (MutMsg s) elt Int i ListOf (MutMsg s) (Struct (MutMsg s)) l) newList :: MutMsg s -> Int -> m (List (MutMsg s) (DiscriminatorOptions (MutMsg s))) newList MutMsg s msg Int len = (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (DiscriminatorOptions (MutMsg s)) forall msg. ListOf msg (Struct msg) -> List msg (DiscriminatorOptions msg) DiscriminatorOptions'List_ (ListOf (MutMsg s) (Struct (MutMsg s)) -> List (MutMsg s) (DiscriminatorOptions (MutMsg s))) -> m (ListOf (MutMsg s) (Struct (MutMsg s))) -> m (List (MutMsg s) (DiscriminatorOptions (MutMsg s))) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s))) Untyped.allocCompositeList MutMsg s msg Word16 0 Word16 2 Int len)) get_DiscriminatorOptions'name :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Basics.Text msg))) => (DiscriminatorOptions msg) -> (m (Basics.Text msg)) get_DiscriminatorOptions'name :: DiscriminatorOptions msg -> m (Text msg) get_DiscriminatorOptions'name (DiscriminatorOptions'newtype_ Struct msg struct) = (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (Text msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) ) set_DiscriminatorOptions'name :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.Text (Message.MutMsg s)))) => (DiscriminatorOptions (Message.MutMsg s)) -> (Basics.Text (Message.MutMsg s)) -> (m ()) set_DiscriminatorOptions'name :: DiscriminatorOptions (MutMsg s) -> Text (MutMsg s) -> m () set_DiscriminatorOptions'name (DiscriminatorOptions'newtype_ Struct (MutMsg s) struct) Text (MutMsg s) value = (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> Text (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) Text (MutMsg s) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 0 Struct (MutMsg s) struct) ) has_DiscriminatorOptions'name :: ((Untyped.ReadCtx m msg)) => (DiscriminatorOptions msg) -> (m Std_.Bool) has_DiscriminatorOptions'name :: DiscriminatorOptions msg -> m Bool has_DiscriminatorOptions'name (DiscriminatorOptions'newtype_ Struct msg struct) = (Maybe (Ptr msg) -> Bool forall a. Maybe a -> Bool Std_.isJust (Maybe (Ptr msg) -> Bool) -> m (Maybe (Ptr msg)) -> m Bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 0 Struct msg struct)) new_DiscriminatorOptions'name :: ((Untyped.RWCtx m s)) => Std_.Int -> (DiscriminatorOptions (Message.MutMsg s)) -> (m (Basics.Text (Message.MutMsg s))) new_DiscriminatorOptions'name :: Int -> DiscriminatorOptions (MutMsg s) -> m (Text (MutMsg s)) new_DiscriminatorOptions'name Int len DiscriminatorOptions (MutMsg s) struct = (do Text (MutMsg s) result <- (MutMsg s -> Int -> m (Text (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Int -> m (Text (MutMsg s)) Basics.newText (DiscriminatorOptions (MutMsg s) -> InMessage (DiscriminatorOptions (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message DiscriminatorOptions (MutMsg s) struct) Int len) (DiscriminatorOptions (MutMsg s) -> Text (MutMsg s) -> m () forall (m :: * -> *) s. (RWCtx m s, ToPtr s (Text (MutMsg s))) => DiscriminatorOptions (MutMsg s) -> Text (MutMsg s) -> m () set_DiscriminatorOptions'name DiscriminatorOptions (MutMsg s) struct Text (MutMsg s) result) (Text (MutMsg s) -> m (Text (MutMsg s)) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure Text (MutMsg s) result) ) get_DiscriminatorOptions'valueName :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Basics.Text msg))) => (DiscriminatorOptions msg) -> (m (Basics.Text msg)) get_DiscriminatorOptions'valueName :: DiscriminatorOptions msg -> m (Text msg) get_DiscriminatorOptions'valueName (DiscriminatorOptions'newtype_ Struct msg struct) = (do Maybe (Ptr msg) ptr <- (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 1 Struct msg struct) (msg -> Maybe (Ptr msg) -> m (Text msg) forall msg a (m :: * -> *). (FromPtr msg a, ReadCtx m msg) => msg -> Maybe (Ptr msg) -> m a Classes.fromPtr (Struct msg -> InMessage (Struct msg) forall a. HasMessage a => a -> InMessage a Untyped.message Struct msg struct) Maybe (Ptr msg) ptr) ) set_DiscriminatorOptions'valueName :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Basics.Text (Message.MutMsg s)))) => (DiscriminatorOptions (Message.MutMsg s)) -> (Basics.Text (Message.MutMsg s)) -> (m ()) set_DiscriminatorOptions'valueName :: DiscriminatorOptions (MutMsg s) -> Text (MutMsg s) -> m () set_DiscriminatorOptions'valueName (DiscriminatorOptions'newtype_ Struct (MutMsg s) struct) Text (MutMsg s) value = (do Maybe (Ptr (MutMsg s)) ptr <- (MutMsg s -> Text (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) forall s a (m :: * -> *). (ToPtr s a, WriteCtx m s) => MutMsg s -> a -> m (Maybe (Ptr (MutMsg s))) Classes.toPtr (Struct (MutMsg s) -> InMessage (Struct (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message Struct (MutMsg s) struct) Text (MutMsg s) value) (Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () forall (m :: * -> *) s. (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Untyped.setPtr Maybe (Ptr (MutMsg s)) ptr Int 1 Struct (MutMsg s) struct) ) has_DiscriminatorOptions'valueName :: ((Untyped.ReadCtx m msg)) => (DiscriminatorOptions msg) -> (m Std_.Bool) has_DiscriminatorOptions'valueName :: DiscriminatorOptions msg -> m Bool has_DiscriminatorOptions'valueName (DiscriminatorOptions'newtype_ Struct msg struct) = (Maybe (Ptr msg) -> Bool forall a. Maybe a -> Bool Std_.isJust (Maybe (Ptr msg) -> Bool) -> m (Maybe (Ptr msg)) -> m Bool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Int -> Struct msg -> m (Maybe (Ptr msg)) forall (m :: * -> *) msg. ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Untyped.getPtr Int 1 Struct msg struct)) new_DiscriminatorOptions'valueName :: ((Untyped.RWCtx m s)) => Std_.Int -> (DiscriminatorOptions (Message.MutMsg s)) -> (m (Basics.Text (Message.MutMsg s))) new_DiscriminatorOptions'valueName :: Int -> DiscriminatorOptions (MutMsg s) -> m (Text (MutMsg s)) new_DiscriminatorOptions'valueName Int len DiscriminatorOptions (MutMsg s) struct = (do Text (MutMsg s) result <- (MutMsg s -> Int -> m (Text (MutMsg s)) forall (m :: * -> *) s. WriteCtx m s => MutMsg s -> Int -> m (Text (MutMsg s)) Basics.newText (DiscriminatorOptions (MutMsg s) -> InMessage (DiscriminatorOptions (MutMsg s)) forall a. HasMessage a => a -> InMessage a Untyped.message DiscriminatorOptions (MutMsg s) struct) Int len) (DiscriminatorOptions (MutMsg s) -> Text (MutMsg s) -> m () forall (m :: * -> *) s. (RWCtx m s, ToPtr s (Text (MutMsg s))) => DiscriminatorOptions (MutMsg s) -> Text (MutMsg s) -> m () set_DiscriminatorOptions'valueName DiscriminatorOptions (MutMsg s) struct Text (MutMsg s) result) (Text (MutMsg s) -> m (Text (MutMsg s)) forall (f :: * -> *) a. Applicative f => a -> f a Std_.pure Text (MutMsg s) result) )