/src/Player/OpenAL.hs

https://github.com/dancor/YampaSynth · Haskell · 183 lines · 144 code · 27 blank · 12 comment · 23 complexity · 9000af26303c89a7cf4cc413dc5431e2 MD5 · raw file

  1. {-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
  2. module Player.OpenAL (
  3. Player.OpenAL.play
  4. , initOpenAL
  5. , deInitOpenAL
  6. , frpSynth
  7. , Chunk (..)
  8. ) where
  9. import Data.Audio
  10. import FRP.Yampa
  11. import Sound.OpenAL
  12. import Data.Int()
  13. import Data.IORef
  14. import Foreign
  15. import Control.Concurrent
  16. import Control.Monad
  17. import Data.Maybe
  18. import Control.Applicative
  19. play :: Int -> Int -> Int -> SF () (Sample, Event ()) -> IO ()
  20. play sampleRate' sampleNumber' numBuffs sf = do
  21. (device,context,pSource,pBuffers) <- initOpenAL numBuffs
  22. frpSynth sampleRate' pSource pBuffers sampleNumber' sf () (return ())
  23. deInitOpenAL device context pSource pBuffers
  24. frpSynth :: Int -> Source -> [Buffer] -> Int -> SF a (Sample, Event b) -> a -> IO a -> IO ()
  25. frpSynth sampleRate' pSource pBuffers sampleNumber' sf ret senseEvt = do
  26. mVarMaybeChunk <- newEmptyMVar
  27. mVarReplyPlayer <- newEmptyMVar
  28. _ <- forkIO $ process sampleRate' pSource pBuffers [] mVarMaybeChunk mVarReplyPlayer
  29. ir <- newIORef (0 :: Int)
  30. chunkData' <- mallocArray sampleNumber'
  31. let sense = (\x -> (1.0 / fromIntegral sampleRate', x)) . Just <$> senseEvt -- ghc 6.12 required for TupleSections :(
  32. chunk = Chunk chunkData' sampleNumber'
  33. actuate _ (s,e) = if (isEvent e)
  34. then return True
  35. else do
  36. i <- readIORef ir
  37. let samp = fromSample s :: Int16 -- the only place we have to specify our sample representation
  38. when (i /= 0 || samp /= 0) $ do -- don't put leading zeros in a chunk
  39. pokeElemOff chunkData' i samp
  40. if i == (sampleNumber' - 1)
  41. then do
  42. putMVar mVarMaybeChunk $ Just chunk
  43. takeMVar mVarReplyPlayer
  44. writeIORef ir 0
  45. else writeIORef ir (i + 1)
  46. return False
  47. reactimate (return ret) (const sense) actuate sf
  48. i <- readIORef ir
  49. putMVar mVarMaybeChunk . Just $ chunk {numElems = i}
  50. takeMVar mVarReplyPlayer
  51. putMVar mVarMaybeChunk Nothing
  52. takeMVar mVarReplyPlayer
  53. free chunkData'
  54. initOpenAL :: Int -> IO (Device, Context, Source, [Buffer])
  55. initOpenAL numBuffs = do
  56. mDevice <- openDevice Nothing
  57. case mDevice of
  58. Nothing -> fail "opening OpenAL device"
  59. Just device -> do
  60. mContext <- createContext device []
  61. case mContext of
  62. Nothing -> fail "opening OpenAL context"
  63. Just context -> do
  64. currentContext $= Just context
  65. [pSource] <- genObjectNames 1
  66. pBuffers <- genObjectNames numBuffs
  67. printErrs
  68. return (device,context,pSource,pBuffers)
  69. deInitOpenAL :: Device -> Context -> Source -> [Buffer] -> IO ()
  70. deInitOpenAL device context pSource pBuffers = do
  71. dequeue pSource
  72. deleteObjectNames [pSource]
  73. deleteObjectNames pBuffers
  74. currentContext $= Nothing
  75. destroyContext context
  76. whenM (not <$> closeDevice device) $ fail "closing OpenAL device"
  77. printErrs
  78. data Chunkable a => Chunk a = Chunk {
  79. chunkData :: Ptr a
  80. , numElems :: Int
  81. } deriving (Eq, Show)
  82. -- does the Bits constraint basically guarantee that it's Integral?
  83. class (Storable a, Bits a, Audible a) => Chunkable a where
  84. instance (Storable a, Bits a, Audible a) => Chunkable a -- thx copumpkin @ #haskell
  85. -- from http://www.haskell.org/pipermail/beginners/2009-January/000690.html (via byorgey @ #haskell)
  86. untilM :: (Monad m) => (a -> Bool) -> (a -> m a) -> a -> m a
  87. untilM p f x | p x = return x
  88. | otherwise = f x >>= untilM p f
  89. lastInd :: (Chunkable a) => (a -> Bool) -> Chunk a -> IO (Maybe Int)
  90. lastInd p c = do
  91. (_,mInd) <- untilM (\(i,x) -> isJust x || i < 0)
  92. (\(i,_) -> do e <- peekElemOff (chunkData c) i
  93. return (i-1, if p e then Just i else Nothing)
  94. )
  95. (numElems c - 1,Nothing)
  96. return $ (+ 1) <$> mInd
  97. process :: (Chunkable a) => Int -> Source -> [Buffer] -> [Buffer] -> MVar (Maybe (Chunk a)) -> MVar () -> IO ()
  98. process sampleRate' pSource freeBuffers usedBuffers mVarMaybeChunk mVarReply = do
  99. mChunk <- takeMVar mVarMaybeChunk
  100. Foreign.void $ reply mChunk (\chunk -> do
  101. mInd <- lastInd (/= 0) chunk -- we aren't sent chunks with leading zeros
  102. (f,u) <- reply mInd (\ind -> do
  103. (buff,newFree,newUsed) <- if null freeBuffers
  104. then do waitForBuffer pSource
  105. let b = head usedBuffers
  106. unqueueBuffers pSource [b]
  107. return (b,[],tail usedBuffers ++ [b])
  108. else do let h = head freeBuffers
  109. return (h, tail freeBuffers, usedBuffers ++ [h])
  110. ((bufferData buff) $=) =<< createBufferData sampleRate' chunk ind
  111. _ <- reply Nothing undefined
  112. queueBuffers pSource [buff]
  113. whenM ((/= Playing) <$> (get $ sourceState pSource)) $ Sound.OpenAL.play [pSource]
  114. printErrs
  115. return (newFree,newUsed)
  116. )
  117. process sampleRate' pSource f u mVarMaybeChunk mVarReply
  118. return (undefined,undefined)
  119. )
  120. dequeue pSource
  121. where reply = flip . maybe $ putMVar mVarReply undefined >> return (freeBuffers,usedBuffers)
  122. printErrs :: IO ()
  123. printErrs = do e <- get alErrors
  124. when (not $ null e) . putStrLn $ show e
  125. dequeue :: Source -> IO ()
  126. dequeue pSource = waitForSource pSource >> buffer pSource $= Nothing
  127. createBufferData :: (Chunkable a) => Int -> Chunk a -> Int -> IO (BufferData a)
  128. createBufferData sampleRate' chunk n = do
  129. ex <- peekElemOff (chunkData chunk) 0
  130. let elemSize = sizeOf ex
  131. format = case elemSize of
  132. 2 -> Mono16
  133. 1 -> Mono8
  134. _ -> error "1 or 2 byte buffer required"
  135. when (not $ isSigned ex) $ fail "signed buffer required" -- how enforce these statically?
  136. return $ BufferData (MemoryRegion (chunkData chunk) (fromIntegral $ n * elemSize))
  137. format
  138. (fromIntegral sampleRate')
  139. {-
  140. untilM_ :: (Functor m, Monad m) => (a -> Bool) -> m a -> m ()
  141. -- untilM_ p f = void $ untilM p (const f) undefined -- isn't there something in this spirit?
  142. untilM_ p f = do b <- p <$> f
  143. if b then return () else untilM_ p f
  144. void :: (Monad m) => m a -> m ()
  145. void = (>> return ())
  146. -}
  147. waitForBuffer :: Source -> IO () -- better to express using untilM_
  148. waitForBuffer s = do b <- (> 0) <$> (get $ buffersProcessed s)
  149. if b then return () else threadDelay 10 >> waitForBuffer s
  150. whenM :: (Monad m, Functor m) => m Bool -> m () -> m ()
  151. whenM test action = join $ flip when action <$> test
  152. waitForSource :: Source -> IO ()
  153. waitForSource pSource = whenM ((== Playing) <$> (get $ sourceState pSource)) delWait
  154. where delWait = do threadDelay 10 -- micro seconds
  155. waitForSource pSource