{-# LANGUAGE BlockArguments #-} {-# LANGUAGE TupleSections #-} import Control.Concurrent (threadDelay) import Control.Monad (when) import Data.Int (Int16) import Foreign.C.String (peekCString, withCString) import qualified Foreign import qualified Sound.OpenAL.FFI.AL as AL import qualified Sound.OpenAL.FFI.ALC as ALC import Sound.OpenAL.FFI.Utils (peekCStrings) main :: IO () main = do extensions <- fmap words $ ALC.alcGetString ALC.nullDevice ALC.EXTENSIONS >>= peekCString putStrLn $ "ALC: " <> show extensions enumerationExt <- fmap (== 1) . withCString "ALC_ENUMERATION_EXT" $ ALC.alcIsExtensionPresent_ ALC.nullDevice putStrLn $ "Enumeration available: " <> show enumerationExt when enumerationExt do allDevices <- ALC.alcGetString ALC.nullDevice ALC.DEVICE_SPECIFIER >>= peekCStrings putStrLn $ "All devices: " <> show allDevices defaultDevice <- ALC.alcGetString ALC.nullDevice ALC.DEFAULT_DEVICE_SPECIFIER >>= peekCString putStrLn $ "Default device: " <> show defaultDevice device <- ALC.alcOpenDevice Foreign.nullPtr context <- ALC.alcCreateContext device Foreign.nullPtr ok <- fmap (== 1) $ ALC.alcMakeContextCurrent context putStrLn $ "Context OK: " <> show ok when ok do buf@(AL.Buffer bufId) <- Foreign.alloca \bufPtr -> do AL.alGenBuffers 1 bufPtr Foreign.peek bufPtr AL.alGetError >>= print . (buf,) Foreign.withArrayLen soundData \bufSize bufData -> AL.alBufferData buf AL.FORMAT_MONO16 (Foreign.castPtr bufData) (fromIntegral bufSize) 48000 AL.alGetError >>= print . (buf,) source <- Foreign.alloca \sourcePtr -> do AL.alGenSources 1 sourcePtr Foreign.peek sourcePtr AL.alGetError >>= print . (source,) AL.alSourcei source AL.BUFFER (fromIntegral bufId) -- XXX: unsigned to signed conversion AL.alGetError >>= print . (buf,) Foreign.with source $ AL.alSourcePlayv 1 threadDelay 1000000 Foreign.with source $ AL.alDeleteSources 1 Foreign.with buf $ AL.alDeleteBuffers 1 ALC.alcDestroyContext context ALC.alcCloseDevice device >>= print -- | Some funky sample soundData :: [Int16] soundData = map convert $ zipWith (+) (sine 220) $ zipWith (*) (sine 440) (sine 3) where convert d = round $ range * 0.5 * d range = fromIntegral (maxBound :: Int16) duration = 10.0 rate = 48000 sine freq = take (round $ duration * rate) $ map sin [0.0 :: Double, step ..] where step = freq * 2 * pi / rate