{-# LANGUAGE CPP #-}
{-# LANGUAGE UnboxedTuples #-}
module Raehik.Compat.GHC.Exts.GHC908MemcpyPrimops
( copyAddrToAddrNonOverlapping#
, setAddrRange#
) where
import GHC.Exts
#if MIN_VERSION_base(4,19,0)
#else
import GHC.IO ( unIO )
import Foreign.Marshal.Utils ( copyBytes, fillBytes )
copyAddrToAddrNonOverlapping#
:: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
copyAddrToAddrNonOverlapping# Addr#
src# Addr#
dest# Int#
len# State# RealWorld
s# =
case IO () -> State# RealWorld -> (# State# RealWorld, () #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (Ptr Any -> Ptr Any -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes (Addr# -> Ptr Any
forall a. Addr# -> Ptr a
Ptr Addr#
dest#) (Addr# -> Ptr Any
forall a. Addr# -> Ptr a
Ptr Addr#
src#) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int# -> Int
I# Int#
len#))) State# RealWorld
s# of
(# State# RealWorld
s'#, () #) -> State# RealWorld
s'#
setAddrRange#
:: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld
setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld
setAddrRange# Addr#
dest# Int#
w# Int#
len# State# RealWorld
s0 =
case IO () -> State# RealWorld -> (# State# RealWorld, () #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (Ptr Any -> Word8 -> Int -> IO ()
forall a. Ptr a -> Word8 -> Int -> IO ()
fillBytes (Addr# -> Ptr Any
forall a. Addr# -> Ptr a
Ptr Addr#
dest#) (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int# -> Int
I# Int#
w#)) (Int# -> Int
I# Int#
len#)) State# RealWorld
s0 of
(# State# RealWorld
s1, () #) -> State# RealWorld
s1
#endif