{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.ControlSimulator ( ControlSimulator, ControlSimulatorClass(..), controlSimulator__0, controlSimulator__1, controlSimulator__2, controlSimulator__3, controlSimulator__4, controlSimulator_getMajorIndex, controlSimulator_getMinorT, controlSimulator_getMinorU, ) 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.Core.Classes.PrintableObject 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 instance Show ControlSimulator where show = unsafePerformIO . printableObject_getDescription -- direct wrapper foreign import ccall unsafe "casadi__ControlSimulator__CONSTRUCTOR__0" c_casadi__ControlSimulator__CONSTRUCTOR__0 :: Ptr (Ptr StdString) -> Ptr Function' -> Ptr DMatrix' -> IO (Ptr ControlSimulator') casadi__ControlSimulator__CONSTRUCTOR__0 :: Function -> DMatrix -> IO ControlSimulator casadi__ControlSimulator__CONSTRUCTOR__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__ControlSimulator__CONSTRUCTOR__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper controlSimulator__0 :: Function -> DMatrix -> IO ControlSimulator controlSimulator__0 = casadi__ControlSimulator__CONSTRUCTOR__0 -- direct wrapper foreign import ccall unsafe "casadi__ControlSimulator__CONSTRUCTOR__1" c_casadi__ControlSimulator__CONSTRUCTOR__1 :: Ptr (Ptr StdString) -> Ptr Function' -> Ptr (StdVec CDouble) -> IO (Ptr ControlSimulator') casadi__ControlSimulator__CONSTRUCTOR__1 :: Function -> Vector Double -> IO ControlSimulator casadi__ControlSimulator__CONSTRUCTOR__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__ControlSimulator__CONSTRUCTOR__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper controlSimulator__1 :: Function -> Vector Double -> IO ControlSimulator controlSimulator__1 = casadi__ControlSimulator__CONSTRUCTOR__1 -- direct wrapper foreign import ccall unsafe "casadi__ControlSimulator__CONSTRUCTOR__2" c_casadi__ControlSimulator__CONSTRUCTOR__2 :: Ptr (Ptr StdString) -> Ptr Function' -> Ptr Function' -> Ptr DMatrix' -> IO (Ptr ControlSimulator') casadi__ControlSimulator__CONSTRUCTOR__2 :: Function -> Function -> DMatrix -> IO ControlSimulator casadi__ControlSimulator__CONSTRUCTOR__2 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__ControlSimulator__CONSTRUCTOR__2 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper controlSimulator__2 :: Function -> Function -> DMatrix -> IO ControlSimulator controlSimulator__2 = casadi__ControlSimulator__CONSTRUCTOR__2 -- direct wrapper foreign import ccall unsafe "casadi__ControlSimulator__CONSTRUCTOR__3" c_casadi__ControlSimulator__CONSTRUCTOR__3 :: Ptr (Ptr StdString) -> Ptr Function' -> Ptr Function' -> Ptr (StdVec CDouble) -> IO (Ptr ControlSimulator') casadi__ControlSimulator__CONSTRUCTOR__3 :: Function -> Function -> Vector Double -> IO ControlSimulator casadi__ControlSimulator__CONSTRUCTOR__3 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__ControlSimulator__CONSTRUCTOR__3 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper controlSimulator__3 :: Function -> Function -> Vector Double -> IO ControlSimulator controlSimulator__3 = casadi__ControlSimulator__CONSTRUCTOR__3 -- direct wrapper foreign import ccall unsafe "casadi__ControlSimulator__CONSTRUCTOR__4" c_casadi__ControlSimulator__CONSTRUCTOR__4 :: Ptr (Ptr StdString) -> IO (Ptr ControlSimulator') casadi__ControlSimulator__CONSTRUCTOR__4 :: IO ControlSimulator casadi__ControlSimulator__CONSTRUCTOR__4 = do errStrPtrP <- new nullPtr ret <- c_casadi__ControlSimulator__CONSTRUCTOR__4 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper controlSimulator__4 :: IO ControlSimulator controlSimulator__4 = casadi__ControlSimulator__CONSTRUCTOR__4 -- direct wrapper foreign import ccall unsafe "casadi__ControlSimulator__getMajorIndex" c_casadi__ControlSimulator__getMajorIndex :: Ptr (Ptr StdString) -> Ptr ControlSimulator' -> IO (Ptr (StdVec CInt)) casadi__ControlSimulator__getMajorIndex :: ControlSimulator -> IO (Vector Int) casadi__ControlSimulator__getMajorIndex x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__ControlSimulator__getMajorIndex errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper controlSimulator_getMajorIndex :: ControlSimulatorClass a => a -> IO (Vector Int) controlSimulator_getMajorIndex x = casadi__ControlSimulator__getMajorIndex (castControlSimulator x) -- direct wrapper foreign import ccall unsafe "casadi__ControlSimulator__getMinorT" c_casadi__ControlSimulator__getMinorT :: Ptr (Ptr StdString) -> Ptr ControlSimulator' -> IO (Ptr (StdVec CDouble)) casadi__ControlSimulator__getMinorT :: ControlSimulator -> IO (Vector Double) casadi__ControlSimulator__getMinorT x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__ControlSimulator__getMinorT errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper controlSimulator_getMinorT :: ControlSimulatorClass a => a -> IO (Vector Double) controlSimulator_getMinorT x = casadi__ControlSimulator__getMinorT (castControlSimulator x) -- direct wrapper foreign import ccall unsafe "casadi__ControlSimulator__getMinorU" c_casadi__ControlSimulator__getMinorU :: Ptr (Ptr StdString) -> Ptr ControlSimulator' -> IO (Ptr DMatrix') casadi__ControlSimulator__getMinorU :: ControlSimulator -> IO DMatrix casadi__ControlSimulator__getMinorU x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__ControlSimulator__getMinorU errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper controlSimulator_getMinorU :: ControlSimulatorClass a => a -> IO DMatrix controlSimulator_getMinorU x = casadi__ControlSimulator__getMinorU (castControlSimulator x)