-- GENERATED by C->Haskell Compiler, version 0.28.3 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}
--
-- This module is auto-generated. Do not edit directly.
--

{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
-- |
-- Module      : Foreign.CUDA.BLAS.Sparse.Precondition
-- Copyright   : [2017] Trevor L. McDonell
-- License     : BSD3
--
-- Maintainer  : Trevor L. McDonell <tmcdonell@cse.unsw.edu.au>
-- Stability   : experimental
-- Portability : non-portable (GHC extensions)
--
-- For more information see the cuSPARSE function reference:
--
-- <http://docs.nvidia.com/cuda/cusparse/index.html#cusparse-preconditioners-reference>
--

module Foreign.CUDA.BLAS.Sparse.Precondition (

  Operation(..),
  Direction(..),
  Policy(..),
  MatrixDescriptor,
  Info,
  Info_csric02,
  Info_csrilu02,
  Info_bsric02,
  Info_bsrilu02,
  scsric0,
  dcsric0,
  ccsric0,
  zcsric0,
  scsric02_bufferSize,
  dcsric02_bufferSize,
  ccsric02_bufferSize,
  zcsric02_bufferSize,
  scsric02_analysis,
  dcsric02_analysis,
  ccsric02_analysis,
  zcsric02_analysis,
  scsric02,
  dcsric02,
  ccsric02,
  zcsric02,
  xcsric02_zeroPivot,
  scsrilu0,
  dcsrilu0,
  ccsrilu0,
  zcsrilu0,
  scsrilu02_numericBoost,
  dcsrilu02_numericBoost,
  ccsrilu02_numericBoost,
  zcsrilu02_numericBoost,
  scsrilu02_bufferSize,
  dcsrilu02_bufferSize,
  ccsrilu02_bufferSize,
  zcsrilu02_bufferSize,
  scsrilu02_analysis,
  dcsrilu02_analysis,
  ccsrilu02_analysis,
  zcsrilu02_analysis,
  scsrilu02,
  dcsrilu02,
  ccsrilu02,
  zcsrilu02,
  xcsrilu02_zeroPivot,
  sbsric02_bufferSize,
  dbsric02_bufferSize,
  cbsric02_bufferSize,
  zbsric02_bufferSize,
  sbsric02_analysis,
  dbsric02_analysis,
  cbsric02_analysis,
  zbsric02_analysis,
  sbsric02,
  dbsric02,
  cbsric02,
  zbsric02,
  xbsric02_zeroPivot,
  sbsrilu02_numericBoost,
  dbsrilu02_numericBoost,
  cbsrilu02_numericBoost,
  zbsrilu02_numericBoost,
  sbsrilu02_bufferSize,
  dbsrilu02_bufferSize,
  cbsrilu02_bufferSize,
  zbsrilu02_bufferSize,
  sbsrilu02_analysis,
  dbsrilu02_analysis,
  cbsrilu02_analysis,
  zbsrilu02_analysis,
  sbsrilu02,
  dbsrilu02,
  cbsrilu02,
  zbsrilu02,
  xbsrilu02_zeroPivot,
  sgtsv,
  dgtsv,
  cgtsv,
  zgtsv,
  sgtsv_nopivot,
  dgtsv_nopivot,
  cgtsv_nopivot,
  zgtsv_nopivot,
  sgtsvStridedBatch,
  dgtsvStridedBatch,
  cgtsvStridedBatch,
  zgtsvStridedBatch,
  csrilu0Ex,

) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp



import Data.Complex
import Numeric.Half
import Foreign
import Foreign.C
import Foreign.Storable.Complex ()
import Foreign.CUDA.Ptr
import Foreign.CUDA.BLAS.Sparse.Analysis
import Foreign.CUDA.BLAS.Sparse.Context
import Foreign.CUDA.BLAS.Sparse.Error
import Foreign.CUDA.BLAS.Sparse.Internal.C2HS
import Foreign.CUDA.BLAS.Sparse.Internal.Types
import Foreign.CUDA.BLAS.Sparse.Matrix.Descriptor
import Foreign.CUDA.BLAS.Sparse.Matrix.Hybrid



{-# LINE 133 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINE useDevP #-}
useDevP :: DevicePtr a -> Ptr b
useDevP = useDevicePtr . castDevPtr

{-# INLINE useHostP #-}
useHostP :: HostPtr a -> Ptr b
useHostP = useHostPtr . castHostPtr


{-# INLINEABLE scsric0 #-}
scsric0 :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> IO ()
scsric0 a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo a8} in 
  scsric0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 145 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsric0 #-}
dcsric0 :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> IO ()
dcsric0 a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo a8} in 
  dcsric0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 148 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsric0 #-}
ccsric0 :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> IO ()
ccsric0 a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo a8} in 
  ccsric0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 151 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsric0 #-}
zcsric0 :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> IO ()
zcsric0 a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo a8} in 
  zcsric0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 154 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE scsric02_bufferSize #-}
scsric02_bufferSize :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> IO ((Int))
scsric02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  alloca $ \a9' -> 
  scsric02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  checkStatus res >> 
  peekIntConv  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 157 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsric02_bufferSize #-}
dcsric02_bufferSize :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> IO ((Int))
dcsric02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  alloca $ \a9' -> 
  dcsric02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  checkStatus res >> 
  peekIntConv  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 160 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsric02_bufferSize #-}
ccsric02_bufferSize :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> IO ((Int))
ccsric02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  alloca $ \a9' -> 
  ccsric02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  checkStatus res >> 
  peekIntConv  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 163 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsric02_bufferSize #-}
zcsric02_bufferSize :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> IO ((Int))
zcsric02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  alloca $ \a9' -> 
  zcsric02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  checkStatus res >> 
  peekIntConv  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 166 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE scsric02_analysis #-}
scsric02_analysis :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> (Policy) -> (DevicePtr ()) -> IO ()
scsric02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  scsric02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 169 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsric02_analysis #-}
dcsric02_analysis :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> (Policy) -> (DevicePtr ()) -> IO ()
dcsric02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  dcsric02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 172 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsric02_analysis #-}
ccsric02_analysis :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> (Policy) -> (DevicePtr ()) -> IO ()
ccsric02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  ccsric02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 175 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsric02_analysis #-}
zcsric02_analysis :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> (Policy) -> (DevicePtr ()) -> IO ()
zcsric02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  zcsric02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 178 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE scsric02 #-}
scsric02 :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> (Policy) -> (DevicePtr ()) -> IO ()
scsric02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  scsric02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 181 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsric02 #-}
dcsric02 :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> (Policy) -> (DevicePtr ()) -> IO ()
dcsric02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  dcsric02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 184 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsric02 #-}
ccsric02 :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> (Policy) -> (DevicePtr ()) -> IO ()
ccsric02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  ccsric02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 187 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsric02 #-}
zcsric02 :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csric02) -> (Policy) -> (DevicePtr ()) -> IO ()
zcsric02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csric02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  zcsric02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 190 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE xcsric02_zeroPivot #-}
xcsric02_zeroPivot :: (Handle) -> (Info_csric02) -> (Ptr Int32) -> IO ()
xcsric02_zeroPivot a1 a2 a3 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_csric02 a2} in 
  let {a3' = castPtr a3} in 
  xcsric02_zeroPivot'_ a1' a2' a3' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 193 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE scsrilu0 #-}
scsrilu0 :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> IO ()
scsrilu0 a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo a8} in 
  scsrilu0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 196 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsrilu0 #-}
dcsrilu0 :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> IO ()
dcsrilu0 a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo a8} in 
  dcsrilu0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 199 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsrilu0 #-}
ccsrilu0 :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> IO ()
ccsrilu0 a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo a8} in 
  ccsrilu0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 202 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsrilu0 #-}
zcsrilu0 :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> IO ()
zcsrilu0 a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo a8} in 
  zcsrilu0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 205 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE scsrilu02_numericBoost #-}
scsrilu02_numericBoost :: (Handle) -> (Info_csrilu02) -> (Int) -> (Ptr Double) -> (Ptr Float) -> IO ()
scsrilu02_numericBoost a1 a2 a3 a4 a5 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_csrilu02 a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = castPtr a4} in 
  let {a5' = castPtr a5} in 
  scsrilu02_numericBoost'_ a1' a2' a3' a4' a5' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 208 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsrilu02_numericBoost #-}
dcsrilu02_numericBoost :: (Handle) -> (Info_csrilu02) -> (Int) -> (Ptr Double) -> (Ptr Double) -> IO ()
dcsrilu02_numericBoost a1 a2 a3 a4 a5 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_csrilu02 a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = castPtr a4} in 
  let {a5' = castPtr a5} in 
  dcsrilu02_numericBoost'_ a1' a2' a3' a4' a5' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 211 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsrilu02_numericBoost #-}
ccsrilu02_numericBoost :: (Handle) -> (Info_csrilu02) -> (Int) -> (Ptr Double) -> (Ptr (Complex Float)) -> IO ()
ccsrilu02_numericBoost a1 a2 a3 a4 a5 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_csrilu02 a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = castPtr a4} in 
  let {a5' = castPtr a5} in 
  ccsrilu02_numericBoost'_ a1' a2' a3' a4' a5' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 214 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsrilu02_numericBoost #-}
zcsrilu02_numericBoost :: (Handle) -> (Info_csrilu02) -> (Int) -> (Ptr Double) -> (Ptr (Complex Double)) -> IO ()
zcsrilu02_numericBoost a1 a2 a3 a4 a5 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_csrilu02 a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = castPtr a4} in 
  let {a5' = castPtr a5} in 
  zcsrilu02_numericBoost'_ a1' a2' a3' a4' a5' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 217 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE scsrilu02_bufferSize #-}
scsrilu02_bufferSize :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> IO ((Int))
scsrilu02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  alloca $ \a9' -> 
  scsrilu02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  checkStatus res >> 
  peekIntConv  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 220 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsrilu02_bufferSize #-}
dcsrilu02_bufferSize :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> IO ((Int))
dcsrilu02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  alloca $ \a9' -> 
  dcsrilu02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  checkStatus res >> 
  peekIntConv  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 223 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsrilu02_bufferSize #-}
ccsrilu02_bufferSize :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> IO ((Int))
ccsrilu02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  alloca $ \a9' -> 
  ccsrilu02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  checkStatus res >> 
  peekIntConv  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 226 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsrilu02_bufferSize #-}
zcsrilu02_bufferSize :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> IO ((Int))
zcsrilu02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  alloca $ \a9' -> 
  zcsrilu02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  checkStatus res >> 
  peekIntConv  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 229 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE scsrilu02_analysis #-}
scsrilu02_analysis :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
scsrilu02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  scsrilu02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 232 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsrilu02_analysis #-}
dcsrilu02_analysis :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
dcsrilu02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  dcsrilu02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 235 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsrilu02_analysis #-}
ccsrilu02_analysis :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
ccsrilu02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  ccsrilu02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 238 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsrilu02_analysis #-}
zcsrilu02_analysis :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
zcsrilu02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  zcsrilu02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 241 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE scsrilu02 #-}
scsrilu02 :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
scsrilu02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  scsrilu02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 244 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dcsrilu02 #-}
dcsrilu02 :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
dcsrilu02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  dcsrilu02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 247 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE ccsrilu02 #-}
ccsrilu02 :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
ccsrilu02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  ccsrilu02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 250 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zcsrilu02 #-}
zcsrilu02 :: (Handle) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info_csrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
zcsrilu02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useInfo_csrilu02 a8} in 
  let {a9' = cFromEnum a9} in 
  let {a10' = useDevP a10} in 
  zcsrilu02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 253 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE xcsrilu02_zeroPivot #-}
xcsrilu02_zeroPivot :: (Handle) -> (Info_csrilu02) -> (Ptr Int32) -> IO ()
xcsrilu02_zeroPivot a1 a2 a3 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_csrilu02 a2} in 
  let {a3' = castPtr a3} in 
  xcsrilu02_zeroPivot'_ a1' a2' a3' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 256 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sbsric02_bufferSize #-}
sbsric02_bufferSize :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> IO ((Int))
sbsric02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  alloca $ \a11' -> 
  sbsric02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  checkStatus res >> 
  peekIntConv  a11'>>= \a11'' -> 
  return (a11'')

{-# LINE 259 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dbsric02_bufferSize #-}
dbsric02_bufferSize :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> IO ((Int))
dbsric02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  alloca $ \a11' -> 
  dbsric02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  checkStatus res >> 
  peekIntConv  a11'>>= \a11'' -> 
  return (a11'')

{-# LINE 262 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cbsric02_bufferSize #-}
cbsric02_bufferSize :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> IO ((Int))
cbsric02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  alloca $ \a11' -> 
  cbsric02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  checkStatus res >> 
  peekIntConv  a11'>>= \a11'' -> 
  return (a11'')

{-# LINE 265 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zbsric02_bufferSize #-}
zbsric02_bufferSize :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> IO ((Int))
zbsric02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  alloca $ \a11' -> 
  zbsric02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  checkStatus res >> 
  peekIntConv  a11'>>= \a11'' -> 
  return (a11'')

{-# LINE 268 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sbsric02_analysis #-}
sbsric02_analysis :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> (Policy) -> (DevicePtr ()) -> IO ()
sbsric02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  sbsric02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 271 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dbsric02_analysis #-}
dbsric02_analysis :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> (Policy) -> (DevicePtr ()) -> IO ()
dbsric02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  dbsric02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 274 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cbsric02_analysis #-}
cbsric02_analysis :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> (Policy) -> (DevicePtr ()) -> IO ()
cbsric02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  cbsric02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 277 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zbsric02_analysis #-}
zbsric02_analysis :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> (Policy) -> (DevicePtr ()) -> IO ()
zbsric02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  zbsric02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 280 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sbsric02 #-}
sbsric02 :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> (Policy) -> (DevicePtr ()) -> IO ()
sbsric02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  sbsric02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 283 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dbsric02 #-}
dbsric02 :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> (Policy) -> (DevicePtr ()) -> IO ()
dbsric02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  dbsric02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 286 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cbsric02 #-}
cbsric02 :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> (Policy) -> (DevicePtr ()) -> IO ()
cbsric02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  cbsric02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 289 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zbsric02 #-}
zbsric02 :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsric02) -> (Policy) -> (DevicePtr ()) -> IO ()
zbsric02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsric02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  zbsric02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 292 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE xbsric02_zeroPivot #-}
xbsric02_zeroPivot :: (Handle) -> (Info_bsric02) -> (Ptr Int32) -> IO ()
xbsric02_zeroPivot a1 a2 a3 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_bsric02 a2} in 
  let {a3' = castPtr a3} in 
  xbsric02_zeroPivot'_ a1' a2' a3' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 295 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sbsrilu02_numericBoost #-}
sbsrilu02_numericBoost :: (Handle) -> (Info_bsrilu02) -> (Int) -> (Ptr Double) -> (Ptr Float) -> IO ()
sbsrilu02_numericBoost a1 a2 a3 a4 a5 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_bsrilu02 a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = castPtr a4} in 
  let {a5' = castPtr a5} in 
  sbsrilu02_numericBoost'_ a1' a2' a3' a4' a5' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 298 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dbsrilu02_numericBoost #-}
dbsrilu02_numericBoost :: (Handle) -> (Info_bsrilu02) -> (Int) -> (Ptr Double) -> (Ptr Double) -> IO ()
dbsrilu02_numericBoost a1 a2 a3 a4 a5 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_bsrilu02 a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = castPtr a4} in 
  let {a5' = castPtr a5} in 
  dbsrilu02_numericBoost'_ a1' a2' a3' a4' a5' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 301 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cbsrilu02_numericBoost #-}
cbsrilu02_numericBoost :: (Handle) -> (Info_bsrilu02) -> (Int) -> (Ptr Double) -> (Ptr (Complex Float)) -> IO ()
cbsrilu02_numericBoost a1 a2 a3 a4 a5 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_bsrilu02 a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = castPtr a4} in 
  let {a5' = castPtr a5} in 
  cbsrilu02_numericBoost'_ a1' a2' a3' a4' a5' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 304 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zbsrilu02_numericBoost #-}
zbsrilu02_numericBoost :: (Handle) -> (Info_bsrilu02) -> (Int) -> (Ptr Double) -> (Ptr (Complex Double)) -> IO ()
zbsrilu02_numericBoost a1 a2 a3 a4 a5 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_bsrilu02 a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = castPtr a4} in 
  let {a5' = castPtr a5} in 
  zbsrilu02_numericBoost'_ a1' a2' a3' a4' a5' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 307 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sbsrilu02_bufferSize #-}
sbsrilu02_bufferSize :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> IO ((Int))
sbsrilu02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  alloca $ \a11' -> 
  sbsrilu02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  checkStatus res >> 
  peekIntConv  a11'>>= \a11'' -> 
  return (a11'')

{-# LINE 310 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dbsrilu02_bufferSize #-}
dbsrilu02_bufferSize :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> IO ((Int))
dbsrilu02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  alloca $ \a11' -> 
  dbsrilu02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  checkStatus res >> 
  peekIntConv  a11'>>= \a11'' -> 
  return (a11'')

{-# LINE 313 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cbsrilu02_bufferSize #-}
cbsrilu02_bufferSize :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> IO ((Int))
cbsrilu02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  alloca $ \a11' -> 
  cbsrilu02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  checkStatus res >> 
  peekIntConv  a11'>>= \a11'' -> 
  return (a11'')

{-# LINE 316 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zbsrilu02_bufferSize #-}
zbsrilu02_bufferSize :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> IO ((Int))
zbsrilu02_bufferSize a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  alloca $ \a11' -> 
  zbsrilu02_bufferSize'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  checkStatus res >> 
  peekIntConv  a11'>>= \a11'' -> 
  return (a11'')

{-# LINE 319 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sbsrilu02_analysis #-}
sbsrilu02_analysis :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
sbsrilu02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  sbsrilu02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 322 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dbsrilu02_analysis #-}
dbsrilu02_analysis :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
dbsrilu02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  dbsrilu02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 325 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cbsrilu02_analysis #-}
cbsrilu02_analysis :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
cbsrilu02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  cbsrilu02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 328 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zbsrilu02_analysis #-}
zbsrilu02_analysis :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
zbsrilu02_analysis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  zbsrilu02_analysis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 331 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sbsrilu02 #-}
sbsrilu02 :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Float) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
sbsrilu02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  sbsrilu02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 334 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dbsrilu02 #-}
dbsrilu02 :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr Double) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
dbsrilu02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  dbsrilu02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 337 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cbsrilu02 #-}
cbsrilu02 :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Float)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
cbsrilu02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  cbsrilu02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 340 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zbsrilu02 #-}
zbsrilu02 :: (Handle) -> (Direction) -> (Int) -> (Int) -> (MatrixDescriptor) -> (DevicePtr (Complex Double)) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Int) -> (Info_bsrilu02) -> (Policy) -> (DevicePtr ()) -> IO ()
zbsrilu02 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = useMatDescr a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = fromIntegral a9} in 
  let {a10' = useInfo_bsrilu02 a10} in 
  let {a11' = cFromEnum a11} in 
  let {a12' = useDevP a12} in 
  zbsrilu02'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 343 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE xbsrilu02_zeroPivot #-}
xbsrilu02_zeroPivot :: (Handle) -> (Info_bsrilu02) -> (Ptr Int32) -> IO ()
xbsrilu02_zeroPivot a1 a2 a3 =
  let {a1' = useHandle a1} in 
  let {a2' = useInfo_bsrilu02 a2} in 
  let {a3' = castPtr a3} in 
  xbsrilu02_zeroPivot'_ a1' a2' a3' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 346 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sgtsv #-}
sgtsv :: (Handle) -> (Int) -> (Int) -> (DevicePtr Float) -> (DevicePtr Float) -> (DevicePtr Float) -> (DevicePtr Float) -> (Int) -> IO ()
sgtsv a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = fromIntegral a8} in 
  sgtsv'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 349 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dgtsv #-}
dgtsv :: (Handle) -> (Int) -> (Int) -> (DevicePtr Double) -> (DevicePtr Double) -> (DevicePtr Double) -> (DevicePtr Double) -> (Int) -> IO ()
dgtsv a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = fromIntegral a8} in 
  dgtsv'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 352 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cgtsv #-}
cgtsv :: (Handle) -> (Int) -> (Int) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (Int) -> IO ()
cgtsv a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = fromIntegral a8} in 
  cgtsv'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 355 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zgtsv #-}
zgtsv :: (Handle) -> (Int) -> (Int) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (Int) -> IO ()
zgtsv a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = fromIntegral a8} in 
  zgtsv'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 358 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sgtsv_nopivot #-}
sgtsv_nopivot :: (Handle) -> (Int) -> (Int) -> (DevicePtr Float) -> (DevicePtr Float) -> (DevicePtr Float) -> (DevicePtr Float) -> (Int) -> IO ()
sgtsv_nopivot a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = fromIntegral a8} in 
  sgtsv_nopivot'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 361 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dgtsv_nopivot #-}
dgtsv_nopivot :: (Handle) -> (Int) -> (Int) -> (DevicePtr Double) -> (DevicePtr Double) -> (DevicePtr Double) -> (DevicePtr Double) -> (Int) -> IO ()
dgtsv_nopivot a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = fromIntegral a8} in 
  dgtsv_nopivot'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 364 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cgtsv_nopivot #-}
cgtsv_nopivot :: (Handle) -> (Int) -> (Int) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (Int) -> IO ()
cgtsv_nopivot a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = fromIntegral a8} in 
  cgtsv_nopivot'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 367 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zgtsv_nopivot #-}
zgtsv_nopivot :: (Handle) -> (Int) -> (Int) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (Int) -> IO ()
zgtsv_nopivot a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = fromIntegral a8} in 
  zgtsv_nopivot'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 370 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE sgtsvStridedBatch #-}
sgtsvStridedBatch :: (Handle) -> (Int) -> (DevicePtr Float) -> (DevicePtr Float) -> (DevicePtr Float) -> (DevicePtr Float) -> (Int) -> (Int) -> IO ()
sgtsvStridedBatch a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = useDevP a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = fromIntegral a7} in 
  let {a8' = fromIntegral a8} in 
  sgtsvStridedBatch'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 373 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE dgtsvStridedBatch #-}
dgtsvStridedBatch :: (Handle) -> (Int) -> (DevicePtr Double) -> (DevicePtr Double) -> (DevicePtr Double) -> (DevicePtr Double) -> (Int) -> (Int) -> IO ()
dgtsvStridedBatch a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = useDevP a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = fromIntegral a7} in 
  let {a8' = fromIntegral a8} in 
  dgtsvStridedBatch'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 376 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE cgtsvStridedBatch #-}
cgtsvStridedBatch :: (Handle) -> (Int) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (DevicePtr (Complex Float)) -> (Int) -> (Int) -> IO ()
cgtsvStridedBatch a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = useDevP a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = fromIntegral a7} in 
  let {a8' = fromIntegral a8} in 
  cgtsvStridedBatch'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 379 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE zgtsvStridedBatch #-}
zgtsvStridedBatch :: (Handle) -> (Int) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (DevicePtr (Complex Double)) -> (Int) -> (Int) -> IO ()
zgtsvStridedBatch a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = useHandle a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = useDevP a3} in 
  let {a4' = useDevP a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = useDevP a6} in 
  let {a7' = fromIntegral a7} in 
  let {a8' = fromIntegral a8} in 
  zgtsvStridedBatch'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 383 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


{-# INLINEABLE csrilu0Ex #-}
csrilu0Ex :: (Handle) -> (Operation) -> (Int) -> (MatrixDescriptor) -> (DevicePtr ()) -> (Type) -> (DevicePtr Int32) -> (DevicePtr Int32) -> (Info) -> (Type) -> IO ()
csrilu0Ex a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  let {a1' = useHandle a1} in 
  let {a2' = cFromEnum a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = useMatDescr a4} in 
  let {a5' = useDevP a5} in 
  let {a6' = cFromEnum a6} in 
  let {a7' = useDevP a7} in 
  let {a8' = useDevP a8} in 
  let {a9' = useInfo a9} in 
  let {a10' = cFromEnum a10} in 
  csrilu0Ex'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 391 "./Foreign/CUDA/BLAS/Sparse/Precondition.chs" #-}


foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsric0"
  scsric0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsric0"
  dcsric0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsric0"
  ccsric0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsric0"
  zcsric0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsric02_bufferSize"
  scsric02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsric02_bufferSize"
  dcsric02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsric02_bufferSize"
  ccsric02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsric02_bufferSize"
  zcsric02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsric02_analysis"
  scsric02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsric02_analysis"
  dcsric02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsric02_analysis"
  ccsric02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsric02_analysis"
  zcsric02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsric02"
  scsric02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsric02"
  dcsric02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsric02"
  ccsric02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsric02"
  zcsric02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseXcsric02_zeroPivot"
  xcsric02_zeroPivot'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsrilu0"
  scsrilu0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsrilu0"
  dcsrilu0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsrilu0"
  ccsrilu0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsrilu0"
  zcsrilu0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsrilu02_numericBoost"
  scsrilu02_numericBoost'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsrilu02_numericBoost"
  dcsrilu02_numericBoost'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CInt))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsrilu02_numericBoost"
  ccsrilu02_numericBoost'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsrilu02_numericBoost"
  zcsrilu02_numericBoost'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsrilu02_bufferSize"
  scsrilu02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsrilu02_bufferSize"
  dcsrilu02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsrilu02_bufferSize"
  ccsrilu02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsrilu02_bufferSize"
  zcsrilu02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsrilu02_analysis"
  scsrilu02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsrilu02_analysis"
  dcsrilu02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsrilu02_analysis"
  ccsrilu02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsrilu02_analysis"
  zcsrilu02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseScsrilu02"
  scsrilu02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDcsrilu02"
  dcsrilu02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCcsrilu02"
  ccsrilu02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZcsrilu02"
  zcsrilu02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseXcsrilu02_zeroPivot"
  xcsrilu02_zeroPivot'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSbsric02_bufferSize"
  sbsric02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDbsric02_bufferSize"
  dbsric02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCbsric02_bufferSize"
  cbsric02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZbsric02_bufferSize"
  zbsric02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSbsric02_analysis"
  sbsric02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDbsric02_analysis"
  dbsric02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCbsric02_analysis"
  cbsric02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZbsric02_analysis"
  zbsric02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSbsric02"
  sbsric02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDbsric02"
  dbsric02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCbsric02"
  cbsric02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZbsric02"
  zbsric02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseXbsric02_zeroPivot"
  xbsric02_zeroPivot'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSbsrilu02_numericBoost"
  sbsrilu02_numericBoost'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDbsrilu02_numericBoost"
  dbsrilu02_numericBoost'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CInt))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCbsrilu02_numericBoost"
  cbsrilu02_numericBoost'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZbsrilu02_numericBoost"
  zbsrilu02_numericBoost'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSbsrilu02_bufferSize"
  sbsrilu02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDbsrilu02_bufferSize"
  dbsrilu02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCbsrilu02_bufferSize"
  cbsrilu02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZbsrilu02_bufferSize"
  zbsrilu02_bufferSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSbsrilu02_analysis"
  sbsrilu02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDbsrilu02_analysis"
  dbsrilu02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCbsrilu02_analysis"
  cbsrilu02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZbsrilu02_analysis"
  zbsrilu02_analysis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSbsrilu02"
  sbsrilu02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDbsrilu02"
  dbsrilu02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCbsrilu02"
  cbsrilu02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZbsrilu02"
  zbsrilu02'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseXbsrilu02_zeroPivot"
  xbsrilu02_zeroPivot'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSgtsv"
  sgtsv'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDgtsv"
  dgtsv'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCgtsv"
  cgtsv'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZgtsv"
  zgtsv'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSgtsv_nopivot"
  sgtsv_nopivot'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDgtsv_nopivot"
  dgtsv_nopivot'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCgtsv_nopivot"
  cgtsv_nopivot'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZgtsv_nopivot"
  zgtsv_nopivot'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseSgtsvStridedBatch"
  sgtsvStridedBatch'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseDgtsvStridedBatch"
  dgtsvStridedBatch'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCgtsvStridedBatch"
  cgtsvStridedBatch'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseZgtsvStridedBatch"
  zgtsvStridedBatch'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Sparse/Precondition.chs.h cusparseCsrilu0Ex"
  csrilu0Ex'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))))))