{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.Integrator ( Integrator, IntegratorClass(..), integrator__0, integrator__1, integrator__2, integrator_clone, integrator_doc, integrator_getDAE, integrator_hasPlugin, integrator_integrate, integrator_integrateB, integrator_loadPlugin, integrator_printStats, integrator_reset, integrator_resetB, integrator_setStopTime, ) 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__Integrator__CONSTRUCTOR__0" c_casadi__Integrator__CONSTRUCTOR__0 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr Function' -> IO (Ptr Integrator') casadi__Integrator__CONSTRUCTOR__0 :: String -> Function -> IO Integrator casadi__Integrator__CONSTRUCTOR__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__CONSTRUCTOR__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator__0 :: String -> Function -> IO Integrator integrator__0 = casadi__Integrator__CONSTRUCTOR__0 -- direct wrapper foreign import ccall unsafe "casadi__Integrator__CONSTRUCTOR__1" c_casadi__Integrator__CONSTRUCTOR__1 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr Function' -> Ptr Function' -> IO (Ptr Integrator') casadi__Integrator__CONSTRUCTOR__1 :: String -> Function -> Function -> IO Integrator casadi__Integrator__CONSTRUCTOR__1 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__CONSTRUCTOR__1 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator__1 :: String -> Function -> Function -> IO Integrator integrator__1 = casadi__Integrator__CONSTRUCTOR__1 -- direct wrapper foreign import ccall unsafe "casadi__Integrator__CONSTRUCTOR__2" c_casadi__Integrator__CONSTRUCTOR__2 :: Ptr (Ptr StdString) -> IO (Ptr Integrator') casadi__Integrator__CONSTRUCTOR__2 :: IO Integrator casadi__Integrator__CONSTRUCTOR__2 = do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__CONSTRUCTOR__2 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator__2 :: IO Integrator integrator__2 = casadi__Integrator__CONSTRUCTOR__2 -- direct wrapper foreign import ccall unsafe "casadi__Integrator__clone" c_casadi__Integrator__clone :: Ptr (Ptr StdString) -> Ptr Integrator' -> IO (Ptr Integrator') casadi__Integrator__clone :: Integrator -> IO Integrator casadi__Integrator__clone x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__clone errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_clone :: IntegratorClass a => a -> IO Integrator integrator_clone x = casadi__Integrator__clone (castIntegrator x) -- direct wrapper foreign import ccall unsafe "casadi__Integrator__doc" c_casadi__Integrator__doc :: Ptr (Ptr StdString) -> Ptr StdString -> IO (Ptr StdString) casadi__Integrator__doc :: String -> IO String casadi__Integrator__doc x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__doc errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_doc :: String -> IO String integrator_doc = casadi__Integrator__doc -- direct wrapper foreign import ccall unsafe "casadi__Integrator__getDAE" c_casadi__Integrator__getDAE :: Ptr (Ptr StdString) -> Ptr Integrator' -> IO (Ptr Function') casadi__Integrator__getDAE :: Integrator -> IO Function casadi__Integrator__getDAE x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__getDAE errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_getDAE :: IntegratorClass a => a -> IO Function integrator_getDAE x = casadi__Integrator__getDAE (castIntegrator x) -- direct wrapper foreign import ccall unsafe "casadi__Integrator__hasPlugin" c_casadi__Integrator__hasPlugin :: Ptr (Ptr StdString) -> Ptr StdString -> IO CInt casadi__Integrator__hasPlugin :: String -> IO Bool casadi__Integrator__hasPlugin x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__hasPlugin errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_hasPlugin :: String -> IO Bool integrator_hasPlugin = casadi__Integrator__hasPlugin -- direct wrapper foreign import ccall unsafe "casadi__Integrator__integrate" c_casadi__Integrator__integrate :: Ptr (Ptr StdString) -> Ptr Integrator' -> CDouble -> IO () casadi__Integrator__integrate :: Integrator -> Double -> IO () casadi__Integrator__integrate x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__integrate errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_integrate :: IntegratorClass a => a -> Double -> IO () integrator_integrate x = casadi__Integrator__integrate (castIntegrator x) -- direct wrapper foreign import ccall unsafe "casadi__Integrator__integrateB" c_casadi__Integrator__integrateB :: Ptr (Ptr StdString) -> Ptr Integrator' -> CDouble -> IO () casadi__Integrator__integrateB :: Integrator -> Double -> IO () casadi__Integrator__integrateB x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__integrateB errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_integrateB :: IntegratorClass a => a -> Double -> IO () integrator_integrateB x = casadi__Integrator__integrateB (castIntegrator x) -- direct wrapper foreign import ccall unsafe "casadi__Integrator__loadPlugin" c_casadi__Integrator__loadPlugin :: Ptr (Ptr StdString) -> Ptr StdString -> IO () casadi__Integrator__loadPlugin :: String -> IO () casadi__Integrator__loadPlugin x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__loadPlugin errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_loadPlugin :: String -> IO () integrator_loadPlugin = casadi__Integrator__loadPlugin -- direct wrapper foreign import ccall unsafe "casadi__Integrator__printStats" c_casadi__Integrator__printStats :: Ptr (Ptr StdString) -> Ptr Integrator' -> IO () casadi__Integrator__printStats :: Integrator -> IO () casadi__Integrator__printStats x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__printStats errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_printStats :: IntegratorClass a => a -> IO () integrator_printStats x = casadi__Integrator__printStats (castIntegrator x) -- direct wrapper foreign import ccall unsafe "casadi__Integrator__reset" c_casadi__Integrator__reset :: Ptr (Ptr StdString) -> Ptr Integrator' -> IO () casadi__Integrator__reset :: Integrator -> IO () casadi__Integrator__reset x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__reset errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_reset :: IntegratorClass a => a -> IO () integrator_reset x = casadi__Integrator__reset (castIntegrator x) -- direct wrapper foreign import ccall unsafe "casadi__Integrator__resetB" c_casadi__Integrator__resetB :: Ptr (Ptr StdString) -> Ptr Integrator' -> IO () casadi__Integrator__resetB :: Integrator -> IO () casadi__Integrator__resetB x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__resetB errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_resetB :: IntegratorClass a => a -> IO () integrator_resetB x = casadi__Integrator__resetB (castIntegrator x) -- direct wrapper foreign import ccall unsafe "casadi__Integrator__setStopTime" c_casadi__Integrator__setStopTime :: Ptr (Ptr StdString) -> Ptr Integrator' -> CDouble -> IO () casadi__Integrator__setStopTime :: Integrator -> Double -> IO () casadi__Integrator__setStopTime x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Integrator__setStopTime errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper integrator_setStopTime :: IntegratorClass a => a -> Double -> IO () integrator_setStopTime x = casadi__Integrator__setStopTime (castIntegrator x)