-- GENERATED by C->Haskell Compiler, version 0.28.1 Switcheroo, 1 April 2016 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/HaskellWorks/Data/Simd/Internal/Foreign.chs" #-}
{-# LANGUAGE CPP #-}

module HaskellWorks.Data.Simd.Internal.Foreign where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp



import Foreign
import HaskellWorks.Data.Simd.Capabilities



type UInt8  = (C2HSImp.CUChar)
{-# LINE 10 "src/HaskellWorks/Data/Simd/Internal/Foreign.chs" #-}

type UInt64 = (C2HSImp.CULong)
{-# LINE 11 "src/HaskellWorks/Data/Simd/Internal/Foreign.chs" #-}

type Size = (C2HSImp.CULong)
{-# LINE 12 "src/HaskellWorks/Data/Simd/Internal/Foreign.chs" #-}


avx2Memcpy :: Ptr UInt8 -> Ptr UInt8 -> Size -> IO ()
avx2Memcpy target source len = requireAvx2 $ do
  c_build_ibs target source len
{-# INLINE avx2Memcpy #-}

avx2Cmpeq8 :: UInt8 -> Ptr UInt8 -> Size -> Ptr UInt8 -> IO ()
avx2Cmpeq8 byte target targetLength source = requireAvx2 $ do
  c_cmpeq8 byte target targetLength source
{-# INLINE avx2Cmpeq8 #-}

avx2AndBits :: Ptr UInt8 -> Size -> Ptr UInt8 -> Ptr UInt8 -> IO ()
avx2AndBits target targetLength source_a source_b = requireAvx2 $ do
  c_avx2_and_bits target targetLength source_a source_b
{-# INLINE avx2AndBits #-}

avx2AndNotBits :: Ptr UInt8 -> Size -> Ptr UInt8 -> Ptr UInt8 -> IO ()
avx2AndNotBits target targetLength source_a source_b = requireAvx2 $ do
  c_avx2_and_not_bits target targetLength source_a source_b
{-# INLINE avx2AndNotBits #-}

avx2NotBits :: Ptr UInt8 -> Size -> Ptr UInt8 -> IO ()
avx2NotBits target targetLength source = requireAvx2 $ do
  c_avx2_not_bits target targetLength source
{-# INLINE avx2NotBits #-}

avx2OrBits :: Ptr UInt8 -> Size -> Ptr UInt8 -> Ptr UInt8 -> IO ()
avx2OrBits target targetLength source_a source_b = requireAvx2 $ do
  c_avx2_or_bits target targetLength source_a source_b
{-# INLINE avx2OrBits #-}

avx2XorBits :: Ptr UInt8 -> Size -> Ptr UInt8 -> Ptr UInt8 -> IO ()
avx2XorBits target targetLength source_a source_b = requireAvx2 $ do
  c_avx2_xor_bits target targetLength source_a source_b
{-# INLINE avx2XorBits #-}

foreign import ccall unsafe "HaskellWorks/Data/Simd/Internal/Foreign.chs.h avx2_memcpy"
  c_build_ibs :: ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> (IO ()))))

foreign import ccall unsafe "HaskellWorks/Data/Simd/Internal/Foreign.chs.h avx2_cmpeq8"
  c_cmpeq8 :: (C2HSImp.CUChar -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO ())))))

foreign import ccall unsafe "HaskellWorks/Data/Simd/Internal/Foreign.chs.h avx2_and_bits"
  c_avx2_and_bits :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO ())))))

foreign import ccall unsafe "HaskellWorks/Data/Simd/Internal/Foreign.chs.h avx2_and_not_bits"
  c_avx2_and_not_bits :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO ())))))

foreign import ccall unsafe "HaskellWorks/Data/Simd/Internal/Foreign.chs.h avx2_not_bits"
  c_avx2_not_bits :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO ()))))

foreign import ccall unsafe "HaskellWorks/Data/Simd/Internal/Foreign.chs.h avx2_or_bits"
  c_avx2_or_bits :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO ())))))

foreign import ccall unsafe "HaskellWorks/Data/Simd/Internal/Foreign.chs.h avx2_xor_bits"
  c_avx2_xor_bits :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO ())))))