{-# LANGUAGE CPP #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE ForeignFunctionInterface #-} -- | -- Module : Foreign.CUDA.BLAS.Sparse.Internal.Types -- Copyright : [2017] Trevor L. McDonell -- License : BSD3 -- -- Maintainer : Trevor L. McDonell -- Stability : experimental -- Portability : non-portable (GHC extensions) -- module Foreign.CUDA.BLAS.Sparse.Internal.Types where -- other import Prelude hiding ( Either(..) ) import Foreign.Ptr #include "cbits/stubs.h" {# context lib="cusparse" #} -- | This type indicates whether the operation is performed only on indices -- ('Symbolic') or on data and indices ('Numeric'). -- -- -- {# enum cusparseAction_t as Action { underscoreToCase } with prefix="CUSPARSE_ACTION" deriving (Eq, Show) #} -- | Indicates the underlying storage model for elements of matrices. -- -- -- {# enum cusparseDirection_t as Direction { underscoreToCase } with prefix="CUSPARSE_DIRECTION" deriving (Eq, Show) #} -- | Indicates which operations need to be performed with the sparse matrix. -- -- * @N@: no transpose selected -- * @T@: transpose operation -- * @C@: conjugate transpose -- -- -- {# enum cusparseOperation_t as Operation { CUSPARSE_OPERATION_NON_TRANSPOSE as N , CUSPARSE_OPERATION_TRANSPOSE as T , CUSPARSE_OPERATION_CONJUGATE_TRANSPOSE as C } deriving (Eq, Show) #} -- | Used to specify the type of data underlying a @void*@ pointer. For example, -- it is used in the routine . -- #if CUDA_VERSION < 8000 data Type #else {# enum cudaDataType_t as Type { underscoreToCase } with prefix="CUDA" deriving (Eq, Show) #} #endif -- | Specify the algorithm to use, for example used in the routine -- . -- #if CUDA_VERSION < 8000 data Algorithm #else {# enum cusparseAlgMode_t as Algorithm { underscoreToCase } with prefix="CUSPARSE" deriving (Eq, Show) #} #endif -- | Indicates whether level information is used by some solver algorithms. -- -- -- {# enum cusparseSolvePolicy_t as Policy { underscoreToCase } with prefix="CUSPARSE_SOLVE_POLICY" deriving (Eq, Show) #}