{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.Variable ( Variable, VariableClass(..), variable, variable_getDescription, variable_getRepresentation, variable_name, variable_setName, ) where import Prelude hiding ( Functor ) import Data.Vector ( Vector ) import Foreign.C.Types import Foreign.Marshal ( new, free ) import Foreign.Storable ( peek ) import Foreign.Ptr ( Ptr, nullPtr ) import Foreign.ForeignPtr ( newForeignPtr ) import System.IO.Unsafe ( unsafePerformIO ) -- for show instances import Casadi.Internal.CToolsInstances ( ) import Casadi.Internal.FormatException ( formatException ) import Casadi.Internal.MarshalTypes ( StdVec, StdString) -- StdPair StdOstream' import Casadi.Internal.Marshal ( Marshal(..), withMarshal ) import Casadi.Internal.WrapReturn ( WrapReturn(..) ) import Casadi.Core.Data import Casadi.Core.Enums -- direct wrapper foreign import ccall unsafe "casadi__Variable__CONSTRUCTOR" c_casadi__Variable__CONSTRUCTOR :: Ptr (Ptr StdString) -> IO (Ptr Variable') casadi__Variable__CONSTRUCTOR :: IO Variable casadi__Variable__CONSTRUCTOR = do errStrPtrP <- new nullPtr ret <- c_casadi__Variable__CONSTRUCTOR errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper variable :: IO Variable variable = casadi__Variable__CONSTRUCTOR -- direct wrapper foreign import ccall unsafe "casadi__Variable__name" c_casadi__Variable__name :: Ptr (Ptr StdString) -> Ptr Variable' -> IO (Ptr StdString) casadi__Variable__name :: Variable -> IO String casadi__Variable__name x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Variable__name errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper variable_name :: VariableClass a => a -> IO String variable_name x = casadi__Variable__name (castVariable x) -- direct wrapper foreign import ccall unsafe "casadi__Variable__setName" c_casadi__Variable__setName :: Ptr (Ptr StdString) -> Ptr Variable' -> Ptr StdString -> IO () casadi__Variable__setName :: Variable -> String -> IO () casadi__Variable__setName x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Variable__setName errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper variable_setName :: VariableClass a => a -> String -> IO () variable_setName x = casadi__Variable__setName (castVariable x) -- direct wrapper foreign import ccall unsafe "casadi__Variable__getRepresentation" c_casadi__Variable__getRepresentation :: Ptr (Ptr StdString) -> Ptr Variable' -> IO (Ptr StdString) casadi__Variable__getRepresentation :: Variable -> IO String casadi__Variable__getRepresentation x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Variable__getRepresentation errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper variable_getRepresentation :: VariableClass a => a -> IO String variable_getRepresentation x = casadi__Variable__getRepresentation (castVariable x) -- direct wrapper foreign import ccall unsafe "casadi__Variable__getDescription" c_casadi__Variable__getDescription :: Ptr (Ptr StdString) -> Ptr Variable' -> IO (Ptr StdString) casadi__Variable__getDescription :: Variable -> IO String casadi__Variable__getDescription x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Variable__getDescription errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper variable_getDescription :: VariableClass a => a -> IO String variable_getDescription x = casadi__Variable__getDescription (castVariable x)