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


{-# 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



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

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

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

type Size   = (C2HSImp.CULong)
{-# LINE 13 "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 17 "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 22 "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 27 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}

{-# NOINLINE enabled_bmi_2 #-}

processChunk :: ()
  => Ptr UInt8    -- in_buffer
  -> Size         -- in_length
  -> Ptr UInt8    -- work_bits_of_d
  -> Ptr UInt8    -- work_bits_of_a
  -> Ptr UInt8    -- work_bits_of_z
  -> Ptr UInt8    -- work_bits_of_q
  -> Ptr UInt8    -- work_bits_of_b
  -> Ptr UInt8    -- work_bits_of_e
  -> Ptr Size     -- last_trailing_ones
  -> Ptr Size     -- quote_odds_carry
  -> Ptr Size     -- quote_evens_carry
  -> Ptr UInt64   -- quote_mask_carry
  -> Ptr UInt8    -- result_ibs
  -> Ptr UInt8    -- result_a
  -> Ptr UInt8    -- result_z
  -> IO UInt64
processChunk = do
  c_hw_json_simd_process_chunk
{-# LINE 48 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}

{-# INLINE processChunk #-}

initBpState :: ()
  => Ptr ()
  -> IO ()
initBpState = c_hw_json_simd_init_bp_state
{-# LINE 54 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}

{-# INLINE initBpState #-}

writeBpChunk :: ()
  => Ptr UInt8  -- result_ib
  -> Ptr UInt8  -- result_a
  -> Ptr UInt8  -- result_z
  -> Size       -- ib_bytes
  -> Ptr ()     -- bp_state
  -> Ptr UInt8  -- out_buffer
  -> IO Size
writeBpChunk = c_hw_json_simd_write_bp_chunk
{-# LINE 65 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}

{-# INLINE writeBpChunk #-}

writeBpChunkFinal :: ()
  => Ptr ()     -- bp_state
  -> Ptr UInt8  -- out_buffer
  -> IO Size
writeBpChunkFinal = c_hw_json_simd_write_bp_chunk_final
{-# LINE 72 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}

{-# INLINE writeBpChunkFinal #-}

smProcessChunk :: ()
  => Ptr UInt8    -- in_buffer
  -> Size         -- in_length
  -> Ptr UInt32   -- inout_state
  -> Ptr UInt32   -- out_phi_buffer
  -> IO ()
smProcessChunk = c_hw_json_simd_sm_process_chunk
{-# LINE 81 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}


smMakeIbOpClChunks :: ()
  => UInt8        -- state
  -> Ptr UInt32   -- in_phis
  -> Size         -- phi_length
  -> Ptr UInt8    -- out_ibs
  -> Ptr UInt8    -- out_ops
  -> Ptr UInt8    -- out_cls
  -> IO ()
smMakeIbOpClChunks = c_hw_json_simd_sm_make_ib_op_cl_chunks
{-# LINE 91 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}


smWriteBpChunk :: ()
  => Ptr UInt8    -- result_op
  -> Ptr UInt8    -- result_cl
  -> Size         -- ib_bytes
  -> Ptr UInt64   -- remaining_bp_bits
  -> Ptr Size     -- remaning_bp_bits_len
  -> Ptr UInt64   -- out_buffer
  -> IO Size
smWriteBpChunk = c_hw_json_simd_sm_write_bp_chunk
{-# LINE 101 "src/HaskellWorks/Data/Json/Simd/Internal/Foreign.chs" #-}


smWriteBpChunkFinal :: ()
  => UInt64       -- remaining_bits
  -> Size         -- remaining_bits_len
  -> Ptr UInt64   -- out_buffer
  -> IO Size
smWriteBpChunkFinal = c_hw_json_simd_sm_write_bp_chunk_final
{-# LINE 108 "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))))