{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveAnyClass #-}

-- | Interface to RtMidi
module Sound.RtMidi
  ( InputDevice
  , OutputDevice
  , IsDevice (getDeviceType)
  , DeviceType (..)
  , Api (..)
  , Error (..)
  , apiName
  , apiDisplayName
  , compiledApiByName
  , ready
  , compiledApis
  , openPort
  , openVirtualPort
  , closePort
  , portCount
  , portName
  , listPorts
  , findPort
  , defaultInput
  , createInput
  , setCallback
  , setUnsafeCallback
  , setForeignCallback
  , cancelCallback
  , ignoreTypes
  , getMessage
  , getMessageSized
  , getMessageMutable
  , defaultOutput
  , createOutput
  , sendMessage
  , currentApi
  ) where

import Control.DeepSeq (NFData)
import Control.Exception (Exception, throwIO)
import Control.Monad (unless, void)
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.IO.Unlift (MonadUnliftIO (..))
import Data.Coerce (coerce)
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Storable.Mutable as VSM
import Data.Word (Word8)
import Foreign (FunPtr, Ptr, Storable (..), alloca, allocaArray, nullPtr, peekArray)
import Foreign.C (CDouble (..), CInt (..), CSize, CString, CUChar (..), peekCString, withCString)
import Foreign.ForeignPtr (ForeignPtr, newForeignPtr, withForeignPtr)
import GHC.Generics (Generic)
import Sound.RtMidi.Foreign

-- The default message size (in bytes) expected from 'getMessage'
-- Mostly just needs to be bigger than the max MIDI message size, which is 3 bytes
-- However, sysex messages can be quite large, so you might have to use the 'getMessageSized' variant.
defaultMessageSize :: Int
defaultMessageSize :: Int
defaultMessageSize = Int
4

-- | Allows us to discriminate in/out functions in generic contexts
data DeviceType =
    InputDeviceType
  | OutputDeviceType
  deriving stock (DeviceType -> DeviceType -> Bool
(DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> Bool) -> Eq DeviceType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceType -> DeviceType -> Bool
$c/= :: DeviceType -> DeviceType -> Bool
== :: DeviceType -> DeviceType -> Bool
$c== :: DeviceType -> DeviceType -> Bool
Eq, Int -> DeviceType -> ShowS
[DeviceType] -> ShowS
DeviceType -> String
(Int -> DeviceType -> ShowS)
-> (DeviceType -> String)
-> ([DeviceType] -> ShowS)
-> Show DeviceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeviceType] -> ShowS
$cshowList :: [DeviceType] -> ShowS
show :: DeviceType -> String
$cshow :: DeviceType -> String
showsPrec :: Int -> DeviceType -> ShowS
$cshowsPrec :: Int -> DeviceType -> ShowS
Show, Eq DeviceType
Eq DeviceType
-> (DeviceType -> DeviceType -> Ordering)
-> (DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> DeviceType)
-> (DeviceType -> DeviceType -> DeviceType)
-> Ord DeviceType
DeviceType -> DeviceType -> Bool
DeviceType -> DeviceType -> Ordering
DeviceType -> DeviceType -> DeviceType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DeviceType -> DeviceType -> DeviceType
$cmin :: DeviceType -> DeviceType -> DeviceType
max :: DeviceType -> DeviceType -> DeviceType
$cmax :: DeviceType -> DeviceType -> DeviceType
>= :: DeviceType -> DeviceType -> Bool
$c>= :: DeviceType -> DeviceType -> Bool
> :: DeviceType -> DeviceType -> Bool
$c> :: DeviceType -> DeviceType -> Bool
<= :: DeviceType -> DeviceType -> Bool
$c<= :: DeviceType -> DeviceType -> Bool
< :: DeviceType -> DeviceType -> Bool
$c< :: DeviceType -> DeviceType -> Bool
compare :: DeviceType -> DeviceType -> Ordering
$ccompare :: DeviceType -> DeviceType -> Ordering
$cp1Ord :: Eq DeviceType
Ord, Int -> DeviceType
DeviceType -> Int
DeviceType -> [DeviceType]
DeviceType -> DeviceType
DeviceType -> DeviceType -> [DeviceType]
DeviceType -> DeviceType -> DeviceType -> [DeviceType]
(DeviceType -> DeviceType)
-> (DeviceType -> DeviceType)
-> (Int -> DeviceType)
-> (DeviceType -> Int)
-> (DeviceType -> [DeviceType])
-> (DeviceType -> DeviceType -> [DeviceType])
-> (DeviceType -> DeviceType -> [DeviceType])
-> (DeviceType -> DeviceType -> DeviceType -> [DeviceType])
-> Enum DeviceType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DeviceType -> DeviceType -> DeviceType -> [DeviceType]
$cenumFromThenTo :: DeviceType -> DeviceType -> DeviceType -> [DeviceType]
enumFromTo :: DeviceType -> DeviceType -> [DeviceType]
$cenumFromTo :: DeviceType -> DeviceType -> [DeviceType]
enumFromThen :: DeviceType -> DeviceType -> [DeviceType]
$cenumFromThen :: DeviceType -> DeviceType -> [DeviceType]
enumFrom :: DeviceType -> [DeviceType]
$cenumFrom :: DeviceType -> [DeviceType]
fromEnum :: DeviceType -> Int
$cfromEnum :: DeviceType -> Int
toEnum :: Int -> DeviceType
$ctoEnum :: Int -> DeviceType
pred :: DeviceType -> DeviceType
$cpred :: DeviceType -> DeviceType
succ :: DeviceType -> DeviceType
$csucc :: DeviceType -> DeviceType
Enum, DeviceType
DeviceType -> DeviceType -> Bounded DeviceType
forall a. a -> a -> Bounded a
maxBound :: DeviceType
$cmaxBound :: DeviceType
minBound :: DeviceType
$cminBound :: DeviceType
Bounded, (forall x. DeviceType -> Rep DeviceType x)
-> (forall x. Rep DeviceType x -> DeviceType) -> Generic DeviceType
forall x. Rep DeviceType x -> DeviceType
forall x. DeviceType -> Rep DeviceType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeviceType x -> DeviceType
$cfrom :: forall x. DeviceType -> Rep DeviceType x
Generic)
  deriving anyclass (DeviceType -> ()
(DeviceType -> ()) -> NFData DeviceType
forall a. (a -> ()) -> NFData a
rnf :: DeviceType -> ()
$crnf :: DeviceType -> ()
NFData)

newtype Device = Device { Device -> ForeignPtr Wrapper
unDevice :: ForeignPtr Wrapper }
  deriving stock (Device -> Device -> Bool
(Device -> Device -> Bool)
-> (Device -> Device -> Bool) -> Eq Device
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Device -> Device -> Bool
$c/= :: Device -> Device -> Bool
== :: Device -> Device -> Bool
$c== :: Device -> Device -> Bool
Eq, Int -> Device -> ShowS
[Device] -> ShowS
Device -> String
(Int -> Device -> ShowS)
-> (Device -> String) -> ([Device] -> ShowS) -> Show Device
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Device] -> ShowS
$cshowList :: [Device] -> ShowS
show :: Device -> String
$cshow :: Device -> String
showsPrec :: Int -> Device -> ShowS
$cshowsPrec :: Int -> Device -> ShowS
Show)

-- | Generalizes 'InputDevice' and 'OutputDevice' for use in common functions
class IsDevice d where
  toDevice :: d -> Device
  getDeviceType :: d -> DeviceType

-- | A handle to a device to be used for input
newtype InputDevice = InputDevice { InputDevice -> Device
unInputDevice :: Device }
  deriving stock (InputDevice -> InputDevice -> Bool
(InputDevice -> InputDevice -> Bool)
-> (InputDevice -> InputDevice -> Bool) -> Eq InputDevice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputDevice -> InputDevice -> Bool
$c/= :: InputDevice -> InputDevice -> Bool
== :: InputDevice -> InputDevice -> Bool
$c== :: InputDevice -> InputDevice -> Bool
Eq, Int -> InputDevice -> ShowS
[InputDevice] -> ShowS
InputDevice -> String
(Int -> InputDevice -> ShowS)
-> (InputDevice -> String)
-> ([InputDevice] -> ShowS)
-> Show InputDevice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputDevice] -> ShowS
$cshowList :: [InputDevice] -> ShowS
show :: InputDevice -> String
$cshow :: InputDevice -> String
showsPrec :: Int -> InputDevice -> ShowS
$cshowsPrec :: Int -> InputDevice -> ShowS
Show)

instance IsDevice InputDevice where
  toDevice :: InputDevice -> Device
toDevice = InputDevice -> Device
unInputDevice
  getDeviceType :: InputDevice -> DeviceType
getDeviceType InputDevice
_ = DeviceType
InputDeviceType

newInputDevice :: Ptr Wrapper -> IO InputDevice
newInputDevice :: Ptr Wrapper -> IO InputDevice
newInputDevice = (ForeignPtr Wrapper -> InputDevice)
-> IO (ForeignPtr Wrapper) -> IO InputDevice
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Device -> InputDevice
InputDevice (Device -> InputDevice)
-> (ForeignPtr Wrapper -> Device)
-> ForeignPtr Wrapper
-> InputDevice
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Wrapper -> Device
Device) (IO (ForeignPtr Wrapper) -> IO InputDevice)
-> (Ptr Wrapper -> IO (ForeignPtr Wrapper))
-> Ptr Wrapper
-> IO InputDevice
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FinalizerPtr Wrapper -> Ptr Wrapper -> IO (ForeignPtr Wrapper)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Wrapper
rtmidi_in_free

-- | A handle to a device to be used for input
newtype OutputDevice = OutputDevice { OutputDevice -> Device
unOutputDevice :: Device }
  deriving stock (OutputDevice -> OutputDevice -> Bool
(OutputDevice -> OutputDevice -> Bool)
-> (OutputDevice -> OutputDevice -> Bool) -> Eq OutputDevice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputDevice -> OutputDevice -> Bool
$c/= :: OutputDevice -> OutputDevice -> Bool
== :: OutputDevice -> OutputDevice -> Bool
$c== :: OutputDevice -> OutputDevice -> Bool
Eq, Int -> OutputDevice -> ShowS
[OutputDevice] -> ShowS
OutputDevice -> String
(Int -> OutputDevice -> ShowS)
-> (OutputDevice -> String)
-> ([OutputDevice] -> ShowS)
-> Show OutputDevice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputDevice] -> ShowS
$cshowList :: [OutputDevice] -> ShowS
show :: OutputDevice -> String
$cshow :: OutputDevice -> String
showsPrec :: Int -> OutputDevice -> ShowS
$cshowsPrec :: Int -> OutputDevice -> ShowS
Show)

instance IsDevice OutputDevice where
  toDevice :: OutputDevice -> Device
toDevice = OutputDevice -> Device
unOutputDevice
  getDeviceType :: OutputDevice -> DeviceType
getDeviceType OutputDevice
_ = DeviceType
OutputDeviceType

newOutputDevice :: Ptr Wrapper -> IO OutputDevice
newOutputDevice :: Ptr Wrapper -> IO OutputDevice
newOutputDevice = (ForeignPtr Wrapper -> OutputDevice)
-> IO (ForeignPtr Wrapper) -> IO OutputDevice
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Device -> OutputDevice
OutputDevice (Device -> OutputDevice)
-> (ForeignPtr Wrapper -> Device)
-> ForeignPtr Wrapper
-> OutputDevice
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Wrapper -> Device
Device) (IO (ForeignPtr Wrapper) -> IO OutputDevice)
-> (Ptr Wrapper -> IO (ForeignPtr Wrapper))
-> Ptr Wrapper
-> IO OutputDevice
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FinalizerPtr Wrapper -> Ptr Wrapper -> IO (ForeignPtr Wrapper)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Wrapper
rtmidi_out_free

-- | An internal RtMidi error
newtype Error = Error { Error -> String
unError :: String }
  deriving stock (Error -> Error -> Bool
(Error -> Error -> Bool) -> (Error -> Error -> Bool) -> Eq Error
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Error -> Error -> Bool
$c/= :: Error -> Error -> Bool
== :: Error -> Error -> Bool
$c== :: Error -> Error -> Bool
Eq, Int -> Error -> ShowS
[Error] -> ShowS
Error -> String
(Int -> Error -> ShowS)
-> (Error -> String) -> ([Error] -> ShowS) -> Show Error
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Error] -> ShowS
$cshowList :: [Error] -> ShowS
show :: Error -> String
$cshow :: Error -> String
showsPrec :: Int -> Error -> ShowS
$cshowsPrec :: Int -> Error -> ShowS
Show, (forall x. Error -> Rep Error x)
-> (forall x. Rep Error x -> Error) -> Generic Error
forall x. Rep Error x -> Error
forall x. Error -> Rep Error x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Error x -> Error
$cfrom :: forall x. Error -> Rep Error x
Generic)
  deriving anyclass (Error -> ()
(Error -> ()) -> NFData Error
forall a. (a -> ()) -> NFData a
rnf :: Error -> ()
$crnf :: Error -> ()
NFData)

instance Exception Error

-- Detects and throws internal errors
guardError :: Ptr Wrapper -> IO ()
guardError :: Ptr Wrapper -> IO ()
guardError Ptr Wrapper
dptr = do
  Wrapper
w <- Ptr Wrapper -> IO Wrapper
forall a. Storable a => Ptr a -> IO a
peek Ptr Wrapper
dptr
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Wrapper -> Bool
ok Wrapper
w) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    String
e <- CString -> IO String
peekCString (Wrapper -> CString
msg Wrapper
w)
    Error -> IO ()
forall e a. Exception e => e -> IO a
throwIO (String -> Error
Error String
e)

-- Operate on the underlying device ptr
withDevicePtrUnguarded :: IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtrUnguarded :: d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtrUnguarded = ForeignPtr Wrapper -> (Ptr Wrapper -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ForeignPtr Wrapper -> (Ptr Wrapper -> IO a) -> IO a)
-> (d -> ForeignPtr Wrapper) -> d -> (Ptr Wrapper -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Device -> ForeignPtr Wrapper
unDevice (Device -> ForeignPtr Wrapper)
-> (d -> Device) -> d -> ForeignPtr Wrapper
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Device
forall d. IsDevice d => d -> Device
toDevice

-- Operate on the underlying device ptr and guard for errors
withDevicePtr :: IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr :: d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr d
d Ptr Wrapper -> IO a
f = d -> (Ptr Wrapper -> IO a) -> IO a
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtrUnguarded d
d (\Ptr Wrapper
dptr -> Ptr Wrapper -> IO a
f Ptr Wrapper
dptr IO a -> IO () -> IO a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Ptr Wrapper -> IO ()
guardError Ptr Wrapper
dptr)

-- | Get the display name for the given 'Api'.
apiDisplayName :: MonadIO m => Api -> m String
apiDisplayName :: Api -> m String
apiDisplayName Api
api = IO String -> m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ApiInternal -> IO CString
rtmidi_api_display_name (Api -> ApiInternal
fromApi Api
api) IO CString -> (CString -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO String
peekCString)

-- | Get the internal name for the given 'Api'.
apiName :: MonadIO m => Api -> m String
apiName :: Api -> m String
apiName Api
api = IO String -> m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ApiInternal -> IO CString
rtmidi_api_name (Api -> ApiInternal
fromApi Api
api) IO CString -> (CString -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO String
peekCString)

-- | Lookup a compiled 'Api' by name.
compiledApiByName :: MonadIO m => String -> m Api
compiledApiByName :: String -> m Api
compiledApiByName String
name = IO Api -> m Api
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((ApiInternal -> Api) -> IO ApiInternal -> IO Api
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ApiInternal -> Api
toApi (String -> (CString -> IO ApiInternal) -> IO ApiInternal
forall a. String -> (CString -> IO a) -> IO a
withCString String
name CString -> IO ApiInternal
rtmidi_compiled_api_by_name))

-- | Check if a device is ok
ready :: (MonadIO m, IsDevice d) => d -> m Bool
ready :: d -> m Bool
ready d
d = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (d -> (Ptr Wrapper -> IO Bool) -> IO Bool
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr d
d ((Wrapper -> Bool) -> IO Wrapper -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Wrapper -> Bool
ok (IO Wrapper -> IO Bool)
-> (Ptr Wrapper -> IO Wrapper) -> Ptr Wrapper -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Wrapper -> IO Wrapper
forall a. Storable a => Ptr a -> IO a
peek))

-- | A static function to determine MIDI 'Api's built in.
compiledApis :: MonadIO m => m [Api]
compiledApis :: m [Api]
compiledApis = IO [Api] -> m [Api]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Api] -> m [Api]) -> IO [Api] -> m [Api]
forall a b. (a -> b) -> a -> b
$ do
  Int
n <- (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Ptr ApiInternal -> CUInt -> IO CInt
rtmidi_get_compiled_api Ptr ApiInternal
forall a. Ptr a
nullPtr CUInt
0)
  [ApiInternal]
as <- Int -> (Ptr ApiInternal -> IO [ApiInternal]) -> IO [ApiInternal]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
n ((Ptr ApiInternal -> IO [ApiInternal]) -> IO [ApiInternal])
-> (Ptr ApiInternal -> IO [ApiInternal]) -> IO [ApiInternal]
forall a b. (a -> b) -> a -> b
$ \Ptr ApiInternal
ptr -> do
    Ptr ApiInternal -> CUInt -> IO CInt
rtmidi_get_compiled_api Ptr ApiInternal
ptr (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
    Int -> Ptr ApiInternal -> IO [ApiInternal]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
n Ptr ApiInternal
ptr
  [Api] -> IO [Api]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ApiInternal -> Api) -> [ApiInternal] -> [Api]
forall a b. (a -> b) -> [a] -> [b]
map ApiInternal -> Api
toApi [ApiInternal]
as)

-- | Open a MIDI connection
openPort :: (MonadIO m, IsDevice d)
         => d
         -> Int          -- ^ port number
         -> String       -- ^ name for the application port that is used
         -> m ()
openPort :: d -> Int -> String -> m ()
openPort d
d Int
n String
name = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ d -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr d
d ((Ptr Wrapper -> IO ()) -> IO ())
-> (Ptr Wrapper -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr ->
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
name (Ptr Wrapper -> CUInt -> CString -> IO ()
rtmidi_open_port Ptr Wrapper
dptr (Int -> CUInt
forall a. Enum a => Int -> a
toEnum Int
n))

-- | This function creates a virtual MIDI output port to which other software applications can connect.
--
-- This type of functionality is currently only supported by the Macintosh OS X, Linux ALSA and JACK APIs
-- (the function does nothing with the other APIs).
openVirtualPort :: (MonadIO m, IsDevice d) => d -> String -> m ()
openVirtualPort :: d -> String -> m ()
openVirtualPort d
d String
name = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ d -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr d
d ((Ptr Wrapper -> IO ()) -> IO ())
-> (Ptr Wrapper -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr -> do
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
name (Ptr Wrapper -> CString -> IO ()
rtmidi_open_virtual_port Ptr Wrapper
dptr)

-- | Close an open MIDI connection (if one exists).
closePort :: (MonadIO m, IsDevice d) => d -> m ()
closePort :: d -> m ()
closePort d
d = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (d -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr d
d Ptr Wrapper -> IO ()
rtmidi_close_port)

-- | Return the number of MIDI ports available to the 'Device'.
portCount :: (MonadIO m, IsDevice d) => d -> m Int
portCount :: d -> m Int
portCount d
d = IO Int -> m Int
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int) -> IO Int -> m Int
forall a b. (a -> b) -> a -> b
$ d -> (Ptr Wrapper -> IO Int) -> IO Int
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr d
d ((Ptr Wrapper -> IO Int) -> IO Int)
-> (Ptr Wrapper -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr -> do
  CUInt
x <- Ptr Wrapper -> IO CUInt
rtmidi_get_port_count Ptr Wrapper
dptr
  Int -> IO Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
x)

-- | Return a string identifier for the specified MIDI port number.
--
-- 'Nothing' is returned if an invalid port specifier is provided.
portName :: (MonadIO m, IsDevice d) => d -> Int -> m (Maybe String)
portName :: d -> Int -> m (Maybe String)
portName d
d Int
n = IO (Maybe String) -> m (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> m (Maybe String))
-> IO (Maybe String) -> m (Maybe String)
forall a b. (a -> b) -> a -> b
$ d -> (Ptr Wrapper -> IO (Maybe String)) -> IO (Maybe String)
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtrUnguarded d
d ((Ptr Wrapper -> IO (Maybe String)) -> IO (Maybe String))
-> (Ptr Wrapper -> IO (Maybe String)) -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr -> do
  CString
x <- Ptr Wrapper -> CUInt -> IO CString
rtmidi_get_port_name Ptr Wrapper
dptr (Int -> CUInt
forall a. Enum a => Int -> a
toEnum Int
n)
  Ptr Wrapper -> IO ()
guardError Ptr Wrapper
dptr
  String
s <- CString -> IO String
peekCString CString
x
  case String
s of
    [] -> Maybe String -> IO (Maybe String)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing
    String
_ -> Maybe String -> IO (Maybe String)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Maybe String
forall a. a -> Maybe a
Just String
s)

-- | Convenience function to list ports.
--
-- Note that the underlying library does not offer an "atomic" interface for this
-- so results may be inconsistent if you connect/disconnect ports during this call.
listPorts :: (MonadIO m, IsDevice d) => d -> m [(Int, String)]
listPorts :: d -> m [(Int, String)]
listPorts d
d = IO [(Int, String)] -> m [(Int, String)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [(Int, String)] -> m [(Int, String)])
-> IO [(Int, String)] -> m [(Int, String)]
forall a b. (a -> b) -> a -> b
$ d -> IO Int
forall (m :: * -> *) d. (MonadIO m, IsDevice d) => d -> m Int
portCount d
d IO Int -> (Int -> IO [(Int, String)]) -> IO [(Int, String)]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [(Int, String)] -> Int -> Int -> IO [(Int, String)]
forall (f :: * -> *).
MonadIO f =>
[(Int, String)] -> Int -> Int -> f [(Int, String)]
go [] Int
0 where
  go :: [(Int, String)] -> Int -> Int -> f [(Int, String)]
go [(Int, String)]
acc Int
i Int
c =
    if Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
c
      then [(Int, String)] -> f [(Int, String)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Int, String)] -> [(Int, String)]
forall a. [a] -> [a]
reverse [(Int, String)]
acc)
      else do
        Maybe String
mn <- d -> Int -> f (Maybe String)
forall (m :: * -> *) d.
(MonadIO m, IsDevice d) =>
d -> Int -> m (Maybe String)
portName d
d Int
i
        let acc' :: [(Int, String)]
acc' = [(Int, String)]
-> (String -> [(Int, String)]) -> Maybe String -> [(Int, String)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [(Int, String)]
acc (\String
n -> (Int
i, String
n)(Int, String) -> [(Int, String)] -> [(Int, String)]
forall a. a -> [a] -> [a]
:[(Int, String)]
acc) Maybe String
mn
        [(Int, String)] -> Int -> Int -> f [(Int, String)]
go [(Int, String)]
acc' (Int -> Int
forall a. Enum a => a -> a
succ Int
i) Int
c

-- | Convenience function to lookup the first port satisfying the predicate.
--
-- You may want to find an exact name:
--
-- > findPort d (== name)
--
-- Or you may want to match part of a name:
--
-- > findPort d (isInfixOf name)
--
-- Note that if you are performing many lookups, it's better to use 'listPorts' and
-- do the lookups yourself (see the caveats there too).
findPort :: (MonadIO m, IsDevice d) => d -> (String -> Bool) -> m (Maybe Int)
findPort :: d -> (String -> Bool) -> m (Maybe Int)
findPort d
d String -> Bool
f = IO (Maybe Int) -> m (Maybe Int)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Int) -> m (Maybe Int))
-> IO (Maybe Int) -> m (Maybe Int)
forall a b. (a -> b) -> a -> b
$ d -> IO Int
forall (m :: * -> *) d. (MonadIO m, IsDevice d) => d -> m Int
portCount d
d IO Int -> (Int -> IO (Maybe Int)) -> IO (Maybe Int)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Int -> IO (Maybe Int)
forall (f :: * -> *). MonadIO f => Int -> Int -> f (Maybe Int)
go Int
0 where
  go :: Int -> Int -> f (Maybe Int)
go Int
i Int
c =
    if Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
c
      then Maybe Int -> f (Maybe Int)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Int
forall a. Maybe a
Nothing
      else do
        Maybe String
mn <- d -> Int -> f (Maybe String)
forall (m :: * -> *) d.
(MonadIO m, IsDevice d) =>
d -> Int -> m (Maybe String)
portName d
d Int
i
        case Maybe String
mn of
          Just String
n | String -> Bool
f String
n -> Maybe Int -> f (Maybe Int)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
i)
          Maybe String
_ -> Int -> Int -> f (Maybe Int)
go (Int -> Int
forall a. Enum a => a -> a
succ Int
i) Int
c

-- | Default constructor for a 'Device' to use for input.
defaultInput :: MonadIO m => m InputDevice
defaultInput :: m InputDevice
defaultInput = IO InputDevice -> m InputDevice
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputDevice -> m InputDevice)
-> IO InputDevice -> m InputDevice
forall a b. (a -> b) -> a -> b
$ do
  Ptr Wrapper
dptr <- IO (Ptr Wrapper)
rtmidi_in_create_default
  Ptr Wrapper -> IO ()
guardError Ptr Wrapper
dptr
  Ptr Wrapper -> IO InputDevice
newInputDevice Ptr Wrapper
dptr

-- | Create a new 'Device' to use for input.
createInput :: MonadIO m
            => Api        -- ^ API to use
            -> String     -- ^ client name
            -> Int        -- ^ size of the MIDI input queue
            -> m InputDevice
createInput :: Api -> String -> Int -> m InputDevice
createInput Api
api String
clientName Int
queueSizeLimit = IO InputDevice -> m InputDevice
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputDevice -> m InputDevice)
-> IO InputDevice -> m InputDevice
forall a b. (a -> b) -> a -> b
$ do
  Ptr Wrapper
dptr <- String -> (CString -> IO (Ptr Wrapper)) -> IO (Ptr Wrapper)
forall a. String -> (CString -> IO a) -> IO a
withCString String
clientName (\CString
str -> ApiInternal -> CString -> CUInt -> IO (Ptr Wrapper)
rtmidi_in_create (Api -> ApiInternal
fromApi Api
api) CString
str (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
queueSizeLimit))
  Ptr Wrapper -> IO ()
guardError Ptr Wrapper
dptr
  Ptr Wrapper -> IO InputDevice
newInputDevice Ptr Wrapper
dptr

foreign import ccall "wrapper"
  mkCallbackPointer :: (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()) -> IO (FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()))

adaptCallbackCTypes :: (Double -> VS.Vector Word8 -> IO ()) -> (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
adaptCallbackCTypes :: (Double -> Vector Word8 -> IO ())
-> CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()
adaptCallbackCTypes !Double -> Vector Word8 -> IO ()
f (CDouble !Double
t) Ptr CUChar
m CInt
s Ptr ()
_ = do
  Vector Word8
buf <- Int -> (Int -> IO Word8) -> IO (Vector Word8)
forall (m :: * -> *) a.
(Monad m, Storable a) =>
Int -> (Int -> m a) -> m (Vector a)
VS.generateM (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
s) (Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff (Ptr CUChar -> Ptr Word8
coerce Ptr CUChar
m))
  Double -> Vector Word8 -> IO ()
f Double
t Vector Word8
buf

adaptUnsafeCallbackCTypes :: (Double -> Ptr Word8 -> Int -> IO ()) -> (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
adaptUnsafeCallbackCTypes :: (Double -> Ptr Word8 -> Int -> IO ())
-> CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()
adaptUnsafeCallbackCTypes !Double -> Ptr Word8 -> Int -> IO ()
f (CDouble !Double
t) Ptr CUChar
m CInt
s Ptr ()
_ = Double -> Ptr Word8 -> Int -> IO ()
f Double
t (Ptr CUChar -> Ptr Word8
coerce Ptr CUChar
m) (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
s)

-- | Set a callback function to be invoked for incoming MIDI messages.
--
-- The callback function will be called whenever an incoming MIDI message is received.
-- While not absolutely necessary, it is best to set the callback function before opening a MIDI port to avoid leaving
-- some messages in the queue.
setCallback :: MonadUnliftIO m
            => InputDevice
            -> (Double -> VS.Vector Word8 -> m ())  -- ^ Function that takes a timestamp and a MIDI message as arguments
            -> m ()
setCallback :: InputDevice -> (Double -> Vector Word8 -> m ()) -> m ()
setCallback InputDevice
d Double -> Vector Word8 -> m ()
c = ((forall a. m a -> IO a) -> IO ()) -> m ()
forall (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. m a -> IO a) -> IO b) -> m b
withRunInIO (((forall a. m a -> IO a) -> IO ()) -> m ())
-> ((forall a. m a -> IO a) -> IO ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> IO a
run -> InputDevice -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr InputDevice
d ((Ptr Wrapper -> IO ()) -> IO ())
-> (Ptr Wrapper -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr -> do
  FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
f <- (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
-> IO (FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()))
mkCallbackPointer ((Double -> Vector Word8 -> IO ())
-> CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()
adaptCallbackCTypes (\Double
ts Vector Word8
bytes -> m () -> IO ()
forall a. m a -> IO a
run (Double -> Vector Word8 -> m ()
c Double
ts Vector Word8
bytes)))
  Ptr Wrapper
-> FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
-> Ptr ()
-> IO ()
rtmidi_in_set_callback Ptr Wrapper
dptr FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
f Ptr ()
forall a. Ptr a
nullPtr

-- | A variant of 'setCallback' that takes a raw pointer and length. It is unsafe to share or reference the pointer beyond the
-- scope of the callback, as the RtMidi-owned memory it references may have been changed or freed.
setUnsafeCallback :: MonadIO m
                  => InputDevice
                  -> (Double -> Ptr Word8 -> Int -> IO ())
                  -> m ()
setUnsafeCallback :: InputDevice -> (Double -> Ptr Word8 -> Int -> IO ()) -> m ()
setUnsafeCallback InputDevice
d Double -> Ptr Word8 -> Int -> IO ()
c = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ InputDevice -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr InputDevice
d ((Ptr Wrapper -> IO ()) -> IO ())
-> (Ptr Wrapper -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr -> do
  FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
f <- (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
-> IO (FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()))
mkCallbackPointer ((Double -> Ptr Word8 -> Int -> IO ())
-> CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ()
adaptUnsafeCallbackCTypes Double -> Ptr Word8 -> Int -> IO ()
c)
  Ptr Wrapper
-> FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
-> Ptr ()
-> IO ()
rtmidi_in_set_callback Ptr Wrapper
dptr FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
f Ptr ()
forall a. Ptr a
nullPtr

-- | Set a /foreign/ callback function to be invoked for incoming MIDI messages.
--
-- This variant allows you to set the callback to a C function pointer so we're not forced
-- to enter a Haskell wrapper every invocation.
setForeignCallback :: MonadIO m
                   => InputDevice
                   -> FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
                   -> Ptr () -- ^ Pointer to context that will be passed into the callback
                   -> m ()
setForeignCallback :: InputDevice
-> FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
-> Ptr ()
-> m ()
setForeignCallback InputDevice
d FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
f Ptr ()
ctx = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ InputDevice -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr InputDevice
d ((Ptr Wrapper -> IO ()) -> IO ())
-> (Ptr Wrapper -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr ->
  Ptr Wrapper
-> FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
-> Ptr ()
-> IO ()
rtmidi_in_set_callback Ptr Wrapper
dptr FunPtr (CDouble -> Ptr CUChar -> CInt -> Ptr () -> IO ())
f Ptr ()
ctx

-- | Cancel use of the current callback function (if one exists).
--
-- Subsequent incoming MIDI messages will be written to the queue and can be retrieved with the `getMessage` function.
cancelCallback :: MonadIO m => InputDevice -> m ()
cancelCallback :: InputDevice -> m ()
cancelCallback InputDevice
d = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (InputDevice -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr InputDevice
d Ptr Wrapper -> IO ()
rtmidi_in_cancel_callback)

-- | Specify whether certain MIDI message types should be queued or ignored during input.
--
-- By default, MIDI timing and active sensing messages are ignored during message input because of their
-- relative high data rates. MIDI sysex messages are ignored by default as well.
-- Variable values of 'True' imply that the respective message type will be ignored.
ignoreTypes :: MonadIO m
            => InputDevice
            -> Bool       -- ^ SysEx messages
            -> Bool       -- ^ Time messages
            -> Bool       -- ^ Sense messages
            -> m ()
ignoreTypes :: InputDevice -> Bool -> Bool -> Bool -> m ()
ignoreTypes InputDevice
d Bool
x Bool
y Bool
z = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (InputDevice -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtrUnguarded InputDevice
d (\Ptr Wrapper
dptr -> Ptr Wrapper -> Bool -> Bool -> Bool -> IO ()
rtmidi_in_ignore_types Ptr Wrapper
dptr Bool
x Bool
y Bool
z))

-- | Variant of 'getMessage' that allows you to fill a shared buffer, returning timestamp and size.
getMessageMutable :: MonadIO m => InputDevice -> VSM.IOVector Word8 -> m (Double, Int)
getMessageMutable :: InputDevice -> IOVector Word8 -> m (Double, Int)
getMessageMutable InputDevice
d IOVector Word8
buf = IO (Double, Int) -> m (Double, Int)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Int) -> m (Double, Int))
-> IO (Double, Int) -> m (Double, Int)
forall a b. (a -> b) -> a -> b
$ (Ptr CSize -> IO (Double, Int)) -> IO (Double, Int)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO (Double, Int)) -> IO (Double, Int))
-> (Ptr CSize -> IO (Double, Int)) -> IO (Double, Int)
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
s -> IOVector Word8
-> (Ptr Word8 -> IO (Double, Int)) -> IO (Double, Int)
forall a b. Storable a => IOVector a -> (Ptr a -> IO b) -> IO b
VSM.unsafeWith IOVector Word8
buf ((Ptr Word8 -> IO (Double, Int)) -> IO (Double, Int))
-> (Ptr Word8 -> IO (Double, Int)) -> IO (Double, Int)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
m -> InputDevice
-> (Ptr Wrapper -> IO (Double, Int)) -> IO (Double, Int)
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtrUnguarded InputDevice
d ((Ptr Wrapper -> IO (Double, Int)) -> IO (Double, Int))
-> (Ptr Wrapper -> IO (Double, Int)) -> IO (Double, Int)
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr -> do
  Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CSize
s (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IOVector Word8 -> Int
forall a s. Storable a => MVector s a -> Int
VSM.length IOVector Word8
buf))
  CDouble !Double
timestamp <- Ptr Wrapper -> Ptr (Ptr CUChar) -> Ptr CSize -> IO CDouble
rtmidi_in_get_message Ptr Wrapper
dptr (Ptr Word8 -> Ptr (Ptr CUChar)
coerce Ptr Word8
m) Ptr CSize
s
  Ptr Wrapper -> IO ()
guardError Ptr Wrapper
dptr
  CSize
csize <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
s
  let !size :: Int
size = CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
csize
  (Double, Int) -> IO (Double, Int)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Double
timestamp, Int
size)

-- | Variant of 'getMessage' that allows you to set message buffer size (typically for large sysex messages).
getMessageSized :: MonadIO m => InputDevice -> Int -> m (Double, VS.Vector Word8)
getMessageSized :: InputDevice -> Int -> m (Double, Vector Word8)
getMessageSized InputDevice
d Int
n = IO (Double, Vector Word8) -> m (Double, Vector Word8)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Vector Word8) -> m (Double, Vector Word8))
-> IO (Double, Vector Word8) -> m (Double, Vector Word8)
forall a b. (a -> b) -> a -> b
$ do
  IOVector Word8
buf <- Int -> IO (MVector (PrimState IO) Word8)
forall (m :: * -> *) a.
(PrimMonad m, Storable a) =>
Int -> m (MVector (PrimState m) a)
VSM.new Int
n
  (!Double
timestamp, !Int
size) <- InputDevice -> IOVector Word8 -> IO (Double, Int)
forall (m :: * -> *).
MonadIO m =>
InputDevice -> IOVector Word8 -> m (Double, Int)
getMessageMutable InputDevice
d IOVector Word8
buf
  Vector Word8
vec <- IOVector Word8
-> (Ptr Word8 -> IO (Vector Word8)) -> IO (Vector Word8)
forall a b. Storable a => IOVector a -> (Ptr a -> IO b) -> IO b
VSM.unsafeWith IOVector Word8
buf (Int -> (Int -> IO Word8) -> IO (Vector Word8)
forall (m :: * -> *) a.
(Monad m, Storable a) =>
Int -> (Int -> m a) -> m (Vector a)
VS.generateM Int
size ((Int -> IO Word8) -> IO (Vector Word8))
-> (Ptr Word8 -> Int -> IO Word8) -> Ptr Word8 -> IO (Vector Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff)
  (Double, Vector Word8) -> IO (Double, Vector Word8)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Double
timestamp, Vector Word8
vec)

-- | Return data bytes for the next available MIDI message in the input queue and the event delta-time in seconds.
--
-- This function returns immediately whether a new message is available or not.
-- A valid message is indicated by whether the list contains any elements.
-- Note that large sysex messages will be silently dropped! Use 'getMessageSized' or use a callback to get these safely.
getMessage :: MonadIO m => InputDevice -> m (Double, VS.Vector Word8)
getMessage :: InputDevice -> m (Double, Vector Word8)
getMessage InputDevice
d = IO (Double, Vector Word8) -> m (Double, Vector Word8)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (InputDevice -> Int -> IO (Double, Vector Word8)
forall (m :: * -> *).
MonadIO m =>
InputDevice -> Int -> m (Double, Vector Word8)
getMessageSized InputDevice
d Int
defaultMessageSize)

-- | Default constructor for a 'Device' to use for output.
defaultOutput :: MonadIO m => m OutputDevice
defaultOutput :: m OutputDevice
defaultOutput = IO OutputDevice -> m OutputDevice
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OutputDevice -> m OutputDevice)
-> IO OutputDevice -> m OutputDevice
forall a b. (a -> b) -> a -> b
$ do
  Ptr Wrapper
dptr <- IO (Ptr Wrapper)
rtmidi_out_create_default
  Ptr Wrapper -> IO ()
guardError Ptr Wrapper
dptr
  Ptr Wrapper -> IO OutputDevice
newOutputDevice Ptr Wrapper
dptr

-- | Create a new 'Device' to use for output.
createOutput :: MonadIO m
             => Api        -- ^ API to use
             -> String     -- ^ client name
             -> m OutputDevice
createOutput :: Api -> String -> m OutputDevice
createOutput Api
api String
clientName = IO OutputDevice -> m OutputDevice
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OutputDevice -> m OutputDevice)
-> IO OutputDevice -> m OutputDevice
forall a b. (a -> b) -> a -> b
$ do
  Ptr Wrapper
dptr <- String -> (CString -> IO (Ptr Wrapper)) -> IO (Ptr Wrapper)
forall a. String -> (CString -> IO a) -> IO a
withCString String
clientName (ApiInternal -> CString -> IO (Ptr Wrapper)
rtmidi_out_create (Api -> ApiInternal
fromApi Api
api))
  Ptr Wrapper -> IO ()
guardError Ptr Wrapper
dptr
  Ptr Wrapper -> IO OutputDevice
newOutputDevice Ptr Wrapper
dptr

-- | Immediately send a single message out an open MIDI output port.
sendMessage :: MonadIO m => OutputDevice -> VS.Vector Word8 -> m ()
sendMessage :: OutputDevice -> Vector Word8 -> m ()
sendMessage OutputDevice
d Vector Word8
buf = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Vector Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
VS.unsafeWith Vector Word8
buf ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
m -> OutputDevice -> (Ptr Wrapper -> IO ()) -> IO ()
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr OutputDevice
d ((Ptr Wrapper -> IO ()) -> IO ())
-> (Ptr Wrapper -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr ->
  IO CInt -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Ptr Wrapper -> Ptr CUChar -> CInt -> IO CInt
rtmidi_out_send_message Ptr Wrapper
dptr (Ptr Word8 -> Ptr CUChar
coerce Ptr Word8
m) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Word8 -> Int
forall a. Storable a => Vector a -> Int
VS.length Vector Word8
buf)))

-- | Returns the specifier for the MIDI 'Api' in use
currentApi :: MonadIO m => IsDevice d => d -> m Api
currentApi :: d -> m Api
currentApi d
d = IO Api -> m Api
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Api -> m Api) -> IO Api -> m Api
forall a b. (a -> b) -> a -> b
$ d -> (Ptr Wrapper -> IO Api) -> IO Api
forall d a. IsDevice d => d -> (Ptr Wrapper -> IO a) -> IO a
withDevicePtr d
d ((Ptr Wrapper -> IO Api) -> IO Api)
-> (Ptr Wrapper -> IO Api) -> IO Api
forall a b. (a -> b) -> a -> b
$ \Ptr Wrapper
dptr -> do
  ApiInternal
res <-
    case d -> DeviceType
forall d. IsDevice d => d -> DeviceType
getDeviceType d
d of
      DeviceType
InputDeviceType -> Ptr Wrapper -> IO ApiInternal
rtmidi_in_get_current_api Ptr Wrapper
dptr
      DeviceType
OutputDeviceType -> Ptr Wrapper -> IO ApiInternal
rtmidi_out_get_current_api Ptr Wrapper
dptr
  Api -> IO Api
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ApiInternal -> Api
toApi ApiInternal
res)