[Haskell-cafe] Problem with OpenAL
Antoine Latter
aslatter at gmail.com
Sat Mar 22 12:13:54 EDT 2008
For those of you following along, you'll need:
> import qualified Sound.OpenAL as AL
> import Data.Maybe
> import Foreign.C.Types
> import Control.Monad
> import Control.Concurrent
> import Foreign.Storable
> import Foreign.Marshal.Alloc
when I run "playOpenAL 440" I get no sound, and the following is
repeatedly printed on the console:
waiting
0
1
waiting
0
1
waiting
0
1
waiting
0
1
What do you think should be happening?
-Antoine
2008/3/21 George Giorgidze <ggg at cs.nott.ac.uk>:
> I tried OpenAL binding (the one which is on the Hackage), but with no luck.
>
> I can not hear anything from speakers and also according to generated output
> on console it seems that "AL.play" never completes playback of a buffer as
> buffer remains registered as "unprocessed" in OpenAL context.
> Here is the piece of code. I am not getting any error messages from OpenAL
> library functions.
>
> playOpenAL :: Int -> IO ()
> playOpenAL sr = do
> mDevice <- AL.openDevice Nothing
> when (isNothing mDevice) $ error "opening OpenAL device"
> let device = fromJust mDevice
>
> mContext <- AL.createContext device [
> AL.Frequency (fromIntegral sr)
> , AL.Refresh (fromIntegral sr)
> ]
> when (isNothing mContext) $ error "creating OpenAL context"
> let context = fromJust mContext
> AL.currentContext AL.$= (Just context)
>
>
> let sampleNumber = 256
> bufSize = sampleNumber * (sizeOf (undefined :: CShort))
> buf2 <- mallocBytes bufSize
>
> -- here I am filling buf2 with noise ....
>
> [source] <- AL.genObjectNames 1
> [buffer] <- AL.genObjectNames 1
>
> let region = AL.MemoryRegion buf2 (fromIntegral bufSize)
> AL.bufferData buffer AL.$= (AL.BufferData region AL.Mono16 (fromIntegral
> sr))
>
>
> AL.queueBuffers source [buffer]
> AL.loopingMode source AL.$= AL.OneShot
>
> let waitForSource = do
> putStrLn "waiting"
> s <- AL.get (AL.buffersProcessed source)
> putStrLn $ show s
> s <- AL.get (AL.buffersQueued source)
> putStrLn $ show s
> state <- AL.get (AL.sourceState source)
> case state of
> AL.Playing -> do
> threadDelay 1024
> waitForSource
> _ -> return ()
>
> putStrLn "Start Playing ... "
> AL.play [source]
> waitForSource
>
>
> AL.currentContext AL.$= Nothing
> AL.destroyContext context
> b <- AL.closeDevice device
> when (not b) $ error "closing device"
>
>
> Is this library still maintained?
>
> Best, George
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
More information about the Haskell-Cafe
mailing list