{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Wrappers.Classes.Sparsity ( Sparsity, SparsityClass(..), sparsity, sparsity', sparsity'', sparsity_append, sparsity_appendColumns, sparsity_band, sparsity_banded, sparsity_checkNode, sparsity_clearCache, sparsity_colind, sparsity_compress, sparsity_compressed, sparsity_dense, sparsity_dense', sparsity_depthFirstSearch, sparsity_diag, sparsity_diag', sparsity_dimString, sparsity_dulmageMendelsohn, sparsity_dulmageMendelsohn', sparsity_eliminationTree, sparsity_eliminationTree', sparsity_enlarge, sparsity_enlargeColumns, sparsity_enlargeRows, sparsity_erase, sparsity_getCCS, sparsity_getCRS, sparsity_getCol, sparsity_getDiag, sparsity_getElements, sparsity_getElements', sparsity_getElements'', sparsity_getElements''', sparsity_getLowerNZ, sparsity_getNZ, sparsity_getNZ', sparsity_getNZ'', sparsity_getNZInplace, sparsity_getTril, sparsity_getTril', sparsity_getTriplet, sparsity_getTriu, sparsity_getTriu', sparsity_getUpperNZ, sparsity_hasNZ, sparsity_hash, sparsity_isDense, sparsity_isDiagonal, sparsity_isEmpty, sparsity_isEmpty', sparsity_isEqual, sparsity_isEqual', sparsity_isReshape, sparsity_isScalar, sparsity_isScalar', sparsity_isSingular, sparsity_isSquare, sparsity_isSymmetric, sparsity_isTranspose, sparsity_isTril, sparsity_isTriu, sparsity_isVector, sparsity_largestFirstOrdering, sparsity_makeDense, sparsity_numel, sparsity_operator_equals, sparsity_operator_mul, sparsity_operator_nequals, sparsity_operator_plus, sparsity_patternCombine, sparsity_patternCombine', sparsity_patternIntersection, sparsity_patternIntersection', sparsity_patternInverse, sparsity_patternProduct, sparsity_patternUnion, sparsity_patternUnion', sparsity_pmult, sparsity_pmult', sparsity_pmult'', sparsity_pmult''', sparsity_printCompact', sparsity_reCache, sparsity_removeDuplicates, sparsity_reserve, sparsity_reshape, sparsity_resize, sparsity_row, sparsity_rowcol, sparsity_rowsSequential, sparsity_rowsSequential', sparsity_sanityCheck, sparsity_sanityCheck', sparsity_scalar, sparsity_scalar', sparsity_size, sparsity_size1, sparsity_size2, sparsity_sizeD, sparsity_sizeL, sparsity_sizeU, sparsity_sparse, sparsity_sparse', sparsity_spy', sparsity_spyMatlab, sparsity_starColoring, sparsity_starColoring', sparsity_starColoring'', sparsity_starColoring2, sparsity_starColoring2', sparsity_starColoring2'', sparsity_stronglyConnectedComponents, sparsity_sub, sparsity_transpose, sparsity_transpose', sparsity_transpose'', sparsity_tril, sparsity_triplet, sparsity_triplet', sparsity_triplet'', sparsity_triu, sparsity_unidirectionalColoring, sparsity_unidirectionalColoring', sparsity_unidirectionalColoring'', sparsity_unit, ) where import Prelude hiding ( Functor ) import Data.Vector ( Vector ) import Foreign.C.Types import Foreign.Ptr ( Ptr ) import Foreign.ForeignPtr ( newForeignPtr ) import System.IO.Unsafe ( unsafePerformIO ) -- for show instances import Casadi.Wrappers.Classes.PrintableObject import Casadi.Wrappers.CToolsInstances ( ) import Casadi.Wrappers.Data import Casadi.Wrappers.Enums import Casadi.MarshalTypes ( CppVec, StdString' ) -- StdOstream' import Casadi.Marshal ( Marshal(..), withMarshal ) import Casadi.WrapReturn ( WrapReturn(..) ) instance Show Sparsity where show = unsafePerformIO . printableObject_getDescription -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__scalar" c_CasADi__Sparsity__scalar :: CInt -> IO (Ptr Sparsity') casADi__Sparsity__scalar :: Bool -> IO Sparsity casADi__Sparsity__scalar x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__scalar x0' >>= wrapReturn -- classy wrapper {-| >Create a scalar sparsity pattern. -} sparsity_scalar :: Bool -> IO Sparsity sparsity_scalar = casADi__Sparsity__scalar -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__scalar_TIC" c_CasADi__Sparsity__scalar_TIC :: IO (Ptr Sparsity') casADi__Sparsity__scalar' :: IO Sparsity casADi__Sparsity__scalar' = c_CasADi__Sparsity__scalar_TIC >>= wrapReturn -- classy wrapper sparsity_scalar' :: IO Sparsity sparsity_scalar' = casADi__Sparsity__scalar' -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__dense" c_CasADi__Sparsity__dense :: CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__dense :: Int -> Int -> IO Sparsity casADi__Sparsity__dense x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__dense x0' x1' >>= wrapReturn -- classy wrapper {-| >Create a dense rectangular sparsity pattern. -} sparsity_dense :: Int -> Int -> IO Sparsity sparsity_dense = casADi__Sparsity__dense -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__dense_TIC" c_CasADi__Sparsity__dense_TIC :: CInt -> IO (Ptr Sparsity') casADi__Sparsity__dense' :: Int -> IO Sparsity casADi__Sparsity__dense' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__dense_TIC x0' >>= wrapReturn -- classy wrapper sparsity_dense' :: Int -> IO Sparsity sparsity_dense' = casADi__Sparsity__dense' -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__sparse" c_CasADi__Sparsity__sparse :: CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__sparse :: Int -> Int -> IO Sparsity casADi__Sparsity__sparse x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__sparse x0' x1' >>= wrapReturn -- classy wrapper {-| >Create a sparse (empty) rectangular sparsity pattern. -} sparsity_sparse :: Int -> Int -> IO Sparsity sparsity_sparse = casADi__Sparsity__sparse -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__sparse_TIC" c_CasADi__Sparsity__sparse_TIC :: CInt -> IO (Ptr Sparsity') casADi__Sparsity__sparse' :: Int -> IO Sparsity casADi__Sparsity__sparse' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__sparse_TIC x0' >>= wrapReturn -- classy wrapper sparsity_sparse' :: Int -> IO Sparsity sparsity_sparse' = casADi__Sparsity__sparse' -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__unit" c_CasADi__Sparsity__unit :: CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__unit :: Int -> Int -> IO Sparsity casADi__Sparsity__unit x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__unit x0' x1' >>= wrapReturn -- classy wrapper {-| >Create the sparsity pattern for a unit vector of length n and a nonzero on >position el. -} sparsity_unit :: Int -> Int -> IO Sparsity sparsity_unit = casADi__Sparsity__unit -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__triu" c_CasADi__Sparsity__triu :: CInt -> IO (Ptr Sparsity') casADi__Sparsity__triu :: Int -> IO Sparsity casADi__Sparsity__triu x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__triu x0' >>= wrapReturn -- classy wrapper sparsity_triu :: Int -> IO Sparsity sparsity_triu = casADi__Sparsity__triu -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__tril" c_CasADi__Sparsity__tril :: CInt -> IO (Ptr Sparsity') casADi__Sparsity__tril :: Int -> IO Sparsity casADi__Sparsity__tril x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__tril x0' >>= wrapReturn -- classy wrapper sparsity_tril :: Int -> IO Sparsity sparsity_tril = casADi__Sparsity__tril -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__diag" c_CasADi__Sparsity__diag :: CInt -> IO (Ptr Sparsity') casADi__Sparsity__diag :: Int -> IO Sparsity casADi__Sparsity__diag x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__diag x0' >>= wrapReturn -- classy wrapper {-| >Create diagonal sparsity pattern. -} sparsity_diag :: Int -> IO Sparsity sparsity_diag = casADi__Sparsity__diag -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__diag_TIC" c_CasADi__Sparsity__diag_TIC :: CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__diag' :: Int -> Int -> IO Sparsity casADi__Sparsity__diag' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__diag_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_diag' :: Int -> Int -> IO Sparsity sparsity_diag' = casADi__Sparsity__diag' -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__band" c_CasADi__Sparsity__band :: CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__band :: Int -> Int -> IO Sparsity casADi__Sparsity__band x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__band x0' x1' >>= wrapReturn -- classy wrapper sparsity_band :: Int -> Int -> IO Sparsity sparsity_band = casADi__Sparsity__band -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__banded" c_CasADi__Sparsity__banded :: CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__banded :: Int -> Int -> IO Sparsity casADi__Sparsity__banded x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__banded x0' x1' >>= wrapReturn -- classy wrapper sparsity_banded :: Int -> Int -> IO Sparsity sparsity_banded = casADi__Sparsity__banded -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__rowcol" c_CasADi__Sparsity__rowcol :: Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__rowcol :: Vector Int -> Vector Int -> Int -> Int -> IO Sparsity casADi__Sparsity__rowcol x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> c_CasADi__Sparsity__rowcol x0' x1' x2' x3' >>= wrapReturn -- classy wrapper sparsity_rowcol :: Vector Int -> Vector Int -> Int -> Int -> IO Sparsity sparsity_rowcol = casADi__Sparsity__rowcol -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__triplet" c_CasADi__Sparsity__triplet :: CInt -> CInt -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__triplet :: Int -> Int -> Vector Int -> Vector Int -> Vector Int -> Bool -> IO Sparsity casADi__Sparsity__triplet x0 x1 x2 x3 x4 x5 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> withMarshal x5 $ \x5' -> c_CasADi__Sparsity__triplet x0' x1' x2' x3' x4' x5' >>= wrapReturn -- classy wrapper sparsity_triplet :: Int -> Int -> Vector Int -> Vector Int -> Vector Int -> Bool -> IO Sparsity sparsity_triplet = casADi__Sparsity__triplet -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__triplet_TIC" c_CasADi__Sparsity__triplet_TIC :: CInt -> CInt -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__triplet' :: Int -> Int -> Vector Int -> Vector Int -> Vector Int -> IO Sparsity casADi__Sparsity__triplet' x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> c_CasADi__Sparsity__triplet_TIC x0' x1' x2' x3' x4' >>= wrapReturn -- classy wrapper sparsity_triplet' :: Int -> Int -> Vector Int -> Vector Int -> Vector Int -> IO Sparsity sparsity_triplet' = casADi__Sparsity__triplet' -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__triplet_TIC_TIC" c_CasADi__Sparsity__triplet_TIC_TIC :: CInt -> CInt -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__triplet'' :: Int -> Int -> Vector Int -> Vector Int -> IO Sparsity casADi__Sparsity__triplet'' x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> c_CasADi__Sparsity__triplet_TIC_TIC x0' x1' x2' x3' >>= wrapReturn -- classy wrapper sparsity_triplet'' :: Int -> Int -> Vector Int -> Vector Int -> IO Sparsity sparsity_triplet'' = casADi__Sparsity__triplet'' -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__compressed" c_CasADi__Sparsity__compressed :: Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__compressed :: Vector Int -> IO Sparsity casADi__Sparsity__compressed x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__compressed x0' >>= wrapReturn -- classy wrapper {-| >> Sparsity CasADi::Sparsity::compressed(const std::vector< int > &v) >------------------------------------------------------------------------ > >Create from a single vector containing the pattern in compressed column >storage format: The format: The first two entries are the number of rows >(nrow) and columns (ncol) The next ncol+1 entries are the column offsets >(colind). Note that the last element, colind[ncol], gives the number of >nonzeros The last colind[ncol] entries are the row indices > >> Sparsity CasADi::Sparsity::compressed(const int *v) >------------------------------------------------------------------------ >[INTERNAL] >Create from a single vector containing the pattern in compressed >column storage format: The format: The first two entries are the >number of rows (nrow) and columns (ncol) The next ncol+1 entries are >the column offsets (colind). Note that the last element, colind[ncol], >gives the number of nonzeros The last colind[ncol] entries are the row >indices -} sparsity_compressed :: Vector Int -> IO Sparsity sparsity_compressed = casADi__Sparsity__compressed -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__reCache" c_CasADi__Sparsity__reCache :: Ptr Sparsity' -> IO () casADi__Sparsity__reCache :: Sparsity -> IO () casADi__Sparsity__reCache x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__reCache x0' >>= wrapReturn -- classy wrapper {-| >[INTERNAL] Check if there >is an identical copy of the sparsity pattern in the cache, and if so, make a >shallow copy of that one. -} sparsity_reCache :: SparsityClass a => a -> IO () sparsity_reCache x = casADi__Sparsity__reCache (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__clearCache" c_CasADi__Sparsity__clearCache :: IO () casADi__Sparsity__clearCache :: IO () casADi__Sparsity__clearCache = c_CasADi__Sparsity__clearCache >>= wrapReturn -- classy wrapper sparsity_clearCache :: IO () sparsity_clearCache = casADi__Sparsity__clearCache -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__sanityCheck" c_CasADi__Sparsity__sanityCheck :: Ptr Sparsity' -> CInt -> IO () casADi__Sparsity__sanityCheck :: Sparsity -> Bool -> IO () casADi__Sparsity__sanityCheck x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__sanityCheck x0' x1' >>= wrapReturn -- classy wrapper {-| >Check if the dimensions and colind, row vectors are compatible. > >Parameters: >----------- > >complete: set to true to also check elementwise throws an error as possible >result -} sparsity_sanityCheck :: SparsityClass a => a -> Bool -> IO () sparsity_sanityCheck x = casADi__Sparsity__sanityCheck (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__sanityCheck_TIC" c_CasADi__Sparsity__sanityCheck_TIC :: Ptr Sparsity' -> IO () casADi__Sparsity__sanityCheck' :: Sparsity -> IO () casADi__Sparsity__sanityCheck' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__sanityCheck_TIC x0' >>= wrapReturn -- classy wrapper sparsity_sanityCheck' :: SparsityClass a => a -> IO () sparsity_sanityCheck' x = casADi__Sparsity__sanityCheck' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getDiag" c_CasADi__Sparsity__getDiag :: Ptr Sparsity' -> Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__getDiag :: Sparsity -> Vector Int -> IO Sparsity casADi__Sparsity__getDiag x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__getDiag x0' x1' >>= wrapReturn -- classy wrapper {-| >Get the diagonal of the matrix/create a diagonal matrix (mapping will >contain the nonzero mapping) When the input is square, the diagonal elements >are returned. If the input is vector-like, a diagonal matrix is constructed >with it. -} sparsity_getDiag :: SparsityClass a => a -> Vector Int -> IO Sparsity sparsity_getDiag x = casADi__Sparsity__getDiag (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__compress" c_CasADi__Sparsity__compress :: Ptr Sparsity' -> IO (Ptr (CppVec CInt)) casADi__Sparsity__compress :: Sparsity -> IO (Vector Int) casADi__Sparsity__compress x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__compress x0' >>= wrapReturn -- classy wrapper {-| >Compress a sparsity pattern. -} sparsity_compress :: SparsityClass a => a -> IO (Vector Int) sparsity_compress x = casADi__Sparsity__compress (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__checkNode" c_CasADi__Sparsity__checkNode :: Ptr Sparsity' -> IO CInt casADi__Sparsity__checkNode :: Sparsity -> IO Bool casADi__Sparsity__checkNode x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__checkNode x0' >>= wrapReturn -- classy wrapper {-| >Check if the node is pointing to the right type of object. -} sparsity_checkNode :: SparsityClass a => a -> IO Bool sparsity_checkNode x = casADi__Sparsity__checkNode (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isEqual" c_CasADi__Sparsity__isEqual :: Ptr Sparsity' -> Ptr Sparsity' -> IO CInt casADi__Sparsity__isEqual :: Sparsity -> Sparsity -> IO Bool casADi__Sparsity__isEqual x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__isEqual x0' x1' >>= wrapReturn -- classy wrapper sparsity_isEqual :: SparsityClass a => a -> Sparsity -> IO Bool sparsity_isEqual x = casADi__Sparsity__isEqual (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isEqual_TIC" c_CasADi__Sparsity__isEqual_TIC :: Ptr Sparsity' -> CInt -> CInt -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO CInt casADi__Sparsity__isEqual' :: Sparsity -> Int -> Int -> Vector Int -> Vector Int -> IO Bool casADi__Sparsity__isEqual' x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> c_CasADi__Sparsity__isEqual_TIC x0' x1' x2' x3' x4' >>= wrapReturn -- classy wrapper sparsity_isEqual' :: SparsityClass a => a -> Int -> Int -> Vector Int -> Vector Int -> IO Bool sparsity_isEqual' x = casADi__Sparsity__isEqual' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__operator_equals" c_CasADi__Sparsity__operator_equals :: Ptr Sparsity' -> Ptr Sparsity' -> IO CInt casADi__Sparsity__operator_equals :: Sparsity -> Sparsity -> IO Bool casADi__Sparsity__operator_equals x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__operator_equals x0' x1' >>= wrapReturn -- classy wrapper sparsity_operator_equals :: SparsityClass a => a -> Sparsity -> IO Bool sparsity_operator_equals x = casADi__Sparsity__operator_equals (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__operator_nequals" c_CasADi__Sparsity__operator_nequals :: Ptr Sparsity' -> Ptr Sparsity' -> IO CInt casADi__Sparsity__operator_nequals :: Sparsity -> Sparsity -> IO Bool casADi__Sparsity__operator_nequals x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__operator_nequals x0' x1' >>= wrapReturn -- classy wrapper sparsity_operator_nequals :: SparsityClass a => a -> Sparsity -> IO Bool sparsity_operator_nequals x = casADi__Sparsity__operator_nequals (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__size1" c_CasADi__Sparsity__size1 :: Ptr Sparsity' -> IO CInt casADi__Sparsity__size1 :: Sparsity -> IO Int casADi__Sparsity__size1 x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__size1 x0' >>= wrapReturn -- classy wrapper {-| >Get the number of rows. -} sparsity_size1 :: SparsityClass a => a -> IO Int sparsity_size1 x = casADi__Sparsity__size1 (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__size2" c_CasADi__Sparsity__size2 :: Ptr Sparsity' -> IO CInt casADi__Sparsity__size2 :: Sparsity -> IO Int casADi__Sparsity__size2 x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__size2 x0' >>= wrapReturn -- classy wrapper {-| >Get the number of columns. -} sparsity_size2 :: SparsityClass a => a -> IO Int sparsity_size2 x = casADi__Sparsity__size2 (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__numel" c_CasADi__Sparsity__numel :: Ptr Sparsity' -> IO CInt casADi__Sparsity__numel :: Sparsity -> IO Int casADi__Sparsity__numel x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__numel x0' >>= wrapReturn -- classy wrapper {-| >The total number of elements, including structural zeros, i.e. >size2()*size1() > >See: size() -} sparsity_numel :: SparsityClass a => a -> IO Int sparsity_numel x = casADi__Sparsity__numel (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isEmpty" c_CasADi__Sparsity__isEmpty :: Ptr Sparsity' -> CInt -> IO CInt casADi__Sparsity__isEmpty :: Sparsity -> Bool -> IO Bool casADi__Sparsity__isEmpty x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__isEmpty x0' x1' >>= wrapReturn -- classy wrapper {-| >Check if the sparsity is empty, i.e. if one of the dimensions is zero (or >optionally both dimensions) -} sparsity_isEmpty :: SparsityClass a => a -> Bool -> IO Bool sparsity_isEmpty x = casADi__Sparsity__isEmpty (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isEmpty_TIC" c_CasADi__Sparsity__isEmpty_TIC :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isEmpty' :: Sparsity -> IO Bool casADi__Sparsity__isEmpty' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isEmpty_TIC x0' >>= wrapReturn -- classy wrapper sparsity_isEmpty' :: SparsityClass a => a -> IO Bool sparsity_isEmpty' x = casADi__Sparsity__isEmpty' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__size" c_CasADi__Sparsity__size :: Ptr Sparsity' -> IO CInt casADi__Sparsity__size :: Sparsity -> IO Int casADi__Sparsity__size x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__size x0' >>= wrapReturn -- classy wrapper {-| >Get the number of (structural) non-zeros. > >See: numel() -} sparsity_size :: SparsityClass a => a -> IO Int sparsity_size x = casADi__Sparsity__size (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__sizeU" c_CasADi__Sparsity__sizeU :: Ptr Sparsity' -> IO CInt casADi__Sparsity__sizeU :: Sparsity -> IO Int casADi__Sparsity__sizeU x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__sizeU x0' >>= wrapReturn -- classy wrapper {-| >Number of non-zeros in the upper triangular half, i.e. the number of >elements (i,j) with j>=i. -} sparsity_sizeU :: SparsityClass a => a -> IO Int sparsity_sizeU x = casADi__Sparsity__sizeU (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__sizeL" c_CasADi__Sparsity__sizeL :: Ptr Sparsity' -> IO CInt casADi__Sparsity__sizeL :: Sparsity -> IO Int casADi__Sparsity__sizeL x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__sizeL x0' >>= wrapReturn -- classy wrapper {-| >Number of non-zeros in the lower triangular half, i.e. the number of >elements (i,j) with j<=i. -} sparsity_sizeL :: SparsityClass a => a -> IO Int sparsity_sizeL x = casADi__Sparsity__sizeL (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__sizeD" c_CasADi__Sparsity__sizeD :: Ptr Sparsity' -> IO CInt casADi__Sparsity__sizeD :: Sparsity -> IO Int casADi__Sparsity__sizeD x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__sizeD x0' >>= wrapReturn -- classy wrapper {-| >Number of non-zeros on the diagonal, i.e. the number of elements (i,j) with >j==i. -} sparsity_sizeD :: SparsityClass a => a -> IO Int sparsity_sizeD x = casADi__Sparsity__sizeD (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__row" c_CasADi__Sparsity__row :: Ptr Sparsity' -> CInt -> IO CInt casADi__Sparsity__row :: Sparsity -> Int -> IO Int casADi__Sparsity__row x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__row x0' x1' >>= wrapReturn -- classy wrapper {-| >> const std::vector< int > & CasADi::Sparsity::row() const >------------------------------------------------------------------------ > >Get a reference to row-vector, containing rows for all non-zero elements >(see class description) > >> int CasADi::Sparsity::row(int el) const >------------------------------------------------------------------------ > >Get the row of a non-zero element. -} sparsity_row :: SparsityClass a => a -> Int -> IO Int sparsity_row x = casADi__Sparsity__row (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__colind" c_CasADi__Sparsity__colind :: Ptr Sparsity' -> CInt -> IO CInt casADi__Sparsity__colind :: Sparsity -> Int -> IO Int casADi__Sparsity__colind x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__colind x0' x1' >>= wrapReturn -- classy wrapper {-| >> const std::vector< int > & CasADi::Sparsity::colind() const >------------------------------------------------------------------------ > >Get a reference to the colindex of all column element (see class >description) > >> int CasADi::Sparsity::colind(int i) const >------------------------------------------------------------------------ > >Get a reference to the colindex of col i (see class description) -} sparsity_colind :: SparsityClass a => a -> Int -> IO Int sparsity_colind x = casADi__Sparsity__colind (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getCol" c_CasADi__Sparsity__getCol :: Ptr Sparsity' -> IO (Ptr (CppVec CInt)) casADi__Sparsity__getCol :: Sparsity -> IO (Vector Int) casADi__Sparsity__getCol x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__getCol x0' >>= wrapReturn -- classy wrapper {-| >Get the column for each non-zero entry Together with the row-vector, this >vector gives the sparsity of the matrix in sparse triplet format, i.e. the >column and row for each non-zero elements. -} sparsity_getCol :: SparsityClass a => a -> IO (Vector Int) sparsity_getCol x = casADi__Sparsity__getCol (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__resize" c_CasADi__Sparsity__resize :: Ptr Sparsity' -> CInt -> CInt -> IO () casADi__Sparsity__resize :: Sparsity -> Int -> Int -> IO () casADi__Sparsity__resize x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__resize x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Resize. -} sparsity_resize :: SparsityClass a => a -> Int -> Int -> IO () sparsity_resize x = casADi__Sparsity__resize (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__reshape" c_CasADi__Sparsity__reshape :: Ptr Sparsity' -> CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__reshape :: Sparsity -> Int -> Int -> IO Sparsity casADi__Sparsity__reshape x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__reshape x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Reshape a sparsity, order of nonzeros remains the same. -} sparsity_reshape :: SparsityClass a => a -> Int -> Int -> IO Sparsity sparsity_reshape x = casADi__Sparsity__reshape (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getNZ" c_CasADi__Sparsity__getNZ :: Ptr Sparsity' -> CInt -> CInt -> IO CInt casADi__Sparsity__getNZ :: Sparsity -> Int -> Int -> IO Int casADi__Sparsity__getNZ x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__getNZ x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >> int CasADi::Sparsity::getNZ(int rr, int cc) >------------------------------------------------------------------------ > >Get the index of a non-zero element Add the element if it does not exist and >copy object if it's not unique. > >> int CasADi::Sparsity::getNZ(int rr, int cc) const >------------------------------------------------------------------------ > >Get the index of an existing non-zero element return -1 if the element does >not exists. > >> std::vector< int > CasADi::Sparsity::getNZ(const std::vector< int > &rr, const std::vector< int > &cc) const >------------------------------------------------------------------------ > >Get a set of non-zero element return -1 if the element does not exists. -} sparsity_getNZ :: SparsityClass a => a -> Int -> Int -> IO Int sparsity_getNZ x = casADi__Sparsity__getNZ (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getNZ_TIC" c_CasADi__Sparsity__getNZ_TIC :: Ptr Sparsity' -> CInt -> CInt -> IO CInt casADi__Sparsity__getNZ' :: Sparsity -> Int -> Int -> IO Int casADi__Sparsity__getNZ' x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__getNZ_TIC x0' x1' x2' >>= wrapReturn -- classy wrapper sparsity_getNZ' :: SparsityClass a => a -> Int -> Int -> IO Int sparsity_getNZ' x = casADi__Sparsity__getNZ' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__hasNZ" c_CasADi__Sparsity__hasNZ :: Ptr Sparsity' -> CInt -> CInt -> IO CInt casADi__Sparsity__hasNZ :: Sparsity -> Int -> Int -> IO Bool casADi__Sparsity__hasNZ x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__hasNZ x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Returns true if the pattern has a non-zero at location rr,cc. -} sparsity_hasNZ :: SparsityClass a => a -> Int -> Int -> IO Bool sparsity_hasNZ x = casADi__Sparsity__hasNZ (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getNZ_TIC_TIC" c_CasADi__Sparsity__getNZ_TIC_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO (Ptr (CppVec CInt)) casADi__Sparsity__getNZ'' :: Sparsity -> Vector Int -> Vector Int -> IO (Vector Int) casADi__Sparsity__getNZ'' x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__getNZ_TIC_TIC x0' x1' x2' >>= wrapReturn -- classy wrapper sparsity_getNZ'' :: SparsityClass a => a -> Vector Int -> Vector Int -> IO (Vector Int) sparsity_getNZ'' x = casADi__Sparsity__getNZ'' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getNZInplace" c_CasADi__Sparsity__getNZInplace :: Ptr Sparsity' -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__getNZInplace :: Sparsity -> Vector Int -> IO () casADi__Sparsity__getNZInplace x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__getNZInplace x0' x1' >>= wrapReturn -- classy wrapper {-| >Get the nonzero index for a set of elements The index vector is used both >for input and outputs and must be sorted by increasing nonzero index, i.e. >column-wise. Elements not found in the sparsity pattern are set to -1. -} sparsity_getNZInplace :: SparsityClass a => a -> Vector Int -> IO () sparsity_getNZInplace x = casADi__Sparsity__getNZInplace (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getLowerNZ" c_CasADi__Sparsity__getLowerNZ :: Ptr Sparsity' -> IO (Ptr (CppVec CInt)) casADi__Sparsity__getLowerNZ :: Sparsity -> IO (Vector Int) casADi__Sparsity__getLowerNZ x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__getLowerNZ x0' >>= wrapReturn -- classy wrapper {-| >Get nonzeros in lower triangular part. -} sparsity_getLowerNZ :: SparsityClass a => a -> IO (Vector Int) sparsity_getLowerNZ x = casADi__Sparsity__getLowerNZ (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getUpperNZ" c_CasADi__Sparsity__getUpperNZ :: Ptr Sparsity' -> IO (Ptr (CppVec CInt)) casADi__Sparsity__getUpperNZ :: Sparsity -> IO (Vector Int) casADi__Sparsity__getUpperNZ x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__getUpperNZ x0' >>= wrapReturn -- classy wrapper {-| >Get nonzeros in upper triangular part. -} sparsity_getUpperNZ :: SparsityClass a => a -> IO (Vector Int) sparsity_getUpperNZ x = casADi__Sparsity__getUpperNZ (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getCCS" c_CasADi__Sparsity__getCCS :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__getCCS :: Sparsity -> Vector Int -> Vector Int -> IO () casADi__Sparsity__getCCS x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__getCCS x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Get the sparsity in compressed column storage (CCS) format. -} sparsity_getCCS :: SparsityClass a => a -> Vector Int -> Vector Int -> IO () sparsity_getCCS x = casADi__Sparsity__getCCS (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getCRS" c_CasADi__Sparsity__getCRS :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__getCRS :: Sparsity -> Vector Int -> Vector Int -> IO () casADi__Sparsity__getCRS x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__getCRS x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Get the sparsity in compressed row storage (CRS) format. -} sparsity_getCRS :: SparsityClass a => a -> Vector Int -> Vector Int -> IO () sparsity_getCRS x = casADi__Sparsity__getCRS (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getTriplet" c_CasADi__Sparsity__getTriplet :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__getTriplet :: Sparsity -> Vector Int -> Vector Int -> IO () casADi__Sparsity__getTriplet x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__getTriplet x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Get the sparsity in sparse triplet format. -} sparsity_getTriplet :: SparsityClass a => a -> Vector Int -> Vector Int -> IO () sparsity_getTriplet x = casADi__Sparsity__getTriplet (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__sub" c_CasADi__Sparsity__sub :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__sub :: Sparsity -> Vector Int -> Vector Int -> Vector Int -> IO Sparsity casADi__Sparsity__sub x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> c_CasADi__Sparsity__sub x0' x1' x2' x3' >>= wrapReturn -- classy wrapper {-| >Get a submatrix. > >Returns the sparsity of the submatrix, with a mapping such that submatrix[k] >= originalmatrix[mapping[k]] -} sparsity_sub :: SparsityClass a => a -> Vector Int -> Vector Int -> Vector Int -> IO Sparsity sparsity_sub x = casADi__Sparsity__sub (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__transpose" c_CasADi__Sparsity__transpose :: Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__transpose :: Sparsity -> IO Sparsity casADi__Sparsity__transpose x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__transpose x0' >>= wrapReturn -- classy wrapper {-| >> Sparsity CasADi::Sparsity::transpose() const >------------------------------------------------------------------------ > >Transpose the matrix. > >> Sparsity CasADi::Sparsity::transpose(std::vector< int > &mapping, bool invert_mapping=false) const >------------------------------------------------------------------------ > >Transpose the matrix and get the reordering of the non-zero entries, i.e. >the non-zeros of the original matrix for each non-zero of the new matrix. -} sparsity_transpose :: SparsityClass a => a -> IO Sparsity sparsity_transpose x = casADi__Sparsity__transpose (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__transpose_TIC" c_CasADi__Sparsity__transpose_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__transpose' :: Sparsity -> Vector Int -> Bool -> IO Sparsity casADi__Sparsity__transpose' x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__transpose_TIC x0' x1' x2' >>= wrapReturn -- classy wrapper sparsity_transpose' :: SparsityClass a => a -> Vector Int -> Bool -> IO Sparsity sparsity_transpose' x = casADi__Sparsity__transpose' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__transpose_TIC_TIC" c_CasADi__Sparsity__transpose_TIC_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__transpose'' :: Sparsity -> Vector Int -> IO Sparsity casADi__Sparsity__transpose'' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__transpose_TIC_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_transpose'' :: SparsityClass a => a -> Vector Int -> IO Sparsity sparsity_transpose'' x = casADi__Sparsity__transpose'' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isTranspose" c_CasADi__Sparsity__isTranspose :: Ptr Sparsity' -> Ptr Sparsity' -> IO CInt casADi__Sparsity__isTranspose :: Sparsity -> Sparsity -> IO Bool casADi__Sparsity__isTranspose x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__isTranspose x0' x1' >>= wrapReturn -- classy wrapper {-| >Check if the sparsity is the transpose of another. -} sparsity_isTranspose :: SparsityClass a => a -> Sparsity -> IO Bool sparsity_isTranspose x = casADi__Sparsity__isTranspose (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isReshape" c_CasADi__Sparsity__isReshape :: Ptr Sparsity' -> Ptr Sparsity' -> IO CInt casADi__Sparsity__isReshape :: Sparsity -> Sparsity -> IO Bool casADi__Sparsity__isReshape x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__isReshape x0' x1' >>= wrapReturn -- classy wrapper {-| >Check if the sparsity is a reshape of another. -} sparsity_isReshape :: SparsityClass a => a -> Sparsity -> IO Bool sparsity_isReshape x = casADi__Sparsity__isReshape (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__patternCombine" c_CasADi__Sparsity__patternCombine :: Ptr Sparsity' -> Ptr Sparsity' -> CInt -> CInt -> Ptr (CppVec CUChar) -> IO (Ptr Sparsity') casADi__Sparsity__patternCombine :: Sparsity -> Sparsity -> Bool -> Bool -> Vector CUChar -> IO Sparsity casADi__Sparsity__patternCombine x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> c_CasADi__Sparsity__patternCombine x0' x1' x2' x3' x4' >>= wrapReturn -- classy wrapper {-| >Combine two sparsity patterns Returns the new sparsity pattern as well as a >mapping with the same length as the number of non-zero elements The mapping >matrix contains the arguments for each nonzero, the first bit indicates if >the first argument is nonzero, the second bit indicates if the second >argument is nonzero (note that none of, one of or both of the arguments can >be nonzero) -} sparsity_patternCombine :: SparsityClass a => a -> Sparsity -> Bool -> Bool -> Vector CUChar -> IO Sparsity sparsity_patternCombine x = casADi__Sparsity__patternCombine (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__patternCombine_TIC" c_CasADi__Sparsity__patternCombine_TIC :: Ptr Sparsity' -> Ptr Sparsity' -> CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__patternCombine' :: Sparsity -> Sparsity -> Bool -> Bool -> IO Sparsity casADi__Sparsity__patternCombine' x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> c_CasADi__Sparsity__patternCombine_TIC x0' x1' x2' x3' >>= wrapReturn -- classy wrapper sparsity_patternCombine' :: SparsityClass a => a -> Sparsity -> Bool -> Bool -> IO Sparsity sparsity_patternCombine' x = casADi__Sparsity__patternCombine' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__patternUnion" c_CasADi__Sparsity__patternUnion :: Ptr Sparsity' -> Ptr Sparsity' -> Ptr (CppVec CUChar) -> IO (Ptr Sparsity') casADi__Sparsity__patternUnion :: Sparsity -> Sparsity -> Vector CUChar -> IO Sparsity casADi__Sparsity__patternUnion x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__patternUnion x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Union of two sparsity patterns. -} sparsity_patternUnion :: SparsityClass a => a -> Sparsity -> Vector CUChar -> IO Sparsity sparsity_patternUnion x = casADi__Sparsity__patternUnion (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__patternUnion_TIC" c_CasADi__Sparsity__patternUnion_TIC :: Ptr Sparsity' -> Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__patternUnion' :: Sparsity -> Sparsity -> IO Sparsity casADi__Sparsity__patternUnion' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__patternUnion_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_patternUnion' :: SparsityClass a => a -> Sparsity -> IO Sparsity sparsity_patternUnion' x = casADi__Sparsity__patternUnion' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__operator_plus" c_CasADi__Sparsity__operator_plus :: Ptr Sparsity' -> Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__operator_plus :: Sparsity -> Sparsity -> IO Sparsity casADi__Sparsity__operator_plus x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__operator_plus x0' x1' >>= wrapReturn -- classy wrapper sparsity_operator_plus :: SparsityClass a => a -> Sparsity -> IO Sparsity sparsity_operator_plus x = casADi__Sparsity__operator_plus (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__patternIntersection" c_CasADi__Sparsity__patternIntersection :: Ptr Sparsity' -> Ptr Sparsity' -> Ptr (CppVec CUChar) -> IO (Ptr Sparsity') casADi__Sparsity__patternIntersection :: Sparsity -> Sparsity -> Vector CUChar -> IO Sparsity casADi__Sparsity__patternIntersection x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__patternIntersection x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Intersection of two sparsity patterns Returns the new sparsity pattern as >well as a mapping with the same length as the number of non-zero elements >The value is 1 if the non-zero comes from the first (i.e. this) object, 2 if >it is from the second and 3 (i.e. 1 | 2) if from both. -} sparsity_patternIntersection :: SparsityClass a => a -> Sparsity -> Vector CUChar -> IO Sparsity sparsity_patternIntersection x = casADi__Sparsity__patternIntersection (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__patternIntersection_TIC" c_CasADi__Sparsity__patternIntersection_TIC :: Ptr Sparsity' -> Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__patternIntersection' :: Sparsity -> Sparsity -> IO Sparsity casADi__Sparsity__patternIntersection' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__patternIntersection_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_patternIntersection' :: SparsityClass a => a -> Sparsity -> IO Sparsity sparsity_patternIntersection' x = casADi__Sparsity__patternIntersection' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__operator_mul" c_CasADi__Sparsity__operator_mul :: Ptr Sparsity' -> Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__operator_mul :: Sparsity -> Sparsity -> IO Sparsity casADi__Sparsity__operator_mul x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__operator_mul x0' x1' >>= wrapReturn -- classy wrapper sparsity_operator_mul :: SparsityClass a => a -> Sparsity -> IO Sparsity sparsity_operator_mul x = casADi__Sparsity__operator_mul (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__patternProduct" c_CasADi__Sparsity__patternProduct :: Ptr Sparsity' -> Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__patternProduct :: Sparsity -> Sparsity -> IO Sparsity casADi__Sparsity__patternProduct x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__patternProduct x0' x1' >>= wrapReturn -- classy wrapper {-| >Sparsity pattern for a matrix-matrix product Returns the sparsity pattern >resulting from premultiplying the pattern with the transpose of x. Returns >the new sparsity pattern as well as a mapping with the same length as the >number of non-zero elements The mapping contains a vector of the index pairs >that makes up the scalar products for each non-zero. -} sparsity_patternProduct :: SparsityClass a => a -> Sparsity -> IO Sparsity sparsity_patternProduct x = casADi__Sparsity__patternProduct (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__patternInverse" c_CasADi__Sparsity__patternInverse :: Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__patternInverse :: Sparsity -> IO Sparsity casADi__Sparsity__patternInverse x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__patternInverse x0' >>= wrapReturn -- classy wrapper {-| >Take the inverse of a sparsity pattern; flip zeros and non-zeros. -} sparsity_patternInverse :: SparsityClass a => a -> IO Sparsity sparsity_patternInverse x = casADi__Sparsity__patternInverse (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__enlarge" c_CasADi__Sparsity__enlarge :: Ptr Sparsity' -> CInt -> CInt -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__enlarge :: Sparsity -> Int -> Int -> Vector Int -> Vector Int -> IO () casADi__Sparsity__enlarge x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> c_CasADi__Sparsity__enlarge x0' x1' x2' x3' x4' >>= wrapReturn -- classy wrapper {-| >Enlarge matrix Make the matrix larger by inserting empty rows and columns, >keeping the existing non-zeros. > >For the matrices A to B A(m,n) length(jj)=m , length(ii)=n B(nrow,ncol) > >A=enlarge(m,n,ii,jj) makes sure that > >B[jj,ii] == A -} sparsity_enlarge :: SparsityClass a => a -> Int -> Int -> Vector Int -> Vector Int -> IO () sparsity_enlarge x = casADi__Sparsity__enlarge (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__enlargeRows" c_CasADi__Sparsity__enlargeRows :: Ptr Sparsity' -> CInt -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__enlargeRows :: Sparsity -> Int -> Vector Int -> IO () casADi__Sparsity__enlargeRows x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__enlargeRows x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Enlarge the matrix along the first dimension (i.e. insert rows) -} sparsity_enlargeRows :: SparsityClass a => a -> Int -> Vector Int -> IO () sparsity_enlargeRows x = casADi__Sparsity__enlargeRows (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__enlargeColumns" c_CasADi__Sparsity__enlargeColumns :: Ptr Sparsity' -> CInt -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__enlargeColumns :: Sparsity -> Int -> Vector Int -> IO () casADi__Sparsity__enlargeColumns x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__enlargeColumns x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Enlarge the matrix along the second dimension (i.e. insert columns) -} sparsity_enlargeColumns :: SparsityClass a => a -> Int -> Vector Int -> IO () sparsity_enlargeColumns x = casADi__Sparsity__enlargeColumns (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__makeDense" c_CasADi__Sparsity__makeDense :: Ptr Sparsity' -> Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__makeDense :: Sparsity -> Vector Int -> IO Sparsity casADi__Sparsity__makeDense x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__makeDense x0' x1' >>= wrapReturn -- classy wrapper {-| >Make a patten dense. -} sparsity_makeDense :: SparsityClass a => a -> Vector Int -> IO Sparsity sparsity_makeDense x = casADi__Sparsity__makeDense (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__erase" c_CasADi__Sparsity__erase :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO (Ptr (CppVec CInt)) casADi__Sparsity__erase :: Sparsity -> Vector Int -> Vector Int -> IO (Vector Int) casADi__Sparsity__erase x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__erase x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Erase rows and/or columns of a matrix. -} sparsity_erase :: SparsityClass a => a -> Vector Int -> Vector Int -> IO (Vector Int) sparsity_erase x = casADi__Sparsity__erase (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__append" c_CasADi__Sparsity__append :: Ptr Sparsity' -> Ptr Sparsity' -> IO () casADi__Sparsity__append :: Sparsity -> Sparsity -> IO () casADi__Sparsity__append x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__append x0' x1' >>= wrapReturn -- classy wrapper {-| >Append another sparsity patten vertically (NOTE: only efficient if vector) -} sparsity_append :: SparsityClass a => a -> Sparsity -> IO () sparsity_append x = casADi__Sparsity__append (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__appendColumns" c_CasADi__Sparsity__appendColumns :: Ptr Sparsity' -> Ptr Sparsity' -> IO () casADi__Sparsity__appendColumns :: Sparsity -> Sparsity -> IO () casADi__Sparsity__appendColumns x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__appendColumns x0' x1' >>= wrapReturn -- classy wrapper {-| >Append another sparsity patten horizontally. -} sparsity_appendColumns :: SparsityClass a => a -> Sparsity -> IO () sparsity_appendColumns x = casADi__Sparsity__appendColumns (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__reserve" c_CasADi__Sparsity__reserve :: Ptr Sparsity' -> CInt -> CInt -> IO () casADi__Sparsity__reserve :: Sparsity -> Int -> Int -> IO () casADi__Sparsity__reserve x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__reserve x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Reserve space. -} sparsity_reserve :: SparsityClass a => a -> Int -> Int -> IO () sparsity_reserve x = casADi__Sparsity__reserve (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isScalar" c_CasADi__Sparsity__isScalar :: Ptr Sparsity' -> CInt -> IO CInt casADi__Sparsity__isScalar :: Sparsity -> Bool -> IO Bool casADi__Sparsity__isScalar x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__isScalar x0' x1' >>= wrapReturn -- classy wrapper {-| >Is scalar? -} sparsity_isScalar :: SparsityClass a => a -> Bool -> IO Bool sparsity_isScalar x = casADi__Sparsity__isScalar (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isScalar_TIC" c_CasADi__Sparsity__isScalar_TIC :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isScalar' :: Sparsity -> IO Bool casADi__Sparsity__isScalar' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isScalar_TIC x0' >>= wrapReturn -- classy wrapper sparsity_isScalar' :: SparsityClass a => a -> IO Bool sparsity_isScalar' x = casADi__Sparsity__isScalar' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isDense" c_CasADi__Sparsity__isDense :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isDense :: Sparsity -> IO Bool casADi__Sparsity__isDense x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isDense x0' >>= wrapReturn -- classy wrapper {-| >Is dense? -} sparsity_isDense :: SparsityClass a => a -> IO Bool sparsity_isDense x = casADi__Sparsity__isDense (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isVector" c_CasADi__Sparsity__isVector :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isVector :: Sparsity -> IO Bool casADi__Sparsity__isVector x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isVector x0' >>= wrapReturn -- classy wrapper {-| >Is vector (i.e. size2()==1) -} sparsity_isVector :: SparsityClass a => a -> IO Bool sparsity_isVector x = casADi__Sparsity__isVector (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isDiagonal" c_CasADi__Sparsity__isDiagonal :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isDiagonal :: Sparsity -> IO Bool casADi__Sparsity__isDiagonal x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isDiagonal x0' >>= wrapReturn -- classy wrapper {-| >Is diagonal? -} sparsity_isDiagonal :: SparsityClass a => a -> IO Bool sparsity_isDiagonal x = casADi__Sparsity__isDiagonal (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isSquare" c_CasADi__Sparsity__isSquare :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isSquare :: Sparsity -> IO Bool casADi__Sparsity__isSquare x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isSquare x0' >>= wrapReturn -- classy wrapper {-| >Is square? -} sparsity_isSquare :: SparsityClass a => a -> IO Bool sparsity_isSquare x = casADi__Sparsity__isSquare (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isSymmetric" c_CasADi__Sparsity__isSymmetric :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isSymmetric :: Sparsity -> IO Bool casADi__Sparsity__isSymmetric x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isSymmetric x0' >>= wrapReturn -- classy wrapper {-| >Is symmetric? -} sparsity_isSymmetric :: SparsityClass a => a -> IO Bool sparsity_isSymmetric x = casADi__Sparsity__isSymmetric (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isTriu" c_CasADi__Sparsity__isTriu :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isTriu :: Sparsity -> IO Bool casADi__Sparsity__isTriu x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isTriu x0' >>= wrapReturn -- classy wrapper {-| >Is upper triangular? -} sparsity_isTriu :: SparsityClass a => a -> IO Bool sparsity_isTriu x = casADi__Sparsity__isTriu (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isTril" c_CasADi__Sparsity__isTril :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isTril :: Sparsity -> IO Bool casADi__Sparsity__isTril x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isTril x0' >>= wrapReturn -- classy wrapper {-| >Is lower triangular? -} sparsity_isTril :: SparsityClass a => a -> IO Bool sparsity_isTril x = casADi__Sparsity__isTril (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__isSingular" c_CasADi__Sparsity__isSingular :: Ptr Sparsity' -> IO CInt casADi__Sparsity__isSingular :: Sparsity -> IO Bool casADi__Sparsity__isSingular x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__isSingular x0' >>= wrapReturn -- classy wrapper {-| >Check whether the sparsity-pattern inidcates structural singularity. -} sparsity_isSingular :: SparsityClass a => a -> IO Bool sparsity_isSingular x = casADi__Sparsity__isSingular (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getTriu" c_CasADi__Sparsity__getTriu :: Ptr Sparsity' -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__getTriu :: Sparsity -> Bool -> IO Sparsity casADi__Sparsity__getTriu x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__getTriu x0' x1' >>= wrapReturn -- classy wrapper {-| >Get upper triangular part. -} sparsity_getTriu :: SparsityClass a => a -> Bool -> IO Sparsity sparsity_getTriu x = casADi__Sparsity__getTriu (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getTriu_TIC" c_CasADi__Sparsity__getTriu_TIC :: Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__getTriu' :: Sparsity -> IO Sparsity casADi__Sparsity__getTriu' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__getTriu_TIC x0' >>= wrapReturn -- classy wrapper sparsity_getTriu' :: SparsityClass a => a -> IO Sparsity sparsity_getTriu' x = casADi__Sparsity__getTriu' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getTril" c_CasADi__Sparsity__getTril :: Ptr Sparsity' -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__getTril :: Sparsity -> Bool -> IO Sparsity casADi__Sparsity__getTril x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__getTril x0' x1' >>= wrapReturn -- classy wrapper {-| >Get lower triangular part. -} sparsity_getTril :: SparsityClass a => a -> Bool -> IO Sparsity sparsity_getTril x = casADi__Sparsity__getTril (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getTril_TIC" c_CasADi__Sparsity__getTril_TIC :: Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__getTril' :: Sparsity -> IO Sparsity casADi__Sparsity__getTril' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__getTril_TIC x0' >>= wrapReturn -- classy wrapper sparsity_getTril' :: SparsityClass a => a -> IO Sparsity sparsity_getTril' x = casADi__Sparsity__getTril' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__rowsSequential" c_CasADi__Sparsity__rowsSequential :: Ptr Sparsity' -> CInt -> IO CInt casADi__Sparsity__rowsSequential :: Sparsity -> Bool -> IO Bool casADi__Sparsity__rowsSequential x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__rowsSequential x0' x1' >>= wrapReturn -- classy wrapper {-| >Do the rows appear sequentially on each column (if strictly==true, then do >not allow multiple entries) -} sparsity_rowsSequential :: SparsityClass a => a -> Bool -> IO Bool sparsity_rowsSequential x = casADi__Sparsity__rowsSequential (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__rowsSequential_TIC" c_CasADi__Sparsity__rowsSequential_TIC :: Ptr Sparsity' -> IO CInt casADi__Sparsity__rowsSequential' :: Sparsity -> IO Bool casADi__Sparsity__rowsSequential' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__rowsSequential_TIC x0' >>= wrapReturn -- classy wrapper sparsity_rowsSequential' :: SparsityClass a => a -> IO Bool sparsity_rowsSequential' x = casADi__Sparsity__rowsSequential' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__removeDuplicates" c_CasADi__Sparsity__removeDuplicates :: Ptr Sparsity' -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__removeDuplicates :: Sparsity -> Vector Int -> IO () casADi__Sparsity__removeDuplicates x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__removeDuplicates x0' x1' >>= wrapReturn -- classy wrapper {-| >Remove duplicate entries: The same indices will be removed from the mapping >vector, which must have the same length as the number of nonzeros. -} sparsity_removeDuplicates :: SparsityClass a => a -> Vector Int -> IO () sparsity_removeDuplicates x = casADi__Sparsity__removeDuplicates (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__eliminationTree" c_CasADi__Sparsity__eliminationTree :: Ptr Sparsity' -> CInt -> IO (Ptr (CppVec CInt)) casADi__Sparsity__eliminationTree :: Sparsity -> Bool -> IO (Vector Int) casADi__Sparsity__eliminationTree x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__eliminationTree x0' x1' >>= wrapReturn -- classy wrapper {-| >Calculate the elimination tree See Direct Methods for Sparse Linear Systems >by Davis (2006). If the parameter ata is false, the algorithm is equivalent >to Matlab's etree(A), except that the indices are zero- based. If ata is >true, the algorithm is equivalent to Matlab's etree(A,'row'). -} sparsity_eliminationTree :: SparsityClass a => a -> Bool -> IO (Vector Int) sparsity_eliminationTree x = casADi__Sparsity__eliminationTree (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__eliminationTree_TIC" c_CasADi__Sparsity__eliminationTree_TIC :: Ptr Sparsity' -> IO (Ptr (CppVec CInt)) casADi__Sparsity__eliminationTree' :: Sparsity -> IO (Vector Int) casADi__Sparsity__eliminationTree' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__eliminationTree_TIC x0' >>= wrapReturn -- classy wrapper sparsity_eliminationTree' :: SparsityClass a => a -> IO (Vector Int) sparsity_eliminationTree' x = casADi__Sparsity__eliminationTree' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__depthFirstSearch" c_CasADi__Sparsity__depthFirstSearch :: Ptr Sparsity' -> CInt -> CInt -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO CInt casADi__Sparsity__depthFirstSearch :: Sparsity -> Int -> Int -> Vector Int -> Vector Int -> Vector Int -> Vector Bool -> IO Int casADi__Sparsity__depthFirstSearch x0 x1 x2 x3 x4 x5 x6 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> withMarshal x5 $ \x5' -> withMarshal x6 $ \x6' -> c_CasADi__Sparsity__depthFirstSearch x0' x1' x2' x3' x4' x5' x6' >>= wrapReturn -- classy wrapper {-| >Depth-first search on the adjacency graph of the sparsity See Direct Methods >for Sparse Linear Systems by Davis (2006). -} sparsity_depthFirstSearch :: SparsityClass a => a -> Int -> Int -> Vector Int -> Vector Int -> Vector Int -> Vector Bool -> IO Int sparsity_depthFirstSearch x = casADi__Sparsity__depthFirstSearch (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__stronglyConnectedComponents" c_CasADi__Sparsity__stronglyConnectedComponents :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO CInt casADi__Sparsity__stronglyConnectedComponents :: Sparsity -> Vector Int -> Vector Int -> IO Int casADi__Sparsity__stronglyConnectedComponents x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__stronglyConnectedComponents x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Find the strongly connected components of the bigraph defined by the >sparsity pattern of a square matrix See Direct Methods for Sparse Linear >Systems by Davis (2006). Returns: > >Number of components > >Offset for each components (length: 1 + number of components) > >Indices for each components, component i has indices index[offset[i]], ..., >index[offset[i+1]] > >In the case that the matrix is symmetric, the result has a particular >interpretation: Given a symmetric matrix A and n = >A.stronglyConnectedComponents(p,r) > >=> A[p,p] will appear block-diagonal with n blocks and with the indices of >the block boundaries to be found in r. -} sparsity_stronglyConnectedComponents :: SparsityClass a => a -> Vector Int -> Vector Int -> IO Int sparsity_stronglyConnectedComponents x = casADi__Sparsity__stronglyConnectedComponents (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__dulmageMendelsohn" c_CasADi__Sparsity__dulmageMendelsohn :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> CInt -> IO CInt casADi__Sparsity__dulmageMendelsohn :: Sparsity -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Int -> IO Int casADi__Sparsity__dulmageMendelsohn x0 x1 x2 x3 x4 x5 x6 x7 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> withMarshal x5 $ \x5' -> withMarshal x6 $ \x6' -> withMarshal x7 $ \x7' -> c_CasADi__Sparsity__dulmageMendelsohn x0' x1' x2' x3' x4' x5' x6' x7' >>= wrapReturn -- classy wrapper {-| >Compute the Dulmage-Mendelsohn decomposition See Direct Methods for Sparse >Linear Systems by Davis (2006). > >Dulmage-Mendelsohn will try to bring your matrix into lower block- >triangular (LBT) form. It will not care about the distance of off- diagonal >elements to the diagonal: there is no guarantee you will get a block- >diagonal matrix if you supply a randomly permuted block- diagonal matrix. > >If your matrix is symmetrical, this method is of limited use; permutation >can make it non-symmetric. > >See: stronglyConnectedComponents -} sparsity_dulmageMendelsohn :: SparsityClass a => a -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Int -> IO Int sparsity_dulmageMendelsohn x = casADi__Sparsity__dulmageMendelsohn (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__dulmageMendelsohn_TIC" c_CasADi__Sparsity__dulmageMendelsohn_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO CInt casADi__Sparsity__dulmageMendelsohn' :: Sparsity -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> IO Int casADi__Sparsity__dulmageMendelsohn' x0 x1 x2 x3 x4 x5 x6 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> withMarshal x5 $ \x5' -> withMarshal x6 $ \x6' -> c_CasADi__Sparsity__dulmageMendelsohn_TIC x0' x1' x2' x3' x4' x5' x6' >>= wrapReturn -- classy wrapper sparsity_dulmageMendelsohn' :: SparsityClass a => a -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -> IO Int sparsity_dulmageMendelsohn' x = casADi__Sparsity__dulmageMendelsohn' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getElements" c_CasADi__Sparsity__getElements :: Ptr Sparsity' -> CInt -> IO (Ptr (CppVec CInt)) casADi__Sparsity__getElements :: Sparsity -> Bool -> IO (Vector Int) casADi__Sparsity__getElements x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__getElements x0' x1' >>= wrapReturn -- classy wrapper {-| >> std::vector< int > CasADi::Sparsity::getElements(bool col_major=true) const >------------------------------------------------------------------------ > >Get the location of all non-zero elements as they would appear in a Dense >matrix A : DenseMatrix 4 x 3 B : SparseMatrix 4 x 3 , 5 structural non- >zeros. > >k = A.getElements() A[k] will contain the elements of A that are non- zero >in B > >> void CasADi::Sparsity::getElements(std::vector< int > &loc, bool col_major=true) const >------------------------------------------------------------------------ > >Get the location of all nonzero elements (inplace version) -} sparsity_getElements :: SparsityClass a => a -> Bool -> IO (Vector Int) sparsity_getElements x = casADi__Sparsity__getElements (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getElements_TIC" c_CasADi__Sparsity__getElements_TIC :: Ptr Sparsity' -> IO (Ptr (CppVec CInt)) casADi__Sparsity__getElements' :: Sparsity -> IO (Vector Int) casADi__Sparsity__getElements' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__getElements_TIC x0' >>= wrapReturn -- classy wrapper sparsity_getElements' :: SparsityClass a => a -> IO (Vector Int) sparsity_getElements' x = casADi__Sparsity__getElements' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getElements_TIC_TIC" c_CasADi__Sparsity__getElements_TIC_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> CInt -> IO () casADi__Sparsity__getElements'' :: Sparsity -> Vector Int -> Bool -> IO () casADi__Sparsity__getElements'' x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__getElements_TIC_TIC x0' x1' x2' >>= wrapReturn -- classy wrapper sparsity_getElements'' :: SparsityClass a => a -> Vector Int -> Bool -> IO () sparsity_getElements'' x = casADi__Sparsity__getElements'' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__getElements_TIC_TIC_TIC" c_CasADi__Sparsity__getElements_TIC_TIC_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> IO () casADi__Sparsity__getElements''' :: Sparsity -> Vector Int -> IO () casADi__Sparsity__getElements''' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__getElements_TIC_TIC_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_getElements''' :: SparsityClass a => a -> Vector Int -> IO () sparsity_getElements''' x = casADi__Sparsity__getElements''' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__unidirectionalColoring" c_CasADi__Sparsity__unidirectionalColoring :: Ptr Sparsity' -> Ptr Sparsity' -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__unidirectionalColoring :: Sparsity -> Sparsity -> Int -> IO Sparsity casADi__Sparsity__unidirectionalColoring x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__unidirectionalColoring x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Perform a unidirectional coloring: A greedy distance-2 coloring algorithm >(Algorithm 3.1 in A. H. GEBREMEDHIN, F. MANNE, A. POTHEN) -} sparsity_unidirectionalColoring :: SparsityClass a => a -> Sparsity -> Int -> IO Sparsity sparsity_unidirectionalColoring x = casADi__Sparsity__unidirectionalColoring (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__unidirectionalColoring_TIC" c_CasADi__Sparsity__unidirectionalColoring_TIC :: Ptr Sparsity' -> Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__unidirectionalColoring' :: Sparsity -> Sparsity -> IO Sparsity casADi__Sparsity__unidirectionalColoring' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__unidirectionalColoring_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_unidirectionalColoring' :: SparsityClass a => a -> Sparsity -> IO Sparsity sparsity_unidirectionalColoring' x = casADi__Sparsity__unidirectionalColoring' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__unidirectionalColoring_TIC_TIC" c_CasADi__Sparsity__unidirectionalColoring_TIC_TIC :: Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__unidirectionalColoring'' :: Sparsity -> IO Sparsity casADi__Sparsity__unidirectionalColoring'' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__unidirectionalColoring_TIC_TIC x0' >>= wrapReturn -- classy wrapper sparsity_unidirectionalColoring'' :: SparsityClass a => a -> IO Sparsity sparsity_unidirectionalColoring'' x = casADi__Sparsity__unidirectionalColoring'' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__starColoring" c_CasADi__Sparsity__starColoring :: Ptr Sparsity' -> CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__starColoring :: Sparsity -> Int -> Int -> IO Sparsity casADi__Sparsity__starColoring x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__starColoring x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Perform a star coloring of a symmetric matrix: A greedy distance-2 coloring >algorithm (Algorithm 4.1 in A. H. GEBREMEDHIN, F. MANNE, A. POTHEN) Ordering >options: None (0), largest first (1) -} sparsity_starColoring :: SparsityClass a => a -> Int -> Int -> IO Sparsity sparsity_starColoring x = casADi__Sparsity__starColoring (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__starColoring_TIC" c_CasADi__Sparsity__starColoring_TIC :: Ptr Sparsity' -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__starColoring' :: Sparsity -> Int -> IO Sparsity casADi__Sparsity__starColoring' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__starColoring_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_starColoring' :: SparsityClass a => a -> Int -> IO Sparsity sparsity_starColoring' x = casADi__Sparsity__starColoring' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__starColoring_TIC_TIC" c_CasADi__Sparsity__starColoring_TIC_TIC :: Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__starColoring'' :: Sparsity -> IO Sparsity casADi__Sparsity__starColoring'' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__starColoring_TIC_TIC x0' >>= wrapReturn -- classy wrapper sparsity_starColoring'' :: SparsityClass a => a -> IO Sparsity sparsity_starColoring'' x = casADi__Sparsity__starColoring'' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__starColoring2" c_CasADi__Sparsity__starColoring2 :: Ptr Sparsity' -> CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__starColoring2 :: Sparsity -> Int -> Int -> IO Sparsity casADi__Sparsity__starColoring2 x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__starColoring2 x0' x1' x2' >>= wrapReturn -- classy wrapper {-| >Perform a star coloring of a symmetric matrix: A new greedy distance-2 >coloring algorithm (Algorithm 4.1 in A. H. GEBREMEDHIN, A. TARAFDAR, F. >MANNE, A. POTHEN) Ordering options: None (0), largest first (1) -} sparsity_starColoring2 :: SparsityClass a => a -> Int -> Int -> IO Sparsity sparsity_starColoring2 x = casADi__Sparsity__starColoring2 (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__starColoring2_TIC" c_CasADi__Sparsity__starColoring2_TIC :: Ptr Sparsity' -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__starColoring2' :: Sparsity -> Int -> IO Sparsity casADi__Sparsity__starColoring2' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__starColoring2_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_starColoring2' :: SparsityClass a => a -> Int -> IO Sparsity sparsity_starColoring2' x = casADi__Sparsity__starColoring2' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__starColoring2_TIC_TIC" c_CasADi__Sparsity__starColoring2_TIC_TIC :: Ptr Sparsity' -> IO (Ptr Sparsity') casADi__Sparsity__starColoring2'' :: Sparsity -> IO Sparsity casADi__Sparsity__starColoring2'' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__starColoring2_TIC_TIC x0' >>= wrapReturn -- classy wrapper sparsity_starColoring2'' :: SparsityClass a => a -> IO Sparsity sparsity_starColoring2'' x = casADi__Sparsity__starColoring2'' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__largestFirstOrdering" c_CasADi__Sparsity__largestFirstOrdering :: Ptr Sparsity' -> IO (Ptr (CppVec CInt)) casADi__Sparsity__largestFirstOrdering :: Sparsity -> IO (Vector Int) casADi__Sparsity__largestFirstOrdering x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__largestFirstOrdering x0' >>= wrapReturn -- classy wrapper {-| >Order the cols by decreasing degree. -} sparsity_largestFirstOrdering :: SparsityClass a => a -> IO (Vector Int) sparsity_largestFirstOrdering x = casADi__Sparsity__largestFirstOrdering (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__pmult" c_CasADi__Sparsity__pmult :: Ptr Sparsity' -> Ptr (CppVec CInt) -> CInt -> CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__pmult :: Sparsity -> Vector Int -> Bool -> Bool -> Bool -> IO Sparsity casADi__Sparsity__pmult x0 x1 x2 x3 x4 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> withMarshal x4 $ \x4' -> c_CasADi__Sparsity__pmult x0' x1' x2' x3' x4' >>= wrapReturn -- classy wrapper {-| >Permute rows and/or columns Multiply the sparsity with a permutation matrix >from the left and/or from the right P * A * trans(P), A * trans(P) or A * >trans(P) with P defined by an index vector containing the row for each col. >As an alternative, P can be transposed (inverted). -} sparsity_pmult :: SparsityClass a => a -> Vector Int -> Bool -> Bool -> Bool -> IO Sparsity sparsity_pmult x = casADi__Sparsity__pmult (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__pmult_TIC" c_CasADi__Sparsity__pmult_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> CInt -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__pmult' :: Sparsity -> Vector Int -> Bool -> Bool -> IO Sparsity casADi__Sparsity__pmult' x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> c_CasADi__Sparsity__pmult_TIC x0' x1' x2' x3' >>= wrapReturn -- classy wrapper sparsity_pmult' :: SparsityClass a => a -> Vector Int -> Bool -> Bool -> IO Sparsity sparsity_pmult' x = casADi__Sparsity__pmult' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__pmult_TIC_TIC" c_CasADi__Sparsity__pmult_TIC_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> CInt -> IO (Ptr Sparsity') casADi__Sparsity__pmult'' :: Sparsity -> Vector Int -> Bool -> IO Sparsity casADi__Sparsity__pmult'' x0 x1 x2 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> c_CasADi__Sparsity__pmult_TIC_TIC x0' x1' x2' >>= wrapReturn -- classy wrapper sparsity_pmult'' :: SparsityClass a => a -> Vector Int -> Bool -> IO Sparsity sparsity_pmult'' x = casADi__Sparsity__pmult'' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__pmult_TIC_TIC_TIC" c_CasADi__Sparsity__pmult_TIC_TIC_TIC :: Ptr Sparsity' -> Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__pmult''' :: Sparsity -> Vector Int -> IO Sparsity casADi__Sparsity__pmult''' x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__pmult_TIC_TIC_TIC x0' x1' >>= wrapReturn -- classy wrapper sparsity_pmult''' :: SparsityClass a => a -> Vector Int -> IO Sparsity sparsity_pmult''' x = casADi__Sparsity__pmult''' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__dimString" c_CasADi__Sparsity__dimString :: Ptr Sparsity' -> IO (Ptr StdString') casADi__Sparsity__dimString :: Sparsity -> IO String casADi__Sparsity__dimString x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__dimString x0' >>= wrapReturn -- classy wrapper {-| >Get the dimension as a string. -} sparsity_dimString :: SparsityClass a => a -> IO String sparsity_dimString x = casADi__Sparsity__dimString (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__spy_TIC" c_CasADi__Sparsity__spy_TIC :: Ptr Sparsity' -> IO () casADi__Sparsity__spy' :: Sparsity -> IO () casADi__Sparsity__spy' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__spy_TIC x0' >>= wrapReturn -- classy wrapper sparsity_spy' :: SparsityClass a => a -> IO () sparsity_spy' x = casADi__Sparsity__spy' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__spyMatlab" c_CasADi__Sparsity__spyMatlab :: Ptr Sparsity' -> Ptr StdString' -> IO () casADi__Sparsity__spyMatlab :: Sparsity -> String -> IO () casADi__Sparsity__spyMatlab x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__Sparsity__spyMatlab x0' x1' >>= wrapReturn -- classy wrapper {-| >Generate a script for Matlab or Octave which visualizes the sparsity using >the spy command. -} sparsity_spyMatlab :: SparsityClass a => a -> String -> IO () sparsity_spyMatlab x = casADi__Sparsity__spyMatlab (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__printCompact_TIC" c_CasADi__Sparsity__printCompact_TIC :: Ptr Sparsity' -> IO () casADi__Sparsity__printCompact' :: Sparsity -> IO () casADi__Sparsity__printCompact' x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__printCompact_TIC x0' >>= wrapReturn -- classy wrapper sparsity_printCompact' :: SparsityClass a => a -> IO () sparsity_printCompact' x = casADi__Sparsity__printCompact' (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__hash" c_CasADi__Sparsity__hash :: Ptr Sparsity' -> IO CSize casADi__Sparsity__hash :: Sparsity -> IO CSize casADi__Sparsity__hash x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__hash x0' >>= wrapReturn -- classy wrapper sparsity_hash :: SparsityClass a => a -> IO CSize sparsity_hash x = casADi__Sparsity__hash (castSparsity x) -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__Sparsity" c_CasADi__Sparsity__Sparsity :: CInt -> IO (Ptr Sparsity') casADi__Sparsity__Sparsity :: Int -> IO Sparsity casADi__Sparsity__Sparsity x0 = withMarshal x0 $ \x0' -> c_CasADi__Sparsity__Sparsity x0' >>= wrapReturn -- classy wrapper {-| >> CasADi::Sparsity::Sparsity(int nrow, int ncol, bool dense=false) >------------------------------------------------------------------------ > >[DEPRECATED] > >> CasADi::Sparsity::Sparsity(int dummy=0) >------------------------------------------------------------------------ > >Default constructor. > >> CasADi::Sparsity::Sparsity(int nrow, int ncol, const std::vector< int > &colind, const std::vector< int > &row) >------------------------------------------------------------------------ > >Construct from sparsity pattern vectors given in compressed column storage >format. -} sparsity :: Int -> IO Sparsity sparsity = casADi__Sparsity__Sparsity -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__Sparsity_TIC" c_CasADi__Sparsity__Sparsity_TIC :: IO (Ptr Sparsity') casADi__Sparsity__Sparsity' :: IO Sparsity casADi__Sparsity__Sparsity' = c_CasADi__Sparsity__Sparsity_TIC >>= wrapReturn -- classy wrapper sparsity' :: IO Sparsity sparsity' = casADi__Sparsity__Sparsity' -- direct wrapper foreign import ccall unsafe "CasADi__Sparsity__Sparsity_TIC_TIC" c_CasADi__Sparsity__Sparsity_TIC_TIC :: CInt -> CInt -> Ptr (CppVec CInt) -> Ptr (CppVec CInt) -> IO (Ptr Sparsity') casADi__Sparsity__Sparsity'' :: Int -> Int -> Vector Int -> Vector Int -> IO Sparsity casADi__Sparsity__Sparsity'' x0 x1 x2 x3 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> withMarshal x2 $ \x2' -> withMarshal x3 $ \x3' -> c_CasADi__Sparsity__Sparsity_TIC_TIC x0' x1' x2' x3' >>= wrapReturn -- classy wrapper sparsity'' :: Int -> Int -> Vector Int -> Vector Int -> IO Sparsity sparsity'' = casADi__Sparsity__Sparsity''