{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.DerivativeGenerator2 ( DerivativeGenerator2, DerivativeGenerator2Class(..), derivativeGenerator2, derivativeGenerator2_create, derivativeGenerator2_operator_call, derivativeGenerator2_original, ) where import Prelude hiding ( Functor ) import Data.Vector ( Vector ) import qualified Data.Map as M 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.FormatException ( formatException ) import Casadi.Internal.MarshalTypes ( StdVec, StdString, StdMap, StdPair ) -- 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__DerivativeGenerator2__CONSTRUCTOR" c_casadi__DerivativeGenerator2__CONSTRUCTOR :: Ptr (Ptr StdString) -> IO (Ptr DerivativeGenerator2') casadi__DerivativeGenerator2__CONSTRUCTOR :: IO DerivativeGenerator2 casadi__DerivativeGenerator2__CONSTRUCTOR = do errStrPtrP <- new nullPtr ret <- c_casadi__DerivativeGenerator2__CONSTRUCTOR errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper derivativeGenerator2 :: IO DerivativeGenerator2 derivativeGenerator2 = casadi__DerivativeGenerator2__CONSTRUCTOR -- direct wrapper foreign import ccall unsafe "casadi__DerivativeGenerator2__create" c_casadi__DerivativeGenerator2__create :: Ptr (Ptr StdString) -> Ptr DerivativeGenerator2' -> IO (Ptr DerivativeGenerator') casadi__DerivativeGenerator2__create :: DerivativeGenerator2 -> IO DerivativeGenerator casadi__DerivativeGenerator2__create x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DerivativeGenerator2__create errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper derivativeGenerator2_create :: DerivativeGenerator2Class a => a -> IO DerivativeGenerator derivativeGenerator2_create x = casadi__DerivativeGenerator2__create (castDerivativeGenerator2 x) -- direct wrapper foreign import ccall unsafe "casadi__DerivativeGenerator2__operator_call" c_casadi__DerivativeGenerator2__operator_call :: Ptr (Ptr StdString) -> Ptr DerivativeGenerator2' -> Ptr Function' -> CInt -> IO (Ptr Function') casadi__DerivativeGenerator2__operator_call :: DerivativeGenerator2 -> Function -> Int -> IO Function casadi__DerivativeGenerator2__operator_call x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DerivativeGenerator2__operator_call errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper derivativeGenerator2_operator_call :: DerivativeGenerator2Class a => a -> Function -> Int -> IO Function derivativeGenerator2_operator_call x = casadi__DerivativeGenerator2__operator_call (castDerivativeGenerator2 x) -- direct wrapper foreign import ccall unsafe "casadi__DerivativeGenerator2__original" c_casadi__DerivativeGenerator2__original :: Ptr (Ptr StdString) -> Ptr DerivativeGenerator2' -> Ptr Function' -> CInt -> CInt -> IO (Ptr Function') casadi__DerivativeGenerator2__original :: DerivativeGenerator2 -> Function -> Int -> Bool -> IO Function casadi__DerivativeGenerator2__original x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DerivativeGenerator2__original errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper derivativeGenerator2_original :: DerivativeGenerator2Class a => a -> Function -> Int -> Bool -> IO Function derivativeGenerator2_original x = casadi__DerivativeGenerator2__original (castDerivativeGenerator2 x)