{-# LINE 1 "Sound/RtMidi/Foreign.hsc" #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ForeignFunctionInterface #-}

-- | FFI defs for RtMidi
module Sound.RtMidi.Foreign
  ( Wrapper (..)
  , rtmidi_close_port
  , rtmidi_get_compiled_api
  , rtmidi_get_port_count
  , rtmidi_get_port_name
  , rtmidi_in_cancel_callback
  , rtmidi_in_create
  , rtmidi_in_create_default
  , rtmidi_in_free
  , rtmidi_in_get_current_api
  , rtmidi_in_get_message
  , rtmidi_in_ignore_types
  , rtmidi_in_set_callback
  , rtmidi_open_port
  , rtmidi_open_virtual_port
  , rtmidi_out_create
  , rtmidi_out_create_default
  , rtmidi_out_free
  , rtmidi_out_get_current_api
  , rtmidi_out_send_message
  ) where



import Foreign (FunPtr, Ptr, Storable (..))
import Foreign.C (CDouble (..), CInt (..), CString, CSize, CUChar, CUInt (..))

data Wrapper = Wrapper
  { Wrapper -> Ptr ()
ptr :: !(Ptr ())
  , Wrapper -> Ptr ()
dat :: !(Ptr ())
  , Wrapper -> Bool
ok  :: !Bool
  , Wrapper -> CString
msg :: !CString
  } deriving (Wrapper -> Wrapper -> Bool
(Wrapper -> Wrapper -> Bool)
-> (Wrapper -> Wrapper -> Bool) -> Eq Wrapper
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Wrapper -> Wrapper -> Bool
$c/= :: Wrapper -> Wrapper -> Bool
== :: Wrapper -> Wrapper -> Bool
$c== :: Wrapper -> Wrapper -> Bool
Eq, Int -> Wrapper -> ShowS
[Wrapper] -> ShowS
Wrapper -> String
(Int -> Wrapper -> ShowS)
-> (Wrapper -> String) -> ([Wrapper] -> ShowS) -> Show Wrapper
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Wrapper] -> ShowS
$cshowList :: [Wrapper] -> ShowS
show :: Wrapper -> String
$cshow :: Wrapper -> String
showsPrec :: Int -> Wrapper -> ShowS
$cshowsPrec :: Int -> Wrapper -> ShowS
Show)

instance Storable Wrapper where
  sizeOf :: Wrapper -> Int
sizeOf _ = (32)
{-# LINE 42 "Sound/RtMidi/Foreign.hsc" #-}
  alignment _ = 8
{-# LINE 43 "Sound/RtMidi/Foreign.hsc" #-}
  poke ptr (Wrapper a b c d) = do
    (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr a
{-# LINE 45 "Sound/RtMidi/Foreign.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr b
{-# LINE 46 "Sound/RtMidi/Foreign.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 16) ptr c
{-# LINE 47 "Sound/RtMidi/Foreign.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 24) ptr d
{-# LINE 48 "Sound/RtMidi/Foreign.hsc" #-}
  peek ptr = do
    a <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 50 "Sound/RtMidi/Foreign.hsc" #-}
    b <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 51 "Sound/RtMidi/Foreign.hsc" #-}
    c <- (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 52 "Sound/RtMidi/Foreign.hsc" #-}
    d <- (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 53 "Sound/RtMidi/Foreign.hsc" #-}
    pure (Wrapper a b c d)

-- A parameter we'll be de/serializing from the 'Api' enum.
type ApiEnum = CInt

foreign import ccall "rtmidi_c.h rtmidi_close_port"
  rtmidi_close_port :: Ptr Wrapper -> IO ()

foreign import ccall "rtmidi_c.h rtmidi_get_compiled_api"
  rtmidi_get_compiled_api :: Ptr ApiEnum -> CUInt -> IO CInt

foreign import ccall "rtmidi_c.h rtmidi_get_port_count"
  rtmidi_get_port_count :: Ptr Wrapper -> IO CUInt

foreign import ccall "rtmidi_c.h rtmidi_get_port_name"
  rtmidi_get_port_name :: Ptr Wrapper -> CUInt -> IO CString

foreign import ccall "rtmidi_c.h rtmidi_in_cancel_callback"
  rtmidi_in_cancel_callback :: Ptr Wrapper -> IO ()

foreign import ccall "rtmidi_c.h rtmidi_in_create"
  rtmidi_in_create :: ApiEnum -> CString -> CUInt -> IO (Ptr Wrapper)

foreign import ccall "rtmidi_c.h rtmidi_in_create_default"
  rtmidi_in_create_default :: IO (Ptr Wrapper)

foreign import ccall "rtmidi_c.h &rtmidi_in_free"
  rtmidi_in_free :: FunPtr (Ptr Wrapper -> IO ())

foreign import ccall "rtmidi_c.h rtmidi_in_get_current_api"
  rtmidi_in_get_current_api :: Ptr Wrapper -> IO ApiEnum

foreign import ccall "rtmidi_c.h rtmidi_in_get_message"
  rtmidi_in_get_message :: Ptr Wrapper -> Ptr (Ptr CUChar) -> Ptr CSize -> IO CDouble

foreign import ccall "rtmidi_c.h rtmidi_in_ignore_types"
  rtmidi_in_ignore_types :: Ptr Wrapper -> Bool -> Bool -> Bool -> IO ()

foreign import ccall "rtmidi_c.h rtmidi_in_set_callback"
  rtmidi_in_set_callback :: Ptr Wrapper -> FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()) -> Ptr () -> IO ()

foreign import ccall "rtmidi_c.h rtmidi_open_port"
  rtmidi_open_port :: Ptr Wrapper -> CUInt -> CString -> IO ()

foreign import ccall "rtmidi_c.h rtmidi_open_virtual_port"
  rtmidi_open_virtual_port :: Ptr Wrapper -> CString -> IO ()

foreign import ccall "rtmidi_c.h rtmidi_out_create"
  rtmidi_out_create :: ApiEnum-> CString -> IO (Ptr Wrapper)

foreign import ccall "rtmidi_c.h rtmidi_out_create_default"
  rtmidi_out_create_default :: IO (Ptr Wrapper)

foreign import ccall "rtmidi_c.h &rtmidi_out_free"
  rtmidi_out_free :: FunPtr (Ptr Wrapper -> IO ())

foreign import ccall "rtmidi_c.h rtmidi_out_get_current_api"
  rtmidi_out_get_current_api :: Ptr Wrapper -> IO ApiEnum

foreign import ccall "rtmidi_c.h rtmidi_out_send_message"
  rtmidi_out_send_message :: Ptr Wrapper -> Ptr CUChar -> CInt -> IO CInt