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


{-# LINE 1 "src/Foreign/CUDA/Driver/Texture.chs" #-}
{-# LANGUAGE BangPatterns             #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# OPTIONS_HADDOCK prune #-}
--------------------------------------------------------------------------------
-- |
-- Module    : Foreign.CUDA.Driver.Texture
-- Copyright : [2009..2018] Trevor L. McDonell
-- License   : BSD
--
-- Texture management for low-level driver interface
--
--------------------------------------------------------------------------------

module Foreign.CUDA.Driver.Texture (

  -- * Texture Reference Management
  Texture(..), Format(..), AddressMode(..), FilterMode(..), ReadMode(..),
  bind, bind2D,
  getAddressMode, getFilterMode, getFormat,
  setAddressMode, setFilterMode, setFormat, setReadMode,

  -- Deprecated
  create, destroy,

  -- Internal
  peekTex

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





{-# LINE 31 "src/Foreign/CUDA/Driver/Texture.chs" #-}


-- Friends
import Foreign.CUDA.Ptr
import Foreign.CUDA.Driver.Error
import Foreign.CUDA.Driver.Marshal
import Foreign.CUDA.Internal.C2HS

-- System
import Foreign
import Foreign.C
import Control.Monad

{-# DEPRECATED create, destroy "as of CUDA version 3.2" #-}


--------------------------------------------------------------------------------
-- Data Types
--------------------------------------------------------------------------------

-- |
-- A texture reference
--
newtype Texture = Texture { Texture -> Ptr ()
useTexture :: ((C2HSImp.Ptr ()))}
  deriving (Texture -> Texture -> Bool
(Texture -> Texture -> Bool)
-> (Texture -> Texture -> Bool) -> Eq Texture
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Texture -> Texture -> Bool
$c/= :: Texture -> Texture -> Bool
== :: Texture -> Texture -> Bool
$c== :: Texture -> Texture -> Bool
Eq, Int -> Texture -> ShowS
[Texture] -> ShowS
Texture -> String
(Int -> Texture -> ShowS)
-> (Texture -> String) -> ([Texture] -> ShowS) -> Show Texture
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Texture] -> ShowS
$cshowList :: [Texture] -> ShowS
show :: Texture -> String
$cshow :: Texture -> String
showsPrec :: Int -> Texture -> ShowS
$cshowsPrec :: Int -> Texture -> ShowS
Show)

instance Storable Texture where
  sizeOf :: Texture -> Int
sizeOf Texture
_    = Ptr () -> Int
forall a. Storable a => a -> Int
sizeOf    (Ptr ()
forall a. HasCallStack => a
undefined :: ((C2HSImp.Ptr ())))
  alignment :: Texture -> Int
alignment Texture
_ = Ptr () -> Int
forall a. Storable a => a -> Int
alignment (Ptr ()
forall a. HasCallStack => a
undefined :: ((C2HSImp.Ptr ())))
  peek :: Ptr Texture -> IO Texture
peek Ptr Texture
p      = Ptr () -> Texture
Texture (Ptr () -> Texture) -> IO (Ptr ()) -> IO Texture
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr Texture -> Ptr (Ptr ())
forall a b. Ptr a -> Ptr b
castPtr Ptr Texture
p)
  poke :: Ptr Texture -> Texture -> IO ()
poke Ptr Texture
p Texture
t    = Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Texture -> Ptr (Ptr ())
forall a b. Ptr a -> Ptr b
castPtr Ptr Texture
p) (Texture -> Ptr ()
useTexture Texture
t)

-- |
-- Texture reference addressing modes
--
data AddressMode = Wrap
                 | Clamp
                 | Mirror
                 | Border
  deriving (AddressMode -> AddressMode -> Bool
(AddressMode -> AddressMode -> Bool)
-> (AddressMode -> AddressMode -> Bool) -> Eq AddressMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressMode -> AddressMode -> Bool
$c/= :: AddressMode -> AddressMode -> Bool
== :: AddressMode -> AddressMode -> Bool
$c== :: AddressMode -> AddressMode -> Bool
Eq,Int -> AddressMode -> ShowS
[AddressMode] -> ShowS
AddressMode -> String
(Int -> AddressMode -> ShowS)
-> (AddressMode -> String)
-> ([AddressMode] -> ShowS)
-> Show AddressMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressMode] -> ShowS
$cshowList :: [AddressMode] -> ShowS
show :: AddressMode -> String
$cshow :: AddressMode -> String
showsPrec :: Int -> AddressMode -> ShowS
$cshowsPrec :: Int -> AddressMode -> ShowS
Show)
instance Enum AddressMode where
  succ :: AddressMode -> AddressMode
succ AddressMode
Wrap = AddressMode
Clamp
  succ AddressMode
Clamp = AddressMode
Mirror
  succ AddressMode
Mirror = AddressMode
Border
  succ AddressMode
Border = String -> AddressMode
forall a. HasCallStack => String -> a
error String
"AddressMode.succ: Border has no successor"

  pred :: AddressMode -> AddressMode
pred AddressMode
Clamp = AddressMode
Int -> FilterMode -> ShowS
[FilterMode] -> ShowS
FilterMode -> String
(Int -> FilterMode -> ShowS)
-> (FilterMode -> String)
-> ([FilterMode] -> ShowS)
-> Show FilterMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilterMode] -> ShowS
$cshowList :: [FilterMode] -> ShowS
show :: FilterMode -> String
$cshow :: FilterMode -> String
showsPrec :: Int -> FilterMode -> ShowS
$cshowsPrec :: Int -> FilterMode -> ShowS
Wrap
  pred AddressMode
Mirror = AddressMode
Clamp
  pred AddressMode
Border = AddressMode
Mirror
  pred AddressMode
Wrap = String -> AddressMode
forall a. HasCallStack => String -> a
error String
"AddressMode.pred: Wrap has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from Border

  fromEnum :: AddressMode -> Int
fromEnum AddressMode
Wrap = Int
0
  enumFrom :: FilterMode -> [FilterMode]
fromEnum AddressMode
Clamp = Int
1
  fromEnum AddressMode
Mirror = Int
2
  fromEnum AddressMode
Border = Int
3

  toEnum 0 = Wrap
  toEnum 1 = Clamp
  toEnum 2 = Mirror
  toEnum 3 = Border
  toEnum unmatched = error ("AddressMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 70 "src/Foreign/CUDA/Driver/Texture.chs" #-}


-- |
-- Texture reference filtering mode
--
data FilterMode = Point
                | Linear
  deriving (Eq,Show)
instance Enum FilterMode where
  succ Point = Linear
  succ Linear = error "FilterMode.succ: Linear has no successor"

  pred Linear = Point
  pred Point = error "FilterMode.pred: Point has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from Linear

  fromEnum Point = 0
  fromEnum Linear = 1

  toEnum 0 = Point
  toEnum 1 = Linear
  toEnum unmatched = error ("FilterMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 77 "src/Foreign/CUDA/Driver/Texture.chs" #-}


-- |
-- Texture read mode options
--
data ReadMode = ReadAsInteger
              | NormalizedCoordinates
              | SRGB
  deriving (Eq,Show)
instance Enum ReadMode where
  succ ReadAsInteger = NormalizedCoordinates
  succ NormalizedCoordinates = SRGB
  succ SRGB = error "ReadMode.succ: SRGB has no successor"

  pred NormalizedCoordinates = ReadAsInteger
  pred SRGB = NormalizedCoordinates
  pred ReadAsInteger = error "ReadMode.pred: ReadAsInteger has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from SRGB

  fromEnum :: ReadMode -> Int
fromEnum ReadMode
ReadAsInteger = Int
1
  fromEnum ReadMode
NormalizedCoordinates = Int
2
  fromEnum ReadMode
SRGB = Int
16

  toEnum :: Int -> ReadMode
toEnum Int
1 = ReadMode
ReadAsInteger
  toEnum 2 = ReadMode
NormalizedCoordinates
  toEnum 16 = ReadMode
SRGB
  toEnum unmatched = String -> ReadMode
forall a. HasCallStack => String -> a
error (String
"ReadMode.toEnum: Cannot match " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
unmatched)

{-# LINE 92 "src/Foreign/CUDA/Driver/Texture.chs" #-}


-- |
-- Texture data formats
--
data Format = Word8
            | Word16
            | Word32
            | Int8
            | Int16
            | Int32
            | Half
            | Float
  deriving (Eq,Show)
instance Enum Format where
  succ Word8 = Word16
  succ Word16 = Word32
  succ Word32 = Int8
  succ Int8 = Int16
  succ Int16 = Int32
  succ Int32 = Half
  succ Half = Float
  succ Float = error "Format.succ: Float has no successor"

  pred :: Format -> Format
pred Format
Word16 = Format
Word8
  pred Format
Word32 = Format
Word16
  pred Format
Int8 = Format
Word32
  pred Format
Int16 = Format
Int8
  pred Int32 = Int16
  pred Half = Int32
  pred Float = Half
  pred Format
Word8 = String -> Format
forall a. HasCallStack => String -> a
error String
"Format.pred: Word8 has no predecessor"

  enumFromTo :: Format -> Format -> [Format]
enumFromTo Format
from Format
to = Format -> [Format]
forall t. Enum t => t -> [t]
go Format
from
    where
      end :: Int
end = Format -> Int
forall a. Enum a => a -> Int
fromEnum Format
to
      go :: t -> [t]
go t
v = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (t -> Int
forall a. Enum a => a -> Int
fromEnum t
v) Int
end of
                 Ordering
LT -> t
v t -> [t] -> [t]
forall a. a -> [a] -> [a]
: t -> [t]
go (t -> t
forall a. Enum a => a -> a
succ t
v)
                 Ordering
EQ -> [t
v]
                 Ordering
GT -> []

  enumFrom :: Format -> [Format]
enumFrom Format
from = Format -> Format -> [Format]
forall a. Enum a => a -> a -> [a]
enumFromTo Format
from Format
Float

  fromEnum :: Format -> Int
fromEnum Format
Word8 = Int
1
  fromEnum Word16 = 2
  fromEnum Format
Word32 = Int
3
  fromEnum Int8 = 8
  fromEnum Int16 = 9
  fromEnum Format
Int32 = Int
10
  fromEnum Format
Half = Int
16
  fromEnum Format
Float = Int
32

  toEnum 1 = Word8
  toEnum 2 = Word16
  toEnum 3 = Word32
  toEnum 8 = Int8
  toEnum 9 = Int16
  toEnum 10 = Int32
  toEnum 16 = Half
  toEnum 32 = Float
  toEnum unmatched = error ("Format.toEnum: Cannot match " ++ show unmatched)

{-# LINE 105 "src/Foreign/CUDA/Driver/Texture.chs" #-}



--------------------------------------------------------------------------------
-- Texture management
--------------------------------------------------------------------------------

-- |
-- Create a new texture reference. Once created, the application must call
-- 'setPtr' to associate the reference with allocated memory. Other texture
-- reference functions are used to specify the format and interpretation to be
-- used when the memory is read through this reference.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF__DEPRECATED.html#group__CUDA__TEXREF__DEPRECATED_1g0084fabe2c6d28ffcf9d9f5c7164f16c>
--
{-# INLINEABLE create #-}
create :: IO Texture
create = resultIfOk =<< cuTexRefCreate

{-# INLINE cuTexRefCreate #-}
cuTexRefCreate :: IO ((Status), (Texture))
cuTexRefCreate =
  alloca $ \a1' -> 
  cuTexRefCreate'_ a1' >>= \res ->
  let {res' = cToEnum res} in
  peekTex  a1'>>= \a1'' -> 
  return (res', a1'')

{-# LINE 126 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Destroy a texture reference.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF__DEPRECATED.html#group__CUDA__TEXREF__DEPRECATED_1gea8edbd6cf9f97e6ab2b41fc6785519d>
--
{-# INLINEABLE destroy #-}
destroy :: Texture -> IO ()
destroy !tex = nothingIfOk =<< cuTexRefDestroy tex

{-# INLINE cuTexRefDestroy #-}
cuTexRefDestroy :: (Texture) -> IO ((Status))
cuTexRefDestroy a1 =
  let {a1' = useTexture a1} in 
  cuTexRefDestroy'_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 140 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Bind a linear array address of the given size (bytes) as a texture
-- reference. Any previously bound references are unbound.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1g44ef7e5055192d52b3d43456602b50a8>
--
{-# INLINEABLE bind #-}
bind :: Texture -> DevicePtr a -> Int64 -> IO ()
bind !tex !dptr !bytes = nothingIfOk =<< cuTexRefSetAddress tex dptr bytes

{-# INLINE cuTexRefSetAddress #-}
cuTexRefSetAddress :: (Texture) -> (DevicePtr a) -> (Int64) -> IO ((Status))
cuTexRefSetAddress :: Texture -> DevicePtr a -> Int64 -> IO Status
cuTexRefSetAddress Texture
a2 DevicePtr a
a3 Int64
a4 =
  (Ptr CULong -> IO Status) -> IO Status
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CULong -> IO Status) -> IO Status)
-> (Ptr CULong -> IO Status) -> IO Status
forall a b. (a -> b) -> a -> b
$ \Ptr CULong
a1' -> 
  let {a2' :: Ptr ()
a2' = Texture -> Ptr ()
useTexture Texture
a2} in 
  let {a3' :: DeviceHandle
a3' = DevicePtr a -> DeviceHandle
forall a. DevicePtr a -> DeviceHandle
useDeviceHandle DevicePtr a
a3} in 
  let {a4' :: CULong
a4' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a4} in 
  Ptr CULong -> Ptr () -> DeviceHandle -> CULong -> IO CInt
cuTexRefSetAddress'_ Ptr CULong
a1' Ptr ()
a2' DeviceHandle
a3' CULong
a4' IO CInt -> (CInt -> IO Status) -> IO Status
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Status -> IO Status
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res')

{-# LINE 158 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Bind a linear address range to the given texture reference as a
-- two-dimensional arena. Any previously bound reference is unbound. Note that
-- calls to 'setFormat' can not follow a call to 'bind2D' for the same texture
-- reference.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1g26f709bbe10516681913d1ffe8756ee2>
--
{-# INLINEABLE bind2D #-}
bind2D :: Texture -> Format -> Int -> DevicePtr a -> (Int,Int) -> Int64 -> IO ()
bind2D :: Texture
-> Format -> Int -> DevicePtr a -> (Int, Int) -> Int64 -> IO ()
bind2D !Texture
tex !Format
fmt !Int
chn !DevicePtr a
dptr (!Int
width,!Int
height) !Int64
pitch =
  Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Texture
-> Format -> Int -> DevicePtr a -> Int -> Int -> Int64 -> IO Status
forall a.
Texture
-> Format -> Int -> DevicePtr a -> Int -> Int -> Int64 -> IO Status
cuTexRefSetAddress2D_simple Texture
tex Format
fmt Int
chn DevicePtr a
dptr Int
width Int
height Int64
pitch

{-# INLINE cuTexRefSetAddress2D_simple #-}
cuTexRefSetAddress2D_simple :: (Texture) -> (Format) -> (Int) -> (DevicePtr a) -> (Int) -> (Int) -> (Int64) -> IO ((Status))
cuTexRefSetAddress2D_simple :: Texture
-> Format -> Int -> DevicePtr a -> Int -> Int -> Int64 -> IO Status
cuTexRefSetAddress2D_simple Texture
a1 Format
a2 Int
a3 DevicePtr a
a4 Int
a5 Int
a6 Int64
a7 =
  let {a1' :: Ptr ()
a1' = Texture -> Ptr ()
useTexture Texture
a1} in 
  let {a2' :: CInt
a2' = Format -> CInt
forall e i. (Enum e, Integral i) => e -> i
cFromEnum Format
a2} in 
  let {a3' :: CUInt
a3' = Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a3} in 
  let {a4' :: DeviceHandle
a4' = DevicePtr a -> DeviceHandle
forall a. DevicePtr a -> DeviceHandle
useDeviceHandle DevicePtr a
a4} in 
  let {a5' :: CULong
a5' = Int -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a5} in 
  let {a6' :: CULong
a6' = Int -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a6} in 
  let {a7' :: CULong
a7' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a7} in 
  Ptr ()
-> CInt
-> CUInt
-> DeviceHandle
-> CULong
-> CULong
-> CULong
-> IO CInt
cuTexRefSetAddress2D_simple'_ Ptr ()
a1' CInt
a2' CUInt
a3' DeviceHandle
a4' CULong
a5' CULong
a6' CULong
a7' IO CInt -> (CInt -> IO Status) -> IO Status
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Status -> IO Status
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res')

{-# LINE 182 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Get the addressing mode used by a texture reference, corresponding to the
-- given dimension (currently the only supported dimension values are 0 or 1).
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1gfb367d93dc1d20aab0cf8ce70d543b33>
--
{-# INLINEABLE getAddressMode #-}
getAddressMode :: Texture -> Int -> IO AddressMode
getAddressMode :: Texture -> Int -> IO AddressMode
getAddressMode !Texture
tex !Int
dim = (Status, AddressMode) -> IO AddressMode
forall a. (Status, a) -> IO a
resultIfOk ((Status, AddressMode) -> IO AddressMode)
-> IO (Status, AddressMode) -> IO AddressMode
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Texture -> Int -> IO (Status, AddressMode)
cuTexRefGetAddressMode Texture
tex Int
dim

{-# INLINE cuTexRefGetAddressMode #-}
cuTexRefGetAddressMode :: (Texture) -> (Int) -> IO ((Status), (AddressMode))
cuTexRefGetAddressMode :: Texture -> Int -> IO (Status, AddressMode)
cuTexRefGetAddressMode Texture
a2 Int
a3 =
  (Ptr CInt -> IO (Status, AddressMode)) -> IO (Status, AddressMode)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Status, AddressMode))
 -> IO (Status, AddressMode))
-> (Ptr CInt -> IO (Status, AddressMode))
-> IO (Status, AddressMode)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
a1' -> 
  let {a2' :: Ptr ()
a2' = Texture -> Ptr ()
useTexture Texture
a2} in 
  let {a3' :: CInt
a3' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a3} in 
  Ptr CInt -> Ptr () -> CInt -> IO CInt
cuTexRefGetAddressMode'_ Ptr CInt
a1' Ptr ()
a2' CInt
a3' IO CInt
-> (CInt -> IO (Status, AddressMode)) -> IO (Status, AddressMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Ptr CInt -> IO AddressMode
forall a b. (Enum a, Integral b, Storable b) => Ptr b -> IO a
peekEnum  Ptr CInt
a1'IO AddressMode
-> (AddressMode -> IO (Status, AddressMode))
-> IO (Status, AddressMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \AddressMode
a1'' -> 
  (Status, AddressMode) -> IO (Status, AddressMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res', AddressMode
a1'')

{-# LINE 199 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Get the filtering mode used by a texture reference.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1g2439e069746f69b940f2f4dbc78cdf87>
--
{-# INLINEABLE getFilterMode #-}
getFilterMode :: Texture -> IO FilterMode
getFilterMode :: Texture -> IO FilterMode
getFilterMode !Texture
tex = (Status, FilterMode) -> IO FilterMode
forall a. (Status, a) -> IO a
resultIfOk ((Status, FilterMode) -> IO FilterMode)
-> IO (Status, FilterMode) -> IO FilterMode
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Texture -> IO (Status, FilterMode)
cuTexRefGetFilterMode Texture
tex

{-# INLINE cuTexRefGetFilterMode #-}
cuTexRefGetFilterMode :: (Texture) -> IO ((Status), (FilterMode))
cuTexRefGetFilterMode :: Texture -> IO (Status, FilterMode)
cuTexRefGetFilterMode Texture
a2 =
  (Ptr CInt -> IO (Status, FilterMode)) -> IO (Status, FilterMode)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Status, FilterMode)) -> IO (Status, FilterMode))
-> (Ptr CInt -> IO (Status, FilterMode)) -> IO (Status, FilterMode)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
a1' -> 
  let {a2' :: Ptr ()
a2' = Texture -> Ptr ()
useTexture Texture
a2} in 
  Ptr CInt -> Ptr () -> IO CInt
cuTexRefGetFilterMode'_ Ptr CInt
a1' Ptr ()
a2' IO CInt
-> (CInt -> IO (Status, FilterMode)) -> IO (Status, FilterMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Ptr CInt -> IO FilterMode
forall a b. (Enum a, Integral b, Storable b) => Ptr b -> IO a
peekEnum  Ptr CInt
a1'IO FilterMode
-> (FilterMode -> IO (Status, FilterMode))
-> IO (Status, FilterMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \FilterMode
a1'' -> 
  (Status, FilterMode) -> IO (Status, FilterMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res', FilterMode
a1'')

{-# LINE 214 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Get the data format and number of channel components of the bound texture.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1g90936eb6c7c4434a609e1160c278ae53>
--
{-# INLINEABLE getFormat #-}
getFormat :: Texture -> IO (Format, Int)
getFormat :: Texture -> IO (Format, Int)
getFormat !Texture
tex = do
  (!Status
status,!Format
fmt,!Int
dim) <- Texture -> IO (Status, Format, Int)
cuTexRefGetFormat Texture
tex
  (Status, (Format, Int)) -> IO (Format, Int)
forall a. (Status, a) -> IO a
resultIfOk (Status
status,(Format
fmt,Int
dim))

{-# INLINE cuTexRefGetFormat #-}
cuTexRefGetFormat :: (Texture) -> IO ((Status), (Format), (Int))
cuTexRefGetFormat :: Texture -> IO (Status, Format, Int)
cuTexRefGetFormat Texture
a3 =
  (Ptr CInt -> IO (Status, Format, Int)) -> IO (Status, Format, Int)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Status, Format, Int))
 -> IO (Status, Format, Int))
-> (Ptr CInt -> IO (Status, Format, Int))
-> IO (Status, Format, Int)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
a1' -> 
  (Ptr CInt -> IO (Status, Format, Int)) -> IO (Status, Format, Int)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Status, Format, Int))
 -> IO (Status, Format, Int))
-> (Ptr CInt -> IO (Status, Format, Int))
-> IO (Status, Format, Int)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
a2' -> 
  let {a3' :: Ptr ()
a3' = Texture -> Ptr ()
useTexture Texture
a3} in 
  Ptr CInt -> Ptr CInt -> Ptr () -> IO CInt
cuTexRefGetFormat'_ Ptr CInt
a1' Ptr CInt
a2' Ptr ()
a3' IO CInt
-> (CInt -> IO (Status, Format, Int)) -> IO (Status, Format, Int)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Ptr CInt -> IO Format
forall a b. (Enum a, Integral b, Storable b) => Ptr b -> IO a
peekEnum  Ptr CInt
a1'IO Format
-> (Format -> IO (Status, Format, Int)) -> IO (Status, Format, Int)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Format
a1'' -> 
  Ptr CInt -> IO Int
forall a b. (Storable a, Integral a, Integral b) => Ptr a -> IO b
peekIntConv  Ptr CInt
a2'IO Int
-> (Int -> IO (Status, Format, Int)) -> IO (Status, Format, Int)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
a2'' -> 
  (Status, Format, Int) -> IO (Status, Format, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res', Format
a1'', Int
a2'')

{-# LINE 232 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Specify the addressing mode for the given dimension of a texture reference.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1g85f4a13eeb94c8072f61091489349bcb>
--
{-# INLINEABLE setAddressMode #-}
setAddressMode :: Texture -> Int -> AddressMode -> IO ()
setAddressMode :: Texture -> Int -> AddressMode -> IO ()
setAddressMode !Texture
tex !Int
dim !AddressMode
mode = Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Texture -> Int -> AddressMode -> IO Status
cuTexRefSetAddressMode Texture
tex Int
dim AddressMode
mode

{-# INLINE cuTexRefSetAddressMode #-}
cuTexRefSetAddressMode :: (Texture) -> (Int) -> (AddressMode) -> IO ((Status))
cuTexRefSetAddressMode :: Texture -> Int -> AddressMode -> IO Status
cuTexRefSetAddressMode Texture
a1 Int
a2 AddressMode
a3 =
  let {a1' :: Ptr ()
a1' = Texture -> Ptr ()
useTexture Texture
a1} in 
  let {a2' :: CInt
a2' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a2} in 
  let {a3' :: CInt
a3' = AddressMode -> CInt
forall e i. (Enum e, Integral i) => e -> i
cFromEnum AddressMode
a3} in 
  Ptr () -> CInt -> CInt -> IO CInt
cuTexRefSetAddressMode'_ Ptr ()
a1' CInt
a2' CInt
a3' IO CInt -> (CInt -> IO Status) -> IO Status
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Status -> IO Status
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res')

{-# LINE 248 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Specify the filtering mode to be used when reading memory through a texture
-- reference.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1g595d0af02c55576f8c835e4efd1f39c0>
--
{-# INLINEABLE setFilterMode #-}
setFilterMode :: Texture -> FilterMode -> IO ()
setFilterMode :: Texture -> FilterMode -> IO ()
setFilterMode !Texture
tex !FilterMode
mode = Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Texture -> FilterMode -> IO Status
cuTexRefSetFilterMode Texture
tex FilterMode
mode

{-# INLINE cuTexRefSetFilterMode #-}
cuTexRefSetFilterMode :: (Texture) -> (FilterMode) -> IO ((Status))
cuTexRefSetFilterMode :: Texture -> FilterMode -> IO Status
cuTexRefSetFilterMode Texture
a1 FilterMode
a2 =
  let {a1' :: Ptr ()
a1' = Texture -> Ptr ()
useTexture Texture
a1} in 
  let {a2' :: CInt
a2' = FilterMode -> CInt
forall e i. (Enum e, Integral i) => e -> i
cFromEnum FilterMode
a2} in 
  Ptr () -> CInt -> IO CInt
cuTexRefSetFilterMode'_ Ptr ()
a1' CInt
a2' IO CInt -> (CInt -> IO Status) -> IO Status
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Status -> IO Status
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res')

{-# LINE 264 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Specify additional characteristics for reading and indexing the texture
-- reference.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1g554ffd896487533c36810f2e45bb7a28>
--
{-# INLINEABLE setReadMode #-}
setReadMode :: Texture -> ReadMode -> IO ()
setReadMode :: Texture -> ReadMode -> IO ()
setReadMode !Texture
tex !ReadMode
mode = Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Texture -> ReadMode -> IO Status
cuTexRefSetFlags Texture
tex ReadMode
mode

{-# INLINE cuTexRefSetFlags #-}
cuTexRefSetFlags :: (Texture) -> (ReadMode) -> IO ((Status))
cuTexRefSetFlags :: Texture -> ReadMode -> IO Status
cuTexRefSetFlags Texture
a1 ReadMode
a2 =
  let {a1' :: Ptr ()
a1' = Texture -> Ptr ()
useTexture Texture
a1} in 
  let {a2' :: CUInt
a2' = ReadMode -> CUInt
forall e i. (Enum e, Integral i) => e -> i
cFromEnum ReadMode
a2} in 
  Ptr () -> CUInt -> IO CInt
cuTexRefSetFlags'_ Ptr ()
a1' CUInt
a2' IO CInt -> (CInt -> IO Status) -> IO Status
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Status -> IO Status
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res')

{-# LINE 280 "src/Foreign/CUDA/Driver/Texture.chs" #-}



-- |
-- Specify the format of the data and number of packed components per element to
-- be read by the texture reference.
--
-- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__TEXREF.html#group__CUDA__TEXREF_1g05585ef8ea2fec728a03c6c8f87cf07a>
--
{-# INLINEABLE setFormat #-}
setFormat :: Texture -> Format -> Int -> IO ()
setFormat :: Texture -> Format -> Int -> IO ()
setFormat !Texture
tex !Format
fmt !Int
chn = Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Texture -> Format -> Int -> IO Status
cuTexRefSetFormat Texture
tex Format
fmt Int
chn

{-# INLINE cuTexRefSetFormat #-}
cuTexRefSetFormat :: (Texture) -> (Format) -> (Int) -> IO ((Status))
cuTexRefSetFormat :: Texture -> Format -> Int -> IO Status
cuTexRefSetFormat Texture
a1 Format
a2 Int
a3 =
  let {a1' :: Ptr ()
a1' = Texture -> Ptr ()
useTexture Texture
a1} in 
  let {a2' :: CInt
a2' = Format -> CInt
forall e i. (Enum e, Integral i) => e -> i
cFromEnum Format
a2} in 
  let {a3' :: CInt
a3' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a3} in 
  Ptr () -> CInt -> CInt -> IO CInt
cuTexRefSetFormat'_ Ptr ()
a1' CInt
a2' CInt
a3' IO CInt -> (CInt -> IO Status) -> IO Status
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Status -> IO Status
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res')

{-# LINE 297 "src/Foreign/CUDA/Driver/Texture.chs" #-}



--------------------------------------------------------------------------------
-- Internal
--------------------------------------------------------------------------------

{-# INLINE peekTex #-}
peekTex :: Ptr ((C2HSImp.Ptr ())) -> IO Texture
peekTex :: Ptr (Ptr ()) -> IO Texture
peekTex = (Ptr () -> Texture) -> IO (Ptr ()) -> IO Texture
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Ptr () -> Texture
Texture (IO (Ptr ()) -> IO Texture)
-> (Ptr (Ptr ()) -> IO (Ptr ())) -> Ptr (Ptr ()) -> IO Texture
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek


foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefCreate"
  cuTexRefCreate'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefDestroy"
  cuTexRefDestroy'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefSetAddress"
  cuTexRefSetAddress'_ :: ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULLong -> (C2HSImp.CULong -> (IO C2HSImp.CInt)))))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefSetAddress2D_simple"
  cuTexRefSetAddress2D_simple'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (C2HSImp.CULLong -> (C2HSImp.CULong -> (C2HSImp.CULong -> (C2HSImp.CULong -> (IO C2HSImp.CInt))))))))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefGetAddressMode"
  cuTexRefGetAddressMode'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefGetFilterMode"
  cuTexRefGetFilterMode'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefGetFormat"
  cuTexRefGetFormat'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefSetAddressMode"
  cuTexRefSetAddressMode'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefSetFilterMode"
  cuTexRefSetFilterMode'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefSetFlags"
  cuTexRefSetFlags'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/Driver/Texture.chs.h cuTexRefSetFormat"
  cuTexRefSetFormat'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))