{-# LINE 1 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module HaskellWorks.Data.Json.Simd.Internal.Foreign where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Foreign
import System.IO.Unsafe
type UInt8 = (C2HSImp.CUChar)
{-# LINE 11 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
type UInt32 = (C2HSImp.CUInt)
{-# LINE 12 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
type UInt64 = (C2HSImp.CULong)
{-# LINE 13 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
type Size = (C2HSImp.CULong)
{-# LINE 14 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
enabled_avx_2 :: IO Int
enabled_avx_2 = fromIntegral <$> do
c_hw_json_simd_avx2_enabled
{-# LINE 18 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
{-# NOINLINE enabled_avx_2 #-}
enabled_sse_4_2 :: IO Int
enabled_sse_4_2 = fromIntegral <$> do
c_hw_json_simd_sse4_2_enabled
{-# LINE 23 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
{-# NOINLINE enabled_sse_4_2 #-}
enabled_bmi_2 :: IO Int
enabled_bmi_2 = fromIntegral <$> do
c_hw_json_simd_bmi2_enabled
{-# LINE 28 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
{-# NOINLINE enabled_bmi_2 #-}
processChunk :: ()
=> Ptr UInt8
-> Size
-> Ptr UInt8
-> Ptr UInt8
-> Ptr UInt8
-> Ptr UInt8
-> Ptr UInt8
-> Ptr UInt8
-> Ptr Size
-> Ptr Size
-> Ptr Size
-> Ptr UInt64
-> Ptr UInt8
-> Ptr UInt8
-> Ptr UInt8
-> IO UInt64
processChunk = do
c_hw_json_simd_process_chunk
{-# LINE 49 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
{-# INLINE processChunk #-}
initBpState :: ()
=> Ptr ()
-> IO ()
initBpState = c_hw_json_simd_init_bp_state
{-# LINE 55 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
{-# INLINE initBpState #-}
writeBpChunk :: ()
=> Ptr UInt8
-> Ptr UInt8
-> Ptr UInt8
-> Size
-> Ptr ()
-> Ptr UInt8
-> IO Size
writeBpChunk = c_hw_json_simd_write_bp_chunk
{-# LINE 66 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
{-# INLINE writeBpChunk #-}
writeBpChunkFinal :: ()
=> Ptr ()
-> Ptr UInt8
-> IO Size
writeBpChunkFinal = c_hw_json_simd_write_bp_chunk_final
{-# LINE 73 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
{-# INLINE writeBpChunkFinal #-}
smProcessChunk :: ()
=> Ptr UInt8
-> Size
-> Ptr UInt32
-> Ptr UInt32
-> IO ()
smProcessChunk = c_hw_json_simd_sm_process_chunk
{-# LINE 82 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
smMakeIbOpClChunks :: ()
=> UInt8
-> Ptr UInt32
-> Size
-> Ptr UInt8
-> Ptr UInt8
-> Ptr UInt8
-> IO ()
smMakeIbOpClChunks = c_hw_json_simd_sm_make_ib_op_cl_chunks
{-# LINE 92 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
smWriteBpChunk :: ()
=> Ptr UInt8
-> Ptr UInt8
-> Size
-> Ptr UInt64
-> Ptr Size
-> Ptr UInt64
-> IO Size
smWriteBpChunk = c_hw_json_simd_sm_write_bp_chunk
{-# LINE 102 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
smWriteBpChunkFinal :: ()
=> UInt64
-> Size
-> Ptr UInt64
-> IO Size
smWriteBpChunkFinal = c_hw_json_simd_sm_write_bp_chunk_final
{-# LINE 109 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_avx2_enabled"
c_hw_json_simd_avx2_enabled :: (IO C2HSImp.CInt)
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_sse4_2_enabled"
c_hw_json_simd_sse4_2_enabled :: (IO C2HSImp.CInt)
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_bmi2_enabled"
c_hw_json_simd_bmi2_enabled :: (IO C2HSImp.CInt)
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_process_chunk"
c_hw_json_simd_process_chunk :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO C2HSImp.CULong))))))))))))))))
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_init_bp_state"
c_hw_json_simd_init_bp_state :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_write_bp_chunk"
c_hw_json_simd_write_bp_chunk :: ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO C2HSImp.CULong)))))))
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_write_bp_chunk_final"
c_hw_json_simd_write_bp_chunk_final :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO C2HSImp.CULong)))
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_sm_process_chunk"
c_hw_json_simd_sm_process_chunk :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUInt) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO ())))))
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_sm_make_ib_op_cl_chunks"
c_hw_json_simd_sm_make_ib_op_cl_chunks :: (C2HSImp.CUChar -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (IO ())))))))
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_sm_write_bp_chunk"
c_hw_json_simd_sm_write_bp_chunk :: ((C2HSImp.Ptr C2HSImp.CUChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CULong)))))))
foreign import ccall unsafe "HaskellWorks/Data/Json/Simd/Internal/Foreign.chs.h hw_json_simd_sm_write_bp_chunk_final"
c_hw_json_simd_sm_write_bp_chunk_final :: (C2HSImp.CULong -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CULong))))