module Sound.SC3.MIDI.Utility where import qualified Sound.ALSA.Sequencer.Client as Client import qualified Sound.ALSA.Sequencer.Port as Port import qualified Sound.ALSA.Sequencer.Event as Event import qualified Sound.ALSA.Sequencer as SndSeq import Control.Monad (liftM2, ) import System.IO.Unsafe (unsafeInterleaveIO, ) withInPort :: String -> String -> SndSeq.BlockMode -> (SndSeq.T SndSeq.InputMode -> Port.T -> IO a) -> IO a withInPort sequName portName blockMode act = SndSeq.with SndSeq.defaultName blockMode $ \h -> Client.setName h sequName >> Port.withSimple h portName (Port.caps [Port.capWrite, Port.capSubsWrite]) Port.typeMidiGeneric (act h) ioToLazyList :: IO a -> IO [a] ioToLazyList m = let go = unsafeInterleaveIO $ liftM2 (:) m go in go withEvents :: String -> String -> ([Event.T] -> IO a) -> IO a withEvents sequName portName act = withInPort sequName portName SndSeq.Block $ \sequ _p -> ioToLazyList (Event.input sequ) >>= act startMessage :: String startMessage = "use 'aconnect -i' to find out the ports from where note messages can be received\n" ++ "and connect the source with this program using 'aconnect' or 'patchage' or 'alsa-patch-bay'\n"