{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.DMatrix ( DMatrix, DMatrixClass(..), dmatrix_T, dmatrix__0, dmatrix__1, dmatrix__2, dmatrix__3, dmatrix__4, dmatrix__5, dmatrix__6, dmatrix__7, dmatrix__8, dmatrix___nonzero__, dmatrix_append, dmatrix_appendColumns, dmatrix_binary, dmatrix_className, dmatrix_clear, dmatrix_colind, dmatrix_dimString, dmatrix_enlarge__0, dmatrix_enlarge__1, dmatrix_erase__0, dmatrix_erase__1, dmatrix_erase__2, dmatrix_erase__3, dmatrix_eye, dmatrix_find__0, dmatrix_find__1, dmatrix_getColind, dmatrix_getDep__0, dmatrix_getDep__1, dmatrix_getDescription, dmatrix_getElementHash, dmatrix_getEqualityCheckingDepth, dmatrix_getIntValue, dmatrix_getNZ__0, dmatrix_getNZ__1, dmatrix_getNZ__2, dmatrix_getName, dmatrix_getNdeps, dmatrix_getRepresentation, dmatrix_getRow, dmatrix_getSparsity, dmatrix_getSym, dmatrix_getValue__0, dmatrix_getValue__1, dmatrix_get__0, dmatrix_get__1, dmatrix_get__2, dmatrix_get__3, dmatrix_get__4, dmatrix_get__5, dmatrix_get__6, dmatrix_get__7, dmatrix_hasDuplicates, dmatrix_hasNZ, dmatrix_hasNonStructuralZeros, dmatrix_inf__0, dmatrix_inf__1, dmatrix_inf__2, dmatrix_inf__3, dmatrix_inf__4, dmatrix_isCommutative, dmatrix_isConstant, dmatrix_isIdentity, dmatrix_isInteger, dmatrix_isLeaf, dmatrix_isMinusOne, dmatrix_isOne, dmatrix_isRegular, dmatrix_isSlice__0, dmatrix_isSlice__1, dmatrix_isSmooth, dmatrix_isSymbolic, dmatrix_isValidInput, dmatrix_isZero, dmatrix_iscolumn, dmatrix_isdense, dmatrix_isempty__0, dmatrix_isempty__1, dmatrix_isrow, dmatrix_isscalar__0, dmatrix_isscalar__1, dmatrix_issquare, dmatrix_istril, dmatrix_istriu, dmatrix_isvector, dmatrix_makeSparse__0, dmatrix_makeSparse__1, dmatrix_matrix_matrix, dmatrix_matrix_scalar, dmatrix_nan__0, dmatrix_nan__1, dmatrix_nan__2, dmatrix_nan__3, dmatrix_nan__4, dmatrix_nnz, dmatrix_nonzeros, dmatrix_nonzeros_int, dmatrix_numel__0, dmatrix_numel__1, dmatrix_ones__0, dmatrix_ones__1, dmatrix_ones__2, dmatrix_ones__3, dmatrix_ones__4, dmatrix_operator_minus, dmatrix_operator_plus, dmatrix_printDense, dmatrix_printScalar, dmatrix_printSparse, dmatrix_printSplit, dmatrix_printVector, dmatrix_printme, dmatrix_remove, dmatrix_reserve__0, dmatrix_reserve__1, dmatrix_resetInput, dmatrix_resize, dmatrix_row, dmatrix_sanityCheck__0, dmatrix_sanityCheck__1, dmatrix_scalar_matrix, dmatrix_setEqualityCheckingDepth__0, dmatrix_setEqualityCheckingDepth__1, dmatrix_setNZ__0, dmatrix_setNZ__1, dmatrix_setNZ__2, dmatrix_setNZ__3, dmatrix_setPrecision, dmatrix_setScientific, dmatrix_setSym, dmatrix_setValue__0, dmatrix_setValue__1, dmatrix_setWidth, dmatrix_setZero, dmatrix_set__0, dmatrix_set__1, dmatrix_set__10, dmatrix_set__2, dmatrix_set__3, dmatrix_set__4, dmatrix_set__5, dmatrix_set__6, dmatrix_set__7, dmatrix_set__8, dmatrix_set__9, dmatrix_shape__0, dmatrix_shape__1, dmatrix_size, dmatrix_size1, dmatrix_size2, dmatrix_sizeD, dmatrix_sizeL, dmatrix_sizeU, dmatrix_sparse__0, dmatrix_sparse__1, dmatrix_sparse__2, dmatrix_sparse__3, dmatrix_sparse__4, dmatrix_sparsity, dmatrix_sym__0, dmatrix_sym__1, dmatrix_sym__2, dmatrix_sym__3, dmatrix_sym__4, dmatrix_sym__5, dmatrix_sym__6, dmatrix_sym__7, dmatrix_sym__8, dmatrix_toSlice__0, dmatrix_toSlice__1, dmatrix_triplet__0, dmatrix_triplet__1, dmatrix_triplet__2, dmatrix_unary, dmatrix_zeros__0, dmatrix_zeros__1, dmatrix_zeros__2, dmatrix_zeros__3, dmatrix_zeros__4, ) 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__DMatrix__CONSTRUCTOR__0" c_casadi__DMatrix__CONSTRUCTOR__0 :: Ptr (Ptr StdString) -> Ptr (StdVec CInt) -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__0 :: Vector Int -> IO DMatrix casadi__DMatrix__CONSTRUCTOR__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__0 :: Vector Int -> IO DMatrix dmatrix__0 = casadi__DMatrix__CONSTRUCTOR__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__CONSTRUCTOR__1" c_casadi__DMatrix__CONSTRUCTOR__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__1 :: IMatrix -> IO DMatrix casadi__DMatrix__CONSTRUCTOR__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__1 :: IMatrix -> IO DMatrix dmatrix__1 = casadi__DMatrix__CONSTRUCTOR__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__CONSTRUCTOR__2" c_casadi__DMatrix__CONSTRUCTOR__2 :: Ptr (Ptr StdString) -> Ptr (StdVec (Ptr (StdVec CDouble))) -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__2 :: Vector (Vector Double) -> IO DMatrix casadi__DMatrix__CONSTRUCTOR__2 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__2 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__2 :: Vector (Vector Double) -> IO DMatrix dmatrix__2 = casadi__DMatrix__CONSTRUCTOR__2 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__CONSTRUCTOR__3" c_casadi__DMatrix__CONSTRUCTOR__3 :: Ptr (Ptr StdString) -> CDouble -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__3 :: Double -> IO DMatrix casadi__DMatrix__CONSTRUCTOR__3 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__3 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__3 :: Double -> IO DMatrix dmatrix__3 = casadi__DMatrix__CONSTRUCTOR__3 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__CONSTRUCTOR__4" c_casadi__DMatrix__CONSTRUCTOR__4 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__4 :: Sparsity -> DMatrix -> IO DMatrix casadi__DMatrix__CONSTRUCTOR__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__4 :: Sparsity -> DMatrix -> IO DMatrix dmatrix__4 = casadi__DMatrix__CONSTRUCTOR__4 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__CONSTRUCTOR__5" c_casadi__DMatrix__CONSTRUCTOR__5 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__5 :: Sparsity -> IO DMatrix casadi__DMatrix__CONSTRUCTOR__5 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__5 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__5 :: Sparsity -> IO DMatrix dmatrix__5 = casadi__DMatrix__CONSTRUCTOR__5 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__CONSTRUCTOR__6" c_casadi__DMatrix__CONSTRUCTOR__6 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__6 :: Int -> Int -> IO DMatrix casadi__DMatrix__CONSTRUCTOR__6 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__6 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__6 :: Int -> Int -> IO DMatrix dmatrix__6 = casadi__DMatrix__CONSTRUCTOR__6 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__CONSTRUCTOR__7" c_casadi__DMatrix__CONSTRUCTOR__7 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__7 :: DMatrix -> IO DMatrix casadi__DMatrix__CONSTRUCTOR__7 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__7 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__7 :: DMatrix -> IO DMatrix dmatrix__7 = casadi__DMatrix__CONSTRUCTOR__7 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__CONSTRUCTOR__8" c_casadi__DMatrix__CONSTRUCTOR__8 :: Ptr (Ptr StdString) -> IO (Ptr DMatrix') casadi__DMatrix__CONSTRUCTOR__8 :: IO DMatrix casadi__DMatrix__CONSTRUCTOR__8 = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__CONSTRUCTOR__8 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix__8 :: IO DMatrix dmatrix__8 = casadi__DMatrix__CONSTRUCTOR__8 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__T" c_casadi__DMatrix__T :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__T :: DMatrix -> IO DMatrix casadi__DMatrix__T x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__T errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_T :: DMatrixClass a => a -> IO DMatrix dmatrix_T x = casadi__DMatrix__T (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix____nonzero__" c_casadi__DMatrix____nonzero__ :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix____nonzero__ :: DMatrix -> IO Bool casadi__DMatrix____nonzero__ x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix____nonzero__ errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix___nonzero__ :: DMatrixClass a => a -> IO Bool dmatrix___nonzero__ x = casadi__DMatrix____nonzero__ (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__append" c_casadi__DMatrix__append :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> IO () casadi__DMatrix__append :: DMatrix -> DMatrix -> IO () casadi__DMatrix__append x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__append errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_append :: DMatrixClass a => a -> DMatrix -> IO () dmatrix_append x = casadi__DMatrix__append (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__appendColumns" c_casadi__DMatrix__appendColumns :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> IO () casadi__DMatrix__appendColumns :: DMatrix -> DMatrix -> IO () casadi__DMatrix__appendColumns x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__appendColumns errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_appendColumns :: DMatrixClass a => a -> DMatrix -> IO () dmatrix_appendColumns x = casadi__DMatrix__appendColumns (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__binary" c_casadi__DMatrix__binary :: Ptr (Ptr StdString) -> CInt -> Ptr DMatrix' -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__binary :: Int -> DMatrix -> DMatrix -> IO DMatrix casadi__DMatrix__binary x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__binary errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_binary :: Int -> DMatrix -> DMatrix -> IO DMatrix dmatrix_binary = casadi__DMatrix__binary -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__className" c_casadi__DMatrix__className :: Ptr (Ptr StdString) -> IO (Ptr StdString) casadi__DMatrix__className :: IO String casadi__DMatrix__className = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__className errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_className :: IO String dmatrix_className = casadi__DMatrix__className -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__clear" c_casadi__DMatrix__clear :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__clear :: DMatrix -> IO () casadi__DMatrix__clear x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__clear errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_clear :: DMatrixClass a => a -> IO () dmatrix_clear x = casadi__DMatrix__clear (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__colind" c_casadi__DMatrix__colind :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO CInt casadi__DMatrix__colind :: DMatrix -> Int -> IO Int casadi__DMatrix__colind x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__colind errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_colind :: DMatrixClass a => a -> Int -> IO Int dmatrix_colind x = casadi__DMatrix__colind (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__dimString" c_casadi__DMatrix__dimString :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr StdString) casadi__DMatrix__dimString :: DMatrix -> IO String casadi__DMatrix__dimString x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__dimString errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_dimString :: DMatrixClass a => a -> IO String dmatrix_dimString x = casadi__DMatrix__dimString (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__enlarge__0" c_casadi__DMatrix__enlarge__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> CInt -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> IO () casadi__DMatrix__enlarge__0 :: DMatrix -> Int -> Int -> Vector Int -> Vector Int -> IO () casadi__DMatrix__enlarge__0 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__DMatrix__enlarge__0 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_enlarge__0 :: DMatrixClass a => a -> Int -> Int -> Vector Int -> Vector Int -> IO () dmatrix_enlarge__0 x = casadi__DMatrix__enlarge__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__enlarge__1" c_casadi__DMatrix__enlarge__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> CInt -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> CInt -> IO () casadi__DMatrix__enlarge__1 :: DMatrix -> Int -> Int -> Vector Int -> Vector Int -> Bool -> IO () casadi__DMatrix__enlarge__1 x0 x1 x2 x3 x4 x5 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> withMarshal x5 $ \x5' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__enlarge__1 errStrPtrP x0' x1' x2' x3' x4' x5' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_enlarge__1 :: DMatrixClass a => a -> Int -> Int -> Vector Int -> Vector Int -> Bool -> IO () dmatrix_enlarge__1 x = casadi__DMatrix__enlarge__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__erase__0" c_casadi__DMatrix__erase__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CInt) -> IO () casadi__DMatrix__erase__0 :: DMatrix -> Vector Int -> IO () casadi__DMatrix__erase__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__erase__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_erase__0 :: DMatrixClass a => a -> Vector Int -> IO () dmatrix_erase__0 x = casadi__DMatrix__erase__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__erase__1" c_casadi__DMatrix__erase__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CInt) -> CInt -> IO () casadi__DMatrix__erase__1 :: DMatrix -> Vector Int -> Bool -> IO () casadi__DMatrix__erase__1 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__erase__1 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_erase__1 :: DMatrixClass a => a -> Vector Int -> Bool -> IO () dmatrix_erase__1 x = casadi__DMatrix__erase__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__erase__2" c_casadi__DMatrix__erase__2 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> IO () casadi__DMatrix__erase__2 :: DMatrix -> Vector Int -> Vector Int -> IO () casadi__DMatrix__erase__2 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__erase__2 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_erase__2 :: DMatrixClass a => a -> Vector Int -> Vector Int -> IO () dmatrix_erase__2 x = casadi__DMatrix__erase__2 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__erase__3" c_casadi__DMatrix__erase__3 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> CInt -> IO () casadi__DMatrix__erase__3 :: DMatrix -> Vector Int -> Vector Int -> Bool -> IO () casadi__DMatrix__erase__3 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__erase__3 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_erase__3 :: DMatrixClass a => a -> Vector Int -> Vector Int -> Bool -> IO () dmatrix_erase__3 x = casadi__DMatrix__erase__3 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__eye" c_casadi__DMatrix__eye :: Ptr (Ptr StdString) -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__eye :: Int -> IO DMatrix casadi__DMatrix__eye x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__eye errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_eye :: Int -> IO DMatrix dmatrix_eye = casadi__DMatrix__eye -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__find__0" c_casadi__DMatrix__find__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr (StdVec CInt)) casadi__DMatrix__find__0 :: DMatrix -> IO (Vector Int) casadi__DMatrix__find__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__find__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_find__0 :: DMatrixClass a => a -> IO (Vector Int) dmatrix_find__0 x = casadi__DMatrix__find__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__find__1" c_casadi__DMatrix__find__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO (Ptr (StdVec CInt)) casadi__DMatrix__find__1 :: DMatrix -> Bool -> IO (Vector Int) casadi__DMatrix__find__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__find__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_find__1 :: DMatrixClass a => a -> Bool -> IO (Vector Int) dmatrix_find__1 x = casadi__DMatrix__find__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__get__0" c_casadi__DMatrix__get__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr IMatrix' -> Ptr IMatrix' -> IO () casadi__DMatrix__get__0 :: DMatrix -> DMatrix -> Bool -> IMatrix -> IMatrix -> IO () casadi__DMatrix__get__0 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__DMatrix__get__0 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_get__0 :: DMatrixClass a => a -> DMatrix -> Bool -> IMatrix -> IMatrix -> IO () dmatrix_get__0 x = casadi__DMatrix__get__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__get__1" c_casadi__DMatrix__get__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr IMatrix' -> Ptr Slice' -> IO () casadi__DMatrix__get__1 :: DMatrix -> DMatrix -> Bool -> IMatrix -> Slice -> IO () casadi__DMatrix__get__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__DMatrix__get__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 dmatrix_get__1 :: DMatrixClass a => a -> DMatrix -> Bool -> IMatrix -> Slice -> IO () dmatrix_get__1 x = casadi__DMatrix__get__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__get__2" c_casadi__DMatrix__get__2 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Slice' -> Ptr IMatrix' -> IO () casadi__DMatrix__get__2 :: DMatrix -> DMatrix -> Bool -> Slice -> IMatrix -> IO () casadi__DMatrix__get__2 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__DMatrix__get__2 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_get__2 :: DMatrixClass a => a -> DMatrix -> Bool -> Slice -> IMatrix -> IO () dmatrix_get__2 x = casadi__DMatrix__get__2 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__get__3" c_casadi__DMatrix__get__3 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Slice' -> Ptr Slice' -> IO () casadi__DMatrix__get__3 :: DMatrix -> DMatrix -> Bool -> Slice -> Slice -> IO () casadi__DMatrix__get__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__DMatrix__get__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 dmatrix_get__3 :: DMatrixClass a => a -> DMatrix -> Bool -> Slice -> Slice -> IO () dmatrix_get__3 x = casadi__DMatrix__get__3 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__get__4" c_casadi__DMatrix__get__4 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Sparsity' -> IO () casadi__DMatrix__get__4 :: DMatrix -> DMatrix -> Bool -> Sparsity -> IO () casadi__DMatrix__get__4 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__get__4 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_get__4 :: DMatrixClass a => a -> DMatrix -> Bool -> Sparsity -> IO () dmatrix_get__4 x = casadi__DMatrix__get__4 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__get__5" c_casadi__DMatrix__get__5 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr IMatrix' -> IO () casadi__DMatrix__get__5 :: DMatrix -> DMatrix -> Bool -> IMatrix -> IO () casadi__DMatrix__get__5 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__get__5 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_get__5 :: DMatrixClass a => a -> DMatrix -> Bool -> IMatrix -> IO () dmatrix_get__5 x = casadi__DMatrix__get__5 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__get__6" c_casadi__DMatrix__get__6 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Slice' -> IO () casadi__DMatrix__get__6 :: DMatrix -> DMatrix -> Bool -> Slice -> IO () casadi__DMatrix__get__6 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__get__6 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_get__6 :: DMatrixClass a => a -> DMatrix -> Bool -> Slice -> IO () dmatrix_get__6 x = casadi__DMatrix__get__6 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__get__7" c_casadi__DMatrix__get__7 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__DMatrix__get__7 :: DMatrix -> Vector Double -> IO () casadi__DMatrix__get__7 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__get__7 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_get__7 :: DMatrixClass a => a -> Vector Double -> IO () dmatrix_get__7 x = casadi__DMatrix__get__7 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getColind" c_casadi__DMatrix__getColind :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr (StdVec CInt)) casadi__DMatrix__getColind :: DMatrix -> IO (Vector Int) casadi__DMatrix__getColind x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getColind errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getColind :: DMatrixClass a => a -> IO (Vector Int) dmatrix_getColind x = casadi__DMatrix__getColind (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getDep__0" c_casadi__DMatrix__getDep__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__getDep__0 :: DMatrix -> IO DMatrix casadi__DMatrix__getDep__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getDep__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getDep__0 :: DMatrixClass a => a -> IO DMatrix dmatrix_getDep__0 x = casadi__DMatrix__getDep__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getDep__1" c_casadi__DMatrix__getDep__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__getDep__1 :: DMatrix -> Int -> IO DMatrix casadi__DMatrix__getDep__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getDep__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getDep__1 :: DMatrixClass a => a -> Int -> IO DMatrix dmatrix_getDep__1 x = casadi__DMatrix__getDep__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getElementHash" c_casadi__DMatrix__getElementHash :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CSize casadi__DMatrix__getElementHash :: DMatrix -> IO CSize casadi__DMatrix__getElementHash x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getElementHash errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getElementHash :: DMatrixClass a => a -> IO CSize dmatrix_getElementHash x = casadi__DMatrix__getElementHash (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getEqualityCheckingDepth" c_casadi__DMatrix__getEqualityCheckingDepth :: Ptr (Ptr StdString) -> IO CInt casadi__DMatrix__getEqualityCheckingDepth :: IO Int casadi__DMatrix__getEqualityCheckingDepth = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getEqualityCheckingDepth errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getEqualityCheckingDepth :: IO Int dmatrix_getEqualityCheckingDepth = casadi__DMatrix__getEqualityCheckingDepth -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getIntValue" c_casadi__DMatrix__getIntValue :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__getIntValue :: DMatrix -> IO Int casadi__DMatrix__getIntValue x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getIntValue errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getIntValue :: DMatrixClass a => a -> IO Int dmatrix_getIntValue x = casadi__DMatrix__getIntValue (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getNZ__0" c_casadi__DMatrix__getNZ__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr IMatrix' -> IO () casadi__DMatrix__getNZ__0 :: DMatrix -> DMatrix -> Bool -> IMatrix -> IO () casadi__DMatrix__getNZ__0 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getNZ__0 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getNZ__0 :: DMatrixClass a => a -> DMatrix -> Bool -> IMatrix -> IO () dmatrix_getNZ__0 x = casadi__DMatrix__getNZ__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getNZ__1" c_casadi__DMatrix__getNZ__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Slice' -> IO () casadi__DMatrix__getNZ__1 :: DMatrix -> DMatrix -> Bool -> Slice -> IO () casadi__DMatrix__getNZ__1 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getNZ__1 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getNZ__1 :: DMatrixClass a => a -> DMatrix -> Bool -> Slice -> IO () dmatrix_getNZ__1 x = casadi__DMatrix__getNZ__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getNZ__2" c_casadi__DMatrix__getNZ__2 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__DMatrix__getNZ__2 :: DMatrix -> Vector Double -> IO () casadi__DMatrix__getNZ__2 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getNZ__2 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getNZ__2 :: DMatrixClass a => a -> Vector Double -> IO () dmatrix_getNZ__2 x = casadi__DMatrix__getNZ__2 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getName" c_casadi__DMatrix__getName :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr StdString) casadi__DMatrix__getName :: DMatrix -> IO String casadi__DMatrix__getName x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getName errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getName :: DMatrixClass a => a -> IO String dmatrix_getName x = casadi__DMatrix__getName (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getNdeps" c_casadi__DMatrix__getNdeps :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__getNdeps :: DMatrix -> IO Int casadi__DMatrix__getNdeps x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getNdeps errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getNdeps :: DMatrixClass a => a -> IO Int dmatrix_getNdeps x = casadi__DMatrix__getNdeps (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getRow" c_casadi__DMatrix__getRow :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr (StdVec CInt)) casadi__DMatrix__getRow :: DMatrix -> IO (Vector Int) casadi__DMatrix__getRow x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getRow errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getRow :: DMatrixClass a => a -> IO (Vector Int) dmatrix_getRow x = casadi__DMatrix__getRow (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getSparsity" c_casadi__DMatrix__getSparsity :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr Sparsity') casadi__DMatrix__getSparsity :: DMatrix -> IO Sparsity casadi__DMatrix__getSparsity x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getSparsity errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getSparsity :: DMatrixClass a => a -> IO Sparsity dmatrix_getSparsity x = casadi__DMatrix__getSparsity (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getSym" c_casadi__DMatrix__getSym :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__DMatrix__getSym :: DMatrix -> Vector Double -> IO () casadi__DMatrix__getSym x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getSym errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getSym :: DMatrixClass a => a -> Vector Double -> IO () dmatrix_getSym x = casadi__DMatrix__getSym (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getValue__0" c_casadi__DMatrix__getValue__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO CDouble casadi__DMatrix__getValue__0 :: DMatrix -> Int -> IO Double casadi__DMatrix__getValue__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getValue__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getValue__0 :: DMatrixClass a => a -> Int -> IO Double dmatrix_getValue__0 x = casadi__DMatrix__getValue__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getValue__1" c_casadi__DMatrix__getValue__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CDouble casadi__DMatrix__getValue__1 :: DMatrix -> IO Double casadi__DMatrix__getValue__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getValue__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getValue__1 :: DMatrixClass a => a -> IO Double dmatrix_getValue__1 x = casadi__DMatrix__getValue__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__hasDuplicates" c_casadi__DMatrix__hasDuplicates :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__hasDuplicates :: DMatrix -> IO Bool casadi__DMatrix__hasDuplicates x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__hasDuplicates errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_hasDuplicates :: DMatrixClass a => a -> IO Bool dmatrix_hasDuplicates x = casadi__DMatrix__hasDuplicates (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__hasNZ" c_casadi__DMatrix__hasNZ :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> CInt -> IO CInt casadi__DMatrix__hasNZ :: DMatrix -> Int -> Int -> IO Bool casadi__DMatrix__hasNZ x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__hasNZ errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_hasNZ :: DMatrixClass a => a -> Int -> Int -> IO Bool dmatrix_hasNZ x = casadi__DMatrix__hasNZ (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__hasNonStructuralZeros" c_casadi__DMatrix__hasNonStructuralZeros :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__hasNonStructuralZeros :: DMatrix -> IO Bool casadi__DMatrix__hasNonStructuralZeros x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__hasNonStructuralZeros errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_hasNonStructuralZeros :: DMatrixClass a => a -> IO Bool dmatrix_hasNonStructuralZeros x = casadi__DMatrix__hasNonStructuralZeros (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__inf__0" c_casadi__DMatrix__inf__0 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr DMatrix') casadi__DMatrix__inf__0 :: (Int, Int) -> IO DMatrix casadi__DMatrix__inf__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__inf__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_inf__0 :: (Int, Int) -> IO DMatrix dmatrix_inf__0 = casadi__DMatrix__inf__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__inf__1" c_casadi__DMatrix__inf__1 :: Ptr (Ptr StdString) -> IO (Ptr DMatrix') casadi__DMatrix__inf__1 :: IO DMatrix casadi__DMatrix__inf__1 = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__inf__1 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_inf__1 :: IO DMatrix dmatrix_inf__1 = casadi__DMatrix__inf__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__inf__2" c_casadi__DMatrix__inf__2 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__inf__2 :: Int -> IO DMatrix casadi__DMatrix__inf__2 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__inf__2 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_inf__2 :: Int -> IO DMatrix dmatrix_inf__2 = casadi__DMatrix__inf__2 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__inf__3" c_casadi__DMatrix__inf__3 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__inf__3 :: Int -> Int -> IO DMatrix casadi__DMatrix__inf__3 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__inf__3 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_inf__3 :: Int -> Int -> IO DMatrix dmatrix_inf__3 = casadi__DMatrix__inf__3 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__inf__4" c_casadi__DMatrix__inf__4 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr DMatrix') casadi__DMatrix__inf__4 :: Sparsity -> IO DMatrix casadi__DMatrix__inf__4 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__inf__4 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_inf__4 :: Sparsity -> IO DMatrix dmatrix_inf__4 = casadi__DMatrix__inf__4 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isCommutative" c_casadi__DMatrix__isCommutative :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isCommutative :: DMatrix -> IO Bool casadi__DMatrix__isCommutative x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isCommutative errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isCommutative :: DMatrixClass a => a -> IO Bool dmatrix_isCommutative x = casadi__DMatrix__isCommutative (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isConstant" c_casadi__DMatrix__isConstant :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isConstant :: DMatrix -> IO Bool casadi__DMatrix__isConstant x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isConstant errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isConstant :: DMatrixClass a => a -> IO Bool dmatrix_isConstant x = casadi__DMatrix__isConstant (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isIdentity" c_casadi__DMatrix__isIdentity :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isIdentity :: DMatrix -> IO Bool casadi__DMatrix__isIdentity x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isIdentity errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isIdentity :: DMatrixClass a => a -> IO Bool dmatrix_isIdentity x = casadi__DMatrix__isIdentity (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isInteger" c_casadi__DMatrix__isInteger :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isInteger :: DMatrix -> IO Bool casadi__DMatrix__isInteger x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isInteger errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isInteger :: DMatrixClass a => a -> IO Bool dmatrix_isInteger x = casadi__DMatrix__isInteger (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isLeaf" c_casadi__DMatrix__isLeaf :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isLeaf :: DMatrix -> IO Bool casadi__DMatrix__isLeaf x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isLeaf errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isLeaf :: DMatrixClass a => a -> IO Bool dmatrix_isLeaf x = casadi__DMatrix__isLeaf (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isMinusOne" c_casadi__DMatrix__isMinusOne :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isMinusOne :: DMatrix -> IO Bool casadi__DMatrix__isMinusOne x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isMinusOne errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isMinusOne :: DMatrixClass a => a -> IO Bool dmatrix_isMinusOne x = casadi__DMatrix__isMinusOne (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isOne" c_casadi__DMatrix__isOne :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isOne :: DMatrix -> IO Bool casadi__DMatrix__isOne x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isOne errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isOne :: DMatrixClass a => a -> IO Bool dmatrix_isOne x = casadi__DMatrix__isOne (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isRegular" c_casadi__DMatrix__isRegular :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isRegular :: DMatrix -> IO Bool casadi__DMatrix__isRegular x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isRegular errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isRegular :: DMatrixClass a => a -> IO Bool dmatrix_isRegular x = casadi__DMatrix__isRegular (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isSlice__0" c_casadi__DMatrix__isSlice__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isSlice__0 :: DMatrix -> IO Bool casadi__DMatrix__isSlice__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isSlice__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isSlice__0 :: DMatrixClass a => a -> IO Bool dmatrix_isSlice__0 x = casadi__DMatrix__isSlice__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isSlice__1" c_casadi__DMatrix__isSlice__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO CInt casadi__DMatrix__isSlice__1 :: DMatrix -> Bool -> IO Bool casadi__DMatrix__isSlice__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isSlice__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isSlice__1 :: DMatrixClass a => a -> Bool -> IO Bool dmatrix_isSlice__1 x = casadi__DMatrix__isSlice__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isSmooth" c_casadi__DMatrix__isSmooth :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isSmooth :: DMatrix -> IO Bool casadi__DMatrix__isSmooth x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isSmooth errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isSmooth :: DMatrixClass a => a -> IO Bool dmatrix_isSmooth x = casadi__DMatrix__isSmooth (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isSymbolic" c_casadi__DMatrix__isSymbolic :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isSymbolic :: DMatrix -> IO Bool casadi__DMatrix__isSymbolic x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isSymbolic errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isSymbolic :: DMatrixClass a => a -> IO Bool dmatrix_isSymbolic x = casadi__DMatrix__isSymbolic (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isValidInput" c_casadi__DMatrix__isValidInput :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isValidInput :: DMatrix -> IO Bool casadi__DMatrix__isValidInput x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isValidInput errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isValidInput :: DMatrixClass a => a -> IO Bool dmatrix_isValidInput x = casadi__DMatrix__isValidInput (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isZero" c_casadi__DMatrix__isZero :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isZero :: DMatrix -> IO Bool casadi__DMatrix__isZero x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isZero errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isZero :: DMatrixClass a => a -> IO Bool dmatrix_isZero x = casadi__DMatrix__isZero (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__iscolumn" c_casadi__DMatrix__iscolumn :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__iscolumn :: DMatrix -> IO Bool casadi__DMatrix__iscolumn x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__iscolumn errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_iscolumn :: DMatrixClass a => a -> IO Bool dmatrix_iscolumn x = casadi__DMatrix__iscolumn (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isdense" c_casadi__DMatrix__isdense :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isdense :: DMatrix -> IO Bool casadi__DMatrix__isdense x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isdense errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isdense :: DMatrixClass a => a -> IO Bool dmatrix_isdense x = casadi__DMatrix__isdense (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isempty__0" c_casadi__DMatrix__isempty__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isempty__0 :: DMatrix -> IO Bool casadi__DMatrix__isempty__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isempty__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isempty__0 :: DMatrixClass a => a -> IO Bool dmatrix_isempty__0 x = casadi__DMatrix__isempty__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isempty__1" c_casadi__DMatrix__isempty__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO CInt casadi__DMatrix__isempty__1 :: DMatrix -> Bool -> IO Bool casadi__DMatrix__isempty__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isempty__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isempty__1 :: DMatrixClass a => a -> Bool -> IO Bool dmatrix_isempty__1 x = casadi__DMatrix__isempty__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isrow" c_casadi__DMatrix__isrow :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isrow :: DMatrix -> IO Bool casadi__DMatrix__isrow x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isrow errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isrow :: DMatrixClass a => a -> IO Bool dmatrix_isrow x = casadi__DMatrix__isrow (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isscalar__0" c_casadi__DMatrix__isscalar__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isscalar__0 :: DMatrix -> IO Bool casadi__DMatrix__isscalar__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isscalar__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isscalar__0 :: DMatrixClass a => a -> IO Bool dmatrix_isscalar__0 x = casadi__DMatrix__isscalar__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isscalar__1" c_casadi__DMatrix__isscalar__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO CInt casadi__DMatrix__isscalar__1 :: DMatrix -> Bool -> IO Bool casadi__DMatrix__isscalar__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isscalar__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isscalar__1 :: DMatrixClass a => a -> Bool -> IO Bool dmatrix_isscalar__1 x = casadi__DMatrix__isscalar__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__issquare" c_casadi__DMatrix__issquare :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__issquare :: DMatrix -> IO Bool casadi__DMatrix__issquare x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__issquare errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_issquare :: DMatrixClass a => a -> IO Bool dmatrix_issquare x = casadi__DMatrix__issquare (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__istril" c_casadi__DMatrix__istril :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__istril :: DMatrix -> IO Bool casadi__DMatrix__istril x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__istril errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_istril :: DMatrixClass a => a -> IO Bool dmatrix_istril x = casadi__DMatrix__istril (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__istriu" c_casadi__DMatrix__istriu :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__istriu :: DMatrix -> IO Bool casadi__DMatrix__istriu x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__istriu errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_istriu :: DMatrixClass a => a -> IO Bool dmatrix_istriu x = casadi__DMatrix__istriu (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__isvector" c_casadi__DMatrix__isvector :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__isvector :: DMatrix -> IO Bool casadi__DMatrix__isvector x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__isvector errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_isvector :: DMatrixClass a => a -> IO Bool dmatrix_isvector x = casadi__DMatrix__isvector (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__makeSparse__0" c_casadi__DMatrix__makeSparse__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__makeSparse__0 :: DMatrix -> IO () casadi__DMatrix__makeSparse__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__makeSparse__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_makeSparse__0 :: DMatrixClass a => a -> IO () dmatrix_makeSparse__0 x = casadi__DMatrix__makeSparse__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__makeSparse__1" c_casadi__DMatrix__makeSparse__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CDouble -> IO () casadi__DMatrix__makeSparse__1 :: DMatrix -> Double -> IO () casadi__DMatrix__makeSparse__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__makeSparse__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_makeSparse__1 :: DMatrixClass a => a -> Double -> IO () dmatrix_makeSparse__1 x = casadi__DMatrix__makeSparse__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__matrix_matrix" c_casadi__DMatrix__matrix_matrix :: Ptr (Ptr StdString) -> CInt -> Ptr DMatrix' -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__matrix_matrix :: Int -> DMatrix -> DMatrix -> IO DMatrix casadi__DMatrix__matrix_matrix x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__matrix_matrix errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_matrix_matrix :: Int -> DMatrix -> DMatrix -> IO DMatrix dmatrix_matrix_matrix = casadi__DMatrix__matrix_matrix -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__matrix_scalar" c_casadi__DMatrix__matrix_scalar :: Ptr (Ptr StdString) -> CInt -> Ptr DMatrix' -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__matrix_scalar :: Int -> DMatrix -> DMatrix -> IO DMatrix casadi__DMatrix__matrix_scalar x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__matrix_scalar errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_matrix_scalar :: Int -> DMatrix -> DMatrix -> IO DMatrix dmatrix_matrix_scalar = casadi__DMatrix__matrix_scalar -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__nan__0" c_casadi__DMatrix__nan__0 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr DMatrix') casadi__DMatrix__nan__0 :: (Int, Int) -> IO DMatrix casadi__DMatrix__nan__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__nan__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_nan__0 :: (Int, Int) -> IO DMatrix dmatrix_nan__0 = casadi__DMatrix__nan__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__nan__1" c_casadi__DMatrix__nan__1 :: Ptr (Ptr StdString) -> IO (Ptr DMatrix') casadi__DMatrix__nan__1 :: IO DMatrix casadi__DMatrix__nan__1 = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__nan__1 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_nan__1 :: IO DMatrix dmatrix_nan__1 = casadi__DMatrix__nan__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__nan__2" c_casadi__DMatrix__nan__2 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__nan__2 :: Int -> IO DMatrix casadi__DMatrix__nan__2 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__nan__2 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_nan__2 :: Int -> IO DMatrix dmatrix_nan__2 = casadi__DMatrix__nan__2 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__nan__3" c_casadi__DMatrix__nan__3 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__nan__3 :: Int -> Int -> IO DMatrix casadi__DMatrix__nan__3 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__nan__3 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_nan__3 :: Int -> Int -> IO DMatrix dmatrix_nan__3 = casadi__DMatrix__nan__3 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__nan__4" c_casadi__DMatrix__nan__4 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr DMatrix') casadi__DMatrix__nan__4 :: Sparsity -> IO DMatrix casadi__DMatrix__nan__4 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__nan__4 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_nan__4 :: Sparsity -> IO DMatrix dmatrix_nan__4 = casadi__DMatrix__nan__4 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__nnz" c_casadi__DMatrix__nnz :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__nnz :: DMatrix -> IO Int casadi__DMatrix__nnz x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__nnz errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_nnz :: DMatrixClass a => a -> IO Int dmatrix_nnz x = casadi__DMatrix__nnz (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__nonzeros" c_casadi__DMatrix__nonzeros :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr (StdVec CDouble)) casadi__DMatrix__nonzeros :: DMatrix -> IO (Vector Double) casadi__DMatrix__nonzeros x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__nonzeros errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_nonzeros :: DMatrixClass a => a -> IO (Vector Double) dmatrix_nonzeros x = casadi__DMatrix__nonzeros (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__nonzeros_int" c_casadi__DMatrix__nonzeros_int :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr (StdVec CInt)) casadi__DMatrix__nonzeros_int :: DMatrix -> IO (Vector Int) casadi__DMatrix__nonzeros_int x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__nonzeros_int errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_nonzeros_int :: DMatrixClass a => a -> IO (Vector Int) dmatrix_nonzeros_int x = casadi__DMatrix__nonzeros_int (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__numel__0" c_casadi__DMatrix__numel__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO CInt casadi__DMatrix__numel__0 :: DMatrix -> Int -> IO Int casadi__DMatrix__numel__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__numel__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_numel__0 :: DMatrixClass a => a -> Int -> IO Int dmatrix_numel__0 x = casadi__DMatrix__numel__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__numel__1" c_casadi__DMatrix__numel__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__numel__1 :: DMatrix -> IO Int casadi__DMatrix__numel__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__numel__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_numel__1 :: DMatrixClass a => a -> IO Int dmatrix_numel__1 x = casadi__DMatrix__numel__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__ones__0" c_casadi__DMatrix__ones__0 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr DMatrix') casadi__DMatrix__ones__0 :: (Int, Int) -> IO DMatrix casadi__DMatrix__ones__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__ones__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_ones__0 :: (Int, Int) -> IO DMatrix dmatrix_ones__0 = casadi__DMatrix__ones__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__ones__1" c_casadi__DMatrix__ones__1 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr DMatrix') casadi__DMatrix__ones__1 :: Sparsity -> IO DMatrix casadi__DMatrix__ones__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__ones__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_ones__1 :: Sparsity -> IO DMatrix dmatrix_ones__1 = casadi__DMatrix__ones__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__ones__2" c_casadi__DMatrix__ones__2 :: Ptr (Ptr StdString) -> IO (Ptr DMatrix') casadi__DMatrix__ones__2 :: IO DMatrix casadi__DMatrix__ones__2 = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__ones__2 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_ones__2 :: IO DMatrix dmatrix_ones__2 = casadi__DMatrix__ones__2 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__ones__3" c_casadi__DMatrix__ones__3 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__ones__3 :: Int -> IO DMatrix casadi__DMatrix__ones__3 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__ones__3 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_ones__3 :: Int -> IO DMatrix dmatrix_ones__3 = casadi__DMatrix__ones__3 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__ones__4" c_casadi__DMatrix__ones__4 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__ones__4 :: Int -> Int -> IO DMatrix casadi__DMatrix__ones__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__ones__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_ones__4 :: Int -> Int -> IO DMatrix dmatrix_ones__4 = casadi__DMatrix__ones__4 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__operator_plus" c_casadi__DMatrix__operator_plus :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__operator_plus :: DMatrix -> IO DMatrix casadi__DMatrix__operator_plus x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__operator_plus errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_operator_plus :: DMatrixClass a => a -> IO DMatrix dmatrix_operator_plus x = casadi__DMatrix__operator_plus (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__operator_minus" c_casadi__DMatrix__operator_minus :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__operator_minus :: DMatrix -> IO DMatrix casadi__DMatrix__operator_minus x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__operator_minus errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_operator_minus :: DMatrixClass a => a -> IO DMatrix dmatrix_operator_minus x = casadi__DMatrix__operator_minus (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__printDense" c_casadi__DMatrix__printDense :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__printDense :: DMatrix -> IO () casadi__DMatrix__printDense x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__printDense errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_printDense :: DMatrixClass a => a -> IO () dmatrix_printDense x = casadi__DMatrix__printDense (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__printScalar" c_casadi__DMatrix__printScalar :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__printScalar :: DMatrix -> IO () casadi__DMatrix__printScalar x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__printScalar errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_printScalar :: DMatrixClass a => a -> IO () dmatrix_printScalar x = casadi__DMatrix__printScalar (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__printSparse" c_casadi__DMatrix__printSparse :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__printSparse :: DMatrix -> IO () casadi__DMatrix__printSparse x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__printSparse errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_printSparse :: DMatrixClass a => a -> IO () dmatrix_printSparse x = casadi__DMatrix__printSparse (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__printSplit" c_casadi__DMatrix__printSplit :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec (Ptr StdString)) -> Ptr (StdVec (Ptr StdString)) -> IO () casadi__DMatrix__printSplit :: DMatrix -> Vector String -> Vector String -> IO () casadi__DMatrix__printSplit x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__printSplit errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_printSplit :: DMatrixClass a => a -> Vector String -> Vector String -> IO () dmatrix_printSplit x = casadi__DMatrix__printSplit (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__printVector" c_casadi__DMatrix__printVector :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__printVector :: DMatrix -> IO () casadi__DMatrix__printVector x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__printVector errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_printVector :: DMatrixClass a => a -> IO () dmatrix_printVector x = casadi__DMatrix__printVector (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__printme" c_casadi__DMatrix__printme :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__printme :: DMatrix -> DMatrix -> IO DMatrix casadi__DMatrix__printme x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__printme errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_printme :: DMatrixClass a => a -> DMatrix -> IO DMatrix dmatrix_printme x = casadi__DMatrix__printme (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__remove" c_casadi__DMatrix__remove :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> IO () casadi__DMatrix__remove :: DMatrix -> Vector Int -> Vector Int -> IO () casadi__DMatrix__remove x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__remove errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_remove :: DMatrixClass a => a -> Vector Int -> Vector Int -> IO () dmatrix_remove x = casadi__DMatrix__remove (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__reserve__0" c_casadi__DMatrix__reserve__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> CInt -> IO () casadi__DMatrix__reserve__0 :: DMatrix -> Int -> Int -> IO () casadi__DMatrix__reserve__0 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__reserve__0 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_reserve__0 :: DMatrixClass a => a -> Int -> Int -> IO () dmatrix_reserve__0 x = casadi__DMatrix__reserve__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__reserve__1" c_casadi__DMatrix__reserve__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO () casadi__DMatrix__reserve__1 :: DMatrix -> Int -> IO () casadi__DMatrix__reserve__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__reserve__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_reserve__1 :: DMatrixClass a => a -> Int -> IO () dmatrix_reserve__1 x = casadi__DMatrix__reserve__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__resetInput" c_casadi__DMatrix__resetInput :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__resetInput :: DMatrix -> IO () casadi__DMatrix__resetInput x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__resetInput errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_resetInput :: DMatrixClass a => a -> IO () dmatrix_resetInput x = casadi__DMatrix__resetInput (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__resize" c_casadi__DMatrix__resize :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> CInt -> IO () casadi__DMatrix__resize :: DMatrix -> Int -> Int -> IO () casadi__DMatrix__resize x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__resize errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_resize :: DMatrixClass a => a -> Int -> Int -> IO () dmatrix_resize x = casadi__DMatrix__resize (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__row" c_casadi__DMatrix__row :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO CInt casadi__DMatrix__row :: DMatrix -> Int -> IO Int casadi__DMatrix__row x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__row errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_row :: DMatrixClass a => a -> Int -> IO Int dmatrix_row x = casadi__DMatrix__row (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sanityCheck__0" c_casadi__DMatrix__sanityCheck__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__sanityCheck__0 :: DMatrix -> IO () casadi__DMatrix__sanityCheck__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sanityCheck__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sanityCheck__0 :: DMatrixClass a => a -> IO () dmatrix_sanityCheck__0 x = casadi__DMatrix__sanityCheck__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sanityCheck__1" c_casadi__DMatrix__sanityCheck__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO () casadi__DMatrix__sanityCheck__1 :: DMatrix -> Bool -> IO () casadi__DMatrix__sanityCheck__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sanityCheck__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sanityCheck__1 :: DMatrixClass a => a -> Bool -> IO () dmatrix_sanityCheck__1 x = casadi__DMatrix__sanityCheck__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__scalar_matrix" c_casadi__DMatrix__scalar_matrix :: Ptr (Ptr StdString) -> CInt -> Ptr DMatrix' -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__scalar_matrix :: Int -> DMatrix -> DMatrix -> IO DMatrix casadi__DMatrix__scalar_matrix x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__scalar_matrix errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_scalar_matrix :: Int -> DMatrix -> DMatrix -> IO DMatrix dmatrix_scalar_matrix = casadi__DMatrix__scalar_matrix -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__0" c_casadi__DMatrix__set__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr IMatrix' -> Ptr IMatrix' -> IO () casadi__DMatrix__set__0 :: DMatrix -> DMatrix -> Bool -> IMatrix -> IMatrix -> IO () casadi__DMatrix__set__0 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__DMatrix__set__0 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__0 :: DMatrixClass a => a -> DMatrix -> Bool -> IMatrix -> IMatrix -> IO () dmatrix_set__0 x = casadi__DMatrix__set__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__1" c_casadi__DMatrix__set__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr IMatrix' -> Ptr Slice' -> IO () casadi__DMatrix__set__1 :: DMatrix -> DMatrix -> Bool -> IMatrix -> Slice -> IO () casadi__DMatrix__set__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__DMatrix__set__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 dmatrix_set__1 :: DMatrixClass a => a -> DMatrix -> Bool -> IMatrix -> Slice -> IO () dmatrix_set__1 x = casadi__DMatrix__set__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__2" c_casadi__DMatrix__set__2 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Slice' -> Ptr IMatrix' -> IO () casadi__DMatrix__set__2 :: DMatrix -> DMatrix -> Bool -> Slice -> IMatrix -> IO () casadi__DMatrix__set__2 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__DMatrix__set__2 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__2 :: DMatrixClass a => a -> DMatrix -> Bool -> Slice -> IMatrix -> IO () dmatrix_set__2 x = casadi__DMatrix__set__2 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__3" c_casadi__DMatrix__set__3 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Slice' -> Ptr Slice' -> IO () casadi__DMatrix__set__3 :: DMatrix -> DMatrix -> Bool -> Slice -> Slice -> IO () casadi__DMatrix__set__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__DMatrix__set__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 dmatrix_set__3 :: DMatrixClass a => a -> DMatrix -> Bool -> Slice -> Slice -> IO () dmatrix_set__3 x = casadi__DMatrix__set__3 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__4" c_casadi__DMatrix__set__4 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Sparsity' -> IO () casadi__DMatrix__set__4 :: DMatrix -> DMatrix -> Bool -> Sparsity -> IO () casadi__DMatrix__set__4 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__set__4 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__4 :: DMatrixClass a => a -> DMatrix -> Bool -> Sparsity -> IO () dmatrix_set__4 x = casadi__DMatrix__set__4 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__5" c_casadi__DMatrix__set__5 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr IMatrix' -> IO () casadi__DMatrix__set__5 :: DMatrix -> DMatrix -> Bool -> IMatrix -> IO () casadi__DMatrix__set__5 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__set__5 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__5 :: DMatrixClass a => a -> DMatrix -> Bool -> IMatrix -> IO () dmatrix_set__5 x = casadi__DMatrix__set__5 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__6" c_casadi__DMatrix__set__6 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Slice' -> IO () casadi__DMatrix__set__6 :: DMatrix -> DMatrix -> Bool -> Slice -> IO () casadi__DMatrix__set__6 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__set__6 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__6 :: DMatrixClass a => a -> DMatrix -> Bool -> Slice -> IO () dmatrix_set__6 x = casadi__DMatrix__set__6 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__7" c_casadi__DMatrix__set__7 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__DMatrix__set__7 :: DMatrix -> Vector Double -> IO () casadi__DMatrix__set__7 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__set__7 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__7 :: DMatrixClass a => a -> Vector Double -> IO () dmatrix_set__7 x = casadi__DMatrix__set__7 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__8" c_casadi__DMatrix__set__8 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CDouble) -> CInt -> IO () casadi__DMatrix__set__8 :: DMatrix -> Vector Double -> Bool -> IO () casadi__DMatrix__set__8 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__set__8 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__8 :: DMatrixClass a => a -> Vector Double -> Bool -> IO () dmatrix_set__8 x = casadi__DMatrix__set__8 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__9" c_casadi__DMatrix__set__9 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CDouble -> IO () casadi__DMatrix__set__9 :: DMatrix -> Double -> IO () casadi__DMatrix__set__9 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__set__9 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__9 :: DMatrixClass a => a -> Double -> IO () dmatrix_set__9 x = casadi__DMatrix__set__9 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__set__10" c_casadi__DMatrix__set__10 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> IO () casadi__DMatrix__set__10 :: DMatrix -> DMatrix -> IO () casadi__DMatrix__set__10 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__set__10 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_set__10 :: DMatrixClass a => a -> DMatrix -> IO () dmatrix_set__10 x = casadi__DMatrix__set__10 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setEqualityCheckingDepth__0" c_casadi__DMatrix__setEqualityCheckingDepth__0 :: Ptr (Ptr StdString) -> IO () casadi__DMatrix__setEqualityCheckingDepth__0 :: IO () casadi__DMatrix__setEqualityCheckingDepth__0 = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setEqualityCheckingDepth__0 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setEqualityCheckingDepth__0 :: IO () dmatrix_setEqualityCheckingDepth__0 = casadi__DMatrix__setEqualityCheckingDepth__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setEqualityCheckingDepth__1" c_casadi__DMatrix__setEqualityCheckingDepth__1 :: Ptr (Ptr StdString) -> CInt -> IO () casadi__DMatrix__setEqualityCheckingDepth__1 :: Int -> IO () casadi__DMatrix__setEqualityCheckingDepth__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setEqualityCheckingDepth__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setEqualityCheckingDepth__1 :: Int -> IO () dmatrix_setEqualityCheckingDepth__1 = casadi__DMatrix__setEqualityCheckingDepth__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setNZ__0" c_casadi__DMatrix__setNZ__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr IMatrix' -> IO () casadi__DMatrix__setNZ__0 :: DMatrix -> DMatrix -> Bool -> IMatrix -> IO () casadi__DMatrix__setNZ__0 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setNZ__0 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setNZ__0 :: DMatrixClass a => a -> DMatrix -> Bool -> IMatrix -> IO () dmatrix_setNZ__0 x = casadi__DMatrix__setNZ__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setNZ__1" c_casadi__DMatrix__setNZ__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr DMatrix' -> CInt -> Ptr Slice' -> IO () casadi__DMatrix__setNZ__1 :: DMatrix -> DMatrix -> Bool -> Slice -> IO () casadi__DMatrix__setNZ__1 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setNZ__1 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setNZ__1 :: DMatrixClass a => a -> DMatrix -> Bool -> Slice -> IO () dmatrix_setNZ__1 x = casadi__DMatrix__setNZ__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setNZ__2" c_casadi__DMatrix__setNZ__2 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__DMatrix__setNZ__2 :: DMatrix -> Vector Double -> IO () casadi__DMatrix__setNZ__2 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setNZ__2 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setNZ__2 :: DMatrixClass a => a -> Vector Double -> IO () dmatrix_setNZ__2 x = casadi__DMatrix__setNZ__2 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setNZ__3" c_casadi__DMatrix__setNZ__3 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CDouble -> IO () casadi__DMatrix__setNZ__3 :: DMatrix -> Double -> IO () casadi__DMatrix__setNZ__3 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setNZ__3 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setNZ__3 :: DMatrixClass a => a -> Double -> IO () dmatrix_setNZ__3 x = casadi__DMatrix__setNZ__3 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setPrecision" c_casadi__DMatrix__setPrecision :: Ptr (Ptr StdString) -> CInt -> IO () casadi__DMatrix__setPrecision :: Int -> IO () casadi__DMatrix__setPrecision x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setPrecision errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setPrecision :: Int -> IO () dmatrix_setPrecision = casadi__DMatrix__setPrecision -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setScientific" c_casadi__DMatrix__setScientific :: Ptr (Ptr StdString) -> CInt -> IO () casadi__DMatrix__setScientific :: Bool -> IO () casadi__DMatrix__setScientific x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setScientific errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setScientific :: Bool -> IO () dmatrix_setScientific = casadi__DMatrix__setScientific -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setSym" c_casadi__DMatrix__setSym :: Ptr (Ptr StdString) -> Ptr DMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__DMatrix__setSym :: DMatrix -> Vector Double -> IO () casadi__DMatrix__setSym x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setSym errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setSym :: DMatrixClass a => a -> Vector Double -> IO () dmatrix_setSym x = casadi__DMatrix__setSym (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setValue__0" c_casadi__DMatrix__setValue__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CDouble -> CInt -> IO () casadi__DMatrix__setValue__0 :: DMatrix -> Double -> Int -> IO () casadi__DMatrix__setValue__0 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setValue__0 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setValue__0 :: DMatrixClass a => a -> Double -> Int -> IO () dmatrix_setValue__0 x = casadi__DMatrix__setValue__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setValue__1" c_casadi__DMatrix__setValue__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CDouble -> IO () casadi__DMatrix__setValue__1 :: DMatrix -> Double -> IO () casadi__DMatrix__setValue__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setValue__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setValue__1 :: DMatrixClass a => a -> Double -> IO () dmatrix_setValue__1 x = casadi__DMatrix__setValue__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setWidth" c_casadi__DMatrix__setWidth :: Ptr (Ptr StdString) -> CInt -> IO () casadi__DMatrix__setWidth :: Int -> IO () casadi__DMatrix__setWidth x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setWidth errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setWidth :: Int -> IO () dmatrix_setWidth = casadi__DMatrix__setWidth -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__setZero" c_casadi__DMatrix__setZero :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO () casadi__DMatrix__setZero :: DMatrix -> IO () casadi__DMatrix__setZero x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__setZero errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_setZero :: DMatrixClass a => a -> IO () dmatrix_setZero x = casadi__DMatrix__setZero (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__shape__0" c_casadi__DMatrix__shape__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO CInt casadi__DMatrix__shape__0 :: DMatrix -> Int -> IO Int casadi__DMatrix__shape__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__shape__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_shape__0 :: DMatrixClass a => a -> Int -> IO Int dmatrix_shape__0 x = casadi__DMatrix__shape__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__shape__1" c_casadi__DMatrix__shape__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr (StdPair CInt CInt)) casadi__DMatrix__shape__1 :: DMatrix -> IO (Int, Int) casadi__DMatrix__shape__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__shape__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_shape__1 :: DMatrixClass a => a -> IO (Int, Int) dmatrix_shape__1 x = casadi__DMatrix__shape__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__size" c_casadi__DMatrix__size :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__size :: DMatrix -> IO Int casadi__DMatrix__size x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__size errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_size :: DMatrixClass a => a -> IO Int dmatrix_size x = casadi__DMatrix__size (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__size1" c_casadi__DMatrix__size1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__size1 :: DMatrix -> IO Int casadi__DMatrix__size1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__size1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_size1 :: DMatrixClass a => a -> IO Int dmatrix_size1 x = casadi__DMatrix__size1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__size2" c_casadi__DMatrix__size2 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__size2 :: DMatrix -> IO Int casadi__DMatrix__size2 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__size2 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_size2 :: DMatrixClass a => a -> IO Int dmatrix_size2 x = casadi__DMatrix__size2 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sizeD" c_casadi__DMatrix__sizeD :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__sizeD :: DMatrix -> IO Int casadi__DMatrix__sizeD x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sizeD errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sizeD :: DMatrixClass a => a -> IO Int dmatrix_sizeD x = casadi__DMatrix__sizeD (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sizeL" c_casadi__DMatrix__sizeL :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__sizeL :: DMatrix -> IO Int casadi__DMatrix__sizeL x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sizeL errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sizeL :: DMatrixClass a => a -> IO Int dmatrix_sizeL x = casadi__DMatrix__sizeL (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sizeU" c_casadi__DMatrix__sizeU :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO CInt casadi__DMatrix__sizeU :: DMatrix -> IO Int casadi__DMatrix__sizeU x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sizeU errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sizeU :: DMatrixClass a => a -> IO Int dmatrix_sizeU x = casadi__DMatrix__sizeU (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sparse__0" c_casadi__DMatrix__sparse__0 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__sparse__0 :: Sparsity -> DMatrix -> IO DMatrix casadi__DMatrix__sparse__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sparse__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sparse__0 :: Sparsity -> DMatrix -> IO DMatrix dmatrix_sparse__0 = casadi__DMatrix__sparse__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sparse__1" c_casadi__DMatrix__sparse__1 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr DMatrix') casadi__DMatrix__sparse__1 :: (Int, Int) -> IO DMatrix casadi__DMatrix__sparse__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sparse__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sparse__1 :: (Int, Int) -> IO DMatrix dmatrix_sparse__1 = casadi__DMatrix__sparse__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sparse__2" c_casadi__DMatrix__sparse__2 :: Ptr (Ptr StdString) -> IO (Ptr DMatrix') casadi__DMatrix__sparse__2 :: IO DMatrix casadi__DMatrix__sparse__2 = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sparse__2 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sparse__2 :: IO DMatrix dmatrix_sparse__2 = casadi__DMatrix__sparse__2 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sparse__3" c_casadi__DMatrix__sparse__3 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__sparse__3 :: Int -> IO DMatrix casadi__DMatrix__sparse__3 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sparse__3 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sparse__3 :: Int -> IO DMatrix dmatrix_sparse__3 = casadi__DMatrix__sparse__3 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sparse__4" c_casadi__DMatrix__sparse__4 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__sparse__4 :: Int -> Int -> IO DMatrix casadi__DMatrix__sparse__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sparse__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sparse__4 :: Int -> Int -> IO DMatrix dmatrix_sparse__4 = casadi__DMatrix__sparse__4 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sparsity" c_casadi__DMatrix__sparsity :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr Sparsity') casadi__DMatrix__sparsity :: DMatrix -> IO Sparsity casadi__DMatrix__sparsity x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sparsity errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sparsity :: DMatrixClass a => a -> IO Sparsity dmatrix_sparsity x = casadi__DMatrix__sparsity (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__0" c_casadi__DMatrix__sym__0 :: Ptr (Ptr StdString) -> Ptr StdString -> CInt -> CInt -> CInt -> CInt -> IO (Ptr (StdVec (Ptr (StdVec (Ptr DMatrix'))))) casadi__DMatrix__sym__0 :: String -> Int -> Int -> Int -> Int -> IO (Vector (Vector DMatrix)) casadi__DMatrix__sym__0 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__DMatrix__sym__0 errStrPtrP x0' x1' x2' x3' x4' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__0 :: String -> Int -> Int -> Int -> Int -> IO (Vector (Vector DMatrix)) dmatrix_sym__0 = casadi__DMatrix__sym__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__1" c_casadi__DMatrix__sym__1 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr Sparsity' -> CInt -> CInt -> IO (Ptr (StdVec (Ptr (StdVec (Ptr DMatrix'))))) casadi__DMatrix__sym__1 :: String -> Sparsity -> Int -> Int -> IO (Vector (Vector DMatrix)) casadi__DMatrix__sym__1 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sym__1 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__1 :: String -> Sparsity -> Int -> Int -> IO (Vector (Vector DMatrix)) dmatrix_sym__1 = casadi__DMatrix__sym__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__2" c_casadi__DMatrix__sym__2 :: Ptr (Ptr StdString) -> Ptr StdString -> CInt -> CInt -> CInt -> IO (Ptr (StdVec (Ptr DMatrix'))) casadi__DMatrix__sym__2 :: String -> Int -> Int -> Int -> IO (Vector DMatrix) casadi__DMatrix__sym__2 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sym__2 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__2 :: String -> Int -> Int -> Int -> IO (Vector DMatrix) dmatrix_sym__2 = casadi__DMatrix__sym__2 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__3" c_casadi__DMatrix__sym__3 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr Sparsity' -> CInt -> IO (Ptr (StdVec (Ptr DMatrix'))) casadi__DMatrix__sym__3 :: String -> Sparsity -> Int -> IO (Vector DMatrix) casadi__DMatrix__sym__3 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sym__3 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__3 :: String -> Sparsity -> Int -> IO (Vector DMatrix) dmatrix_sym__3 = casadi__DMatrix__sym__3 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__4" c_casadi__DMatrix__sym__4 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr Sparsity' -> IO (Ptr DMatrix') casadi__DMatrix__sym__4 :: String -> Sparsity -> IO DMatrix casadi__DMatrix__sym__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sym__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__4 :: String -> Sparsity -> IO DMatrix dmatrix_sym__4 = casadi__DMatrix__sym__4 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__5" c_casadi__DMatrix__sym__5 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr (StdPair CInt CInt) -> IO (Ptr DMatrix') casadi__DMatrix__sym__5 :: String -> (Int, Int) -> IO DMatrix casadi__DMatrix__sym__5 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sym__5 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__5 :: String -> (Int, Int) -> IO DMatrix dmatrix_sym__5 = casadi__DMatrix__sym__5 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__6" c_casadi__DMatrix__sym__6 :: Ptr (Ptr StdString) -> Ptr StdString -> IO (Ptr DMatrix') casadi__DMatrix__sym__6 :: String -> IO DMatrix casadi__DMatrix__sym__6 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sym__6 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__6 :: String -> IO DMatrix dmatrix_sym__6 = casadi__DMatrix__sym__6 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__7" c_casadi__DMatrix__sym__7 :: Ptr (Ptr StdString) -> Ptr StdString -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__sym__7 :: String -> Int -> IO DMatrix casadi__DMatrix__sym__7 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sym__7 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__7 :: String -> Int -> IO DMatrix dmatrix_sym__7 = casadi__DMatrix__sym__7 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__sym__8" c_casadi__DMatrix__sym__8 :: Ptr (Ptr StdString) -> Ptr StdString -> CInt -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__sym__8 :: String -> Int -> Int -> IO DMatrix casadi__DMatrix__sym__8 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__sym__8 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_sym__8 :: String -> Int -> Int -> IO DMatrix dmatrix_sym__8 = casadi__DMatrix__sym__8 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__toSlice__0" c_casadi__DMatrix__toSlice__0 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr Slice') casadi__DMatrix__toSlice__0 :: DMatrix -> IO Slice casadi__DMatrix__toSlice__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__toSlice__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_toSlice__0 :: DMatrixClass a => a -> IO Slice dmatrix_toSlice__0 x = casadi__DMatrix__toSlice__0 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__toSlice__1" c_casadi__DMatrix__toSlice__1 :: Ptr (Ptr StdString) -> Ptr DMatrix' -> CInt -> IO (Ptr Slice') casadi__DMatrix__toSlice__1 :: DMatrix -> Bool -> IO Slice casadi__DMatrix__toSlice__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__toSlice__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_toSlice__1 :: DMatrixClass a => a -> Bool -> IO Slice dmatrix_toSlice__1 x = casadi__DMatrix__toSlice__1 (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__triplet__0" c_casadi__DMatrix__triplet__0 :: Ptr (Ptr StdString) -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> Ptr DMatrix' -> Ptr (StdPair CInt CInt) -> IO (Ptr DMatrix') casadi__DMatrix__triplet__0 :: Vector Int -> Vector Int -> DMatrix -> (Int, Int) -> IO DMatrix casadi__DMatrix__triplet__0 x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__triplet__0 errStrPtrP x0' x1' x2' x3' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_triplet__0 :: Vector Int -> Vector Int -> DMatrix -> (Int, Int) -> IO DMatrix dmatrix_triplet__0 = casadi__DMatrix__triplet__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__triplet__1" c_casadi__DMatrix__triplet__1 :: Ptr (Ptr StdString) -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> Ptr DMatrix' -> CInt -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__triplet__1 :: Vector Int -> Vector Int -> DMatrix -> Int -> Int -> IO DMatrix casadi__DMatrix__triplet__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__DMatrix__triplet__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 dmatrix_triplet__1 :: Vector Int -> Vector Int -> DMatrix -> Int -> Int -> IO DMatrix dmatrix_triplet__1 = casadi__DMatrix__triplet__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__triplet__2" c_casadi__DMatrix__triplet__2 :: Ptr (Ptr StdString) -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__triplet__2 :: Vector Int -> Vector Int -> DMatrix -> IO DMatrix casadi__DMatrix__triplet__2 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__triplet__2 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_triplet__2 :: Vector Int -> Vector Int -> DMatrix -> IO DMatrix dmatrix_triplet__2 = casadi__DMatrix__triplet__2 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__unary" c_casadi__DMatrix__unary :: Ptr (Ptr StdString) -> CInt -> Ptr DMatrix' -> IO (Ptr DMatrix') casadi__DMatrix__unary :: Int -> DMatrix -> IO DMatrix casadi__DMatrix__unary x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__unary errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_unary :: Int -> DMatrix -> IO DMatrix dmatrix_unary = casadi__DMatrix__unary -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__zeros__0" c_casadi__DMatrix__zeros__0 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr DMatrix') casadi__DMatrix__zeros__0 :: (Int, Int) -> IO DMatrix casadi__DMatrix__zeros__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__zeros__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_zeros__0 :: (Int, Int) -> IO DMatrix dmatrix_zeros__0 = casadi__DMatrix__zeros__0 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__zeros__1" c_casadi__DMatrix__zeros__1 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr DMatrix') casadi__DMatrix__zeros__1 :: Sparsity -> IO DMatrix casadi__DMatrix__zeros__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__zeros__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_zeros__1 :: Sparsity -> IO DMatrix dmatrix_zeros__1 = casadi__DMatrix__zeros__1 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__zeros__2" c_casadi__DMatrix__zeros__2 :: Ptr (Ptr StdString) -> IO (Ptr DMatrix') casadi__DMatrix__zeros__2 :: IO DMatrix casadi__DMatrix__zeros__2 = do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__zeros__2 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_zeros__2 :: IO DMatrix dmatrix_zeros__2 = casadi__DMatrix__zeros__2 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__zeros__3" c_casadi__DMatrix__zeros__3 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__zeros__3 :: Int -> IO DMatrix casadi__DMatrix__zeros__3 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__zeros__3 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_zeros__3 :: Int -> IO DMatrix dmatrix_zeros__3 = casadi__DMatrix__zeros__3 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__zeros__4" c_casadi__DMatrix__zeros__4 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr DMatrix') casadi__DMatrix__zeros__4 :: Int -> Int -> IO DMatrix casadi__DMatrix__zeros__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__zeros__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_zeros__4 :: Int -> Int -> IO DMatrix dmatrix_zeros__4 = casadi__DMatrix__zeros__4 -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getRepresentation" c_casadi__DMatrix__getRepresentation :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr StdString) casadi__DMatrix__getRepresentation :: DMatrix -> IO String casadi__DMatrix__getRepresentation x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getRepresentation errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getRepresentation :: DMatrixClass a => a -> IO String dmatrix_getRepresentation x = casadi__DMatrix__getRepresentation (castDMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__DMatrix__getDescription" c_casadi__DMatrix__getDescription :: Ptr (Ptr StdString) -> Ptr DMatrix' -> IO (Ptr StdString) casadi__DMatrix__getDescription :: DMatrix -> IO String casadi__DMatrix__getDescription x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__DMatrix__getDescription errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper dmatrix_getDescription :: DMatrixClass a => a -> IO String dmatrix_getDescription x = casadi__DMatrix__getDescription (castDMatrix x)