{-# 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.Generics 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 Maybe t msg = Maybe'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Maybe t msg)) where fromStruct struct = (Std_.pure (Maybe'newtype_ struct)) instance (Classes.ToStruct msg (Maybe t msg)) where toStruct (Maybe'newtype_ struct) = struct instance (Untyped.HasMessage (Maybe t msg)) where type InMessage (Maybe t msg) = msg message (Maybe'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Maybe t msg)) where messageDefault msg = (Maybe'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Maybe t msg)) where fromPtr msg ptr = (Maybe'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Maybe t (Message.MutMsg s))) where toPtr msg (Maybe'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Maybe t (Message.MutMsg s))) where new msg = (Maybe'newtype_ <$> (Untyped.allocStruct msg 1 1)) instance (Basics.ListElem msg (Maybe t msg)) where newtype List msg (Maybe t msg) = Maybe'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Maybe'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Maybe'List_ l) = (Untyped.ListStruct l) length (Maybe'List_ l) = (Untyped.length l) index i (Maybe'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Maybe t (Message.MutMsg s))) where setIndex (Maybe'newtype_ elt) i (Maybe'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Maybe'List_ <$> (Untyped.allocCompositeList msg 1 1 len)) data Maybe' t msg = Maybe'nothing | Maybe'just t | Maybe'unknown' Std_.Word16 instance ((Classes.FromPtr msg t)) => (Classes.FromStruct msg (Maybe' t msg)) where fromStruct struct = (do tag <- (GenHelpers.getTag struct 0) case tag of 0 -> (Std_.pure Maybe'nothing) 1 -> (Maybe'just <$> (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) )) _ -> (Std_.pure (Maybe'unknown' (Std_.fromIntegral tag))) ) get_Maybe' :: ((Untyped.ReadCtx m msg) ,(Classes.FromStruct msg (Maybe' t msg))) => (Maybe t msg) -> (m (Maybe' t msg)) get_Maybe' (Maybe'newtype_ struct) = (Classes.fromStruct struct) set_Maybe'nothing :: ((Untyped.RWCtx m s)) => (Maybe t (Message.MutMsg s)) -> (m ()) set_Maybe'nothing (Maybe'newtype_ struct) = (do (GenHelpers.setWordField struct (0 :: Std_.Word16) 0 0 0) (Std_.pure ()) ) set_Maybe'just :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s t)) => (Maybe t (Message.MutMsg s)) -> t -> (m ()) set_Maybe'just (Maybe'newtype_ struct) value = (do (GenHelpers.setWordField struct (1 :: Std_.Word16) 0 0 0) (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) ) set_Maybe'unknown' :: ((Untyped.RWCtx m s)) => (Maybe t (Message.MutMsg s)) -> Std_.Word16 -> (m ()) set_Maybe'unknown' (Maybe'newtype_ struct) value = (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word16) 0 0 0) newtype Either a b msg = Either'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Either a b msg)) where fromStruct struct = (Std_.pure (Either'newtype_ struct)) instance (Classes.ToStruct msg (Either a b msg)) where toStruct (Either'newtype_ struct) = struct instance (Untyped.HasMessage (Either a b msg)) where type InMessage (Either a b msg) = msg message (Either'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Either a b msg)) where messageDefault msg = (Either'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Either a b msg)) where fromPtr msg ptr = (Either'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Either a b (Message.MutMsg s))) where toPtr msg (Either'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Either a b (Message.MutMsg s))) where new msg = (Either'newtype_ <$> (Untyped.allocStruct msg 1 1)) instance (Basics.ListElem msg (Either a b msg)) where newtype List msg (Either a b msg) = Either'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Either'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Either'List_ l) = (Untyped.ListStruct l) length (Either'List_ l) = (Untyped.length l) index i (Either'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Either a b (Message.MutMsg s))) where setIndex (Either'newtype_ elt) i (Either'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Either'List_ <$> (Untyped.allocCompositeList msg 1 1 len)) data Either' a b msg = Either'left a | Either'right b | Either'unknown' Std_.Word16 instance ((Classes.FromPtr msg a) ,(Classes.FromPtr msg b)) => (Classes.FromStruct msg (Either' a b msg)) where fromStruct struct = (do tag <- (GenHelpers.getTag struct 0) case tag of 0 -> (Either'left <$> (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) )) 1 -> (Either'right <$> (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) )) _ -> (Std_.pure (Either'unknown' (Std_.fromIntegral tag))) ) get_Either' :: ((Untyped.ReadCtx m msg) ,(Classes.FromStruct msg (Either' a b msg))) => (Either a b msg) -> (m (Either' a b msg)) get_Either' (Either'newtype_ struct) = (Classes.fromStruct struct) set_Either'left :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s a)) => (Either a b (Message.MutMsg s)) -> a -> (m ()) set_Either'left (Either'newtype_ struct) value = (do (GenHelpers.setWordField struct (0 :: Std_.Word16) 0 0 0) (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) ) set_Either'right :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s b)) => (Either a b (Message.MutMsg s)) -> b -> (m ()) set_Either'right (Either'newtype_ struct) value = (do (GenHelpers.setWordField struct (1 :: Std_.Word16) 0 0 0) (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) ) set_Either'unknown' :: ((Untyped.RWCtx m s)) => (Either a b (Message.MutMsg s)) -> Std_.Word16 -> (m ()) set_Either'unknown' (Either'newtype_ struct) value = (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word16) 0 0 0) newtype Pair a b msg = Pair'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Pair a b msg)) where fromStruct struct = (Std_.pure (Pair'newtype_ struct)) instance (Classes.ToStruct msg (Pair a b msg)) where toStruct (Pair'newtype_ struct) = struct instance (Untyped.HasMessage (Pair a b msg)) where type InMessage (Pair a b msg) = msg message (Pair'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Pair a b msg)) where messageDefault msg = (Pair'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Pair a b msg)) where fromPtr msg ptr = (Pair'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Pair a b (Message.MutMsg s))) where toPtr msg (Pair'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Pair a b (Message.MutMsg s))) where new msg = (Pair'newtype_ <$> (Untyped.allocStruct msg 0 2)) instance (Basics.ListElem msg (Pair a b msg)) where newtype List msg (Pair a b msg) = Pair'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Pair'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Pair'List_ l) = (Untyped.ListStruct l) length (Pair'List_ l) = (Untyped.length l) index i (Pair'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Pair a b (Message.MutMsg s))) where setIndex (Pair'newtype_ elt) i (Pair'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Pair'List_ <$> (Untyped.allocCompositeList msg 0 2 len)) get_Pair'fst :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg a)) => (Pair a b msg) -> (m a) get_Pair'fst (Pair'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Pair'fst :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s a)) => (Pair a b (Message.MutMsg s)) -> a -> (m ()) set_Pair'fst (Pair'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Pair'fst :: ((Untyped.ReadCtx m msg)) => (Pair a b msg) -> (m Std_.Bool) has_Pair'fst (Pair'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) get_Pair'snd :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg b)) => (Pair a b msg) -> (m b) get_Pair'snd (Pair'newtype_ struct) = (do ptr <- (Untyped.getPtr 1 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Pair'snd :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s b)) => (Pair a b (Message.MutMsg s)) -> b -> (m ()) set_Pair'snd (Pair'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 1 struct) ) has_Pair'snd :: ((Untyped.ReadCtx m msg)) => (Pair a b msg) -> (m Std_.Bool) has_Pair'snd (Pair'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 1 struct)) newtype Nested t msg = Nested'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Nested t msg)) where fromStruct struct = (Std_.pure (Nested'newtype_ struct)) instance (Classes.ToStruct msg (Nested t msg)) where toStruct (Nested'newtype_ struct) = struct instance (Untyped.HasMessage (Nested t msg)) where type InMessage (Nested t msg) = msg message (Nested'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Nested t msg)) where messageDefault msg = (Nested'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Nested t msg)) where fromPtr msg ptr = (Nested'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Nested t (Message.MutMsg s))) where toPtr msg (Nested'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Nested t (Message.MutMsg s))) where new msg = (Nested'newtype_ <$> (Untyped.allocStruct msg 0 0)) instance (Basics.ListElem msg (Nested t msg)) where newtype List msg (Nested t msg) = Nested'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Nested'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Nested'List_ l) = (Untyped.ListStruct l) length (Nested'List_ l) = (Untyped.length l) index i (Nested'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Nested t (Message.MutMsg s))) where setIndex (Nested'newtype_ elt) i (Nested'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Nested'List_ <$> (Untyped.allocCompositeList msg 0 0 len)) newtype Nested'SomeStruct t msg = Nested'SomeStruct'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Nested'SomeStruct t msg)) where fromStruct struct = (Std_.pure (Nested'SomeStruct'newtype_ struct)) instance (Classes.ToStruct msg (Nested'SomeStruct t msg)) where toStruct (Nested'SomeStruct'newtype_ struct) = struct instance (Untyped.HasMessage (Nested'SomeStruct t msg)) where type InMessage (Nested'SomeStruct t msg) = msg message (Nested'SomeStruct'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Nested'SomeStruct t msg)) where messageDefault msg = (Nested'SomeStruct'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Nested'SomeStruct t msg)) where fromPtr msg ptr = (Nested'SomeStruct'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Nested'SomeStruct t (Message.MutMsg s))) where toPtr msg (Nested'SomeStruct'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Nested'SomeStruct t (Message.MutMsg s))) where new msg = (Nested'SomeStruct'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (Nested'SomeStruct t msg)) where newtype List msg (Nested'SomeStruct t msg) = Nested'SomeStruct'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Nested'SomeStruct'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Nested'SomeStruct'List_ l) = (Untyped.ListStruct l) length (Nested'SomeStruct'List_ l) = (Untyped.length l) index i (Nested'SomeStruct'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Nested'SomeStruct t (Message.MutMsg s))) where setIndex (Nested'SomeStruct'newtype_ elt) i (Nested'SomeStruct'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Nested'SomeStruct'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_Nested'SomeStruct'value :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg t)) => (Nested'SomeStruct t msg) -> (m t) get_Nested'SomeStruct'value (Nested'SomeStruct'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Nested'SomeStruct'value :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s t)) => (Nested'SomeStruct t (Message.MutMsg s)) -> t -> (m ()) set_Nested'SomeStruct'value (Nested'SomeStruct'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Nested'SomeStruct'value :: ((Untyped.ReadCtx m msg)) => (Nested'SomeStruct t msg) -> (m Std_.Bool) has_Nested'SomeStruct'value (Nested'SomeStruct'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) newtype Nested'SomeInterface t msg = Nested'SomeInterface'newtype_ (Std_.Maybe (Untyped.Cap msg)) instance (Classes.FromPtr msg (Nested'SomeInterface t msg)) where fromPtr msg ptr = (Nested'SomeInterface'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Nested'SomeInterface t (Message.MutMsg s))) where toPtr msg (Nested'SomeInterface'newtype_ (Std_.Nothing)) = (Std_.pure Std_.Nothing) toPtr msg (Nested'SomeInterface'newtype_ (Std_.Just cap)) = (Std_.pure (Std_.Just (Untyped.PtrCap cap))) newtype Nested'SomeInterface'method'params t msg = Nested'SomeInterface'method'params'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Nested'SomeInterface'method'params t msg)) where fromStruct struct = (Std_.pure (Nested'SomeInterface'method'params'newtype_ struct)) instance (Classes.ToStruct msg (Nested'SomeInterface'method'params t msg)) where toStruct (Nested'SomeInterface'method'params'newtype_ struct) = struct instance (Untyped.HasMessage (Nested'SomeInterface'method'params t msg)) where type InMessage (Nested'SomeInterface'method'params t msg) = msg message (Nested'SomeInterface'method'params'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Nested'SomeInterface'method'params t msg)) where messageDefault msg = (Nested'SomeInterface'method'params'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Nested'SomeInterface'method'params t msg)) where fromPtr msg ptr = (Nested'SomeInterface'method'params'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Nested'SomeInterface'method'params t (Message.MutMsg s))) where toPtr msg (Nested'SomeInterface'method'params'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Nested'SomeInterface'method'params t (Message.MutMsg s))) where new msg = (Nested'SomeInterface'method'params'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (Nested'SomeInterface'method'params t msg)) where newtype List msg (Nested'SomeInterface'method'params t msg) = Nested'SomeInterface'method'params'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Nested'SomeInterface'method'params'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Nested'SomeInterface'method'params'List_ l) = (Untyped.ListStruct l) length (Nested'SomeInterface'method'params'List_ l) = (Untyped.length l) index i (Nested'SomeInterface'method'params'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Nested'SomeInterface'method'params t (Message.MutMsg s))) where setIndex (Nested'SomeInterface'method'params'newtype_ elt) i (Nested'SomeInterface'method'params'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Nested'SomeInterface'method'params'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_Nested'SomeInterface'method'params'arg :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg t)) => (Nested'SomeInterface'method'params t msg) -> (m t) get_Nested'SomeInterface'method'params'arg (Nested'SomeInterface'method'params'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Nested'SomeInterface'method'params'arg :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s t)) => (Nested'SomeInterface'method'params t (Message.MutMsg s)) -> t -> (m ()) set_Nested'SomeInterface'method'params'arg (Nested'SomeInterface'method'params'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Nested'SomeInterface'method'params'arg :: ((Untyped.ReadCtx m msg)) => (Nested'SomeInterface'method'params t msg) -> (m Std_.Bool) has_Nested'SomeInterface'method'params'arg (Nested'SomeInterface'method'params'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) newtype Nested'SomeInterface'method'results t msg = Nested'SomeInterface'method'results'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Nested'SomeInterface'method'results t msg)) where fromStruct struct = (Std_.pure (Nested'SomeInterface'method'results'newtype_ struct)) instance (Classes.ToStruct msg (Nested'SomeInterface'method'results t msg)) where toStruct (Nested'SomeInterface'method'results'newtype_ struct) = struct instance (Untyped.HasMessage (Nested'SomeInterface'method'results t msg)) where type InMessage (Nested'SomeInterface'method'results t msg) = msg message (Nested'SomeInterface'method'results'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Nested'SomeInterface'method'results t msg)) where messageDefault msg = (Nested'SomeInterface'method'results'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Nested'SomeInterface'method'results t msg)) where fromPtr msg ptr = (Nested'SomeInterface'method'results'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Nested'SomeInterface'method'results t (Message.MutMsg s))) where toPtr msg (Nested'SomeInterface'method'results'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Nested'SomeInterface'method'results t (Message.MutMsg s))) where new msg = (Nested'SomeInterface'method'results'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (Nested'SomeInterface'method'results t msg)) where newtype List msg (Nested'SomeInterface'method'results t msg) = Nested'SomeInterface'method'results'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Nested'SomeInterface'method'results'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Nested'SomeInterface'method'results'List_ l) = (Untyped.ListStruct l) length (Nested'SomeInterface'method'results'List_ l) = (Untyped.length l) index i (Nested'SomeInterface'method'results'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Nested'SomeInterface'method'results t (Message.MutMsg s))) where setIndex (Nested'SomeInterface'method'results'newtype_ elt) i (Nested'SomeInterface'method'results'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Nested'SomeInterface'method'results'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_Nested'SomeInterface'method'results'result :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg t)) => (Nested'SomeInterface'method'results t msg) -> (m t) get_Nested'SomeInterface'method'results'result (Nested'SomeInterface'method'results'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Nested'SomeInterface'method'results'result :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s t)) => (Nested'SomeInterface'method'results t (Message.MutMsg s)) -> t -> (m ()) set_Nested'SomeInterface'method'results'result (Nested'SomeInterface'method'results'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Nested'SomeInterface'method'results'result :: ((Untyped.ReadCtx m msg)) => (Nested'SomeInterface'method'results t msg) -> (m Std_.Bool) has_Nested'SomeInterface'method'results'result (Nested'SomeInterface'method'results'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) newtype Specialized t msg = Specialized'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (Specialized t msg)) where fromStruct struct = (Std_.pure (Specialized'newtype_ struct)) instance (Classes.ToStruct msg (Specialized t msg)) where toStruct (Specialized'newtype_ struct) = struct instance (Untyped.HasMessage (Specialized t msg)) where type InMessage (Specialized t msg) = msg message (Specialized'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Specialized t msg)) where messageDefault msg = (Specialized'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Specialized t msg)) where fromPtr msg ptr = (Specialized'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Specialized t (Message.MutMsg s))) where toPtr msg (Specialized'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Specialized t (Message.MutMsg s))) where new msg = (Specialized'newtype_ <$> (Untyped.allocStruct msg 0 2)) instance (Basics.ListElem msg (Specialized t msg)) where newtype List msg (Specialized t msg) = Specialized'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Specialized'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Specialized'List_ l) = (Untyped.ListStruct l) length (Specialized'List_ l) = (Untyped.length l) index i (Specialized'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Specialized t (Message.MutMsg s))) where setIndex (Specialized'newtype_ elt) i (Specialized'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Specialized'List_ <$> (Untyped.allocCompositeList msg 0 2 len)) get_Specialized'either :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Either (Basics.Text msg) t msg))) => (Specialized t msg) -> (m (Either (Basics.Text msg) t msg)) get_Specialized'either (Specialized'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Specialized'either :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Either (Basics.Text (Message.MutMsg s)) t (Message.MutMsg s)))) => (Specialized t (Message.MutMsg s)) -> (Either (Basics.Text (Message.MutMsg s)) t (Message.MutMsg s)) -> (m ()) set_Specialized'either (Specialized'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Specialized'either :: ((Untyped.ReadCtx m msg)) => (Specialized t msg) -> (m Std_.Bool) has_Specialized'either (Specialized'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) new_Specialized'either :: ((Untyped.RWCtx m s)) => (Specialized t (Message.MutMsg s)) -> (m (Either (Basics.Text (Message.MutMsg s)) t (Message.MutMsg s))) new_Specialized'either struct = (do result <- (Classes.new (Untyped.message struct)) (set_Specialized'either struct result) (Std_.pure result) ) get_Specialized'nestedStruct :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg (Nested'SomeStruct (Basics.Data msg) msg))) => (Specialized t msg) -> (m (Nested'SomeStruct (Basics.Data msg) msg)) get_Specialized'nestedStruct (Specialized'newtype_ struct) = (do ptr <- (Untyped.getPtr 1 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Specialized'nestedStruct :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s (Nested'SomeStruct (Basics.Data (Message.MutMsg s)) (Message.MutMsg s)))) => (Specialized t (Message.MutMsg s)) -> (Nested'SomeStruct (Basics.Data (Message.MutMsg s)) (Message.MutMsg s)) -> (m ()) set_Specialized'nestedStruct (Specialized'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 1 struct) ) has_Specialized'nestedStruct :: ((Untyped.ReadCtx m msg)) => (Specialized t msg) -> (m Std_.Bool) has_Specialized'nestedStruct (Specialized'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 1 struct)) new_Specialized'nestedStruct :: ((Untyped.RWCtx m s)) => (Specialized t (Message.MutMsg s)) -> (m (Nested'SomeStruct (Basics.Data (Message.MutMsg s)) (Message.MutMsg s))) new_Specialized'nestedStruct struct = (do result <- (Classes.new (Untyped.message struct)) (set_Specialized'nestedStruct struct result) (Std_.pure result) ) newtype HasGroup t msg = HasGroup'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (HasGroup t msg)) where fromStruct struct = (Std_.pure (HasGroup'newtype_ struct)) instance (Classes.ToStruct msg (HasGroup t msg)) where toStruct (HasGroup'newtype_ struct) = struct instance (Untyped.HasMessage (HasGroup t msg)) where type InMessage (HasGroup t msg) = msg message (HasGroup'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (HasGroup t msg)) where messageDefault msg = (HasGroup'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (HasGroup t msg)) where fromPtr msg ptr = (HasGroup'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (HasGroup t (Message.MutMsg s))) where toPtr msg (HasGroup'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (HasGroup t (Message.MutMsg s))) where new msg = (HasGroup'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (HasGroup t msg)) where newtype List msg (HasGroup t msg) = HasGroup'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (HasGroup'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (HasGroup'List_ l) = (Untyped.ListStruct l) length (HasGroup'List_ l) = (Untyped.length l) index i (HasGroup'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (HasGroup t (Message.MutMsg s))) where setIndex (HasGroup'newtype_ elt) i (HasGroup'List_ l) = (Untyped.setIndex elt i l) newList msg len = (HasGroup'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_HasGroup'theGroup :: ((Untyped.ReadCtx m msg) ,(Classes.FromStruct msg (HasGroup'theGroup t msg))) => (HasGroup t msg) -> (m (HasGroup'theGroup t msg)) get_HasGroup'theGroup (HasGroup'newtype_ struct) = (Classes.fromStruct struct) newtype HasGroup'theGroup t msg = HasGroup'theGroup'newtype_ (Untyped.Struct msg) instance (Classes.FromStruct msg (HasGroup'theGroup t msg)) where fromStruct struct = (Std_.pure (HasGroup'theGroup'newtype_ struct)) instance (Classes.ToStruct msg (HasGroup'theGroup t msg)) where toStruct (HasGroup'theGroup'newtype_ struct) = struct instance (Untyped.HasMessage (HasGroup'theGroup t msg)) where type InMessage (HasGroup'theGroup t msg) = msg message (HasGroup'theGroup'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (HasGroup'theGroup t msg)) where messageDefault msg = (HasGroup'theGroup'newtype_ (Untyped.messageDefault msg)) get_HasGroup'theGroup'value :: ((Untyped.ReadCtx m msg) ,(Classes.FromPtr msg t)) => (HasGroup'theGroup t msg) -> (m t) get_HasGroup'theGroup'value (HasGroup'theGroup'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_HasGroup'theGroup'value :: ((Untyped.RWCtx m s) ,(Classes.ToPtr s t)) => (HasGroup'theGroup t (Message.MutMsg s)) -> t -> (m ()) set_HasGroup'theGroup'value (HasGroup'theGroup'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_HasGroup'theGroup'value :: ((Untyped.ReadCtx m msg)) => (HasGroup'theGroup t msg) -> (m Std_.Bool) has_HasGroup'theGroup'value (HasGroup'theGroup'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct))