{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Classes.IMatrix ( IMatrix, IMatrixClass(..), imatrix_T, imatrix__0, imatrix__1, imatrix__2, imatrix__3, imatrix__4, imatrix__5, imatrix__6, imatrix___nonzero__, imatrix_append, imatrix_appendColumns, imatrix_binary, imatrix_className, imatrix_clear, imatrix_colind, imatrix_dimString, imatrix_enlarge__0, imatrix_enlarge__1, imatrix_erase__0, imatrix_erase__1, imatrix_erase__2, imatrix_erase__3, imatrix_eye, imatrix_find__0, imatrix_find__1, imatrix_getColind, imatrix_getDep__0, imatrix_getDep__1, imatrix_getDescription, imatrix_getElementHash, imatrix_getEqualityCheckingDepth, imatrix_getIntValue, imatrix_getNZ__0, imatrix_getNZ__1, imatrix_getNZ__2, imatrix_getName, imatrix_getNdeps, imatrix_getRepresentation, imatrix_getRow, imatrix_getSparsity, imatrix_getSym, imatrix_getValue__0, imatrix_getValue__1, imatrix_get__0, imatrix_get__1, imatrix_get__2, imatrix_get__3, imatrix_get__4, imatrix_get__5, imatrix_get__6, imatrix_get__7, imatrix_hasDuplicates, imatrix_hasNZ, imatrix_hasNonStructuralZeros, imatrix_inf__0, imatrix_inf__1, imatrix_inf__2, imatrix_inf__3, imatrix_inf__4, imatrix_isCommutative, imatrix_isConstant, imatrix_isIdentity, imatrix_isInteger, imatrix_isLeaf, imatrix_isMinusOne, imatrix_isOne, imatrix_isRegular, imatrix_isSlice__0, imatrix_isSlice__1, imatrix_isSmooth, imatrix_isSymbolic, imatrix_isValidInput, imatrix_isZero, imatrix_iscolumn, imatrix_isdense, imatrix_isempty__0, imatrix_isempty__1, imatrix_isrow, imatrix_isscalar__0, imatrix_isscalar__1, imatrix_issquare, imatrix_istril, imatrix_istriu, imatrix_isvector, imatrix_makeSparse__0, imatrix_makeSparse__1, imatrix_matrix_matrix, imatrix_matrix_scalar, imatrix_nan__0, imatrix_nan__1, imatrix_nan__2, imatrix_nan__3, imatrix_nan__4, imatrix_nnz, imatrix_nonzeros, imatrix_nonzeros_int, imatrix_numel__0, imatrix_numel__1, imatrix_ones__0, imatrix_ones__1, imatrix_ones__2, imatrix_ones__3, imatrix_ones__4, imatrix_operator_minus, imatrix_operator_plus, imatrix_printDense, imatrix_printScalar, imatrix_printSparse, imatrix_printSplit, imatrix_printVector, imatrix_printme, imatrix_remove, imatrix_reserve__0, imatrix_reserve__1, imatrix_resetInput, imatrix_resize, imatrix_row, imatrix_sanityCheck__0, imatrix_sanityCheck__1, imatrix_scalar_matrix, imatrix_setEqualityCheckingDepth__0, imatrix_setEqualityCheckingDepth__1, imatrix_setNZ__0, imatrix_setNZ__1, imatrix_setNZ__2, imatrix_setNZ__3, imatrix_setPrecision, imatrix_setScientific, imatrix_setSym, imatrix_setValue__0, imatrix_setValue__1, imatrix_setWidth, imatrix_setZero, imatrix_set__0, imatrix_set__1, imatrix_set__10, imatrix_set__2, imatrix_set__3, imatrix_set__4, imatrix_set__5, imatrix_set__6, imatrix_set__7, imatrix_set__8, imatrix_set__9, imatrix_shape__0, imatrix_shape__1, imatrix_size, imatrix_size1, imatrix_size2, imatrix_sizeD, imatrix_sizeL, imatrix_sizeU, imatrix_sparse__0, imatrix_sparse__1, imatrix_sparse__2, imatrix_sparse__3, imatrix_sparse__4, imatrix_sparsity, imatrix_sym__0, imatrix_sym__1, imatrix_sym__2, imatrix_sym__3, imatrix_sym__4, imatrix_sym__5, imatrix_sym__6, imatrix_sym__7, imatrix_sym__8, imatrix_toSlice__0, imatrix_toSlice__1, imatrix_triplet__0, imatrix_triplet__1, imatrix_triplet__2, imatrix_unary, imatrix_zeros__0, imatrix_zeros__1, imatrix_zeros__2, imatrix_zeros__3, imatrix_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__IMatrix__CONSTRUCTOR__0" c_casadi__IMatrix__CONSTRUCTOR__0 :: Ptr (Ptr StdString) -> Ptr (StdVec (Ptr (StdVec CDouble))) -> IO (Ptr IMatrix') casadi__IMatrix__CONSTRUCTOR__0 :: Vector (Vector Double) -> IO IMatrix casadi__IMatrix__CONSTRUCTOR__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__CONSTRUCTOR__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix__0 :: Vector (Vector Double) -> IO IMatrix imatrix__0 = casadi__IMatrix__CONSTRUCTOR__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__CONSTRUCTOR__1" c_casadi__IMatrix__CONSTRUCTOR__1 :: Ptr (Ptr StdString) -> CDouble -> IO (Ptr IMatrix') casadi__IMatrix__CONSTRUCTOR__1 :: Double -> IO IMatrix casadi__IMatrix__CONSTRUCTOR__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__CONSTRUCTOR__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix__1 :: Double -> IO IMatrix imatrix__1 = casadi__IMatrix__CONSTRUCTOR__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__CONSTRUCTOR__2" c_casadi__IMatrix__CONSTRUCTOR__2 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__CONSTRUCTOR__2 :: Sparsity -> IMatrix -> IO IMatrix casadi__IMatrix__CONSTRUCTOR__2 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__CONSTRUCTOR__2 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix__2 :: Sparsity -> IMatrix -> IO IMatrix imatrix__2 = casadi__IMatrix__CONSTRUCTOR__2 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__CONSTRUCTOR__3" c_casadi__IMatrix__CONSTRUCTOR__3 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr IMatrix') casadi__IMatrix__CONSTRUCTOR__3 :: Sparsity -> IO IMatrix casadi__IMatrix__CONSTRUCTOR__3 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__CONSTRUCTOR__3 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix__3 :: Sparsity -> IO IMatrix imatrix__3 = casadi__IMatrix__CONSTRUCTOR__3 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__CONSTRUCTOR__4" c_casadi__IMatrix__CONSTRUCTOR__4 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__CONSTRUCTOR__4 :: Int -> Int -> IO IMatrix casadi__IMatrix__CONSTRUCTOR__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__CONSTRUCTOR__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix__4 :: Int -> Int -> IO IMatrix imatrix__4 = casadi__IMatrix__CONSTRUCTOR__4 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__CONSTRUCTOR__5" c_casadi__IMatrix__CONSTRUCTOR__5 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__CONSTRUCTOR__5 :: IMatrix -> IO IMatrix casadi__IMatrix__CONSTRUCTOR__5 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__CONSTRUCTOR__5 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix__5 :: IMatrix -> IO IMatrix imatrix__5 = casadi__IMatrix__CONSTRUCTOR__5 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__CONSTRUCTOR__6" c_casadi__IMatrix__CONSTRUCTOR__6 :: Ptr (Ptr StdString) -> IO (Ptr IMatrix') casadi__IMatrix__CONSTRUCTOR__6 :: IO IMatrix casadi__IMatrix__CONSTRUCTOR__6 = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__CONSTRUCTOR__6 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix__6 :: IO IMatrix imatrix__6 = casadi__IMatrix__CONSTRUCTOR__6 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__T" c_casadi__IMatrix__T :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__T :: IMatrix -> IO IMatrix casadi__IMatrix__T x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__T errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_T :: IMatrixClass a => a -> IO IMatrix imatrix_T x = casadi__IMatrix__T (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix____nonzero__" c_casadi__IMatrix____nonzero__ :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix____nonzero__ :: IMatrix -> IO Bool casadi__IMatrix____nonzero__ x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix____nonzero__ errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix___nonzero__ :: IMatrixClass a => a -> IO Bool imatrix___nonzero__ x = casadi__IMatrix____nonzero__ (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__append" c_casadi__IMatrix__append :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> IO () casadi__IMatrix__append :: IMatrix -> IMatrix -> IO () casadi__IMatrix__append x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__append errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_append :: IMatrixClass a => a -> IMatrix -> IO () imatrix_append x = casadi__IMatrix__append (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__appendColumns" c_casadi__IMatrix__appendColumns :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> IO () casadi__IMatrix__appendColumns :: IMatrix -> IMatrix -> IO () casadi__IMatrix__appendColumns x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__appendColumns errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_appendColumns :: IMatrixClass a => a -> IMatrix -> IO () imatrix_appendColumns x = casadi__IMatrix__appendColumns (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__binary" c_casadi__IMatrix__binary :: Ptr (Ptr StdString) -> CInt -> Ptr IMatrix' -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__binary :: Int -> IMatrix -> IMatrix -> IO IMatrix casadi__IMatrix__binary x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__binary errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_binary :: Int -> IMatrix -> IMatrix -> IO IMatrix imatrix_binary = casadi__IMatrix__binary -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__className" c_casadi__IMatrix__className :: Ptr (Ptr StdString) -> IO (Ptr StdString) casadi__IMatrix__className :: IO String casadi__IMatrix__className = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__className errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_className :: IO String imatrix_className = casadi__IMatrix__className -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__clear" c_casadi__IMatrix__clear :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__clear :: IMatrix -> IO () casadi__IMatrix__clear x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__clear errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_clear :: IMatrixClass a => a -> IO () imatrix_clear x = casadi__IMatrix__clear (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__colind" c_casadi__IMatrix__colind :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO CInt casadi__IMatrix__colind :: IMatrix -> Int -> IO Int casadi__IMatrix__colind x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__colind errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_colind :: IMatrixClass a => a -> Int -> IO Int imatrix_colind x = casadi__IMatrix__colind (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__dimString" c_casadi__IMatrix__dimString :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr StdString) casadi__IMatrix__dimString :: IMatrix -> IO String casadi__IMatrix__dimString x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__dimString errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_dimString :: IMatrixClass a => a -> IO String imatrix_dimString x = casadi__IMatrix__dimString (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__enlarge__0" c_casadi__IMatrix__enlarge__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> CInt -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> IO () casadi__IMatrix__enlarge__0 :: IMatrix -> Int -> Int -> Vector Int -> Vector Int -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_enlarge__0 :: IMatrixClass a => a -> Int -> Int -> Vector Int -> Vector Int -> IO () imatrix_enlarge__0 x = casadi__IMatrix__enlarge__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__enlarge__1" c_casadi__IMatrix__enlarge__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> CInt -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> CInt -> IO () casadi__IMatrix__enlarge__1 :: IMatrix -> Int -> Int -> Vector Int -> Vector Int -> Bool -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_enlarge__1 :: IMatrixClass a => a -> Int -> Int -> Vector Int -> Vector Int -> Bool -> IO () imatrix_enlarge__1 x = casadi__IMatrix__enlarge__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__erase__0" c_casadi__IMatrix__erase__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CInt) -> IO () casadi__IMatrix__erase__0 :: IMatrix -> Vector Int -> IO () casadi__IMatrix__erase__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__erase__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_erase__0 :: IMatrixClass a => a -> Vector Int -> IO () imatrix_erase__0 x = casadi__IMatrix__erase__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__erase__1" c_casadi__IMatrix__erase__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CInt) -> CInt -> IO () casadi__IMatrix__erase__1 :: IMatrix -> Vector Int -> Bool -> IO () casadi__IMatrix__erase__1 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__erase__1 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_erase__1 :: IMatrixClass a => a -> Vector Int -> Bool -> IO () imatrix_erase__1 x = casadi__IMatrix__erase__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__erase__2" c_casadi__IMatrix__erase__2 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> IO () casadi__IMatrix__erase__2 :: IMatrix -> Vector Int -> Vector Int -> IO () casadi__IMatrix__erase__2 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__erase__2 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_erase__2 :: IMatrixClass a => a -> Vector Int -> Vector Int -> IO () imatrix_erase__2 x = casadi__IMatrix__erase__2 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__erase__3" c_casadi__IMatrix__erase__3 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> CInt -> IO () casadi__IMatrix__erase__3 :: IMatrix -> Vector Int -> Vector Int -> Bool -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_erase__3 :: IMatrixClass a => a -> Vector Int -> Vector Int -> Bool -> IO () imatrix_erase__3 x = casadi__IMatrix__erase__3 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__eye" c_casadi__IMatrix__eye :: Ptr (Ptr StdString) -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__eye :: Int -> IO IMatrix casadi__IMatrix__eye x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__eye errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_eye :: Int -> IO IMatrix imatrix_eye = casadi__IMatrix__eye -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__find__0" c_casadi__IMatrix__find__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr (StdVec CInt)) casadi__IMatrix__find__0 :: IMatrix -> IO (Vector Int) casadi__IMatrix__find__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__find__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_find__0 :: IMatrixClass a => a -> IO (Vector Int) imatrix_find__0 x = casadi__IMatrix__find__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__find__1" c_casadi__IMatrix__find__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO (Ptr (StdVec CInt)) casadi__IMatrix__find__1 :: IMatrix -> Bool -> IO (Vector Int) casadi__IMatrix__find__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__find__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_find__1 :: IMatrixClass a => a -> Bool -> IO (Vector Int) imatrix_find__1 x = casadi__IMatrix__find__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__get__0" c_casadi__IMatrix__get__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr IMatrix' -> Ptr IMatrix' -> IO () casadi__IMatrix__get__0 :: IMatrix -> IMatrix -> Bool -> IMatrix -> IMatrix -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_get__0 :: IMatrixClass a => a -> IMatrix -> Bool -> IMatrix -> IMatrix -> IO () imatrix_get__0 x = casadi__IMatrix__get__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__get__1" c_casadi__IMatrix__get__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr IMatrix' -> Ptr Slice' -> IO () casadi__IMatrix__get__1 :: IMatrix -> IMatrix -> Bool -> IMatrix -> Slice -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_get__1 :: IMatrixClass a => a -> IMatrix -> Bool -> IMatrix -> Slice -> IO () imatrix_get__1 x = casadi__IMatrix__get__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__get__2" c_casadi__IMatrix__get__2 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Slice' -> Ptr IMatrix' -> IO () casadi__IMatrix__get__2 :: IMatrix -> IMatrix -> Bool -> Slice -> IMatrix -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_get__2 :: IMatrixClass a => a -> IMatrix -> Bool -> Slice -> IMatrix -> IO () imatrix_get__2 x = casadi__IMatrix__get__2 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__get__3" c_casadi__IMatrix__get__3 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Slice' -> Ptr Slice' -> IO () casadi__IMatrix__get__3 :: IMatrix -> IMatrix -> Bool -> Slice -> Slice -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_get__3 :: IMatrixClass a => a -> IMatrix -> Bool -> Slice -> Slice -> IO () imatrix_get__3 x = casadi__IMatrix__get__3 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__get__4" c_casadi__IMatrix__get__4 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Sparsity' -> IO () casadi__IMatrix__get__4 :: IMatrix -> IMatrix -> Bool -> Sparsity -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_get__4 :: IMatrixClass a => a -> IMatrix -> Bool -> Sparsity -> IO () imatrix_get__4 x = casadi__IMatrix__get__4 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__get__5" c_casadi__IMatrix__get__5 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr IMatrix' -> IO () casadi__IMatrix__get__5 :: IMatrix -> IMatrix -> Bool -> IMatrix -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_get__5 :: IMatrixClass a => a -> IMatrix -> Bool -> IMatrix -> IO () imatrix_get__5 x = casadi__IMatrix__get__5 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__get__6" c_casadi__IMatrix__get__6 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Slice' -> IO () casadi__IMatrix__get__6 :: IMatrix -> IMatrix -> Bool -> Slice -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_get__6 :: IMatrixClass a => a -> IMatrix -> Bool -> Slice -> IO () imatrix_get__6 x = casadi__IMatrix__get__6 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__get__7" c_casadi__IMatrix__get__7 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__IMatrix__get__7 :: IMatrix -> Vector Double -> IO () casadi__IMatrix__get__7 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__get__7 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_get__7 :: IMatrixClass a => a -> Vector Double -> IO () imatrix_get__7 x = casadi__IMatrix__get__7 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getColind" c_casadi__IMatrix__getColind :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr (StdVec CInt)) casadi__IMatrix__getColind :: IMatrix -> IO (Vector Int) casadi__IMatrix__getColind x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getColind errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getColind :: IMatrixClass a => a -> IO (Vector Int) imatrix_getColind x = casadi__IMatrix__getColind (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getDep__0" c_casadi__IMatrix__getDep__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__getDep__0 :: IMatrix -> IO IMatrix casadi__IMatrix__getDep__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getDep__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getDep__0 :: IMatrixClass a => a -> IO IMatrix imatrix_getDep__0 x = casadi__IMatrix__getDep__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getDep__1" c_casadi__IMatrix__getDep__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__getDep__1 :: IMatrix -> Int -> IO IMatrix casadi__IMatrix__getDep__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getDep__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getDep__1 :: IMatrixClass a => a -> Int -> IO IMatrix imatrix_getDep__1 x = casadi__IMatrix__getDep__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getElementHash" c_casadi__IMatrix__getElementHash :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CSize casadi__IMatrix__getElementHash :: IMatrix -> IO CSize casadi__IMatrix__getElementHash x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getElementHash errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getElementHash :: IMatrixClass a => a -> IO CSize imatrix_getElementHash x = casadi__IMatrix__getElementHash (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getEqualityCheckingDepth" c_casadi__IMatrix__getEqualityCheckingDepth :: Ptr (Ptr StdString) -> IO CInt casadi__IMatrix__getEqualityCheckingDepth :: IO Int casadi__IMatrix__getEqualityCheckingDepth = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getEqualityCheckingDepth errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getEqualityCheckingDepth :: IO Int imatrix_getEqualityCheckingDepth = casadi__IMatrix__getEqualityCheckingDepth -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getIntValue" c_casadi__IMatrix__getIntValue :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__getIntValue :: IMatrix -> IO Int casadi__IMatrix__getIntValue x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getIntValue errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getIntValue :: IMatrixClass a => a -> IO Int imatrix_getIntValue x = casadi__IMatrix__getIntValue (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getNZ__0" c_casadi__IMatrix__getNZ__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr IMatrix' -> IO () casadi__IMatrix__getNZ__0 :: IMatrix -> IMatrix -> Bool -> IMatrix -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_getNZ__0 :: IMatrixClass a => a -> IMatrix -> Bool -> IMatrix -> IO () imatrix_getNZ__0 x = casadi__IMatrix__getNZ__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getNZ__1" c_casadi__IMatrix__getNZ__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Slice' -> IO () casadi__IMatrix__getNZ__1 :: IMatrix -> IMatrix -> Bool -> Slice -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_getNZ__1 :: IMatrixClass a => a -> IMatrix -> Bool -> Slice -> IO () imatrix_getNZ__1 x = casadi__IMatrix__getNZ__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getNZ__2" c_casadi__IMatrix__getNZ__2 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__IMatrix__getNZ__2 :: IMatrix -> Vector Double -> IO () casadi__IMatrix__getNZ__2 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getNZ__2 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getNZ__2 :: IMatrixClass a => a -> Vector Double -> IO () imatrix_getNZ__2 x = casadi__IMatrix__getNZ__2 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getName" c_casadi__IMatrix__getName :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr StdString) casadi__IMatrix__getName :: IMatrix -> IO String casadi__IMatrix__getName x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getName errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getName :: IMatrixClass a => a -> IO String imatrix_getName x = casadi__IMatrix__getName (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getNdeps" c_casadi__IMatrix__getNdeps :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__getNdeps :: IMatrix -> IO Int casadi__IMatrix__getNdeps x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getNdeps errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getNdeps :: IMatrixClass a => a -> IO Int imatrix_getNdeps x = casadi__IMatrix__getNdeps (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getRow" c_casadi__IMatrix__getRow :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr (StdVec CInt)) casadi__IMatrix__getRow :: IMatrix -> IO (Vector Int) casadi__IMatrix__getRow x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getRow errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getRow :: IMatrixClass a => a -> IO (Vector Int) imatrix_getRow x = casadi__IMatrix__getRow (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getSparsity" c_casadi__IMatrix__getSparsity :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr Sparsity') casadi__IMatrix__getSparsity :: IMatrix -> IO Sparsity casadi__IMatrix__getSparsity x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getSparsity errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getSparsity :: IMatrixClass a => a -> IO Sparsity imatrix_getSparsity x = casadi__IMatrix__getSparsity (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getSym" c_casadi__IMatrix__getSym :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__IMatrix__getSym :: IMatrix -> Vector Double -> IO () casadi__IMatrix__getSym x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getSym errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getSym :: IMatrixClass a => a -> Vector Double -> IO () imatrix_getSym x = casadi__IMatrix__getSym (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getValue__0" c_casadi__IMatrix__getValue__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO CDouble casadi__IMatrix__getValue__0 :: IMatrix -> Int -> IO Double casadi__IMatrix__getValue__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getValue__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getValue__0 :: IMatrixClass a => a -> Int -> IO Double imatrix_getValue__0 x = casadi__IMatrix__getValue__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getValue__1" c_casadi__IMatrix__getValue__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CDouble casadi__IMatrix__getValue__1 :: IMatrix -> IO Double casadi__IMatrix__getValue__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getValue__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getValue__1 :: IMatrixClass a => a -> IO Double imatrix_getValue__1 x = casadi__IMatrix__getValue__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__hasDuplicates" c_casadi__IMatrix__hasDuplicates :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__hasDuplicates :: IMatrix -> IO Bool casadi__IMatrix__hasDuplicates x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__hasDuplicates errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_hasDuplicates :: IMatrixClass a => a -> IO Bool imatrix_hasDuplicates x = casadi__IMatrix__hasDuplicates (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__hasNZ" c_casadi__IMatrix__hasNZ :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> CInt -> IO CInt casadi__IMatrix__hasNZ :: IMatrix -> Int -> Int -> IO Bool casadi__IMatrix__hasNZ x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__hasNZ errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_hasNZ :: IMatrixClass a => a -> Int -> Int -> IO Bool imatrix_hasNZ x = casadi__IMatrix__hasNZ (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__hasNonStructuralZeros" c_casadi__IMatrix__hasNonStructuralZeros :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__hasNonStructuralZeros :: IMatrix -> IO Bool casadi__IMatrix__hasNonStructuralZeros x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__hasNonStructuralZeros errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_hasNonStructuralZeros :: IMatrixClass a => a -> IO Bool imatrix_hasNonStructuralZeros x = casadi__IMatrix__hasNonStructuralZeros (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__inf__0" c_casadi__IMatrix__inf__0 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr IMatrix') casadi__IMatrix__inf__0 :: (Int, Int) -> IO IMatrix casadi__IMatrix__inf__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__inf__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_inf__0 :: (Int, Int) -> IO IMatrix imatrix_inf__0 = casadi__IMatrix__inf__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__inf__1" c_casadi__IMatrix__inf__1 :: Ptr (Ptr StdString) -> IO (Ptr IMatrix') casadi__IMatrix__inf__1 :: IO IMatrix casadi__IMatrix__inf__1 = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__inf__1 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_inf__1 :: IO IMatrix imatrix_inf__1 = casadi__IMatrix__inf__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__inf__2" c_casadi__IMatrix__inf__2 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__inf__2 :: Int -> IO IMatrix casadi__IMatrix__inf__2 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__inf__2 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_inf__2 :: Int -> IO IMatrix imatrix_inf__2 = casadi__IMatrix__inf__2 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__inf__3" c_casadi__IMatrix__inf__3 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__inf__3 :: Int -> Int -> IO IMatrix casadi__IMatrix__inf__3 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__inf__3 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_inf__3 :: Int -> Int -> IO IMatrix imatrix_inf__3 = casadi__IMatrix__inf__3 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__inf__4" c_casadi__IMatrix__inf__4 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr IMatrix') casadi__IMatrix__inf__4 :: Sparsity -> IO IMatrix casadi__IMatrix__inf__4 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__inf__4 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_inf__4 :: Sparsity -> IO IMatrix imatrix_inf__4 = casadi__IMatrix__inf__4 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isCommutative" c_casadi__IMatrix__isCommutative :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isCommutative :: IMatrix -> IO Bool casadi__IMatrix__isCommutative x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isCommutative errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isCommutative :: IMatrixClass a => a -> IO Bool imatrix_isCommutative x = casadi__IMatrix__isCommutative (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isConstant" c_casadi__IMatrix__isConstant :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isConstant :: IMatrix -> IO Bool casadi__IMatrix__isConstant x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isConstant errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isConstant :: IMatrixClass a => a -> IO Bool imatrix_isConstant x = casadi__IMatrix__isConstant (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isIdentity" c_casadi__IMatrix__isIdentity :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isIdentity :: IMatrix -> IO Bool casadi__IMatrix__isIdentity x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isIdentity errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isIdentity :: IMatrixClass a => a -> IO Bool imatrix_isIdentity x = casadi__IMatrix__isIdentity (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isInteger" c_casadi__IMatrix__isInteger :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isInteger :: IMatrix -> IO Bool casadi__IMatrix__isInteger x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isInteger errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isInteger :: IMatrixClass a => a -> IO Bool imatrix_isInteger x = casadi__IMatrix__isInteger (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isLeaf" c_casadi__IMatrix__isLeaf :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isLeaf :: IMatrix -> IO Bool casadi__IMatrix__isLeaf x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isLeaf errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isLeaf :: IMatrixClass a => a -> IO Bool imatrix_isLeaf x = casadi__IMatrix__isLeaf (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isMinusOne" c_casadi__IMatrix__isMinusOne :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isMinusOne :: IMatrix -> IO Bool casadi__IMatrix__isMinusOne x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isMinusOne errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isMinusOne :: IMatrixClass a => a -> IO Bool imatrix_isMinusOne x = casadi__IMatrix__isMinusOne (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isOne" c_casadi__IMatrix__isOne :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isOne :: IMatrix -> IO Bool casadi__IMatrix__isOne x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isOne errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isOne :: IMatrixClass a => a -> IO Bool imatrix_isOne x = casadi__IMatrix__isOne (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isRegular" c_casadi__IMatrix__isRegular :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isRegular :: IMatrix -> IO Bool casadi__IMatrix__isRegular x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isRegular errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isRegular :: IMatrixClass a => a -> IO Bool imatrix_isRegular x = casadi__IMatrix__isRegular (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isSlice__0" c_casadi__IMatrix__isSlice__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isSlice__0 :: IMatrix -> IO Bool casadi__IMatrix__isSlice__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isSlice__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isSlice__0 :: IMatrixClass a => a -> IO Bool imatrix_isSlice__0 x = casadi__IMatrix__isSlice__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isSlice__1" c_casadi__IMatrix__isSlice__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO CInt casadi__IMatrix__isSlice__1 :: IMatrix -> Bool -> IO Bool casadi__IMatrix__isSlice__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isSlice__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isSlice__1 :: IMatrixClass a => a -> Bool -> IO Bool imatrix_isSlice__1 x = casadi__IMatrix__isSlice__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isSmooth" c_casadi__IMatrix__isSmooth :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isSmooth :: IMatrix -> IO Bool casadi__IMatrix__isSmooth x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isSmooth errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isSmooth :: IMatrixClass a => a -> IO Bool imatrix_isSmooth x = casadi__IMatrix__isSmooth (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isSymbolic" c_casadi__IMatrix__isSymbolic :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isSymbolic :: IMatrix -> IO Bool casadi__IMatrix__isSymbolic x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isSymbolic errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isSymbolic :: IMatrixClass a => a -> IO Bool imatrix_isSymbolic x = casadi__IMatrix__isSymbolic (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isValidInput" c_casadi__IMatrix__isValidInput :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isValidInput :: IMatrix -> IO Bool casadi__IMatrix__isValidInput x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isValidInput errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isValidInput :: IMatrixClass a => a -> IO Bool imatrix_isValidInput x = casadi__IMatrix__isValidInput (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isZero" c_casadi__IMatrix__isZero :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isZero :: IMatrix -> IO Bool casadi__IMatrix__isZero x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isZero errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isZero :: IMatrixClass a => a -> IO Bool imatrix_isZero x = casadi__IMatrix__isZero (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__iscolumn" c_casadi__IMatrix__iscolumn :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__iscolumn :: IMatrix -> IO Bool casadi__IMatrix__iscolumn x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__iscolumn errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_iscolumn :: IMatrixClass a => a -> IO Bool imatrix_iscolumn x = casadi__IMatrix__iscolumn (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isdense" c_casadi__IMatrix__isdense :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isdense :: IMatrix -> IO Bool casadi__IMatrix__isdense x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isdense errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isdense :: IMatrixClass a => a -> IO Bool imatrix_isdense x = casadi__IMatrix__isdense (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isempty__0" c_casadi__IMatrix__isempty__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isempty__0 :: IMatrix -> IO Bool casadi__IMatrix__isempty__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isempty__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isempty__0 :: IMatrixClass a => a -> IO Bool imatrix_isempty__0 x = casadi__IMatrix__isempty__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isempty__1" c_casadi__IMatrix__isempty__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO CInt casadi__IMatrix__isempty__1 :: IMatrix -> Bool -> IO Bool casadi__IMatrix__isempty__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isempty__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isempty__1 :: IMatrixClass a => a -> Bool -> IO Bool imatrix_isempty__1 x = casadi__IMatrix__isempty__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isrow" c_casadi__IMatrix__isrow :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isrow :: IMatrix -> IO Bool casadi__IMatrix__isrow x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isrow errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isrow :: IMatrixClass a => a -> IO Bool imatrix_isrow x = casadi__IMatrix__isrow (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isscalar__0" c_casadi__IMatrix__isscalar__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isscalar__0 :: IMatrix -> IO Bool casadi__IMatrix__isscalar__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isscalar__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isscalar__0 :: IMatrixClass a => a -> IO Bool imatrix_isscalar__0 x = casadi__IMatrix__isscalar__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isscalar__1" c_casadi__IMatrix__isscalar__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO CInt casadi__IMatrix__isscalar__1 :: IMatrix -> Bool -> IO Bool casadi__IMatrix__isscalar__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isscalar__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isscalar__1 :: IMatrixClass a => a -> Bool -> IO Bool imatrix_isscalar__1 x = casadi__IMatrix__isscalar__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__issquare" c_casadi__IMatrix__issquare :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__issquare :: IMatrix -> IO Bool casadi__IMatrix__issquare x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__issquare errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_issquare :: IMatrixClass a => a -> IO Bool imatrix_issquare x = casadi__IMatrix__issquare (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__istril" c_casadi__IMatrix__istril :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__istril :: IMatrix -> IO Bool casadi__IMatrix__istril x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__istril errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_istril :: IMatrixClass a => a -> IO Bool imatrix_istril x = casadi__IMatrix__istril (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__istriu" c_casadi__IMatrix__istriu :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__istriu :: IMatrix -> IO Bool casadi__IMatrix__istriu x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__istriu errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_istriu :: IMatrixClass a => a -> IO Bool imatrix_istriu x = casadi__IMatrix__istriu (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__isvector" c_casadi__IMatrix__isvector :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__isvector :: IMatrix -> IO Bool casadi__IMatrix__isvector x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__isvector errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_isvector :: IMatrixClass a => a -> IO Bool imatrix_isvector x = casadi__IMatrix__isvector (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__makeSparse__0" c_casadi__IMatrix__makeSparse__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__makeSparse__0 :: IMatrix -> IO () casadi__IMatrix__makeSparse__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__makeSparse__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_makeSparse__0 :: IMatrixClass a => a -> IO () imatrix_makeSparse__0 x = casadi__IMatrix__makeSparse__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__makeSparse__1" c_casadi__IMatrix__makeSparse__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CDouble -> IO () casadi__IMatrix__makeSparse__1 :: IMatrix -> Double -> IO () casadi__IMatrix__makeSparse__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__makeSparse__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_makeSparse__1 :: IMatrixClass a => a -> Double -> IO () imatrix_makeSparse__1 x = casadi__IMatrix__makeSparse__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__matrix_matrix" c_casadi__IMatrix__matrix_matrix :: Ptr (Ptr StdString) -> CInt -> Ptr IMatrix' -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__matrix_matrix :: Int -> IMatrix -> IMatrix -> IO IMatrix casadi__IMatrix__matrix_matrix x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__matrix_matrix errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_matrix_matrix :: Int -> IMatrix -> IMatrix -> IO IMatrix imatrix_matrix_matrix = casadi__IMatrix__matrix_matrix -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__matrix_scalar" c_casadi__IMatrix__matrix_scalar :: Ptr (Ptr StdString) -> CInt -> Ptr IMatrix' -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__matrix_scalar :: Int -> IMatrix -> IMatrix -> IO IMatrix casadi__IMatrix__matrix_scalar x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__matrix_scalar errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_matrix_scalar :: Int -> IMatrix -> IMatrix -> IO IMatrix imatrix_matrix_scalar = casadi__IMatrix__matrix_scalar -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__nan__0" c_casadi__IMatrix__nan__0 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr IMatrix') casadi__IMatrix__nan__0 :: (Int, Int) -> IO IMatrix casadi__IMatrix__nan__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__nan__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_nan__0 :: (Int, Int) -> IO IMatrix imatrix_nan__0 = casadi__IMatrix__nan__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__nan__1" c_casadi__IMatrix__nan__1 :: Ptr (Ptr StdString) -> IO (Ptr IMatrix') casadi__IMatrix__nan__1 :: IO IMatrix casadi__IMatrix__nan__1 = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__nan__1 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_nan__1 :: IO IMatrix imatrix_nan__1 = casadi__IMatrix__nan__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__nan__2" c_casadi__IMatrix__nan__2 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__nan__2 :: Int -> IO IMatrix casadi__IMatrix__nan__2 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__nan__2 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_nan__2 :: Int -> IO IMatrix imatrix_nan__2 = casadi__IMatrix__nan__2 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__nan__3" c_casadi__IMatrix__nan__3 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__nan__3 :: Int -> Int -> IO IMatrix casadi__IMatrix__nan__3 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__nan__3 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_nan__3 :: Int -> Int -> IO IMatrix imatrix_nan__3 = casadi__IMatrix__nan__3 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__nan__4" c_casadi__IMatrix__nan__4 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr IMatrix') casadi__IMatrix__nan__4 :: Sparsity -> IO IMatrix casadi__IMatrix__nan__4 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__nan__4 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_nan__4 :: Sparsity -> IO IMatrix imatrix_nan__4 = casadi__IMatrix__nan__4 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__nnz" c_casadi__IMatrix__nnz :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__nnz :: IMatrix -> IO Int casadi__IMatrix__nnz x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__nnz errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_nnz :: IMatrixClass a => a -> IO Int imatrix_nnz x = casadi__IMatrix__nnz (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__nonzeros" c_casadi__IMatrix__nonzeros :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr (StdVec CDouble)) casadi__IMatrix__nonzeros :: IMatrix -> IO (Vector Double) casadi__IMatrix__nonzeros x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__nonzeros errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_nonzeros :: IMatrixClass a => a -> IO (Vector Double) imatrix_nonzeros x = casadi__IMatrix__nonzeros (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__nonzeros_int" c_casadi__IMatrix__nonzeros_int :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr (StdVec CInt)) casadi__IMatrix__nonzeros_int :: IMatrix -> IO (Vector Int) casadi__IMatrix__nonzeros_int x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__nonzeros_int errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_nonzeros_int :: IMatrixClass a => a -> IO (Vector Int) imatrix_nonzeros_int x = casadi__IMatrix__nonzeros_int (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__numel__0" c_casadi__IMatrix__numel__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO CInt casadi__IMatrix__numel__0 :: IMatrix -> Int -> IO Int casadi__IMatrix__numel__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__numel__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_numel__0 :: IMatrixClass a => a -> Int -> IO Int imatrix_numel__0 x = casadi__IMatrix__numel__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__numel__1" c_casadi__IMatrix__numel__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__numel__1 :: IMatrix -> IO Int casadi__IMatrix__numel__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__numel__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_numel__1 :: IMatrixClass a => a -> IO Int imatrix_numel__1 x = casadi__IMatrix__numel__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__ones__0" c_casadi__IMatrix__ones__0 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr IMatrix') casadi__IMatrix__ones__0 :: (Int, Int) -> IO IMatrix casadi__IMatrix__ones__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__ones__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_ones__0 :: (Int, Int) -> IO IMatrix imatrix_ones__0 = casadi__IMatrix__ones__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__ones__1" c_casadi__IMatrix__ones__1 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr IMatrix') casadi__IMatrix__ones__1 :: Sparsity -> IO IMatrix casadi__IMatrix__ones__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__ones__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_ones__1 :: Sparsity -> IO IMatrix imatrix_ones__1 = casadi__IMatrix__ones__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__ones__2" c_casadi__IMatrix__ones__2 :: Ptr (Ptr StdString) -> IO (Ptr IMatrix') casadi__IMatrix__ones__2 :: IO IMatrix casadi__IMatrix__ones__2 = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__ones__2 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_ones__2 :: IO IMatrix imatrix_ones__2 = casadi__IMatrix__ones__2 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__ones__3" c_casadi__IMatrix__ones__3 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__ones__3 :: Int -> IO IMatrix casadi__IMatrix__ones__3 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__ones__3 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_ones__3 :: Int -> IO IMatrix imatrix_ones__3 = casadi__IMatrix__ones__3 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__ones__4" c_casadi__IMatrix__ones__4 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__ones__4 :: Int -> Int -> IO IMatrix casadi__IMatrix__ones__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__ones__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_ones__4 :: Int -> Int -> IO IMatrix imatrix_ones__4 = casadi__IMatrix__ones__4 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__operator_plus" c_casadi__IMatrix__operator_plus :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__operator_plus :: IMatrix -> IO IMatrix casadi__IMatrix__operator_plus x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__operator_plus errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_operator_plus :: IMatrixClass a => a -> IO IMatrix imatrix_operator_plus x = casadi__IMatrix__operator_plus (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__operator_minus" c_casadi__IMatrix__operator_minus :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__operator_minus :: IMatrix -> IO IMatrix casadi__IMatrix__operator_minus x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__operator_minus errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_operator_minus :: IMatrixClass a => a -> IO IMatrix imatrix_operator_minus x = casadi__IMatrix__operator_minus (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__printDense" c_casadi__IMatrix__printDense :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__printDense :: IMatrix -> IO () casadi__IMatrix__printDense x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__printDense errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_printDense :: IMatrixClass a => a -> IO () imatrix_printDense x = casadi__IMatrix__printDense (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__printScalar" c_casadi__IMatrix__printScalar :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__printScalar :: IMatrix -> IO () casadi__IMatrix__printScalar x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__printScalar errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_printScalar :: IMatrixClass a => a -> IO () imatrix_printScalar x = casadi__IMatrix__printScalar (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__printSparse" c_casadi__IMatrix__printSparse :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__printSparse :: IMatrix -> IO () casadi__IMatrix__printSparse x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__printSparse errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_printSparse :: IMatrixClass a => a -> IO () imatrix_printSparse x = casadi__IMatrix__printSparse (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__printSplit" c_casadi__IMatrix__printSplit :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec (Ptr StdString)) -> Ptr (StdVec (Ptr StdString)) -> IO () casadi__IMatrix__printSplit :: IMatrix -> Vector String -> Vector String -> IO () casadi__IMatrix__printSplit x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__printSplit errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_printSplit :: IMatrixClass a => a -> Vector String -> Vector String -> IO () imatrix_printSplit x = casadi__IMatrix__printSplit (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__printVector" c_casadi__IMatrix__printVector :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__printVector :: IMatrix -> IO () casadi__IMatrix__printVector x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__printVector errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_printVector :: IMatrixClass a => a -> IO () imatrix_printVector x = casadi__IMatrix__printVector (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__printme" c_casadi__IMatrix__printme :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__printme :: IMatrix -> IMatrix -> IO IMatrix casadi__IMatrix__printme x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__printme errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_printme :: IMatrixClass a => a -> IMatrix -> IO IMatrix imatrix_printme x = casadi__IMatrix__printme (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__remove" c_casadi__IMatrix__remove :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> IO () casadi__IMatrix__remove :: IMatrix -> Vector Int -> Vector Int -> IO () casadi__IMatrix__remove x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__remove errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_remove :: IMatrixClass a => a -> Vector Int -> Vector Int -> IO () imatrix_remove x = casadi__IMatrix__remove (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__reserve__0" c_casadi__IMatrix__reserve__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> CInt -> IO () casadi__IMatrix__reserve__0 :: IMatrix -> Int -> Int -> IO () casadi__IMatrix__reserve__0 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__reserve__0 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_reserve__0 :: IMatrixClass a => a -> Int -> Int -> IO () imatrix_reserve__0 x = casadi__IMatrix__reserve__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__reserve__1" c_casadi__IMatrix__reserve__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO () casadi__IMatrix__reserve__1 :: IMatrix -> Int -> IO () casadi__IMatrix__reserve__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__reserve__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_reserve__1 :: IMatrixClass a => a -> Int -> IO () imatrix_reserve__1 x = casadi__IMatrix__reserve__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__resetInput" c_casadi__IMatrix__resetInput :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__resetInput :: IMatrix -> IO () casadi__IMatrix__resetInput x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__resetInput errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_resetInput :: IMatrixClass a => a -> IO () imatrix_resetInput x = casadi__IMatrix__resetInput (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__resize" c_casadi__IMatrix__resize :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> CInt -> IO () casadi__IMatrix__resize :: IMatrix -> Int -> Int -> IO () casadi__IMatrix__resize x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__resize errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_resize :: IMatrixClass a => a -> Int -> Int -> IO () imatrix_resize x = casadi__IMatrix__resize (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__row" c_casadi__IMatrix__row :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO CInt casadi__IMatrix__row :: IMatrix -> Int -> IO Int casadi__IMatrix__row x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__row errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_row :: IMatrixClass a => a -> Int -> IO Int imatrix_row x = casadi__IMatrix__row (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sanityCheck__0" c_casadi__IMatrix__sanityCheck__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__sanityCheck__0 :: IMatrix -> IO () casadi__IMatrix__sanityCheck__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sanityCheck__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sanityCheck__0 :: IMatrixClass a => a -> IO () imatrix_sanityCheck__0 x = casadi__IMatrix__sanityCheck__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sanityCheck__1" c_casadi__IMatrix__sanityCheck__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO () casadi__IMatrix__sanityCheck__1 :: IMatrix -> Bool -> IO () casadi__IMatrix__sanityCheck__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sanityCheck__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sanityCheck__1 :: IMatrixClass a => a -> Bool -> IO () imatrix_sanityCheck__1 x = casadi__IMatrix__sanityCheck__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__scalar_matrix" c_casadi__IMatrix__scalar_matrix :: Ptr (Ptr StdString) -> CInt -> Ptr IMatrix' -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__scalar_matrix :: Int -> IMatrix -> IMatrix -> IO IMatrix casadi__IMatrix__scalar_matrix x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__scalar_matrix errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_scalar_matrix :: Int -> IMatrix -> IMatrix -> IO IMatrix imatrix_scalar_matrix = casadi__IMatrix__scalar_matrix -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__0" c_casadi__IMatrix__set__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr IMatrix' -> Ptr IMatrix' -> IO () casadi__IMatrix__set__0 :: IMatrix -> IMatrix -> Bool -> IMatrix -> IMatrix -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_set__0 :: IMatrixClass a => a -> IMatrix -> Bool -> IMatrix -> IMatrix -> IO () imatrix_set__0 x = casadi__IMatrix__set__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__1" c_casadi__IMatrix__set__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr IMatrix' -> Ptr Slice' -> IO () casadi__IMatrix__set__1 :: IMatrix -> IMatrix -> Bool -> IMatrix -> Slice -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_set__1 :: IMatrixClass a => a -> IMatrix -> Bool -> IMatrix -> Slice -> IO () imatrix_set__1 x = casadi__IMatrix__set__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__2" c_casadi__IMatrix__set__2 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Slice' -> Ptr IMatrix' -> IO () casadi__IMatrix__set__2 :: IMatrix -> IMatrix -> Bool -> Slice -> IMatrix -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_set__2 :: IMatrixClass a => a -> IMatrix -> Bool -> Slice -> IMatrix -> IO () imatrix_set__2 x = casadi__IMatrix__set__2 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__3" c_casadi__IMatrix__set__3 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Slice' -> Ptr Slice' -> IO () casadi__IMatrix__set__3 :: IMatrix -> IMatrix -> Bool -> Slice -> Slice -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_set__3 :: IMatrixClass a => a -> IMatrix -> Bool -> Slice -> Slice -> IO () imatrix_set__3 x = casadi__IMatrix__set__3 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__4" c_casadi__IMatrix__set__4 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Sparsity' -> IO () casadi__IMatrix__set__4 :: IMatrix -> IMatrix -> Bool -> Sparsity -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_set__4 :: IMatrixClass a => a -> IMatrix -> Bool -> Sparsity -> IO () imatrix_set__4 x = casadi__IMatrix__set__4 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__5" c_casadi__IMatrix__set__5 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr IMatrix' -> IO () casadi__IMatrix__set__5 :: IMatrix -> IMatrix -> Bool -> IMatrix -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_set__5 :: IMatrixClass a => a -> IMatrix -> Bool -> IMatrix -> IO () imatrix_set__5 x = casadi__IMatrix__set__5 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__6" c_casadi__IMatrix__set__6 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Slice' -> IO () casadi__IMatrix__set__6 :: IMatrix -> IMatrix -> Bool -> Slice -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_set__6 :: IMatrixClass a => a -> IMatrix -> Bool -> Slice -> IO () imatrix_set__6 x = casadi__IMatrix__set__6 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__7" c_casadi__IMatrix__set__7 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__IMatrix__set__7 :: IMatrix -> Vector Double -> IO () casadi__IMatrix__set__7 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__set__7 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_set__7 :: IMatrixClass a => a -> Vector Double -> IO () imatrix_set__7 x = casadi__IMatrix__set__7 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__8" c_casadi__IMatrix__set__8 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CDouble) -> CInt -> IO () casadi__IMatrix__set__8 :: IMatrix -> Vector Double -> Bool -> IO () casadi__IMatrix__set__8 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__set__8 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_set__8 :: IMatrixClass a => a -> Vector Double -> Bool -> IO () imatrix_set__8 x = casadi__IMatrix__set__8 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__9" c_casadi__IMatrix__set__9 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CDouble -> IO () casadi__IMatrix__set__9 :: IMatrix -> Double -> IO () casadi__IMatrix__set__9 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__set__9 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_set__9 :: IMatrixClass a => a -> Double -> IO () imatrix_set__9 x = casadi__IMatrix__set__9 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__set__10" c_casadi__IMatrix__set__10 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> IO () casadi__IMatrix__set__10 :: IMatrix -> IMatrix -> IO () casadi__IMatrix__set__10 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__set__10 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_set__10 :: IMatrixClass a => a -> IMatrix -> IO () imatrix_set__10 x = casadi__IMatrix__set__10 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setEqualityCheckingDepth__0" c_casadi__IMatrix__setEqualityCheckingDepth__0 :: Ptr (Ptr StdString) -> IO () casadi__IMatrix__setEqualityCheckingDepth__0 :: IO () casadi__IMatrix__setEqualityCheckingDepth__0 = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setEqualityCheckingDepth__0 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setEqualityCheckingDepth__0 :: IO () imatrix_setEqualityCheckingDepth__0 = casadi__IMatrix__setEqualityCheckingDepth__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setEqualityCheckingDepth__1" c_casadi__IMatrix__setEqualityCheckingDepth__1 :: Ptr (Ptr StdString) -> CInt -> IO () casadi__IMatrix__setEqualityCheckingDepth__1 :: Int -> IO () casadi__IMatrix__setEqualityCheckingDepth__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setEqualityCheckingDepth__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setEqualityCheckingDepth__1 :: Int -> IO () imatrix_setEqualityCheckingDepth__1 = casadi__IMatrix__setEqualityCheckingDepth__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setNZ__0" c_casadi__IMatrix__setNZ__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr IMatrix' -> IO () casadi__IMatrix__setNZ__0 :: IMatrix -> IMatrix -> Bool -> IMatrix -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_setNZ__0 :: IMatrixClass a => a -> IMatrix -> Bool -> IMatrix -> IO () imatrix_setNZ__0 x = casadi__IMatrix__setNZ__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setNZ__1" c_casadi__IMatrix__setNZ__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr IMatrix' -> CInt -> Ptr Slice' -> IO () casadi__IMatrix__setNZ__1 :: IMatrix -> IMatrix -> Bool -> Slice -> IO () casadi__IMatrix__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__IMatrix__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 imatrix_setNZ__1 :: IMatrixClass a => a -> IMatrix -> Bool -> Slice -> IO () imatrix_setNZ__1 x = casadi__IMatrix__setNZ__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setNZ__2" c_casadi__IMatrix__setNZ__2 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__IMatrix__setNZ__2 :: IMatrix -> Vector Double -> IO () casadi__IMatrix__setNZ__2 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setNZ__2 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setNZ__2 :: IMatrixClass a => a -> Vector Double -> IO () imatrix_setNZ__2 x = casadi__IMatrix__setNZ__2 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setNZ__3" c_casadi__IMatrix__setNZ__3 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CDouble -> IO () casadi__IMatrix__setNZ__3 :: IMatrix -> Double -> IO () casadi__IMatrix__setNZ__3 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setNZ__3 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setNZ__3 :: IMatrixClass a => a -> Double -> IO () imatrix_setNZ__3 x = casadi__IMatrix__setNZ__3 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setPrecision" c_casadi__IMatrix__setPrecision :: Ptr (Ptr StdString) -> CInt -> IO () casadi__IMatrix__setPrecision :: Int -> IO () casadi__IMatrix__setPrecision x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setPrecision errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setPrecision :: Int -> IO () imatrix_setPrecision = casadi__IMatrix__setPrecision -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setScientific" c_casadi__IMatrix__setScientific :: Ptr (Ptr StdString) -> CInt -> IO () casadi__IMatrix__setScientific :: Bool -> IO () casadi__IMatrix__setScientific x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setScientific errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setScientific :: Bool -> IO () imatrix_setScientific = casadi__IMatrix__setScientific -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setSym" c_casadi__IMatrix__setSym :: Ptr (Ptr StdString) -> Ptr IMatrix' -> Ptr (StdVec CDouble) -> IO () casadi__IMatrix__setSym :: IMatrix -> Vector Double -> IO () casadi__IMatrix__setSym x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setSym errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setSym :: IMatrixClass a => a -> Vector Double -> IO () imatrix_setSym x = casadi__IMatrix__setSym (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setValue__0" c_casadi__IMatrix__setValue__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CDouble -> CInt -> IO () casadi__IMatrix__setValue__0 :: IMatrix -> Double -> Int -> IO () casadi__IMatrix__setValue__0 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setValue__0 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setValue__0 :: IMatrixClass a => a -> Double -> Int -> IO () imatrix_setValue__0 x = casadi__IMatrix__setValue__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setValue__1" c_casadi__IMatrix__setValue__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CDouble -> IO () casadi__IMatrix__setValue__1 :: IMatrix -> Double -> IO () casadi__IMatrix__setValue__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setValue__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setValue__1 :: IMatrixClass a => a -> Double -> IO () imatrix_setValue__1 x = casadi__IMatrix__setValue__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setWidth" c_casadi__IMatrix__setWidth :: Ptr (Ptr StdString) -> CInt -> IO () casadi__IMatrix__setWidth :: Int -> IO () casadi__IMatrix__setWidth x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setWidth errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setWidth :: Int -> IO () imatrix_setWidth = casadi__IMatrix__setWidth -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__setZero" c_casadi__IMatrix__setZero :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO () casadi__IMatrix__setZero :: IMatrix -> IO () casadi__IMatrix__setZero x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__setZero errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_setZero :: IMatrixClass a => a -> IO () imatrix_setZero x = casadi__IMatrix__setZero (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__shape__0" c_casadi__IMatrix__shape__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO CInt casadi__IMatrix__shape__0 :: IMatrix -> Int -> IO Int casadi__IMatrix__shape__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__shape__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_shape__0 :: IMatrixClass a => a -> Int -> IO Int imatrix_shape__0 x = casadi__IMatrix__shape__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__shape__1" c_casadi__IMatrix__shape__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr (StdPair CInt CInt)) casadi__IMatrix__shape__1 :: IMatrix -> IO (Int, Int) casadi__IMatrix__shape__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__shape__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_shape__1 :: IMatrixClass a => a -> IO (Int, Int) imatrix_shape__1 x = casadi__IMatrix__shape__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__size" c_casadi__IMatrix__size :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__size :: IMatrix -> IO Int casadi__IMatrix__size x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__size errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_size :: IMatrixClass a => a -> IO Int imatrix_size x = casadi__IMatrix__size (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__size1" c_casadi__IMatrix__size1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__size1 :: IMatrix -> IO Int casadi__IMatrix__size1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__size1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_size1 :: IMatrixClass a => a -> IO Int imatrix_size1 x = casadi__IMatrix__size1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__size2" c_casadi__IMatrix__size2 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__size2 :: IMatrix -> IO Int casadi__IMatrix__size2 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__size2 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_size2 :: IMatrixClass a => a -> IO Int imatrix_size2 x = casadi__IMatrix__size2 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sizeD" c_casadi__IMatrix__sizeD :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__sizeD :: IMatrix -> IO Int casadi__IMatrix__sizeD x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sizeD errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sizeD :: IMatrixClass a => a -> IO Int imatrix_sizeD x = casadi__IMatrix__sizeD (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sizeL" c_casadi__IMatrix__sizeL :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__sizeL :: IMatrix -> IO Int casadi__IMatrix__sizeL x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sizeL errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sizeL :: IMatrixClass a => a -> IO Int imatrix_sizeL x = casadi__IMatrix__sizeL (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sizeU" c_casadi__IMatrix__sizeU :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO CInt casadi__IMatrix__sizeU :: IMatrix -> IO Int casadi__IMatrix__sizeU x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sizeU errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sizeU :: IMatrixClass a => a -> IO Int imatrix_sizeU x = casadi__IMatrix__sizeU (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sparse__0" c_casadi__IMatrix__sparse__0 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__sparse__0 :: Sparsity -> IMatrix -> IO IMatrix casadi__IMatrix__sparse__0 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sparse__0 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sparse__0 :: Sparsity -> IMatrix -> IO IMatrix imatrix_sparse__0 = casadi__IMatrix__sparse__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sparse__1" c_casadi__IMatrix__sparse__1 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr IMatrix') casadi__IMatrix__sparse__1 :: (Int, Int) -> IO IMatrix casadi__IMatrix__sparse__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sparse__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sparse__1 :: (Int, Int) -> IO IMatrix imatrix_sparse__1 = casadi__IMatrix__sparse__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sparse__2" c_casadi__IMatrix__sparse__2 :: Ptr (Ptr StdString) -> IO (Ptr IMatrix') casadi__IMatrix__sparse__2 :: IO IMatrix casadi__IMatrix__sparse__2 = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sparse__2 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sparse__2 :: IO IMatrix imatrix_sparse__2 = casadi__IMatrix__sparse__2 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sparse__3" c_casadi__IMatrix__sparse__3 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__sparse__3 :: Int -> IO IMatrix casadi__IMatrix__sparse__3 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sparse__3 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sparse__3 :: Int -> IO IMatrix imatrix_sparse__3 = casadi__IMatrix__sparse__3 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sparse__4" c_casadi__IMatrix__sparse__4 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__sparse__4 :: Int -> Int -> IO IMatrix casadi__IMatrix__sparse__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sparse__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sparse__4 :: Int -> Int -> IO IMatrix imatrix_sparse__4 = casadi__IMatrix__sparse__4 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sparsity" c_casadi__IMatrix__sparsity :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr Sparsity') casadi__IMatrix__sparsity :: IMatrix -> IO Sparsity casadi__IMatrix__sparsity x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sparsity errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sparsity :: IMatrixClass a => a -> IO Sparsity imatrix_sparsity x = casadi__IMatrix__sparsity (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__0" c_casadi__IMatrix__sym__0 :: Ptr (Ptr StdString) -> Ptr StdString -> CInt -> CInt -> CInt -> CInt -> IO (Ptr (StdVec (Ptr (StdVec (Ptr IMatrix'))))) casadi__IMatrix__sym__0 :: String -> Int -> Int -> Int -> Int -> IO (Vector (Vector IMatrix)) casadi__IMatrix__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__IMatrix__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 imatrix_sym__0 :: String -> Int -> Int -> Int -> Int -> IO (Vector (Vector IMatrix)) imatrix_sym__0 = casadi__IMatrix__sym__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__1" c_casadi__IMatrix__sym__1 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr Sparsity' -> CInt -> CInt -> IO (Ptr (StdVec (Ptr (StdVec (Ptr IMatrix'))))) casadi__IMatrix__sym__1 :: String -> Sparsity -> Int -> Int -> IO (Vector (Vector IMatrix)) casadi__IMatrix__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__IMatrix__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 imatrix_sym__1 :: String -> Sparsity -> Int -> Int -> IO (Vector (Vector IMatrix)) imatrix_sym__1 = casadi__IMatrix__sym__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__2" c_casadi__IMatrix__sym__2 :: Ptr (Ptr StdString) -> Ptr StdString -> CInt -> CInt -> CInt -> IO (Ptr (StdVec (Ptr IMatrix'))) casadi__IMatrix__sym__2 :: String -> Int -> Int -> Int -> IO (Vector IMatrix) casadi__IMatrix__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__IMatrix__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 imatrix_sym__2 :: String -> Int -> Int -> Int -> IO (Vector IMatrix) imatrix_sym__2 = casadi__IMatrix__sym__2 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__3" c_casadi__IMatrix__sym__3 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr Sparsity' -> CInt -> IO (Ptr (StdVec (Ptr IMatrix'))) casadi__IMatrix__sym__3 :: String -> Sparsity -> Int -> IO (Vector IMatrix) casadi__IMatrix__sym__3 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sym__3 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sym__3 :: String -> Sparsity -> Int -> IO (Vector IMatrix) imatrix_sym__3 = casadi__IMatrix__sym__3 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__4" c_casadi__IMatrix__sym__4 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr Sparsity' -> IO (Ptr IMatrix') casadi__IMatrix__sym__4 :: String -> Sparsity -> IO IMatrix casadi__IMatrix__sym__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sym__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sym__4 :: String -> Sparsity -> IO IMatrix imatrix_sym__4 = casadi__IMatrix__sym__4 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__5" c_casadi__IMatrix__sym__5 :: Ptr (Ptr StdString) -> Ptr StdString -> Ptr (StdPair CInt CInt) -> IO (Ptr IMatrix') casadi__IMatrix__sym__5 :: String -> (Int, Int) -> IO IMatrix casadi__IMatrix__sym__5 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sym__5 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sym__5 :: String -> (Int, Int) -> IO IMatrix imatrix_sym__5 = casadi__IMatrix__sym__5 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__6" c_casadi__IMatrix__sym__6 :: Ptr (Ptr StdString) -> Ptr StdString -> IO (Ptr IMatrix') casadi__IMatrix__sym__6 :: String -> IO IMatrix casadi__IMatrix__sym__6 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sym__6 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sym__6 :: String -> IO IMatrix imatrix_sym__6 = casadi__IMatrix__sym__6 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__7" c_casadi__IMatrix__sym__7 :: Ptr (Ptr StdString) -> Ptr StdString -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__sym__7 :: String -> Int -> IO IMatrix casadi__IMatrix__sym__7 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sym__7 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sym__7 :: String -> Int -> IO IMatrix imatrix_sym__7 = casadi__IMatrix__sym__7 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__sym__8" c_casadi__IMatrix__sym__8 :: Ptr (Ptr StdString) -> Ptr StdString -> CInt -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__sym__8 :: String -> Int -> Int -> IO IMatrix casadi__IMatrix__sym__8 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__sym__8 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_sym__8 :: String -> Int -> Int -> IO IMatrix imatrix_sym__8 = casadi__IMatrix__sym__8 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__toSlice__0" c_casadi__IMatrix__toSlice__0 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr Slice') casadi__IMatrix__toSlice__0 :: IMatrix -> IO Slice casadi__IMatrix__toSlice__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__toSlice__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_toSlice__0 :: IMatrixClass a => a -> IO Slice imatrix_toSlice__0 x = casadi__IMatrix__toSlice__0 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__toSlice__1" c_casadi__IMatrix__toSlice__1 :: Ptr (Ptr StdString) -> Ptr IMatrix' -> CInt -> IO (Ptr Slice') casadi__IMatrix__toSlice__1 :: IMatrix -> Bool -> IO Slice casadi__IMatrix__toSlice__1 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__toSlice__1 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_toSlice__1 :: IMatrixClass a => a -> Bool -> IO Slice imatrix_toSlice__1 x = casadi__IMatrix__toSlice__1 (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__triplet__0" c_casadi__IMatrix__triplet__0 :: Ptr (Ptr StdString) -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> Ptr IMatrix' -> Ptr (StdPair CInt CInt) -> IO (Ptr IMatrix') casadi__IMatrix__triplet__0 :: Vector Int -> Vector Int -> IMatrix -> (Int, Int) -> IO IMatrix casadi__IMatrix__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__IMatrix__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 imatrix_triplet__0 :: Vector Int -> Vector Int -> IMatrix -> (Int, Int) -> IO IMatrix imatrix_triplet__0 = casadi__IMatrix__triplet__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__triplet__1" c_casadi__IMatrix__triplet__1 :: Ptr (Ptr StdString) -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> Ptr IMatrix' -> CInt -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__triplet__1 :: Vector Int -> Vector Int -> IMatrix -> Int -> Int -> IO IMatrix casadi__IMatrix__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__IMatrix__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 imatrix_triplet__1 :: Vector Int -> Vector Int -> IMatrix -> Int -> Int -> IO IMatrix imatrix_triplet__1 = casadi__IMatrix__triplet__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__triplet__2" c_casadi__IMatrix__triplet__2 :: Ptr (Ptr StdString) -> Ptr (StdVec CInt) -> Ptr (StdVec CInt) -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__triplet__2 :: Vector Int -> Vector Int -> IMatrix -> IO IMatrix casadi__IMatrix__triplet__2 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__triplet__2 errStrPtrP x0' x1' x2' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_triplet__2 :: Vector Int -> Vector Int -> IMatrix -> IO IMatrix imatrix_triplet__2 = casadi__IMatrix__triplet__2 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__unary" c_casadi__IMatrix__unary :: Ptr (Ptr StdString) -> CInt -> Ptr IMatrix' -> IO (Ptr IMatrix') casadi__IMatrix__unary :: Int -> IMatrix -> IO IMatrix casadi__IMatrix__unary x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__unary errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_unary :: Int -> IMatrix -> IO IMatrix imatrix_unary = casadi__IMatrix__unary -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__zeros__0" c_casadi__IMatrix__zeros__0 :: Ptr (Ptr StdString) -> Ptr (StdPair CInt CInt) -> IO (Ptr IMatrix') casadi__IMatrix__zeros__0 :: (Int, Int) -> IO IMatrix casadi__IMatrix__zeros__0 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__zeros__0 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_zeros__0 :: (Int, Int) -> IO IMatrix imatrix_zeros__0 = casadi__IMatrix__zeros__0 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__zeros__1" c_casadi__IMatrix__zeros__1 :: Ptr (Ptr StdString) -> Ptr Sparsity' -> IO (Ptr IMatrix') casadi__IMatrix__zeros__1 :: Sparsity -> IO IMatrix casadi__IMatrix__zeros__1 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__zeros__1 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_zeros__1 :: Sparsity -> IO IMatrix imatrix_zeros__1 = casadi__IMatrix__zeros__1 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__zeros__2" c_casadi__IMatrix__zeros__2 :: Ptr (Ptr StdString) -> IO (Ptr IMatrix') casadi__IMatrix__zeros__2 :: IO IMatrix casadi__IMatrix__zeros__2 = do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__zeros__2 errStrPtrP errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_zeros__2 :: IO IMatrix imatrix_zeros__2 = casadi__IMatrix__zeros__2 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__zeros__3" c_casadi__IMatrix__zeros__3 :: Ptr (Ptr StdString) -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__zeros__3 :: Int -> IO IMatrix casadi__IMatrix__zeros__3 x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__zeros__3 errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_zeros__3 :: Int -> IO IMatrix imatrix_zeros__3 = casadi__IMatrix__zeros__3 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__zeros__4" c_casadi__IMatrix__zeros__4 :: Ptr (Ptr StdString) -> CInt -> CInt -> IO (Ptr IMatrix') casadi__IMatrix__zeros__4 :: Int -> Int -> IO IMatrix casadi__IMatrix__zeros__4 x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__zeros__4 errStrPtrP x0' x1' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_zeros__4 :: Int -> Int -> IO IMatrix imatrix_zeros__4 = casadi__IMatrix__zeros__4 -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getRepresentation" c_casadi__IMatrix__getRepresentation :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr StdString) casadi__IMatrix__getRepresentation :: IMatrix -> IO String casadi__IMatrix__getRepresentation x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getRepresentation errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getRepresentation :: IMatrixClass a => a -> IO String imatrix_getRepresentation x = casadi__IMatrix__getRepresentation (castIMatrix x) -- direct wrapper foreign import ccall unsafe "casadi__IMatrix__getDescription" c_casadi__IMatrix__getDescription :: Ptr (Ptr StdString) -> Ptr IMatrix' -> IO (Ptr StdString) casadi__IMatrix__getDescription :: IMatrix -> IO String casadi__IMatrix__getDescription x0 = withMarshal x0 $ \x0' -> do errStrPtrP <- new nullPtr ret <- c_casadi__IMatrix__getDescription errStrPtrP x0' errStrPtr <- peek errStrPtrP free errStrPtrP if errStrPtr == nullPtr then wrapReturn ret else wrapReturn errStrPtr >>= (error . formatException) -- classy wrapper imatrix_getDescription :: IMatrixClass a => a -> IO String imatrix_getDescription x = casadi__IMatrix__getDescription (castIMatrix x)