-- 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/Runtime/Marshal.chs" #-}
{-# LANGUAGE BangPatterns             #-}
{-# LANGUAGE EmptyDataDecls           #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TemplateHaskell          #-}
--------------------------------------------------------------------------------
-- |
-- Module    : Foreign.CUDA.Runtime.Marshal
-- Copyright : [2009..2018] Trevor L. McDonell
-- License   : BSD
--
-- Memory management for CUDA devices
--
--------------------------------------------------------------------------------

module Foreign.CUDA.Runtime.Marshal (

  -- * Host Allocation
  AllocFlag(..),
  mallocHostArray, freeHost,

  -- * Device Allocation
  mallocArray, allocaArray, free,

  -- * Unified Memory Allocation
  AttachFlag(..),
  mallocManagedArray,

  -- * Marshalling
  peekArray, peekArrayAsync, peekArray2D, peekArray2DAsync, peekListArray,
  pokeArray, pokeArrayAsync, pokeArray2D, pokeArray2DAsync, pokeListArray,
  copyArray, copyArrayAsync, copyArray2D, copyArray2DAsync,

  -- * Combined Allocation and Marshalling
  newListArray,  newListArrayLen,
  withListArray, withListArrayLen,

  -- * Utility
  memset

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





{-# LINE 43 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}


-- Friends
import Foreign.CUDA.Ptr
import Foreign.CUDA.Runtime.Error
import Foreign.CUDA.Runtime.Stream
import Foreign.CUDA.Internal.C2HS

-- System
import Data.Int
import Data.Maybe
import Control.Exception

import Foreign.C
import Foreign.Ptr
import Foreign.Storable
import qualified Foreign.Marshal as F





--------------------------------------------------------------------------------
-- Host Allocation
--------------------------------------------------------------------------------

-- |
-- Options for host allocation
--
data AllocFlag = Portable
               | DeviceMapped
               | WriteCombined
  deriving (AllocFlag -> AllocFlag -> Bool
(AllocFlag -> AllocFlag -> Bool)
-> (AllocFlag -> AllocFlag -> Bool) -> Eq AllocFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AllocFlag -> AllocFlag -> Bool
$c/= :: AllocFlag -> AllocFlag -> Bool
== :: AllocFlag -> AllocFlag -> Bool
$c== :: AllocFlag -> AllocFlag -> Bool
Eq,Int -> AllocFlag -> ShowS
[AllocFlag] -> ShowS
AllocFlag -> String
(Int -> AllocFlag -> ShowS)
-> (AllocFlag -> String)
-> ([AllocFlag] -> ShowS)
-> Show AllocFlag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AllocFlag] -> ShowS
$cshowList :: [AllocFlag] -> ShowS
show :: AllocFlag -> String
$cshow :: AllocFlag -> String
showsPrec :: Int -> AllocFlag -> ShowS
$cshowsPrec :: Int -> AllocFlag -> ShowS
Show,AllocFlag
AllocFlag -> AllocFlag -> Bounded AllocFlag
forall a. a -> a -> Bounded a
maxBound :: AllocFlag
$cmaxBound :: AllocFlag
minBound :: AllocFlag
$cminBound :: AllocFlag
Bounded)
instance Enum AllocFlag where
  succ :: AllocFlag -> AllocFlag
succ AllocFlag
Portable = AllocFlag
DeviceMapped
  succ AllocFlag
DeviceMapped = AllocFlag
WriteCombined
  succ AllocFlag
WriteCombined = String -> AllocFlag
forall a. HasCallStack => String -> a
error String
"AllocFlag.succ: WriteCombined has no successor"

  pred :: AllocFlag -> AllocFlag
pred AllocFlag
DeviceMapped = AllocFlag
Portable
  pred AllocFlag
WriteCombined = AllocFlag
DeviceMapped
  pred AllocFlag
Portable = String -> AllocFlag
forall a. HasCallStack => String -> a
error String
"AllocFlag.pred: Portable has no predecessor"

  enumFromTo :: AllocFlag -> AllocFlag -> [AllocFlag]
enumFromTo AllocFlag
from AllocFlag
to = AllocFlag -> [AllocFlag]
forall t. Enum t => t -> [t]
go AllocFlag
from
    where
      end :: Int
end = AllocFlag -> Int
forall a. Enum a => a -> Int
fromEnum AllocFlag
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 :: AllocFlag -> [AllocFlag]
enumFrom AllocFlag
from = AllocFlag -> AllocFlag -> [AllocFlag]
forall a. Enum a => a -> a -> [a]
enumFromTo AllocFlag
from AllocFlag
WriteCombined

  fromEnum :: AllocFlag -> Int
fromEnum AllocFlag
Portable = Int
1
  fromEnum AllocFlag
DeviceMapped = Int
2
  fromEnum AllocFlag
WriteCombined = Int
4

  toEnum :: Int -> AllocFlag
toEnum Int
1 = AllocFlag
Portable
  toEnum Int
2 = AllocFlag
DeviceMapped
  toEnum Int
4 = AllocFlag
WriteCombined
  toEnum unmatched = error ("AllocFlag.toEnum: Cannot match " ++ show unmatched)

{-# LINE 88 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}



-- |
-- Allocate a section of linear memory on the host which is page-locked and
-- directly accessible from the device. The storage is sufficient to hold the
-- given number of elements of a storable type. The runtime system automatically
-- accelerates calls to functions such as 'peekArrayAsync' and 'pokeArrayAsync'
-- that refer to page-locked memory.
--
-- Note that since the amount of pageable memory is thusly reduced, overall
-- system performance may suffer. This is best used sparingly to allocate
-- staging areas for data exchange
--
{-# INLINEABLE mallocHostArray #-}
mallocHostArray :: Storable a => [AllocFlag] -> Int -> IO (HostPtr a)
mallocHostArray !flags = doMalloc undefined
  where
    doMalloc :: Storable a' => a' -> Int -> IO (HostPtr a')
    doMalloc x !n = resultIfOk =<< cudaHostAlloc (fromIntegral n * fromIntegral (sizeOf x)) flags

{-# INLINE cudaHostAlloc #-}
cudaHostAlloc :: (Int64) -> ([AllocFlag]) -> IO ((Status), (HostPtr a))
cudaHostAlloc :: Int64 -> [AllocFlag] -> IO (Status, HostPtr a)
cudaHostAlloc Int64
a2 [AllocFlag]
a3 =
  (Ptr (Ptr ()) -> IO (Status, HostPtr a)) -> IO (Status, HostPtr a)
forall b b. (Ptr b -> IO b) -> IO b
alloca' ((Ptr (Ptr ()) -> IO (Status, HostPtr a))
 -> IO (Status, HostPtr a))
-> (Ptr (Ptr ()) -> IO (Status, HostPtr a))
-> IO (Status, HostPtr a)
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr ())
a1' -> 
  let {a2' :: CULong
a2' = Int64 -> CULong
forall a b. (Integral a, Integral b) => a -> b
cIntConv Int64
a2} in 
  let {a3' :: CUInt
a3' = [AllocFlag] -> CUInt
forall a b. (Enum a, Num b, Bits b) => [a] -> b
combineBitMasks [AllocFlag]
a3} in 
  Ptr (Ptr ()) -> CULong -> CUInt -> IO CInt
cudaHostAlloc'_ Ptr (Ptr ())
a1' CULong
a2' CUInt
a3' IO CInt
-> (CInt -> IO (Status, HostPtr a)) -> IO (Status, HostPtr a)
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 (Ptr ()) -> IO (HostPtr a)
forall a a. Ptr (Ptr a) -> IO (HostPtr a)
hptr  Ptr (Ptr ())
a1'IO (HostPtr a)
-> (HostPtr a -> IO (Status, HostPtr a)) -> IO (Status, HostPtr a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \HostPtr a
a1'' -> 
  (Status, HostPtr a) -> IO (Status, HostPtr a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res', HostPtr a
a1'')

{-# LINE 113 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}

  where
    alloca' !f = F.alloca $ \ !p -> poke p nullPtr >> f (castPtr p)
    hptr !p    = (HostPtr . castPtr) `fmap` peek p


-- |
-- Free page-locked host memory previously allocated with 'mallecHost'
--
{-# INLINEABLE freeHost #-}
freeHost :: HostPtr a -> IO ()
freeHost :: HostPtr a -> IO ()
freeHost !HostPtr a
p = Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< HostPtr a -> IO Status
forall a. HostPtr a -> IO Status
cudaFreeHost HostPtr a
p

{-# INLINE cudaFreeHost #-}
cudaFreeHost :: (HostPtr a) -> IO ((Status))
cudaFreeHost :: HostPtr a -> IO Status
cudaFreeHost HostPtr a
a1 =
  let {a1' :: Ptr b
a1' = HostPtr a -> Ptr b
forall a b. HostPtr a -> Ptr b
hptr HostPtr a
a1} in 
  Ptr () -> IO CInt
cudaFreeHost'_ Ptr ()
forall b. Ptr b
a1' 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 128 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}

  where hptr = castPtr . useHostPtr


--------------------------------------------------------------------------------
-- Device Allocation
--------------------------------------------------------------------------------

-- |
-- Allocate a section of linear memory on the device, and return a reference to
-- it. The memory is sufficient to hold the given number of elements of storable
-- type. It is suitable aligned, and not cleared.
--
{-# INLINEABLE mallocArray #-}
mallocArray :: Storable a => Int -> IO (DevicePtr a)
mallocArray :: Int -> IO (DevicePtr a)
mallocArray = a -> Int -> IO (DevicePtr a)
forall a'. Storable a' => a' -> Int -> IO (DevicePtr a')
doMalloc a
forall a. HasCallStack => a
undefined
  where
    doMalloc :: Storable a' => a' -> Int -> IO (DevicePtr a')
    doMalloc :: a' -> Int -> IO (DevicePtr a')
doMalloc a'
x !Int
n = (Status, DevicePtr a') -> IO (DevicePtr a')
forall a. (Status, a) -> IO a
resultIfOk ((Status, DevicePtr a') -> IO (DevicePtr a'))
-> IO (Status, DevicePtr a') -> IO (DevicePtr a')
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Int64 -> IO (Status, DevicePtr a')
forall a. Int64 -> IO (Status, DevicePtr a)
cudaMalloc (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a' -> Int
forall a. Storable a => a -> Int
sizeOf a'
x))

{-# INLINE cudaMalloc #-}
cudaMalloc :: (Int64) -> IO ((Status), (DevicePtr a))
cudaMalloc :: Int64 -> IO (Status, DevicePtr a)
cudaMalloc Int64
a2 =
  (Ptr (Ptr ()) -> IO (Status, DevicePtr a))
-> IO (Status, DevicePtr a)
forall b b. (Ptr b -> IO b) -> IO b
alloca' ((Ptr (Ptr ()) -> IO (Status, DevicePtr a))
 -> IO (Status, DevicePtr a))
-> (Ptr (Ptr ()) -> IO (Status, DevicePtr a))
-> IO (Status, DevicePtr a)
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr ())
a1' -> 
  let {a2' :: CULong
a2' = Int64 -> CULong
forall a b. (Integral a, Integral b) => a -> b
cIntConv Int64
a2} in 
  Ptr (Ptr ()) -> CULong -> IO CInt
cudaMalloc'_ Ptr (Ptr ())
a1' CULong
a2' IO CInt
-> (CInt -> IO (Status, DevicePtr a)) -> IO (Status, DevicePtr a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' = cToEnum res} in
  Ptr (Ptr ()) -> IO (DevicePtr a)
forall a b. Ptr (Ptr a) -> IO (DevicePtr b)
dptr  Ptr (Ptr ())
a1'IO (DevicePtr a)
-> (DevicePtr a -> IO (Status, DevicePtr a))
-> IO (Status, DevicePtr a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DevicePtr a
a1'' -> 
  (Status, DevicePtr a) -> IO (Status, DevicePtr a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res', DevicePtr a
a1'')

{-# LINE 151 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}

  where
    -- C-> Haskell doesn't like qualified imports in marshaller specifications
    alloca' !f = F.alloca $ \ !p -> poke p nullPtr >> f (castPtr p)
    dptr !p    = (castDevPtr . DevicePtr) `fmap` peek p


-- |
-- Execute a computation, passing a pointer to a temporarily allocated block of
-- memory sufficient to hold the given number of elements of storable type. The
-- memory is freed when the computation terminates (normally or via an
-- exception), so the pointer must not be used after this.
--
-- Note that kernel launches can be asynchronous, so you may need to add a
-- synchronisation point at the end of the computation.
--
{-# INLINEABLE allocaArray #-}
allocaArray :: Storable a => Int -> (DevicePtr a -> IO b) -> IO b
allocaArray :: Int -> (DevicePtr a -> IO b) -> IO b
allocaArray Int
n = IO (DevicePtr a)
-> (DevicePtr a -> IO ()) -> (DevicePtr a -> IO b) -> IO b
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (DevicePtr a)
forall a. Storable a => Int -> IO (DevicePtr a)
mallocArray Int
n) DevicePtr a -> IO ()
forall a. DevicePtr a -> IO ()
free


-- |
-- Free previously allocated memory on the device
--
{-# INLINEABLE free #-}
free :: DevicePtr a -> IO ()
free :: DevicePtr a -> IO ()
free !DevicePtr a
p = Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DevicePtr a -> IO Status
forall a. DevicePtr a -> IO Status
cudaFree DevicePtr a
p

{-# INLINE cudaFree #-}
cudaFree :: (DevicePtr a) -> IO ((Status))
cudaFree :: DevicePtr a -> IO Status
cudaFree DevicePtr a
a1 =
  let {a1' :: Ptr a
a1' = DevicePtr a -> Ptr a
forall a a. DevicePtr a -> Ptr a
dptr DevicePtr a
a1} in 
  Ptr () -> IO CInt
cudaFree'_ Ptr ()
forall b. Ptr b
a1' IO CInt -> (CInt -> IO Status) -> IO Status
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \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 181 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}

  where
    dptr = useDevicePtr . castDevPtr


--------------------------------------------------------------------------------
-- Unified memory allocation
--------------------------------------------------------------------------------

-- |
-- Options for unified memory allocations
--
data AttachFlag = Global
                | Host
                | Single
  deriving (AttachFlag -> AttachFlag -> Bool
(AttachFlag -> AttachFlag -> Bool)
-> (AttachFlag -> AttachFlag -> Bool) -> Eq AttachFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachFlag -> AttachFlag -> Bool
$c/= :: AttachFlag -> AttachFlag -> Bool
== :: AttachFlag -> AttachFlag -> Bool
$c== :: AttachFlag -> AttachFlag -> Bool
Eq,Int -> AttachFlag -> ShowS
[AttachFlag] -> ShowS
AttachFlag -> String
(Int -> AttachFlag -> ShowS)
-> (AttachFlag -> String)
-> ([AttachFlag] -> ShowS)
-> Show AttachFlag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachFlag] -> ShowS
$cshowList :: [AttachFlag] -> ShowS
show :: AttachFlag -> String
$cshow :: AttachFlag -> String
showsPrec :: Int -> AttachFlag -> ShowS
$cshowsPrec :: Int -> AttachFlag -> ShowS
Show,AttachFlag
AttachFlag -> AttachFlag -> Bounded AttachFlag
forall a. a -> a -> Bounded a
maxBound :: AttachFlag
$cmaxBound :: AttachFlag
minBound :: AttachFlag
$cminBound :: AttachFlag
Bounded)
instance Enum AttachFlag where
  succ :: AttachFlag -> AttachFlag
succ AttachFlag
Global = AttachFlag
Host
  succ AttachFlag
Host = AttachFlag
Single
  succ AttachFlag
Single = String -> AttachFlag
forall a. HasCallStack => String -> a
error String
"AttachFlag.succ: Single has no successor"

  pred :: AttachFlag -> AttachFlag
pred AttachFlag
Host = AttachFlag
Global
  pred AttachFlag
Single = AttachFlag
Host
  pred AttachFlag
Global = String -> AttachFlag
forall a. HasCallStack => String -> a
error String
"AttachFlag.pred: Global 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 Single

  fromEnum Global = 1
  fromEnum Host = 2
  fromEnum Single = 4

  toEnum 1 = Global
  toEnum 2 = Host
  toEnum 4 = Single
  toEnum unmatched = error ("AttachFlag.toEnum: Cannot match " ++ show unmatched)

{-# LINE 199 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}


-- |
-- Allocates memory that will be automatically managed by the Unified Memory
-- system
--
{-# INLINEABLE mallocManagedArray #-}
mallocManagedArray :: Storable a => [AttachFlag] -> Int -> IO (DevicePtr a)
mallocManagedArray !flags = doMalloc undefined
  where
    doMalloc :: Storable a' => a' -> Int -> IO (DevicePtr a')
    doMalloc x !n = resultIfOk =<< cudaMallocManaged (fromIntegral n * fromIntegral (sizeOf x)) flags

{-# INLINE cudaMallocManaged #-}
cudaMallocManaged :: (Int64) -> ([AttachFlag]) -> IO ((Status), (DevicePtr a))
cudaMallocManaged a2 a3 =
  alloca' $ \a1' -> 
  let {a2' = cIntConv a2} in 
  let {a3' = combineBitMasks a3} in 
  cudaMallocManaged'_ a1' a2' a3' >>= \res ->
  let {res' = cToEnum res} in
  dptr  a1'>>= \a1'' -> 
  return (res', a1'')

{-# LINE 219 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}

  where
    alloca' !f = F.alloca $ \ !p -> poke p nullPtr >> f (castPtr p)
    dptr !p    = (castDevPtr . DevicePtr) `fmap` peek p


--------------------------------------------------------------------------------
-- Marshalling
--------------------------------------------------------------------------------

-- |
-- Copy a number of elements from the device to host memory. This is a
-- synchronous operation.
--
{-# INLINEABLE peekArray #-}
peekArray :: Storable a => Int -> DevicePtr a -> Ptr a -> IO ()
peekArray :: Int -> DevicePtr a -> Ptr a -> IO ()
peekArray !Int
n !DevicePtr a
dptr !Ptr a
hptr = Ptr a -> Ptr a -> Int -> CopyDirection -> IO ()
forall a.
Storable a =>
Ptr a -> Ptr a -> Int -> CopyDirection -> IO ()
memcpy Ptr a
hptr (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dptr) Int
n CopyDirection
DeviceToHost


-- |
-- Copy memory from the device asynchronously, possibly associated with a
-- particular stream. The destination memory must be page locked.
--
{-# INLINEABLE peekArrayAsync #-}
peekArrayAsync :: Storable a => Int -> DevicePtr a -> HostPtr a -> Maybe Stream -> IO ()
peekArrayAsync :: Int -> DevicePtr a -> HostPtr a -> Maybe Stream -> IO ()
peekArrayAsync !Int
n !DevicePtr a
dptr !HostPtr a
hptr !Maybe Stream
mst =
  Ptr a -> Ptr a -> Int -> CopyDirection -> Maybe Stream -> IO ()
forall a.
Storable a =>
Ptr a -> Ptr a -> Int -> CopyDirection -> Maybe Stream -> IO ()
memcpyAsync (HostPtr a -> Ptr a
forall a. HostPtr a -> Ptr a
useHostPtr HostPtr a
hptr) (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dptr) Int
n CopyDirection
DeviceToHost Maybe Stream
mst


-- |
-- Copy a 2D memory area from the device to the host. This is a synchronous
-- operation.
--
{-# INLINEABLE peekArray2D #-}
peekArray2D
    :: Storable a
    => Int                      -- ^ width to copy (elements)
    -> Int                      -- ^ height to copy (elements)
    -> DevicePtr a              -- ^ source array
    -> Int                      -- ^ source array width
    -> Ptr a                    -- ^ destination array
    -> Int                      -- ^ destination array width
    -> IO ()
peekArray2D :: Int -> Int -> DevicePtr a -> Int -> Ptr a -> Int -> IO ()
peekArray2D !Int
w !Int
h !DevicePtr a
dptr !Int
dw !Ptr a
hptr !Int
hw =
  Ptr a
-> Int -> Ptr a -> Int -> Int -> Int -> CopyDirection -> IO ()
forall a.
Storable a =>
Ptr a
-> Int -> Ptr a -> Int -> Int -> Int -> CopyDirection -> IO ()
memcpy2D Ptr a
hptr Int
hw (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dptr) Int
dw Int
w Int
h CopyDirection
DeviceToHost


-- |
-- Copy a 2D memory area from the device to the host asynchronously, possibly
-- associated with a particular stream. The destination array must be page
-- locked.
--
{-# INLINEABLE peekArray2DAsync #-}
peekArray2DAsync
    :: Storable a
    => Int                      -- ^ width to copy (elements)
    -> Int                      -- ^ height to copy (elements)
    -> DevicePtr a              -- ^ source array
    -> Int                      -- ^ source array width
    -> HostPtr a                -- ^ destination array
    -> Int                      -- ^ destination array width
    -> Maybe Stream
    -> IO ()
peekArray2DAsync :: Int
-> Int
-> DevicePtr a
-> Int
-> HostPtr a
-> Int
-> Maybe Stream
-> IO ()
peekArray2DAsync !Int
w !Int
h !DevicePtr a
dptr !Int
dw !HostPtr a
hptr !Int
hw !Maybe Stream
mst =
  Ptr a
-> Int
-> Ptr a
-> Int
-> Int
-> Int
-> CopyDirection
-> Maybe Stream
-> IO ()
forall a.
Storable a =>
Ptr a
-> Int
-> Ptr a
-> Int
-> Int
-> Int
-> CopyDirection
-> Maybe Stream
-> IO ()
memcpy2DAsync (HostPtr a -> Ptr a
forall a. HostPtr a -> Ptr a
useHostPtr HostPtr a
hptr) Int
hw (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dptr) Int
dw Int
w Int
h CopyDirection
DeviceToHost Maybe Stream
mst


-- |
-- Copy a number of elements from the device into a new Haskell list. Note that
-- this requires two memory copies: firstly from the device into a heap
-- allocated array, and from there marshalled into a list
--
{-# INLINEABLE peekListArray #-}
peekListArray :: Storable a => Int -> DevicePtr a -> IO [a]
peekListArray :: Int -> DevicePtr a -> IO [a]
peekListArray !Int
n !DevicePtr a
dptr =
  Int -> (Ptr a -> IO [a]) -> IO [a]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
F.allocaArray Int
n ((Ptr a -> IO [a]) -> IO [a]) -> (Ptr a -> IO [a]) -> IO [a]
forall a b. (a -> b) -> a -> b
$ \Ptr a
p -> do
    Int -> DevicePtr a -> Ptr a -> IO ()
forall a. Storable a => Int -> DevicePtr a -> Ptr a -> IO ()
peekArray   Int
n DevicePtr a
dptr Ptr a
p
    Int -> Ptr a -> IO [a]
forall a. Storable a => Int -> Ptr a -> IO [a]
F.peekArray Int
n Ptr a
p


-- |
-- Copy a number of elements onto the device. This is a synchronous operation.
--
{-# INLINEABLE pokeArray #-}
pokeArray :: Storable a => Int -> Ptr a -> DevicePtr a -> IO ()
pokeArray :: Int -> Ptr a -> DevicePtr a -> IO ()
pokeArray !Int
n !Ptr a
hptr !DevicePtr a
dptr = Ptr a -> Ptr a -> Int -> CopyDirection -> IO ()
forall a.
Storable a =>
Ptr a -> Ptr a -> Int -> CopyDirection -> IO ()
memcpy (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dptr) Ptr a
hptr Int
n CopyDirection
HostToDevice


-- |
-- Copy memory onto the device asynchronously, possibly associated with a
-- particular stream. The source memory must be page-locked.
--
{-# INLINEABLE pokeArrayAsync #-}
pokeArrayAsync :: Storable a => Int -> HostPtr a -> DevicePtr a -> Maybe Stream -> IO ()
pokeArrayAsync :: Int -> HostPtr a -> DevicePtr a -> Maybe Stream -> IO ()
pokeArrayAsync !Int
n !HostPtr a
hptr !DevicePtr a
dptr !Maybe Stream
mst =
  Ptr a -> Ptr a -> Int -> CopyDirection -> Maybe Stream -> IO ()
forall a.
Storable a =>
Ptr a -> Ptr a -> Int -> CopyDirection -> Maybe Stream -> IO ()
memcpyAsync (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dptr) (HostPtr a -> Ptr a
forall a. HostPtr a -> Ptr a
useHostPtr HostPtr a
hptr) Int
n CopyDirection
HostToDevice Maybe Stream
mst


-- |
-- Copy a 2D memory area onto the device. This is a synchronous operation.
--
{-# INLINEABLE pokeArray2D #-}
pokeArray2D
    :: Storable a
    => Int                      -- ^ width to copy (elements)
    -> Int                      -- ^ height to copy (elements)
    -> Ptr a                    -- ^ source array
    -> Int                      -- ^ source array width
    -> DevicePtr a              -- ^ destination array
    -> Int                      -- ^ destination array width
    -> IO ()
pokeArray2D :: Int -> Int -> Ptr a -> Int -> DevicePtr a -> Int -> IO ()
pokeArray2D !Int
w !Int
h !Ptr a
hptr !Int
dw !DevicePtr a
dptr !Int
hw =
  Ptr a
-> Int -> Ptr a -> Int -> Int -> Int -> CopyDirection -> IO ()
forall a.
Storable a =>
Ptr a
-> Int -> Ptr a -> Int -> Int -> Int -> CopyDirection -> IO ()
memcpy2D (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dptr) Int
dw Ptr a
hptr Int
hw Int
w Int
h CopyDirection
HostToDevice


-- |
-- Copy a 2D memory area onto the device asynchronously, possibly associated
-- with a particular stream. The source array must be page locked.
--
{-# INLINEABLE pokeArray2DAsync #-}
pokeArray2DAsync
    :: Storable a
    => Int                      -- ^ width to copy (elements)
    -> Int                      -- ^ height to copy (elements)
    -> HostPtr a                -- ^ source array
    -> Int                      -- ^ source array width
    -> DevicePtr a              -- ^ destination array
    -> Int                      -- ^ destination array width
    -> Maybe Stream
    -> IO ()
pokeArray2DAsync :: Int
-> Int
-> HostPtr a
-> Int
-> DevicePtr a
-> Int
-> Maybe Stream
-> IO ()
pokeArray2DAsync !Int
w !Int
h !HostPtr a
hptr !Int
hw !DevicePtr a
dptr !Int
dw !Maybe Stream
mst =
  Ptr a
-> Int
-> Ptr a
-> Int
-> Int
-> Int
-> CopyDirection
-> Maybe Stream
-> IO ()
forall a.
Storable a =>
Ptr a
-> Int
-> Ptr a
-> Int
-> Int
-> Int
-> CopyDirection
-> Maybe Stream
-> IO ()
memcpy2DAsync (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dptr) Int
dw (HostPtr a -> Ptr a
forall a. HostPtr a -> Ptr a
useHostPtr HostPtr a
hptr) Int
hw Int
w Int
h CopyDirection
HostToDevice Maybe Stream
mst

-- |
-- Write a list of storable elements into a device array. The array must be
-- sufficiently large to hold the entire list. This requires two marshalling
-- operations
--
{-# INLINEABLE pokeListArray #-}
pokeListArray :: Storable a => [a] -> DevicePtr a -> IO ()
pokeListArray :: [a] -> DevicePtr a -> IO ()
pokeListArray ![a]
xs !DevicePtr a
dptr = [a] -> (Int -> Ptr a -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
F.withArrayLen [a]
xs ((Int -> Ptr a -> IO ()) -> IO ())
-> (Int -> Ptr a -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Int
len Ptr a
p -> Int -> Ptr a -> DevicePtr a -> IO ()
forall a. Storable a => Int -> Ptr a -> DevicePtr a -> IO ()
pokeArray Int
len Ptr a
p DevicePtr a
dptr


-- |
-- Copy the given number of elements from the first device array (source) to the
-- second (destination). The copied areas may not overlap. This operation is
-- asynchronous with respect to host, but will not overlap other device
-- operations.
--
{-# INLINEABLE copyArray #-}
copyArray :: Storable a => Int -> DevicePtr a -> DevicePtr a -> IO ()
copyArray :: Int -> DevicePtr a -> DevicePtr a -> IO ()
copyArray !Int
n !DevicePtr a
src !DevicePtr a
dst = Ptr a -> Ptr a -> Int -> CopyDirection -> IO ()
forall a.
Storable a =>
Ptr a -> Ptr a -> Int -> CopyDirection -> IO ()
memcpy (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dst) (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
src) Int
n CopyDirection
DeviceToDevice


-- |
-- Copy the given number of elements from the first device array (source) to the
-- second (destination). The copied areas may not overlap. This operation is
-- asynchronous with respect to the host, and may be associated with a
-- particular stream.
--
{-# INLINEABLE copyArrayAsync #-}
copyArrayAsync :: Storable a => Int -> DevicePtr a -> DevicePtr a -> Maybe Stream -> IO ()
copyArrayAsync :: Int -> DevicePtr a -> DevicePtr a -> Maybe Stream -> IO ()
copyArrayAsync !Int
n !DevicePtr a
src !DevicePtr a
dst !Maybe Stream
mst =
  Ptr a -> Ptr a -> Int -> CopyDirection -> Maybe Stream -> IO ()
forall a.
Storable a =>
Ptr a -> Ptr a -> Int -> CopyDirection -> Maybe Stream -> IO ()
memcpyAsync (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dst) (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
src) Int
n CopyDirection
DeviceToDevice Maybe Stream
mst


-- |
-- Copy a 2D memory area from the first device array (source) to the second
-- (destination). The copied areas may not overlap. This operation is
-- asynchronous with respect to the host, but will not overlap other device
-- operations.
--
{-# INLINEABLE copyArray2D #-}
copyArray2D
    :: Storable a
    => Int                      -- ^ width to copy (elements)
    -> Int                      -- ^ height to copy (elements)
    -> DevicePtr a              -- ^ source array
    -> Int                      -- ^ source array width
    -> DevicePtr a              -- ^ destination array
    -> Int                      -- ^ destination array width
    -> IO ()
copyArray2D :: Int -> Int -> DevicePtr a -> Int -> DevicePtr a -> Int -> IO ()
copyArray2D !Int
w !Int
h !DevicePtr a
src !Int
sw !DevicePtr a
dst !Int
dw =
  Ptr a
-> Int -> Ptr a -> Int -> Int -> Int -> CopyDirection -> IO ()
forall a.
Storable a =>
Ptr a
-> Int -> Ptr a -> Int -> Int -> Int -> CopyDirection -> IO ()
memcpy2D (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dst) Int
dw (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
src) Int
sw Int
w Int
h CopyDirection
DeviceToDevice


-- |
-- Copy a 2D memory area from the first device array (source) to the second
-- device array (destination). The copied areas may not overlay. This operation
-- is asynchronous with respect to the host, and may be associated with a
-- particular stream.
--
{-# INLINEABLE copyArray2DAsync #-}
copyArray2DAsync
    :: Storable a
    => Int                      -- ^ width to copy (elements)
    -> Int                      -- ^ height to copy (elements)
    -> DevicePtr a              -- ^ source array
    -> Int                      -- ^ source array width
    -> DevicePtr a              -- ^ destination array
    -> Int                      -- ^ destination array width
    -> Maybe Stream
    -> IO ()
copyArray2DAsync :: Int
-> Int
-> DevicePtr a
-> Int
-> DevicePtr a
-> Int
-> Maybe Stream
-> IO ()
copyArray2DAsync !Int
w !Int
h !DevicePtr a
src !Int
sw !DevicePtr a
dst !Int
dw !Maybe Stream
mst =
  Ptr a
-> Int
-> Ptr a
-> Int
-> Int
-> Int
-> CopyDirection
-> Maybe Stream
-> IO ()
forall a.
Storable a =>
Ptr a
-> Int
-> Ptr a
-> Int
-> Int
-> Int
-> CopyDirection
-> Maybe Stream
-> IO ()
memcpy2DAsync (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
dst) Int
dw (DevicePtr a -> Ptr a
forall a. DevicePtr a -> Ptr a
useDevicePtr DevicePtr a
src) Int
sw Int
w Int
h CopyDirection
DeviceToDevice Maybe Stream
mst


--
-- Memory copy kind
--
data CopyDirection = HostToHost
                   | HostToDevice
                   | DeviceToHost
                   | DeviceToDevice
                   | Default
  deriving (CopyDirection -> CopyDirection -> Bool
(CopyDirection -> CopyDirection -> Bool)
-> (CopyDirection -> CopyDirection -> Bool) -> Eq CopyDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyDirection -> CopyDirection -> Bool
$c/= :: CopyDirection -> CopyDirection -> Bool
== :: CopyDirection -> CopyDirection -> Bool
$c== :: CopyDirection -> CopyDirection -> Bool
Eq,Int -> CopyDirection -> ShowS
[CopyDirection] -> ShowS
CopyDirection -> String
(Int -> CopyDirection -> ShowS)
-> (CopyDirection -> String)
-> ([CopyDirection] -> ShowS)
-> Show CopyDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyDirection] -> ShowS
$cshowList :: [CopyDirection] -> ShowS
show :: CopyDirection -> String
$cshow :: CopyDirection -> String
showsPrec :: Int -> CopyDirection -> ShowS
$cshowsPrec :: Int -> CopyDirection -> ShowS
Show)
instance Enum CopyDirection where
  succ HostToHost = HostToDevice
  succ HostToDevice = DeviceToHost
  succ DeviceToHost = DeviceToDevice
  succ DeviceToDevice = Default
  succ Default = error "CopyDirection.succ: Default has no successor"

  pred :: CopyDirection -> CopyDirection
pred CopyDirection
HostToDevice = CopyDirection
HostToHost
  pred CopyDirection
DeviceToHost = CopyDirection
HostToDevice
  pred CopyDirection
DeviceToDevice = CopyDirection
DeviceToHost
  pred CopyDirection
Default = CopyDirection
DeviceToDevice
  pred CopyDirection
HostToHost = String -> CopyDirection
forall a. HasCallStack => String -> a
error String
"CopyDirection.pred: HostToHost has no predecessor"

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

  enumFrom :: CopyDirection -> [CopyDirection]
enumFrom CopyDirection
from = CopyDirection -> CopyDirection -> [CopyDirection]
forall a. Enum a => a -> a -> [a]
enumFromTo CopyDirection
from CopyDirection
Default

  fromEnum :: CopyDirection -> Int
fromEnum CopyDirection
HostToHost = Int
0
  fromEnum CopyDirection
HostToDevice = Int
1
  fromEnum CopyDirection
DeviceToHost = Int
2
  fromEnum CopyDirection
DeviceToDevice = Int
3
  fromEnum CopyDirection
Default = Int
4

  toEnum 0 = HostToHost
  toEnum 1 = HostToDevice
  toEnum 2 = DeviceToHost
  toEnum 3 = DeviceToDevice
  toEnum 4 = Default
  toEnum unmatched = error ("CopyDirection.toEnum: Cannot match " ++ show unmatched)

{-# LINE 431 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}


-- |
-- Copy data between host and device. This is a synchronous operation.
--
{-# INLINEABLE memcpy #-}
memcpy :: Storable a
       => Ptr a                 -- ^ destination
       -> Ptr a                 -- ^ source
       -> Int                   -- ^ number of elements
       -> CopyDirection
       -> IO ()
memcpy !dst !src !n !dir = doMemcpy undefined dst
  where
    doMemcpy :: Storable a' => a' -> Ptr a' -> IO ()
    doMemcpy x _ =
      nothingIfOk =<< cudaMemcpy dst src (fromIntegral n * fromIntegral (sizeOf x)) dir

{-# INLINE cudaMemcpy #-}
cudaMemcpy :: (Ptr a) -> (Ptr a) -> (Int64) -> (CopyDirection) -> IO ((Status))
cudaMemcpy a1 a2 a3 a4 =
  let {a1' = castPtr a1} in 
  let {a2' = castPtr a2} in 
  let {a3' = cIntConv a3} in 
  let {a4' = cFromEnum a4} in 
  cudaMemcpy'_ a1' a2' a3' a4' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 454 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}



-- |
-- Copy data between the host and device asynchronously, possibly associated
-- with a particular stream. The host-side memory must be page-locked (allocated
-- with 'mallocHostArray').
--
{-# INLINEABLE memcpyAsync #-}
memcpyAsync :: Storable a
            => Ptr a            -- ^ destination
            -> Ptr a            -- ^ source
            -> Int              -- ^ number of elements
            -> CopyDirection
            -> Maybe Stream
            -> IO ()
memcpyAsync !dst !src !n !kind !mst = doMemcpy undefined dst
  where
    doMemcpy :: Storable a' => a' -> Ptr a' -> IO ()
    doMemcpy x _ =
      let bytes = fromIntegral n * fromIntegral (sizeOf x) in
      nothingIfOk =<< cudaMemcpyAsync dst src bytes kind (fromMaybe defaultStream mst)

{-# INLINE cudaMemcpyAsync #-}
cudaMemcpyAsync :: (Ptr a) -> (Ptr a) -> (Int64) -> (CopyDirection) -> (Stream) -> IO ((Status))
cudaMemcpyAsync :: Ptr a -> Ptr a -> Int64 -> CopyDirection -> Stream -> IO Status
cudaMemcpyAsync Ptr a
a1 Ptr a
a2 Int64
a3 CopyDirection
a4 Stream
a5 =
  let {a1' :: Ptr b
a1' = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
a1} in 
  let {a2' :: Ptr b
a2' = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
a2} in 
  let {a3' :: CULong
a3' = Int64 -> CULong
forall a b. (Integral a, Integral b) => a -> b
cIntConv Int64
a3} in 
  let {a4' :: CInt
a4' = CopyDirection -> CInt
forall e i. (Enum e, Integral i) => e -> i
cFromEnum CopyDirection
a4} in 
  let {a5' :: Ptr ()
a5' = Stream -> Ptr ()
useStream Stream
a5} in 
  Ptr () -> Ptr () -> CULong -> CInt -> Ptr () -> IO CInt
cudaMemcpyAsync'_ Ptr ()
forall b. Ptr b
a1' Ptr ()
forall b. Ptr b
a2' CULong
a3' CInt
a4' Ptr ()
a5' 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 483 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}



-- |
-- Copy a 2D memory area between the host and device. This is a synchronous
-- operation.
--
{-# INLINEABLE memcpy2D #-}
memcpy2D :: Storable a
         => Ptr a               -- ^ destination
         -> Int                 -- ^ width of destination array
         -> Ptr a               -- ^ source
         -> Int                 -- ^ width of source array
         -> Int                 -- ^ width to copy
         -> Int                 -- ^ height to copy
         -> CopyDirection
         -> IO ()
memcpy2D :: Ptr a
-> Int -> Ptr a -> Int -> Int -> Int -> CopyDirection -> IO ()
memcpy2D !Ptr a
dst !Int
dw !Ptr a
src !Int
sw !Int
w !Int
h !CopyDirection
kind = a -> Ptr a -> IO ()
forall a'. Storable a' => a' -> Ptr a' -> IO ()
doCopy a
forall a. HasCallStack => a
undefined Ptr a
dst
  where
    doCopy :: Storable a' => a' -> Ptr a' -> IO ()
    doCopy :: a' -> Ptr a' -> IO ()
doCopy a'
x Ptr a'
_ =
      let bytes :: Int64
bytes = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a' -> Int
forall a. Storable a => a -> Int
sizeOf a'
x)
          dw' :: Int64
dw'   = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dw Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
bytes
          sw' :: Int64
sw'   = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sw Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
bytes
          w' :: Int64
w'    = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w  Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
bytes
          h' :: Int64
h'    = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
h
      in
      Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr a
-> Int64
-> Ptr a
-> Int64
-> Int64
-> Int64
-> CopyDirection
-> IO Status
forall a.
Ptr a
-> Int64
-> Ptr a
-> Int64
-> Int64
-> Int64
-> CopyDirection
-> IO Status
cudaMemcpy2D Ptr a
dst Int64
dw' Ptr a
src Int64
sw' Int64
w' Int64
h' CopyDirection
kind

{-# INLINE cudaMemcpy2D #-}
cudaMemcpy2D :: (Ptr a) -> (Int64) -> (Ptr a) -> (Int64) -> (Int64) -> (Int64) -> (CopyDirection) -> IO ((Status))
cudaMemcpy2D :: Ptr a
-> Int64
-> Ptr a
-> Int64
-> Int64
-> Int64
-> CopyDirection
-> IO Status
cudaMemcpy2D Ptr a
a1 Int64
a2 Ptr a
a3 Int64
a4 Int64
a5 Int64
a6 CopyDirection
a7 =
  let {a1' :: Ptr b
a1' = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
a1} in 
  let {a2' :: CULong
a2' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a2} in 
  let {a3' :: Ptr b
a3' = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
a3} in 
  let {a4' :: CULong
a4' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a4} in 
  let {a5' :: CULong
a5' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a5} in 
  let {a6' :: CULong
a6' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a6} in 
  let {a7' :: CInt
a7' = CopyDirection -> CInt
forall e i. (Enum e, Integral i) => e -> i
cFromEnum CopyDirection
a7} in 
  Ptr ()
-> CULong
-> Ptr ()
-> CULong
-> CULong
-> CULong
-> CInt
-> IO CInt
cudaMemcpy2D'_ Ptr ()
forall b. Ptr b
a1' CULong
a2' Ptr ()
forall b. Ptr b
a3' CULong
a4' CULong
a5' CULong
a6' CInt
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 522 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}



-- |
-- Copy a 2D memory area between the host and device asynchronously, possibly
-- associated with a particular stream. The host-side memory must be
-- page-locked.
--
{-# INLINEABLE memcpy2DAsync #-}
memcpy2DAsync :: Storable a
              => Ptr a          -- ^ destination
              -> Int            -- ^ width of destination array
              -> Ptr a          -- ^ source
              -> Int            -- ^ width of source array
              -> Int            -- ^ width to copy
              -> Int            -- ^ height to copy
              -> CopyDirection
              -> Maybe Stream
              -> IO ()
memcpy2DAsync :: Ptr a
-> Int
-> Ptr a
-> Int
-> Int
-> Int
-> CopyDirection
-> Maybe Stream
-> IO ()
memcpy2DAsync !Ptr a
dst !Int
dw !Ptr a
src !Int
sw !Int
w !Int
h !CopyDirection
kind !Maybe Stream
mst = a -> Ptr a -> IO ()
forall a'. Storable a' => a' -> Ptr a' -> IO ()
doCopy a
forall a. HasCallStack => a
undefined Ptr a
dst
  where
    doCopy :: Storable a' => a' -> Ptr a' -> IO ()
    doCopy :: a' -> Ptr a' -> IO ()
doCopy a'
x Ptr a'
_ =
      let bytes :: Int64
bytes = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a' -> Int
forall a. Storable a => a -> Int
sizeOf a'
x)
          dw' :: Int64
dw'   = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dw Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
bytes
          sw' :: Int64
sw'   = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sw Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
bytes
          w' :: Int64
w'    = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w  Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
bytes
          h' :: Int64
h'    = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
h
          st :: Stream
st    = Stream -> Maybe Stream -> Stream
forall a. a -> Maybe a -> a
fromMaybe Stream
defaultStream Maybe Stream
mst
      in
      Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr a
-> Int64
-> Ptr a
-> Int64
-> Int64
-> Int64
-> CopyDirection
-> Stream
-> IO Status
forall a.
Ptr a
-> Int64
-> Ptr a
-> Int64
-> Int64
-> Int64
-> CopyDirection
-> Stream
-> IO Status
cudaMemcpy2DAsync Ptr a
dst Int64
dw' Ptr a
src Int64
sw' Int64
w' Int64
h' CopyDirection
kind Stream
st

{-# INLINE cudaMemcpy2DAsync #-}
cudaMemcpy2DAsync :: (Ptr a) -> (Int64) -> (Ptr a) -> (Int64) -> (Int64) -> (Int64) -> (CopyDirection) -> (Stream) -> IO ((Status))
cudaMemcpy2DAsync :: Ptr a
-> Int64
-> Ptr a
-> Int64
-> Int64
-> Int64
-> CopyDirection
-> Stream
-> IO Status
cudaMemcpy2DAsync Ptr a
a1 Int64
a2 Ptr a
a3 Int64
a4 Int64
a5 Int64
a6 CopyDirection
a7 Stream
a8 =
  let {a1' :: Ptr b
a1' = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
a1} in 
  let {a2' :: CULong
a2' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a2} in 
  let {a3' :: Ptr b
a3' = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
a3} in 
  let {a4' :: CULong
a4' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a4} in 
  let {a5' :: CULong
a5' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a5} in 
  let {a6' :: CULong
a6' = Int64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a6} in 
  let {a7' :: CInt
a7' = CopyDirection -> CInt
forall e i. (Enum e, Integral i) => e -> i
cFromEnum CopyDirection
a7} in 
  let {a8' :: Ptr ()
a8' = Stream -> Ptr ()
useStream Stream
a8} in 
  Ptr ()
-> CULong
-> Ptr ()
-> CULong
-> CULong
-> CULong
-> CInt
-> Ptr ()
-> IO CInt
cudaMemcpy2DAsync'_ Ptr ()
forall b. Ptr b
a1' CULong
a2' Ptr ()
forall b. Ptr b
a3' CULong
a4' CULong
a5' CULong
a6' CInt
a7' Ptr ()
a8' 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 565 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}



--------------------------------------------------------------------------------
-- Combined Allocation and Marshalling
--------------------------------------------------------------------------------

-- |
-- Write a list of storable elements into a newly allocated device array,
-- returning the device pointer together with the number of elements that were
-- written. Note that this requires two copy operations: firstly from a Haskell
-- list into a heap-allocated array, and from there into device memory. The
-- array should be 'free'd when no longer required.
--
{-# INLINEABLE newListArrayLen #-}
newListArrayLen :: Storable a => [a] -> IO (DevicePtr a, Int)
newListArrayLen :: [a] -> IO (DevicePtr a, Int)
newListArrayLen ![a]
xs =
  [a]
-> (Int -> Ptr a -> IO (DevicePtr a, Int)) -> IO (DevicePtr a, Int)
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
F.withArrayLen [a]
xs                     ((Int -> Ptr a -> IO (DevicePtr a, Int)) -> IO (DevicePtr a, Int))
-> (Int -> Ptr a -> IO (DevicePtr a, Int)) -> IO (DevicePtr a, Int)
forall a b. (a -> b) -> a -> b
$ \Int
len Ptr a
p ->
  IO (DevicePtr a)
-> (DevicePtr a -> IO ())
-> (DevicePtr a -> IO (DevicePtr a, Int))
-> IO (DevicePtr a, Int)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError (Int -> IO (DevicePtr a)
forall a. Storable a => Int -> IO (DevicePtr a)
mallocArray Int
len) DevicePtr a -> IO ()
forall a. DevicePtr a -> IO ()
free ((DevicePtr a -> IO (DevicePtr a, Int)) -> IO (DevicePtr a, Int))
-> (DevicePtr a -> IO (DevicePtr a, Int)) -> IO (DevicePtr a, Int)
forall a b. (a -> b) -> a -> b
$ \DevicePtr a
d_xs  -> do
    Int -> Ptr a -> DevicePtr a -> IO ()
forall a. Storable a => Int -> Ptr a -> DevicePtr a -> IO ()
pokeArray Int
len Ptr a
p DevicePtr a
d_xs
    (DevicePtr a, Int) -> IO (DevicePtr a, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (DevicePtr a
d_xs, Int
len)


-- |
-- Write a list of storable elements into a newly allocated device array. This
-- is 'newListArrayLen' composed with 'fst'.
--
{-# INLINEABLE newListArray #-}
newListArray :: Storable a => [a] -> IO (DevicePtr a)
newListArray :: [a] -> IO (DevicePtr a)
newListArray ![a]
xs = (DevicePtr a, Int) -> DevicePtr a
forall a b. (a, b) -> a
fst ((DevicePtr a, Int) -> DevicePtr a)
-> IO (DevicePtr a, Int) -> IO (DevicePtr a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` [a] -> IO (DevicePtr a, Int)
forall a. Storable a => [a] -> IO (DevicePtr a, Int)
newListArrayLen [a]
xs


-- |
-- Temporarily store a list of elements into a newly allocated device array. An
-- IO action is applied to the array, the result of which is returned. Similar
-- to 'newListArray', this requires two marshalling operations of the data.
--
-- As with 'allocaArray', the memory is freed once the action completes, so you
-- should not return the pointer from the action, and be sure that any
-- asynchronous operations (such as kernel execution) have completed.
--
{-# INLINEABLE withListArray #-}
withListArray :: Storable a => [a] -> (DevicePtr a -> IO b) -> IO b
withListArray :: [a] -> (DevicePtr a -> IO b) -> IO b
withListArray ![a]
xs = [a] -> (Int -> DevicePtr a -> IO b) -> IO b
forall a b.
Storable a =>
[a] -> (Int -> DevicePtr a -> IO b) -> IO b
withListArrayLen [a]
xs ((Int -> DevicePtr a -> IO b) -> IO b)
-> ((DevicePtr a -> IO b) -> Int -> DevicePtr a -> IO b)
-> (DevicePtr a -> IO b)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DevicePtr a -> IO b) -> Int -> DevicePtr a -> IO b
forall a b. a -> b -> a
const


-- |
-- A variant of 'withListArray' which also supplies the number of elements in
-- the array to the applied function
--
{-# INLINEABLE withListArrayLen #-}
withListArrayLen :: Storable a => [a] -> (Int -> DevicePtr a -> IO b) -> IO b
withListArrayLen :: [a] -> (Int -> DevicePtr a -> IO b) -> IO b
withListArrayLen ![a]
xs !Int -> DevicePtr a -> IO b
f =
  IO (DevicePtr a, Int)
-> ((DevicePtr a, Int) -> IO ())
-> ((DevicePtr a, Int) -> IO b)
-> IO b
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket ([a] -> IO (DevicePtr a, Int)
forall a. Storable a => [a] -> IO (DevicePtr a, Int)
newListArrayLen [a]
xs) (DevicePtr a -> IO ()
forall a. DevicePtr a -> IO ()
free (DevicePtr a -> IO ())
-> ((DevicePtr a, Int) -> DevicePtr a)
-> (DevicePtr a, Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DevicePtr a, Int) -> DevicePtr a
forall a b. (a, b) -> a
fst) ((DevicePtr a -> Int -> IO b) -> (DevicePtr a, Int) -> IO b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((DevicePtr a -> Int -> IO b) -> (DevicePtr a, Int) -> IO b)
-> ((Int -> DevicePtr a -> IO b) -> DevicePtr a -> Int -> IO b)
-> (Int -> DevicePtr a -> IO b)
-> (DevicePtr a, Int)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> DevicePtr a -> IO b) -> DevicePtr a -> Int -> IO b
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Int -> DevicePtr a -> IO b) -> (DevicePtr a, Int) -> IO b)
-> (Int -> DevicePtr a -> IO b) -> (DevicePtr a, Int) -> IO b
forall a b. (a -> b) -> a -> b
$ Int -> DevicePtr a -> IO b
f)
--
-- XXX: Will this attempt to double-free the device array on error (together
-- with newListArrayLen)?
--


--------------------------------------------------------------------------------
-- Utility
--------------------------------------------------------------------------------

-- |
-- Initialise device memory to a given 8-bit value
--
{-# INLINEABLE memset #-}
memset :: DevicePtr a                   -- ^ The device memory
       -> Int64                         -- ^ Number of bytes
       -> Int8                          -- ^ Value to set for each byte
       -> IO ()
memset :: DevicePtr a -> Int64 -> Int8 -> IO ()
memset !DevicePtr a
dptr !Int64
bytes !Int8
symbol = Status -> IO ()
nothingIfOk (Status -> IO ()) -> IO Status -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DevicePtr a -> Int8 -> Int64 -> IO Status
forall a. DevicePtr a -> Int8 -> Int64 -> IO Status
cudaMemset DevicePtr a
dptr Int8
symbol Int64
bytes

{-# INLINE cudaMemset #-}
cudaMemset :: (DevicePtr a) -> (Int8) -> (Int64) -> IO ((Status))
cudaMemset :: DevicePtr a -> Int8 -> Int64 -> IO Status
cudaMemset DevicePtr a
a1 Int8
a2 Int64
a3 =
  let {a1' :: Ptr a
a1' = DevicePtr a -> Ptr a
forall a a. DevicePtr a -> Ptr a
dptr DevicePtr a
a1} in 
  let {a2' :: CInt
a2' = Int8 -> CInt
forall a b. (Integral a, Integral b) => a -> b
cIntConv Int8
a2} in 
  let {a3' :: CULong
a3' = Int64 -> CULong
forall a b. (Integral a, Integral b) => a -> b
cIntConv Int64
a3} in 
  Ptr () -> CInt -> CULong -> IO CInt
cudaMemset'_ Ptr ()
forall b. Ptr b
a1' CInt
a2' CULong
a3' IO CInt -> (CInt -> IO Status) -> IO Status
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \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 643 "src/Foreign/CUDA/Runtime/Marshal.chs" #-}

  where
    dptr = useDevicePtr . castDevPtr


foreign import ccall unsafe "Foreign/CUDA/Runtime/Marshal.chs.h cudaHostAlloc"
  cudaHostAlloc'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (C2HSImp.CULong -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall unsafe "Foreign/CUDA/Runtime/Marshal.chs.h cudaFreeHost"
  cudaFreeHost'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Foreign/CUDA/Runtime/Marshal.chs.h cudaMalloc"
  cudaMalloc'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (C2HSImp.CULong -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/Runtime/Marshal.chs.h cudaFree"
  cudaFree'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Foreign/CUDA/Runtime/Marshal.chs.h cudaMallocManaged"
  cudaMallocManaged'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (C2HSImp.CULong -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Foreign/CUDA/Runtime/Marshal.chs.h cudaMemcpy"
  cudaMemcpy'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Foreign/CUDA/Runtime/Marshal.chs.h cudaMemcpyAsync"
  cudaMemcpyAsync'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))

foreign import ccall safe "Foreign/CUDA/Runtime/Marshal.chs.h cudaMemcpy2D"
  cudaMemcpy2D'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> (C2HSImp.CULong -> (C2HSImp.CULong -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))))

foreign import ccall safe "Foreign/CUDA/Runtime/Marshal.chs.h cudaMemcpy2DAsync"
  cudaMemcpy2DAsync'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> (C2HSImp.CULong -> (C2HSImp.CULong -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))

foreign import ccall unsafe "Foreign/CUDA/Runtime/Marshal.chs.h cudaMemset"
  cudaMemset'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CULong -> (IO C2HSImp.CInt))))