module Sound.ProteaAudio (
Sample(),
initAudio,
finishAudio,
volume,
soundActive,
soundStopAll,
loaderAvailable,
sampleFromMemoryWav,
sampleFromMemoryOgg,
sampleFromFile,
soundLoop,
soundPlay,
soundUpdate,
soundStop
) where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Foreign
import Foreign.C
import Data.ByteString (ByteString, useAsCStringLen)
newtype Sample = Sample{ fromSample :: (C2HSImp.CInt) }
initAudio :: (Int)
-> (Int)
-> (Int)
-> IO ((Bool))
initAudio a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
initAudio'_ a1' a2' a3' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
finishAudio :: IO ()
finishAudio =
finishAudio'_ >>
return ()
loaderAvailable :: (String)
-> IO ((Bool))
loaderAvailable a1 =
C2HSImp.withCString a1 $ \a1' ->
loaderAvailable'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
_sampleFromMemoryWav :: (Ptr CChar)
-> (Int)
-> (Float)
-> IO ((Sample))
_sampleFromMemoryWav a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = realToFrac a3} in
_sampleFromMemoryWav'_ a1' a2' a3' >>= \res ->
let {res' = Sample res} in
return (res')
_sampleFromMemoryOgg :: (Ptr CChar)
-> (Int)
-> (Float)
-> IO ((Sample))
_sampleFromMemoryOgg a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = realToFrac a3} in
_sampleFromMemoryOgg'_ a1' a2' a3' >>= \res ->
let {res' = Sample res} in
return (res')
sampleFromMemoryWav :: ByteString
-> Float
-> IO Sample
sampleFromMemoryWav wavData volume = useAsCStringLen wavData $ \(ptr, size) -> _sampleFromMemoryWav ptr size volume
sampleFromMemoryOgg :: ByteString
-> Float
-> IO Sample
sampleFromMemoryOgg oggData volume = useAsCStringLen oggData $ \(ptr, size) -> _sampleFromMemoryOgg ptr size volume
sampleFromFile :: (String)
-> (Float)
-> IO ((Sample))
sampleFromFile a1 a2 =
C2HSImp.withCString a1 $ \a1' ->
let {a2' = realToFrac a2} in
sampleFromFile'_ a1' a2' >>= \res ->
let {res' = Sample res} in
return (res')
volume :: (Float)
-> (Float)
-> IO ()
volume a1 a2 =
let {a1' = realToFrac a1} in
let {a2' = realToFrac a2} in
volume'_ a1' a2' >>
return ()
soundActive :: IO ((Int))
soundActive =
soundActive'_ >>= \res ->
let {res' = fromIntegral res} in
return (res')
soundStopAll :: IO ()
soundStopAll =
soundStopAll'_ >>
return ()
soundLoop :: (Sample)
-> (Float)
-> (Float)
-> (Float)
-> (Float)
-> IO ()
soundLoop a1 a2 a3 a4 a5 =
let {a1' = fromSample a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = realToFrac a4} in
let {a5' = realToFrac a5} in
soundLoop'_ a1' a2' a3' a4' a5' >>
return ()
soundPlay :: (Sample)
-> (Float)
-> (Float)
-> (Float)
-> (Float)
-> IO ()
soundPlay a1 a2 a3 a4 a5 =
let {a1' = fromSample a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = realToFrac a4} in
let {a5' = realToFrac a5} in
soundPlay'_ a1' a2' a3' a4' a5' >>
return ()
soundUpdate :: (Sample)
-> (Float)
-> (Float)
-> (Float)
-> (Float)
-> IO ((Bool))
soundUpdate a1 a2 a3 a4 a5 =
let {a1' = fromSample a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = realToFrac a4} in
let {a5' = realToFrac a5} in
soundUpdate'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
soundStop :: (Sample) -> IO ((Bool))
soundStop a1 =
let {a1' = fromSample a1} in
soundStop'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
foreign import ccall safe "Sound/ProteaAudio.chs.h initAudio"
initAudio'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))
foreign import ccall safe "Sound/ProteaAudio.chs.h finishAudio"
finishAudio'_ :: (IO ())
foreign import ccall safe "Sound/ProteaAudio.chs.h loaderAvailable"
loaderAvailable'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))
foreign import ccall safe "Sound/ProteaAudio.chs.h _sampleFromMemoryWav"
_sampleFromMemoryWav'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO C2HSImp.CInt))))
foreign import ccall safe "Sound/ProteaAudio.chs.h _sampleFromMemoryOgg"
_sampleFromMemoryOgg'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO C2HSImp.CInt))))
foreign import ccall safe "Sound/ProteaAudio.chs.h sampleFromFile"
sampleFromFile'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CFloat -> (IO C2HSImp.CInt)))
foreign import ccall safe "Sound/ProteaAudio.chs.h volume"
volume'_ :: (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Sound/ProteaAudio.chs.h soundActive"
soundActive'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Sound/ProteaAudio.chs.h soundStopAll"
soundStopAll'_ :: (IO ())
foreign import ccall safe "Sound/ProteaAudio.chs.h soundLoop"
soundLoop'_ :: (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))))
foreign import ccall safe "Sound/ProteaAudio.chs.h soundPlay"
soundPlay'_ :: (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))))
foreign import ccall safe "Sound/ProteaAudio.chs.h soundUpdate"
soundUpdate'_ :: (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO C2HSImp.CInt))))))
foreign import ccall safe "Sound/ProteaAudio.chs.h soundStop"
soundStop'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))