{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.CasadiOptions ( CasadiOptions, CasadiOptionsClass(..), casadiOptions_getAllowedInternalAPI, casadiOptions_getCatchErrorsSwig, casadiOptions_getProfilingBinary, casadiOptions_getSimplificationOnTheFly, casadiOptions_setAllowedInternalAPI, casadiOptions_setCatchErrorsSwig, casadiOptions_setProfilingBinary, casadiOptions_setPurgeSeeds__0, casadiOptions_setPurgeSeeds__1, casadiOptions_setSimplificationOnTheFly, casadiOptions_startProfiling, casadiOptions_stopProfiling, ) 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__CasadiOptions__getAllowedInternalAPI" c_casadi__CasadiOptions__getAllowedInternalAPI :: Ptr (Ptr StdString) -> IO CInt casadi__CasadiOptions__getAllowedInternalAPI :: IO Bool casadi__CasadiOptions__getAllowedInternalAPI = do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__getAllowedInternalAPI errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_getAllowedInternalAPI :: IO Bool casadiOptions_getAllowedInternalAPI = casadi__CasadiOptions__getAllowedInternalAPI -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__getCatchErrorsSwig" c_casadi__CasadiOptions__getCatchErrorsSwig :: Ptr (Ptr StdString) -> IO CInt casadi__CasadiOptions__getCatchErrorsSwig :: IO Bool casadi__CasadiOptions__getCatchErrorsSwig = do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__getCatchErrorsSwig errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_getCatchErrorsSwig :: IO Bool casadiOptions_getCatchErrorsSwig = casadi__CasadiOptions__getCatchErrorsSwig -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__getProfilingBinary" c_casadi__CasadiOptions__getProfilingBinary :: Ptr (Ptr StdString) -> IO CInt casadi__CasadiOptions__getProfilingBinary :: IO Bool casadi__CasadiOptions__getProfilingBinary = do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__getProfilingBinary errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_getProfilingBinary :: IO Bool casadiOptions_getProfilingBinary = casadi__CasadiOptions__getProfilingBinary -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__getSimplificationOnTheFly" c_casadi__CasadiOptions__getSimplificationOnTheFly :: Ptr (Ptr StdString) -> IO CInt casadi__CasadiOptions__getSimplificationOnTheFly :: IO Bool casadi__CasadiOptions__getSimplificationOnTheFly = do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__getSimplificationOnTheFly errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_getSimplificationOnTheFly :: IO Bool casadiOptions_getSimplificationOnTheFly = casadi__CasadiOptions__getSimplificationOnTheFly -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__setAllowedInternalAPI" c_casadi__CasadiOptions__setAllowedInternalAPI :: Ptr (Ptr StdString) -> CInt -> IO () casadi__CasadiOptions__setAllowedInternalAPI :: Bool -> IO () casadi__CasadiOptions__setAllowedInternalAPI x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__setAllowedInternalAPI errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_setAllowedInternalAPI :: Bool -> IO () casadiOptions_setAllowedInternalAPI = casadi__CasadiOptions__setAllowedInternalAPI -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__setCatchErrorsSwig" c_casadi__CasadiOptions__setCatchErrorsSwig :: Ptr (Ptr StdString) -> CInt -> IO () casadi__CasadiOptions__setCatchErrorsSwig :: Bool -> IO () casadi__CasadiOptions__setCatchErrorsSwig x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__setCatchErrorsSwig errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_setCatchErrorsSwig :: Bool -> IO () casadiOptions_setCatchErrorsSwig = casadi__CasadiOptions__setCatchErrorsSwig -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__setProfilingBinary" c_casadi__CasadiOptions__setProfilingBinary :: Ptr (Ptr StdString) -> CInt -> IO () casadi__CasadiOptions__setProfilingBinary :: Bool -> IO () casadi__CasadiOptions__setProfilingBinary x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__setProfilingBinary errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_setProfilingBinary :: Bool -> IO () casadiOptions_setProfilingBinary = casadi__CasadiOptions__setProfilingBinary -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__setPurgeSeeds__0" c_casadi__CasadiOptions__setPurgeSeeds__0 :: Ptr (Ptr StdString) -> IO CInt casadi__CasadiOptions__setPurgeSeeds__0 :: IO Bool casadi__CasadiOptions__setPurgeSeeds__0 = do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__setPurgeSeeds__0 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_setPurgeSeeds__0 :: IO Bool casadiOptions_setPurgeSeeds__0 = casadi__CasadiOptions__setPurgeSeeds__0 -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__setPurgeSeeds__1" c_casadi__CasadiOptions__setPurgeSeeds__1 :: Ptr (Ptr StdString) -> CInt -> IO () casadi__CasadiOptions__setPurgeSeeds__1 :: Bool -> IO () casadi__CasadiOptions__setPurgeSeeds__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__setPurgeSeeds__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_setPurgeSeeds__1 :: Bool -> IO () casadiOptions_setPurgeSeeds__1 = casadi__CasadiOptions__setPurgeSeeds__1 -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__setSimplificationOnTheFly" c_casadi__CasadiOptions__setSimplificationOnTheFly :: Ptr (Ptr StdString) -> CInt -> IO () casadi__CasadiOptions__setSimplificationOnTheFly :: Bool -> IO () casadi__CasadiOptions__setSimplificationOnTheFly x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__setSimplificationOnTheFly errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_setSimplificationOnTheFly :: Bool -> IO () casadiOptions_setSimplificationOnTheFly = casadi__CasadiOptions__setSimplificationOnTheFly -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__startProfiling" c_casadi__CasadiOptions__startProfiling :: Ptr (Ptr StdString) -> Ptr StdString -> IO () casadi__CasadiOptions__startProfiling :: String -> IO () casadi__CasadiOptions__startProfiling x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__startProfiling errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_startProfiling :: String -> IO () casadiOptions_startProfiling = casadi__CasadiOptions__startProfiling -- direct wrapper foreign import ccall unsafe "casadi__CasadiOptions__stopProfiling" c_casadi__CasadiOptions__stopProfiling :: Ptr (Ptr StdString) -> IO () casadi__CasadiOptions__stopProfiling :: IO () casadi__CasadiOptions__stopProfiling = do errStrPtrP <- new nullPtr ret <- c_casadi__CasadiOptions__stopProfiling errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper casadiOptions_stopProfiling :: IO () casadiOptions_stopProfiling = casadi__CasadiOptions__stopProfiling