{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.CustomFunction ( CustomFunction, CustomFunctionClass(..), customFunction__0, customFunction__1, customFunction__2, customFunction__3, customFunction__4, customFunction__5, customFunction__6, customFunction__7, customFunction__8, ) 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__CustomFunction__CONSTRUCTOR__0" c_casadi__CustomFunction__CONSTRUCTOR__0 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr CustomEvaluate' -> Ptr (StdPair (Ptr (StdMap StdString (Ptr Sparsity'))) (Ptr (StdVec (Ptr StdString)))) -> Ptr (StdPair (Ptr (StdMap StdString (Ptr Sparsity'))) (Ptr (StdVec (Ptr StdString)))) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__0 :: String -> CustomEvaluate -> (M.Map String Sparsity, Vector String) -> (M.Map String Sparsity, Vector String) -> IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__0 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__0 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__0 :: String -> CustomEvaluate -> (M.Map String Sparsity, Vector String) -> (M.Map String Sparsity, Vector String) -> IO CustomFunction customFunction__0 = casadi__CustomFunction__CONSTRUCTOR__0 -- direct wrapper foreign import ccall unsafe "casadi__CustomFunction__CONSTRUCTOR__1" c_casadi__CustomFunction__CONSTRUCTOR__1 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr CustomEvaluate' -> Ptr (StdPair (Ptr (StdMap StdString (Ptr Sparsity'))) (Ptr (StdVec (Ptr StdString)))) -> Ptr (StdPair (Ptr (StdMap StdString (Ptr Sparsity'))) (Ptr (StdVec (Ptr StdString)))) -> Ptr (StdMap StdString (Ptr GenericType')) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__1 :: String -> CustomEvaluate -> (M.Map String Sparsity, Vector String) -> (M.Map String Sparsity, Vector String) -> M.Map String GenericType -> IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__1 x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__1 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__1 :: String -> CustomEvaluate -> (M.Map String Sparsity, Vector String) -> (M.Map String Sparsity, Vector String) -> M.Map String GenericType -> IO CustomFunction customFunction__1 = casadi__CustomFunction__CONSTRUCTOR__1 -- direct wrapper foreign import ccall unsafe "casadi__CustomFunction__CONSTRUCTOR__2" c_casadi__CustomFunction__CONSTRUCTOR__2 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr CustomEvaluate' -> Ptr (StdVec (Ptr Sparsity')) -> Ptr (StdPair (Ptr (StdMap StdString (Ptr Sparsity'))) (Ptr (StdVec (Ptr StdString)))) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__2 :: String -> CustomEvaluate -> Vector Sparsity -> (M.Map String Sparsity, Vector String) -> IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__2 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__2 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__2 :: String -> CustomEvaluate -> Vector Sparsity -> (M.Map String Sparsity, Vector String) -> IO CustomFunction customFunction__2 = casadi__CustomFunction__CONSTRUCTOR__2 -- direct wrapper foreign import ccall unsafe "casadi__CustomFunction__CONSTRUCTOR__3" c_casadi__CustomFunction__CONSTRUCTOR__3 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr CustomEvaluate' -> Ptr (StdVec (Ptr Sparsity')) -> Ptr (StdPair (Ptr (StdMap StdString (Ptr Sparsity'))) (Ptr (StdVec (Ptr StdString)))) -> Ptr (StdMap StdString (Ptr GenericType')) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__3 :: String -> CustomEvaluate -> Vector Sparsity -> (M.Map String Sparsity, Vector String) -> M.Map String GenericType -> IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__3 x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__3 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__3 :: String -> CustomEvaluate -> Vector Sparsity -> (M.Map String Sparsity, Vector String) -> M.Map String GenericType -> IO CustomFunction customFunction__3 = casadi__CustomFunction__CONSTRUCTOR__3 -- direct wrapper foreign import ccall unsafe "casadi__CustomFunction__CONSTRUCTOR__4" c_casadi__CustomFunction__CONSTRUCTOR__4 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr CustomEvaluate' -> Ptr (StdPair (Ptr (StdMap StdString (Ptr Sparsity'))) (Ptr (StdVec (Ptr StdString)))) -> Ptr (StdVec (Ptr Sparsity')) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__4 :: String -> CustomEvaluate -> (M.Map String Sparsity, Vector String) -> Vector Sparsity -> IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__4 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__4 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__4 :: String -> CustomEvaluate -> (M.Map String Sparsity, Vector String) -> Vector Sparsity -> IO CustomFunction customFunction__4 = casadi__CustomFunction__CONSTRUCTOR__4 -- direct wrapper foreign import ccall unsafe "casadi__CustomFunction__CONSTRUCTOR__5" c_casadi__CustomFunction__CONSTRUCTOR__5 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr CustomEvaluate' -> Ptr (StdPair (Ptr (StdMap StdString (Ptr Sparsity'))) (Ptr (StdVec (Ptr StdString)))) -> Ptr (StdVec (Ptr Sparsity')) -> Ptr (StdMap StdString (Ptr GenericType')) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__5 :: String -> CustomEvaluate -> (M.Map String Sparsity, Vector String) -> Vector Sparsity -> M.Map String GenericType -> IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__5 x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__5 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__5 :: String -> CustomEvaluate -> (M.Map String Sparsity, Vector String) -> Vector Sparsity -> M.Map String GenericType -> IO CustomFunction customFunction__5 = casadi__CustomFunction__CONSTRUCTOR__5 -- direct wrapper foreign import ccall unsafe "casadi__CustomFunction__CONSTRUCTOR__6" c_casadi__CustomFunction__CONSTRUCTOR__6 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr CustomEvaluate' -> Ptr (StdVec (Ptr Sparsity')) -> Ptr (StdVec (Ptr Sparsity')) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__6 :: String -> CustomEvaluate -> Vector Sparsity -> Vector Sparsity -> IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__6 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__6 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__6 :: String -> CustomEvaluate -> Vector Sparsity -> Vector Sparsity -> IO CustomFunction customFunction__6 = casadi__CustomFunction__CONSTRUCTOR__6 -- direct wrapper foreign import ccall unsafe "casadi__CustomFunction__CONSTRUCTOR__7" c_casadi__CustomFunction__CONSTRUCTOR__7 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr CustomEvaluate' -> Ptr (StdVec (Ptr Sparsity')) -> Ptr (StdVec (Ptr Sparsity')) -> Ptr (StdMap StdString (Ptr GenericType')) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__7 :: String -> CustomEvaluate -> Vector Sparsity -> Vector Sparsity -> M.Map String GenericType -> IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__7 x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__7 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__7 :: String -> CustomEvaluate -> Vector Sparsity -> Vector Sparsity -> M.Map String GenericType -> IO CustomFunction customFunction__7 = casadi__CustomFunction__CONSTRUCTOR__7 -- direct wrapper foreign import ccall unsafe "casadi__CustomFunction__CONSTRUCTOR__8" c_casadi__CustomFunction__CONSTRUCTOR__8 :: Ptr (Ptr StdString) -> IO (Ptr CustomFunction') casadi__CustomFunction__CONSTRUCTOR__8 :: IO CustomFunction casadi__CustomFunction__CONSTRUCTOR__8 = do errStrPtrP <- new nullPtr ret <- c_casadi__CustomFunction__CONSTRUCTOR__8 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper customFunction__8 :: IO CustomFunction customFunction__8 = casadi__CustomFunction__CONSTRUCTOR__8