{-# 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.Calculator 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 Calculator msg = Calculator'newtype_ (Std_.Maybe (Untyped.Cap msg)) instance (Classes.FromPtr msg (Calculator msg)) where fromPtr msg ptr = (Calculator'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Calculator (Message.MutMsg s))) where toPtr msg (Calculator'newtype_ (Std_.Nothing)) = (Std_.pure Std_.Nothing) toPtr msg (Calculator'newtype_ (Std_.Just cap)) = (Std_.pure (Std_.Just (Untyped.PtrCap cap))) newtype Calculator'evaluate'params msg = Calculator'evaluate'params'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Calculator'evaluate'params) where tMsg f (Calculator'evaluate'params'newtype_ s) = (Calculator'evaluate'params'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Calculator'evaluate'params msg)) where fromStruct struct = (Std_.pure (Calculator'evaluate'params'newtype_ struct)) instance (Classes.ToStruct msg (Calculator'evaluate'params msg)) where toStruct (Calculator'evaluate'params'newtype_ struct) = struct instance (Untyped.HasMessage (Calculator'evaluate'params msg)) where type InMessage (Calculator'evaluate'params msg) = msg message (Calculator'evaluate'params'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Calculator'evaluate'params msg)) where messageDefault msg = (Calculator'evaluate'params'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Calculator'evaluate'params msg)) where fromPtr msg ptr = (Calculator'evaluate'params'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Calculator'evaluate'params (Message.MutMsg s))) where toPtr msg (Calculator'evaluate'params'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Calculator'evaluate'params (Message.MutMsg s))) where new msg = (Calculator'evaluate'params'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (Calculator'evaluate'params msg)) where newtype List msg (Calculator'evaluate'params msg) = Calculator'evaluate'params'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Calculator'evaluate'params'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Calculator'evaluate'params'List_ l) = (Untyped.ListStruct l) length (Calculator'evaluate'params'List_ l) = (Untyped.length l) index i (Calculator'evaluate'params'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Calculator'evaluate'params (Message.MutMsg s))) where setIndex (Calculator'evaluate'params'newtype_ elt) i (Calculator'evaluate'params'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Calculator'evaluate'params'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_Calculator'evaluate'params'expression :: ((Untyped.ReadCtx m msg)) => (Calculator'evaluate'params msg) -> (m (Expression msg)) get_Calculator'evaluate'params'expression (Calculator'evaluate'params'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Calculator'evaluate'params'expression :: ((Untyped.RWCtx m s)) => (Calculator'evaluate'params (Message.MutMsg s)) -> (Expression (Message.MutMsg s)) -> (m ()) set_Calculator'evaluate'params'expression (Calculator'evaluate'params'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Calculator'evaluate'params'expression :: ((Untyped.ReadCtx m msg)) => (Calculator'evaluate'params msg) -> (m Std_.Bool) has_Calculator'evaluate'params'expression (Calculator'evaluate'params'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) new_Calculator'evaluate'params'expression :: ((Untyped.RWCtx m s)) => (Calculator'evaluate'params (Message.MutMsg s)) -> (m (Expression (Message.MutMsg s))) new_Calculator'evaluate'params'expression struct = (do result <- (Classes.new (Untyped.message struct)) (set_Calculator'evaluate'params'expression struct result) (Std_.pure result) ) newtype Calculator'evaluate'results msg = Calculator'evaluate'results'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Calculator'evaluate'results) where tMsg f (Calculator'evaluate'results'newtype_ s) = (Calculator'evaluate'results'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Calculator'evaluate'results msg)) where fromStruct struct = (Std_.pure (Calculator'evaluate'results'newtype_ struct)) instance (Classes.ToStruct msg (Calculator'evaluate'results msg)) where toStruct (Calculator'evaluate'results'newtype_ struct) = struct instance (Untyped.HasMessage (Calculator'evaluate'results msg)) where type InMessage (Calculator'evaluate'results msg) = msg message (Calculator'evaluate'results'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Calculator'evaluate'results msg)) where messageDefault msg = (Calculator'evaluate'results'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Calculator'evaluate'results msg)) where fromPtr msg ptr = (Calculator'evaluate'results'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Calculator'evaluate'results (Message.MutMsg s))) where toPtr msg (Calculator'evaluate'results'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Calculator'evaluate'results (Message.MutMsg s))) where new msg = (Calculator'evaluate'results'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (Calculator'evaluate'results msg)) where newtype List msg (Calculator'evaluate'results msg) = Calculator'evaluate'results'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Calculator'evaluate'results'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Calculator'evaluate'results'List_ l) = (Untyped.ListStruct l) length (Calculator'evaluate'results'List_ l) = (Untyped.length l) index i (Calculator'evaluate'results'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Calculator'evaluate'results (Message.MutMsg s))) where setIndex (Calculator'evaluate'results'newtype_ elt) i (Calculator'evaluate'results'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Calculator'evaluate'results'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_Calculator'evaluate'results'value :: ((Untyped.ReadCtx m msg)) => (Calculator'evaluate'results msg) -> (m (Value msg)) get_Calculator'evaluate'results'value (Calculator'evaluate'results'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Calculator'evaluate'results'value :: ((Untyped.RWCtx m s)) => (Calculator'evaluate'results (Message.MutMsg s)) -> (Value (Message.MutMsg s)) -> (m ()) set_Calculator'evaluate'results'value (Calculator'evaluate'results'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Calculator'evaluate'results'value :: ((Untyped.ReadCtx m msg)) => (Calculator'evaluate'results msg) -> (m Std_.Bool) has_Calculator'evaluate'results'value (Calculator'evaluate'results'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) newtype Calculator'defFunction'params msg = Calculator'defFunction'params'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Calculator'defFunction'params) where tMsg f (Calculator'defFunction'params'newtype_ s) = (Calculator'defFunction'params'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Calculator'defFunction'params msg)) where fromStruct struct = (Std_.pure (Calculator'defFunction'params'newtype_ struct)) instance (Classes.ToStruct msg (Calculator'defFunction'params msg)) where toStruct (Calculator'defFunction'params'newtype_ struct) = struct instance (Untyped.HasMessage (Calculator'defFunction'params msg)) where type InMessage (Calculator'defFunction'params msg) = msg message (Calculator'defFunction'params'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Calculator'defFunction'params msg)) where messageDefault msg = (Calculator'defFunction'params'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Calculator'defFunction'params msg)) where fromPtr msg ptr = (Calculator'defFunction'params'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Calculator'defFunction'params (Message.MutMsg s))) where toPtr msg (Calculator'defFunction'params'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Calculator'defFunction'params (Message.MutMsg s))) where new msg = (Calculator'defFunction'params'newtype_ <$> (Untyped.allocStruct msg 1 1)) instance (Basics.ListElem msg (Calculator'defFunction'params msg)) where newtype List msg (Calculator'defFunction'params msg) = Calculator'defFunction'params'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Calculator'defFunction'params'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Calculator'defFunction'params'List_ l) = (Untyped.ListStruct l) length (Calculator'defFunction'params'List_ l) = (Untyped.length l) index i (Calculator'defFunction'params'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Calculator'defFunction'params (Message.MutMsg s))) where setIndex (Calculator'defFunction'params'newtype_ elt) i (Calculator'defFunction'params'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Calculator'defFunction'params'List_ <$> (Untyped.allocCompositeList msg 1 1 len)) get_Calculator'defFunction'params'paramCount :: ((Untyped.ReadCtx m msg)) => (Calculator'defFunction'params msg) -> (m Std_.Int32) get_Calculator'defFunction'params'paramCount (Calculator'defFunction'params'newtype_ struct) = (GenHelpers.getWordField struct 0 0 0) set_Calculator'defFunction'params'paramCount :: ((Untyped.RWCtx m s)) => (Calculator'defFunction'params (Message.MutMsg s)) -> Std_.Int32 -> (m ()) set_Calculator'defFunction'params'paramCount (Calculator'defFunction'params'newtype_ struct) value = (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word32) 0 0 0) get_Calculator'defFunction'params'body :: ((Untyped.ReadCtx m msg)) => (Calculator'defFunction'params msg) -> (m (Expression msg)) get_Calculator'defFunction'params'body (Calculator'defFunction'params'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Calculator'defFunction'params'body :: ((Untyped.RWCtx m s)) => (Calculator'defFunction'params (Message.MutMsg s)) -> (Expression (Message.MutMsg s)) -> (m ()) set_Calculator'defFunction'params'body (Calculator'defFunction'params'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Calculator'defFunction'params'body :: ((Untyped.ReadCtx m msg)) => (Calculator'defFunction'params msg) -> (m Std_.Bool) has_Calculator'defFunction'params'body (Calculator'defFunction'params'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) new_Calculator'defFunction'params'body :: ((Untyped.RWCtx m s)) => (Calculator'defFunction'params (Message.MutMsg s)) -> (m (Expression (Message.MutMsg s))) new_Calculator'defFunction'params'body struct = (do result <- (Classes.new (Untyped.message struct)) (set_Calculator'defFunction'params'body struct result) (Std_.pure result) ) newtype Calculator'defFunction'results msg = Calculator'defFunction'results'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Calculator'defFunction'results) where tMsg f (Calculator'defFunction'results'newtype_ s) = (Calculator'defFunction'results'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Calculator'defFunction'results msg)) where fromStruct struct = (Std_.pure (Calculator'defFunction'results'newtype_ struct)) instance (Classes.ToStruct msg (Calculator'defFunction'results msg)) where toStruct (Calculator'defFunction'results'newtype_ struct) = struct instance (Untyped.HasMessage (Calculator'defFunction'results msg)) where type InMessage (Calculator'defFunction'results msg) = msg message (Calculator'defFunction'results'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Calculator'defFunction'results msg)) where messageDefault msg = (Calculator'defFunction'results'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Calculator'defFunction'results msg)) where fromPtr msg ptr = (Calculator'defFunction'results'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Calculator'defFunction'results (Message.MutMsg s))) where toPtr msg (Calculator'defFunction'results'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Calculator'defFunction'results (Message.MutMsg s))) where new msg = (Calculator'defFunction'results'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (Calculator'defFunction'results msg)) where newtype List msg (Calculator'defFunction'results msg) = Calculator'defFunction'results'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Calculator'defFunction'results'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Calculator'defFunction'results'List_ l) = (Untyped.ListStruct l) length (Calculator'defFunction'results'List_ l) = (Untyped.length l) index i (Calculator'defFunction'results'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Calculator'defFunction'results (Message.MutMsg s))) where setIndex (Calculator'defFunction'results'newtype_ elt) i (Calculator'defFunction'results'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Calculator'defFunction'results'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_Calculator'defFunction'results'func :: ((Untyped.ReadCtx m msg)) => (Calculator'defFunction'results msg) -> (m (Function msg)) get_Calculator'defFunction'results'func (Calculator'defFunction'results'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Calculator'defFunction'results'func :: ((Untyped.RWCtx m s)) => (Calculator'defFunction'results (Message.MutMsg s)) -> (Function (Message.MutMsg s)) -> (m ()) set_Calculator'defFunction'results'func (Calculator'defFunction'results'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Calculator'defFunction'results'func :: ((Untyped.ReadCtx m msg)) => (Calculator'defFunction'results msg) -> (m Std_.Bool) has_Calculator'defFunction'results'func (Calculator'defFunction'results'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) newtype Calculator'getOperator'params msg = Calculator'getOperator'params'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Calculator'getOperator'params) where tMsg f (Calculator'getOperator'params'newtype_ s) = (Calculator'getOperator'params'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Calculator'getOperator'params msg)) where fromStruct struct = (Std_.pure (Calculator'getOperator'params'newtype_ struct)) instance (Classes.ToStruct msg (Calculator'getOperator'params msg)) where toStruct (Calculator'getOperator'params'newtype_ struct) = struct instance (Untyped.HasMessage (Calculator'getOperator'params msg)) where type InMessage (Calculator'getOperator'params msg) = msg message (Calculator'getOperator'params'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Calculator'getOperator'params msg)) where messageDefault msg = (Calculator'getOperator'params'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Calculator'getOperator'params msg)) where fromPtr msg ptr = (Calculator'getOperator'params'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Calculator'getOperator'params (Message.MutMsg s))) where toPtr msg (Calculator'getOperator'params'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Calculator'getOperator'params (Message.MutMsg s))) where new msg = (Calculator'getOperator'params'newtype_ <$> (Untyped.allocStruct msg 1 0)) instance (Basics.ListElem msg (Calculator'getOperator'params msg)) where newtype List msg (Calculator'getOperator'params msg) = Calculator'getOperator'params'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Calculator'getOperator'params'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Calculator'getOperator'params'List_ l) = (Untyped.ListStruct l) length (Calculator'getOperator'params'List_ l) = (Untyped.length l) index i (Calculator'getOperator'params'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Calculator'getOperator'params (Message.MutMsg s))) where setIndex (Calculator'getOperator'params'newtype_ elt) i (Calculator'getOperator'params'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Calculator'getOperator'params'List_ <$> (Untyped.allocCompositeList msg 1 0 len)) get_Calculator'getOperator'params'op :: ((Untyped.ReadCtx m msg)) => (Calculator'getOperator'params msg) -> (m Operator) get_Calculator'getOperator'params'op (Calculator'getOperator'params'newtype_ struct) = (GenHelpers.getWordField struct 0 0 0) set_Calculator'getOperator'params'op :: ((Untyped.RWCtx m s)) => (Calculator'getOperator'params (Message.MutMsg s)) -> Operator -> (m ()) set_Calculator'getOperator'params'op (Calculator'getOperator'params'newtype_ struct) value = (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word16) 0 0 0) newtype Calculator'getOperator'results msg = Calculator'getOperator'results'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Calculator'getOperator'results) where tMsg f (Calculator'getOperator'results'newtype_ s) = (Calculator'getOperator'results'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Calculator'getOperator'results msg)) where fromStruct struct = (Std_.pure (Calculator'getOperator'results'newtype_ struct)) instance (Classes.ToStruct msg (Calculator'getOperator'results msg)) where toStruct (Calculator'getOperator'results'newtype_ struct) = struct instance (Untyped.HasMessage (Calculator'getOperator'results msg)) where type InMessage (Calculator'getOperator'results msg) = msg message (Calculator'getOperator'results'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Calculator'getOperator'results msg)) where messageDefault msg = (Calculator'getOperator'results'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Calculator'getOperator'results msg)) where fromPtr msg ptr = (Calculator'getOperator'results'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Calculator'getOperator'results (Message.MutMsg s))) where toPtr msg (Calculator'getOperator'results'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Calculator'getOperator'results (Message.MutMsg s))) where new msg = (Calculator'getOperator'results'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (Calculator'getOperator'results msg)) where newtype List msg (Calculator'getOperator'results msg) = Calculator'getOperator'results'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Calculator'getOperator'results'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Calculator'getOperator'results'List_ l) = (Untyped.ListStruct l) length (Calculator'getOperator'results'List_ l) = (Untyped.length l) index i (Calculator'getOperator'results'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Calculator'getOperator'results (Message.MutMsg s))) where setIndex (Calculator'getOperator'results'newtype_ elt) i (Calculator'getOperator'results'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Calculator'getOperator'results'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_Calculator'getOperator'results'func :: ((Untyped.ReadCtx m msg)) => (Calculator'getOperator'results msg) -> (m (Function msg)) get_Calculator'getOperator'results'func (Calculator'getOperator'results'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Calculator'getOperator'results'func :: ((Untyped.RWCtx m s)) => (Calculator'getOperator'results (Message.MutMsg s)) -> (Function (Message.MutMsg s)) -> (m ()) set_Calculator'getOperator'results'func (Calculator'getOperator'results'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Calculator'getOperator'results'func :: ((Untyped.ReadCtx m msg)) => (Calculator'getOperator'results msg) -> (m Std_.Bool) has_Calculator'getOperator'results'func (Calculator'getOperator'results'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) newtype Expression msg = Expression'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Expression) where tMsg f (Expression'newtype_ s) = (Expression'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Expression msg)) where fromStruct struct = (Std_.pure (Expression'newtype_ struct)) instance (Classes.ToStruct msg (Expression msg)) where toStruct (Expression'newtype_ struct) = struct instance (Untyped.HasMessage (Expression msg)) where type InMessage (Expression msg) = msg message (Expression'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Expression msg)) where messageDefault msg = (Expression'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Expression msg)) where fromPtr msg ptr = (Expression'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Expression (Message.MutMsg s))) where toPtr msg (Expression'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Expression (Message.MutMsg s))) where new msg = (Expression'newtype_ <$> (Untyped.allocStruct msg 2 2)) instance (Basics.ListElem msg (Expression msg)) where newtype List msg (Expression msg) = Expression'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Expression'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Expression'List_ l) = (Untyped.ListStruct l) length (Expression'List_ l) = (Untyped.length l) index i (Expression'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Expression (Message.MutMsg s))) where setIndex (Expression'newtype_ elt) i (Expression'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Expression'List_ <$> (Untyped.allocCompositeList msg 2 2 len)) data Expression' msg = Expression'literal Std_.Double | Expression'previousResult (Value msg) | Expression'parameter Std_.Word32 | Expression'call (Expression'call msg) | Expression'unknown' Std_.Word16 instance (Classes.FromStruct msg (Expression' msg)) where fromStruct struct = (do tag <- (GenHelpers.getTag struct 4) case tag of 0 -> (Expression'literal <$> (GenHelpers.getWordField struct 0 0 0)) 1 -> (Expression'previousResult <$> (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) )) 2 -> (Expression'parameter <$> (GenHelpers.getWordField struct 0 0 0)) 3 -> (Expression'call <$> (Classes.fromStruct struct)) _ -> (Std_.pure (Expression'unknown' (Std_.fromIntegral tag))) ) get_Expression' :: ((Untyped.ReadCtx m msg)) => (Expression msg) -> (m (Expression' msg)) get_Expression' (Expression'newtype_ struct) = (Classes.fromStruct struct) set_Expression'literal :: ((Untyped.RWCtx m s)) => (Expression (Message.MutMsg s)) -> Std_.Double -> (m ()) set_Expression'literal (Expression'newtype_ struct) value = (do (GenHelpers.setWordField struct (0 :: Std_.Word16) 1 0 0) (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word64) 0 0 0) ) set_Expression'previousResult :: ((Untyped.RWCtx m s)) => (Expression (Message.MutMsg s)) -> (Value (Message.MutMsg s)) -> (m ()) set_Expression'previousResult (Expression'newtype_ struct) value = (do (GenHelpers.setWordField struct (1 :: Std_.Word16) 1 0 0) (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) ) set_Expression'parameter :: ((Untyped.RWCtx m s)) => (Expression (Message.MutMsg s)) -> Std_.Word32 -> (m ()) set_Expression'parameter (Expression'newtype_ struct) value = (do (GenHelpers.setWordField struct (2 :: Std_.Word16) 1 0 0) (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word32) 0 0 0) ) set_Expression'call :: ((Untyped.RWCtx m s)) => (Expression (Message.MutMsg s)) -> (m (Expression'call (Message.MutMsg s))) set_Expression'call (Expression'newtype_ struct) = (do (GenHelpers.setWordField struct (3 :: Std_.Word16) 1 0 0) (Classes.fromStruct struct) ) set_Expression'unknown' :: ((Untyped.RWCtx m s)) => (Expression (Message.MutMsg s)) -> Std_.Word16 -> (m ()) set_Expression'unknown' (Expression'newtype_ struct) value = (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word16) 1 0 0) newtype Expression'call msg = Expression'call'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Expression'call) where tMsg f (Expression'call'newtype_ s) = (Expression'call'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Expression'call msg)) where fromStruct struct = (Std_.pure (Expression'call'newtype_ struct)) instance (Classes.ToStruct msg (Expression'call msg)) where toStruct (Expression'call'newtype_ struct) = struct instance (Untyped.HasMessage (Expression'call msg)) where type InMessage (Expression'call msg) = msg message (Expression'call'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Expression'call msg)) where messageDefault msg = (Expression'call'newtype_ (Untyped.messageDefault msg)) get_Expression'call'function :: ((Untyped.ReadCtx m msg)) => (Expression'call msg) -> (m (Function msg)) get_Expression'call'function (Expression'call'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Expression'call'function :: ((Untyped.RWCtx m s)) => (Expression'call (Message.MutMsg s)) -> (Function (Message.MutMsg s)) -> (m ()) set_Expression'call'function (Expression'call'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Expression'call'function :: ((Untyped.ReadCtx m msg)) => (Expression'call msg) -> (m Std_.Bool) has_Expression'call'function (Expression'call'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) get_Expression'call'params :: ((Untyped.ReadCtx m msg)) => (Expression'call msg) -> (m (Basics.List msg (Expression msg))) get_Expression'call'params (Expression'call'newtype_ struct) = (do ptr <- (Untyped.getPtr 1 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Expression'call'params :: ((Untyped.RWCtx m s)) => (Expression'call (Message.MutMsg s)) -> (Basics.List (Message.MutMsg s) (Expression (Message.MutMsg s))) -> (m ()) set_Expression'call'params (Expression'call'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 1 struct) ) has_Expression'call'params :: ((Untyped.ReadCtx m msg)) => (Expression'call msg) -> (m Std_.Bool) has_Expression'call'params (Expression'call'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 1 struct)) new_Expression'call'params :: ((Untyped.RWCtx m s)) => Std_.Int -> (Expression'call (Message.MutMsg s)) -> (m (Basics.List (Message.MutMsg s) (Expression (Message.MutMsg s)))) new_Expression'call'params len struct = (do result <- (Classes.newList (Untyped.message struct) len) (set_Expression'call'params struct result) (Std_.pure result) ) newtype Value msg = Value'newtype_ (Std_.Maybe (Untyped.Cap msg)) instance (Classes.FromPtr msg (Value msg)) where fromPtr msg ptr = (Value'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Value (Message.MutMsg s))) where toPtr msg (Value'newtype_ (Std_.Nothing)) = (Std_.pure Std_.Nothing) toPtr msg (Value'newtype_ (Std_.Just cap)) = (Std_.pure (Std_.Just (Untyped.PtrCap cap))) newtype Value'read'params msg = Value'read'params'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Value'read'params) where tMsg f (Value'read'params'newtype_ s) = (Value'read'params'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Value'read'params msg)) where fromStruct struct = (Std_.pure (Value'read'params'newtype_ struct)) instance (Classes.ToStruct msg (Value'read'params msg)) where toStruct (Value'read'params'newtype_ struct) = struct instance (Untyped.HasMessage (Value'read'params msg)) where type InMessage (Value'read'params msg) = msg message (Value'read'params'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Value'read'params msg)) where messageDefault msg = (Value'read'params'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Value'read'params msg)) where fromPtr msg ptr = (Value'read'params'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Value'read'params (Message.MutMsg s))) where toPtr msg (Value'read'params'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Value'read'params (Message.MutMsg s))) where new msg = (Value'read'params'newtype_ <$> (Untyped.allocStruct msg 0 0)) instance (Basics.ListElem msg (Value'read'params msg)) where newtype List msg (Value'read'params msg) = Value'read'params'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Value'read'params'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Value'read'params'List_ l) = (Untyped.ListStruct l) length (Value'read'params'List_ l) = (Untyped.length l) index i (Value'read'params'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Value'read'params (Message.MutMsg s))) where setIndex (Value'read'params'newtype_ elt) i (Value'read'params'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Value'read'params'List_ <$> (Untyped.allocCompositeList msg 0 0 len)) newtype Value'read'results msg = Value'read'results'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Value'read'results) where tMsg f (Value'read'results'newtype_ s) = (Value'read'results'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Value'read'results msg)) where fromStruct struct = (Std_.pure (Value'read'results'newtype_ struct)) instance (Classes.ToStruct msg (Value'read'results msg)) where toStruct (Value'read'results'newtype_ struct) = struct instance (Untyped.HasMessage (Value'read'results msg)) where type InMessage (Value'read'results msg) = msg message (Value'read'results'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Value'read'results msg)) where messageDefault msg = (Value'read'results'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Value'read'results msg)) where fromPtr msg ptr = (Value'read'results'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Value'read'results (Message.MutMsg s))) where toPtr msg (Value'read'results'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Value'read'results (Message.MutMsg s))) where new msg = (Value'read'results'newtype_ <$> (Untyped.allocStruct msg 1 0)) instance (Basics.ListElem msg (Value'read'results msg)) where newtype List msg (Value'read'results msg) = Value'read'results'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Value'read'results'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Value'read'results'List_ l) = (Untyped.ListStruct l) length (Value'read'results'List_ l) = (Untyped.length l) index i (Value'read'results'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Value'read'results (Message.MutMsg s))) where setIndex (Value'read'results'newtype_ elt) i (Value'read'results'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Value'read'results'List_ <$> (Untyped.allocCompositeList msg 1 0 len)) get_Value'read'results'value :: ((Untyped.ReadCtx m msg)) => (Value'read'results msg) -> (m Std_.Double) get_Value'read'results'value (Value'read'results'newtype_ struct) = (GenHelpers.getWordField struct 0 0 0) set_Value'read'results'value :: ((Untyped.RWCtx m s)) => (Value'read'results (Message.MutMsg s)) -> Std_.Double -> (m ()) set_Value'read'results'value (Value'read'results'newtype_ struct) value = (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word64) 0 0 0) newtype Function msg = Function'newtype_ (Std_.Maybe (Untyped.Cap msg)) instance (Classes.FromPtr msg (Function msg)) where fromPtr msg ptr = (Function'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Function (Message.MutMsg s))) where toPtr msg (Function'newtype_ (Std_.Nothing)) = (Std_.pure Std_.Nothing) toPtr msg (Function'newtype_ (Std_.Just cap)) = (Std_.pure (Std_.Just (Untyped.PtrCap cap))) newtype Function'call'params msg = Function'call'params'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Function'call'params) where tMsg f (Function'call'params'newtype_ s) = (Function'call'params'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Function'call'params msg)) where fromStruct struct = (Std_.pure (Function'call'params'newtype_ struct)) instance (Classes.ToStruct msg (Function'call'params msg)) where toStruct (Function'call'params'newtype_ struct) = struct instance (Untyped.HasMessage (Function'call'params msg)) where type InMessage (Function'call'params msg) = msg message (Function'call'params'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Function'call'params msg)) where messageDefault msg = (Function'call'params'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Function'call'params msg)) where fromPtr msg ptr = (Function'call'params'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Function'call'params (Message.MutMsg s))) where toPtr msg (Function'call'params'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Function'call'params (Message.MutMsg s))) where new msg = (Function'call'params'newtype_ <$> (Untyped.allocStruct msg 0 1)) instance (Basics.ListElem msg (Function'call'params msg)) where newtype List msg (Function'call'params msg) = Function'call'params'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Function'call'params'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Function'call'params'List_ l) = (Untyped.ListStruct l) length (Function'call'params'List_ l) = (Untyped.length l) index i (Function'call'params'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Function'call'params (Message.MutMsg s))) where setIndex (Function'call'params'newtype_ elt) i (Function'call'params'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Function'call'params'List_ <$> (Untyped.allocCompositeList msg 0 1 len)) get_Function'call'params'params :: ((Untyped.ReadCtx m msg)) => (Function'call'params msg) -> (m (Basics.List msg Std_.Double)) get_Function'call'params'params (Function'call'params'newtype_ struct) = (do ptr <- (Untyped.getPtr 0 struct) (Classes.fromPtr (Untyped.message struct) ptr) ) set_Function'call'params'params :: ((Untyped.RWCtx m s)) => (Function'call'params (Message.MutMsg s)) -> (Basics.List (Message.MutMsg s) Std_.Double) -> (m ()) set_Function'call'params'params (Function'call'params'newtype_ struct) value = (do ptr <- (Classes.toPtr (Untyped.message struct) value) (Untyped.setPtr ptr 0 struct) ) has_Function'call'params'params :: ((Untyped.ReadCtx m msg)) => (Function'call'params msg) -> (m Std_.Bool) has_Function'call'params'params (Function'call'params'newtype_ struct) = (Std_.isJust <$> (Untyped.getPtr 0 struct)) new_Function'call'params'params :: ((Untyped.RWCtx m s)) => Std_.Int -> (Function'call'params (Message.MutMsg s)) -> (m (Basics.List (Message.MutMsg s) Std_.Double)) new_Function'call'params'params len struct = (do result <- (Classes.newList (Untyped.message struct) len) (set_Function'call'params'params struct result) (Std_.pure result) ) newtype Function'call'results msg = Function'call'results'newtype_ (Untyped.Struct msg) instance (Untyped.TraverseMsg Function'call'results) where tMsg f (Function'call'results'newtype_ s) = (Function'call'results'newtype_ <$> (Untyped.tMsg f s)) instance (Classes.FromStruct msg (Function'call'results msg)) where fromStruct struct = (Std_.pure (Function'call'results'newtype_ struct)) instance (Classes.ToStruct msg (Function'call'results msg)) where toStruct (Function'call'results'newtype_ struct) = struct instance (Untyped.HasMessage (Function'call'results msg)) where type InMessage (Function'call'results msg) = msg message (Function'call'results'newtype_ struct) = (Untyped.message struct) instance (Untyped.MessageDefault (Function'call'results msg)) where messageDefault msg = (Function'call'results'newtype_ (Untyped.messageDefault msg)) instance (Classes.FromPtr msg (Function'call'results msg)) where fromPtr msg ptr = (Function'call'results'newtype_ <$> (Classes.fromPtr msg ptr)) instance (Classes.ToPtr s (Function'call'results (Message.MutMsg s))) where toPtr msg (Function'call'results'newtype_ struct) = (Classes.toPtr msg struct) instance (Classes.Allocate s (Function'call'results (Message.MutMsg s))) where new msg = (Function'call'results'newtype_ <$> (Untyped.allocStruct msg 1 0)) instance (Basics.ListElem msg (Function'call'results msg)) where newtype List msg (Function'call'results msg) = Function'call'results'List_ (Untyped.ListOf msg (Untyped.Struct msg)) listFromPtr msg ptr = (Function'call'results'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Function'call'results'List_ l) = (Untyped.ListStruct l) length (Function'call'results'List_ l) = (Untyped.length l) index i (Function'call'results'List_ l) = (do elt <- (Untyped.index i l) (Classes.fromStruct elt) ) instance (Basics.MutListElem s (Function'call'results (Message.MutMsg s))) where setIndex (Function'call'results'newtype_ elt) i (Function'call'results'List_ l) = (Untyped.setIndex elt i l) newList msg len = (Function'call'results'List_ <$> (Untyped.allocCompositeList msg 1 0 len)) get_Function'call'results'value :: ((Untyped.ReadCtx m msg)) => (Function'call'results msg) -> (m Std_.Double) get_Function'call'results'value (Function'call'results'newtype_ struct) = (GenHelpers.getWordField struct 0 0 0) set_Function'call'results'value :: ((Untyped.RWCtx m s)) => (Function'call'results (Message.MutMsg s)) -> Std_.Double -> (m ()) set_Function'call'results'value (Function'call'results'newtype_ struct) value = (GenHelpers.setWordField struct ((Std_.fromIntegral (Classes.toWord value)) :: Std_.Word64) 0 0 0) data Operator = Operator'add | Operator'subtract | Operator'multiply | Operator'divide | Operator'unknown' Std_.Word16 deriving(Std_.Show ,Std_.Read ,Std_.Eq ,Generics.Generic) instance (Classes.IsWord Operator) where fromWord n = case ((Std_.fromIntegral n) :: Std_.Word16) of 0 -> Operator'add 1 -> Operator'subtract 2 -> Operator'multiply 3 -> Operator'divide tag -> (Operator'unknown' tag) toWord (Operator'add) = 0 toWord (Operator'subtract) = 1 toWord (Operator'multiply) = 2 toWord (Operator'divide) = 3 toWord (Operator'unknown' tag) = (Std_.fromIntegral tag) instance (Std_.Enum Operator) where fromEnum x = (Std_.fromIntegral (Classes.toWord x)) toEnum x = (Classes.fromWord (Std_.fromIntegral x)) instance (Basics.ListElem msg Operator) where newtype List msg Operator = Operator'List_ (Untyped.ListOf msg Std_.Word16) index i (Operator'List_ l) = (Classes.fromWord <$> (Std_.fromIntegral <$> (Untyped.index i l))) listFromPtr msg ptr = (Operator'List_ <$> (Classes.fromPtr msg ptr)) toUntypedList (Operator'List_ l) = (Untyped.List16 l) length (Operator'List_ l) = (Untyped.length l) instance (Classes.MutListElem s Operator) where setIndex elt i (Operator'List_ l) = (Untyped.setIndex (Std_.fromIntegral (Classes.toWord elt)) i l) newList msg size = (Operator'List_ <$> (Untyped.allocList16 msg size))