module Sound.UI.ALURE.Raw ( -- * Main and Miscellanious getVersion, getErrorString, getDeviceNames, initDevice, shutdownDevice, -- * File Loading createBufferFromFile, bufferDataFromFile, -- * Streaming ) where import Sound.UI.ALURE.Internal import Sound.UI.ALURE.Marshal import Foreign.Marshal.Alloc import Foreign.C.String import Foreign.Ptr import Foreign.Storable import Foreign.Marshal.Array import Control.Monad import Sound.OpenAL.ALC.Device() import Sound.OpenAL.ALC.Context import Sound.OpenAL.AL.Buffer -------------------------------------------------------------------------------- -- Main and Miscellanious -- | Gets major and minor version of ALURE C library, if provided. getVersion :: IO (Maybe Int, Maybe Int) getVersion = do alloca $ \pMajor -> do alloca $ \pMinor -> do c_alureGetVersion pMajor pMinor a <- if pMajor == nullPtr then return Nothing else liftM (Just . fromIntegral) (peek pMajor) b <- if pMinor == nullPtr then return Nothing else liftM (Just . fromIntegral) (peek pMinor) return (a, b) -- | Returns a string describing the last error encountered. getErrorString :: IO String getErrorString = do c_alureGetErrorString >>= peekCString -- | Gets a list of device names from OpenAL. This encapsulates AL_ENUMERATE_ALL_EXT -- (if supported and 'allExt' is true). getDeviceNames :: Bool -> IO (Maybe [String]) getDeviceNames allExt = do alloca $ \pCount -> do pStr <- c_alureGetDeviceNames (marshalBool allExt) pCount res <- if pStr == nullPtr then return Nothing else do count <- peek pCount liftM Just $ peekStrings (fromIntegral count) pStr c_alureFreeDeviceNames pStr return res where peekStrings len pStr = forM [0..len-1] $ \i -> do p <- peekElemOff pStr i peekCString p -- | Opens the named device, creates a context with the given attributes, and sets that -- context as current. 'name' and 'attrs' would be the same as what's passed to 'openDevice' -- and 'createContext' respectively. initDevice :: Maybe String -> [ContextAttribute] -> IO Bool initDevice name attrs = do withCStringFromMaybe name $ \p -> do withArray0 0 (fromContextAttributes attrs) $ \array -> do liftM unmarshalBool $ c_alureInitDevice p array where withCStringFromMaybe Nothing f = f nullPtr withCStringFromMaybe (Just str) f = withCString str f -- | Destroys the current context and closes its associated device. shutdownDevice :: IO Bool shutdownDevice = do liftM unmarshalBool c_alureShutdownDevice -------------------------------------------------------------------------------- -- File Loading -- | Loads the given file into a new OpenAL buffer object. The formats supported depend -- on the options the C library was compiled with, what libraries available at runtime, -- and the installed decode callbacks. Requieres an active context. createBufferFromFile :: String -> IO (Maybe Buffer) createBufferFromFile fname = do withCString fname $ \p -> do liftM unmarshalBuffer $ c_alureCreateBufferFromFile p -- | Loads the given file into an existing OpenAL buffer object. The previous contents of -- the buffer are replaced. Requires an active context. bufferDataFromFile :: Buffer -> String -> IO Bool bufferDataFromFile buffer fname = do withCString fname $ \p -> do liftM unmarshalBool $ c_alureBufferDataFromFile p (marshalBuffer . Just $ buffer) -------------------------------------------------------------------------------- -- Streaming