{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.Compiler ( Compiler, CompilerClass(..), compiler__0, compiler__1, compiler__2, compiler_doc, compiler_hasPlugin, compiler_loadPlugin, compiler_plugin_name, ) 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__Compiler__CONSTRUCTOR__0" c_casadi__Compiler__CONSTRUCTOR__0 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr StdString -> IO (Ptr Compiler') casadi__Compiler__CONSTRUCTOR__0 :: String -> String -> IO Compiler casadi__Compiler__CONSTRUCTOR__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Compiler__CONSTRUCTOR__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper compiler__0 :: String -> String -> IO Compiler compiler__0 = casadi__Compiler__CONSTRUCTOR__0 -- direct wrapper foreign import ccall unsafe "casadi__Compiler__CONSTRUCTOR__1" c_casadi__Compiler__CONSTRUCTOR__1 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr StdString -> Ptr (StdMap StdString (Ptr GenericType')) -> IO (Ptr Compiler') casadi__Compiler__CONSTRUCTOR__1 :: String -> String -> M.Map String GenericType -> IO Compiler casadi__Compiler__CONSTRUCTOR__1 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Compiler__CONSTRUCTOR__1 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper compiler__1 :: String -> String -> M.Map String GenericType -> IO Compiler compiler__1 = casadi__Compiler__CONSTRUCTOR__1 -- direct wrapper foreign import ccall unsafe "casadi__Compiler__CONSTRUCTOR__2" c_casadi__Compiler__CONSTRUCTOR__2 :: Ptr (Ptr StdString) -> IO (Ptr Compiler') casadi__Compiler__CONSTRUCTOR__2 :: IO Compiler casadi__Compiler__CONSTRUCTOR__2 = do errStrPtrP <- new nullPtr ret <- c_casadi__Compiler__CONSTRUCTOR__2 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper compiler__2 :: IO Compiler compiler__2 = casadi__Compiler__CONSTRUCTOR__2 -- direct wrapper foreign import ccall unsafe "casadi__Compiler__doc" c_casadi__Compiler__doc :: Ptr (Ptr StdString) -> Ptr StdString -> IO (Ptr StdString) casadi__Compiler__doc :: String -> IO String casadi__Compiler__doc x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Compiler__doc errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper compiler_doc :: String -> IO String compiler_doc = casadi__Compiler__doc -- direct wrapper foreign import ccall unsafe "casadi__Compiler__hasPlugin" c_casadi__Compiler__hasPlugin :: Ptr (Ptr StdString) -> Ptr StdString -> IO CInt casadi__Compiler__hasPlugin :: String -> IO Bool casadi__Compiler__hasPlugin x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Compiler__hasPlugin errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper compiler_hasPlugin :: String -> IO Bool compiler_hasPlugin = casadi__Compiler__hasPlugin -- direct wrapper foreign import ccall unsafe "casadi__Compiler__loadPlugin" c_casadi__Compiler__loadPlugin :: Ptr (Ptr StdString) -> Ptr StdString -> IO () casadi__Compiler__loadPlugin :: String -> IO () casadi__Compiler__loadPlugin x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Compiler__loadPlugin errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper compiler_loadPlugin :: String -> IO () compiler_loadPlugin = casadi__Compiler__loadPlugin -- direct wrapper foreign import ccall unsafe "casadi__Compiler__plugin_name" c_casadi__Compiler__plugin_name :: Ptr (Ptr StdString) -> Ptr Compiler' -> IO (Ptr StdString) casadi__Compiler__plugin_name :: Compiler -> IO String casadi__Compiler__plugin_name x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__Compiler__plugin_name errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper compiler_plugin_name :: CompilerClass a => a -> IO String compiler_plugin_name x = casadi__Compiler__plugin_name (castCompiler x)