{-# OPTIONS -Wall #-}
{-# LANGUAGE ForeignFunctionInterface #-}

module Raylib.Core.Audio where

import Foreign
  ( Ptr,
    Storable (peek, sizeOf),
    castPtr,
    toBool,
  )
import Foreign.C (CUChar, withCString)
import Raylib.ForeignUtil
  ( pop,
    popCArray,
    withFreeable,
    withFreeableArrayLen,
  )
import Raylib.Internal (addAudioBuffer, addCtxData, unloadAudioBuffers, unloadCtxData, unloadSingleAudioBuffer, unloadSingleCtxDataPtr, WindowResources)
import Raylib.Native
  ( c'closeAudioDevice,
    c'exportWave,
    c'exportWaveAsCode,
    c'getMusicTimeLength,
    c'getMusicTimePlayed,
    c'isAudioDeviceReady,
    c'isAudioStreamPlaying,
    c'isAudioStreamProcessed,
    c'isAudioStreamReady,
    c'isMusicReady,
    c'isMusicStreamPlaying,
    c'isSoundPlaying,
    c'isSoundReady,
    c'isWaveReady,
    c'loadAudioStream,
    c'loadMusicStream,
    c'loadMusicStreamFromMemory,
    c'loadSound,
    c'loadSoundFromWave,
    c'loadWave,
    c'loadWaveFromMemory,
    c'loadWaveSamples,
    c'pauseAudioStream,
    c'pauseMusicStream,
    c'pauseSound,
    c'playAudioStream,
    c'playMusicStream,
    c'playSound,
    c'resumeAudioStream,
    c'resumeMusicStream,
    c'resumeSound,
    c'seekMusicStream,
    c'setAudioStreamPan,
    c'setAudioStreamPitch,
    c'setAudioStreamVolume,
    c'setMasterVolume,
    c'setMusicPan,
    c'setMusicPitch,
    c'setMusicVolume,
    c'setSoundPan,
    c'setSoundPitch,
    c'setSoundVolume,
    c'stopAudioStream,
    c'stopMusicStream,
    c'stopSound,
    c'updateAudioStream,
    c'updateMusicStream,
    c'updateSound,
    c'waveCopy,
    c'waveCrop,
    c'waveFormat,
  )
import Raylib.Types
  ( AudioStream (audioStream'buffer),
    Music (music'ctxData, music'ctxType, music'stream),
    Sound (sound'stream),
    Wave (wave'channels, wave'frameCount),
  )

foreign import ccall safe "raylib.h InitAudioDevice"
  initAudioDevice ::
    IO ()

closeAudioDevice :: WindowResources -> IO ()
closeAudioDevice :: WindowResources -> IO ()
closeAudioDevice WindowResources
wr = do
  WindowResources -> IO ()
unloadCtxData WindowResources
wr
  WindowResources -> IO ()
unloadAudioBuffers WindowResources
wr
  IO ()
c'closeAudioDevice

isAudioDeviceReady :: IO Bool
isAudioDeviceReady :: IO Bool
isAudioDeviceReady = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO CBool
c'isAudioDeviceReady

setMasterVolume :: Float -> IO ()
setMasterVolume :: Float -> IO ()
setMasterVolume Float
volume = CFloat -> IO ()
c'setMasterVolume (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
volume)

loadWave :: String -> IO Wave
loadWave :: String -> IO Wave
loadWave String
fileName = forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName CString -> IO (Ptr Wave)
c'loadWave forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop

loadWaveFromMemory :: String -> [Integer] -> IO Wave
loadWaveFromMemory :: String -> [Integer] -> IO Wave
loadWaveFromMemory String
fileType [Integer]
fileData = forall a. String -> (CString -> IO a) -> IO a
withCString String
fileType (\CString
f -> forall a b.
(Freeable a, Storable a) =>
[a] -> (Int -> Ptr a -> IO b) -> IO b
withFreeableArrayLen (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral [Integer]
fileData) (\Int
size Ptr CUChar
d -> CString -> Ptr CUChar -> CInt -> IO (Ptr Wave)
c'loadWaveFromMemory CString
f Ptr CUChar
d (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
size forall a. Num a => a -> a -> a
* forall a. Storable a => a -> Int
sizeOf (CUChar
0 :: CUChar)))) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop

loadSound :: String -> IO Sound
loadSound :: String -> IO Sound
loadSound String
fileName = forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName CString -> IO (Ptr Sound)
c'loadSound forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop

loadSoundFromWave :: Wave -> IO Sound
loadSoundFromWave :: Wave -> IO Sound
loadSoundFromWave Wave
wave = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Wave
wave Ptr Wave -> IO (Ptr Sound)
c'loadSoundFromWave forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop

updateSound :: Sound -> Ptr () -> Int -> IO ()
updateSound :: Sound -> Ptr () -> Int -> IO ()
updateSound Sound
sound Ptr ()
dataValue Int
sampleCount = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound (\Ptr Sound
s -> Ptr Sound -> Ptr () -> CInt -> IO ()
c'updateSound Ptr Sound
s Ptr ()
dataValue (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sampleCount))

-- | Unloads an sound from RAM. Sounds are automatically unloaded

-- when `closeAudioDevice` is called, so manually unloading sounds is

-- not required. In larger projects, you may want to manually unload

-- sounds to avoid having them in RAM for too long.

unloadSound :: Sound -> WindowResources -> IO ()
unloadSound :: Sound -> WindowResources -> IO ()
unloadSound Sound
sound = AudioStream -> WindowResources -> IO ()
unloadAudioStream (Sound -> AudioStream
sound'stream Sound
sound)

isWaveReady :: Wave -> IO Bool
isWaveReady :: Wave -> IO Bool
isWaveReady Wave
wave = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Wave
wave Ptr Wave -> IO CBool
c'isWaveReady

isSoundReady :: Sound -> IO Bool
isSoundReady :: Sound -> IO Bool
isSoundReady Sound
sound = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound Ptr Sound -> IO CBool
c'isSoundReady

exportWave :: Wave -> String -> IO Bool
exportWave :: Wave -> String -> IO Bool
exportWave Wave
wave String
fileName = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Wave
wave (forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Wave -> CString -> IO CBool
c'exportWave)

exportWaveAsCode :: Wave -> String -> IO Bool
exportWaveAsCode :: Wave -> String -> IO Bool
exportWaveAsCode Wave
wave String
fileName = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Wave
wave (forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Wave -> CString -> IO CBool
c'exportWaveAsCode)

playSound :: Sound -> IO ()
playSound :: Sound -> IO ()
playSound Sound
sound = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound Ptr Sound -> IO ()
c'playSound

stopSound :: Sound -> IO ()
stopSound :: Sound -> IO ()
stopSound Sound
sound = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound Ptr Sound -> IO ()
c'stopSound

pauseSound :: Sound -> IO ()
pauseSound :: Sound -> IO ()
pauseSound Sound
sound = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound Ptr Sound -> IO ()
c'pauseSound

resumeSound :: Sound -> IO ()
resumeSound :: Sound -> IO ()
resumeSound Sound
sound = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound Ptr Sound -> IO ()
c'resumeSound

isSoundPlaying :: Sound -> IO Bool
isSoundPlaying :: Sound -> IO Bool
isSoundPlaying Sound
sound = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound Ptr Sound -> IO CBool
c'isSoundPlaying

setSoundVolume :: Sound -> Float -> IO ()
setSoundVolume :: Sound -> Float -> IO ()
setSoundVolume Sound
sound Float
volume = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound (\Ptr Sound
s -> Ptr Sound -> CFloat -> IO ()
c'setSoundVolume Ptr Sound
s (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
volume))

setSoundPitch :: Sound -> Float -> IO ()
setSoundPitch :: Sound -> Float -> IO ()
setSoundPitch Sound
sound Float
pitch = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound (\Ptr Sound
s -> Ptr Sound -> CFloat -> IO ()
c'setSoundPitch Ptr Sound
s (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
pitch))

setSoundPan :: Sound -> Float -> IO ()
setSoundPan :: Sound -> Float -> IO ()
setSoundPan Sound
sound Float
pan = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Sound
sound (\Ptr Sound
s -> Ptr Sound -> CFloat -> IO ()
c'setSoundPan Ptr Sound
s (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
pan))

waveCopy :: Wave -> IO Wave
waveCopy :: Wave -> IO Wave
waveCopy Wave
wave = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Wave
wave Ptr Wave -> IO (Ptr Wave)
c'waveCopy forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop

waveCrop :: Wave -> Int -> Int -> IO Wave
waveCrop :: Wave -> Int -> Int -> IO Wave
waveCrop Wave
wave Int
initSample Int
finalSample = do
  Wave
new <- Wave -> IO Wave
waveCopy Wave
wave
  forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Wave
new (\Ptr Wave
w -> Ptr Wave -> CInt -> CInt -> IO ()
c'waveCrop Ptr Wave
w (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
initSample) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
finalSample) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Storable a => Ptr a -> IO a
peek Ptr Wave
w)

waveFormat :: Wave -> Int -> Int -> Int -> IO ()
waveFormat :: Wave -> Int -> Int -> Int -> IO ()
waveFormat Wave
wave Int
sampleRate Int
sampleSize Int
channels = do
  Wave
new <- Wave -> IO Wave
waveCopy Wave
wave
  forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Wave
new (\Ptr Wave
n -> Ptr Wave -> CInt -> CInt -> CInt -> IO ()
c'waveFormat Ptr Wave
n (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sampleRate) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sampleSize) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
channels))

loadWaveSamples :: Wave -> IO [Float]
loadWaveSamples :: Wave -> IO [Float]
loadWaveSamples Wave
wave =
  forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable
    Wave
wave
    (\Ptr Wave
w -> forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Real a, Fractional b) => a -> b
realToFrac forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. (Freeable a, Storable a) => Int -> Ptr a -> IO [a]
popCArray (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Wave -> Integer
wave'frameCount Wave
wave forall a. Num a => a -> a -> a
* Wave -> Integer
wave'channels Wave
wave) forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr Wave -> IO (Ptr CFloat)
c'loadWaveSamples Ptr Wave
w))

loadMusicStream :: String -> WindowResources -> IO Music
loadMusicStream :: String -> WindowResources -> IO Music
loadMusicStream String
fileName WindowResources
wr = do
  Music
music <- forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName CString -> IO (Ptr Music)
c'loadMusicStream forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
  Ptr () -> WindowResources -> IO ()
addAudioBuffer (forall a b. Ptr a -> Ptr b
castPtr (AudioStream -> Ptr RAudioBuffer
audioStream'buffer forall a b. (a -> b) -> a -> b
$ Music -> AudioStream
music'stream Music
music)) WindowResources
wr
  forall a. Integral a => a -> Ptr () -> WindowResources -> IO ()
addCtxData (forall a. Enum a => a -> Int
fromEnum forall a b. (a -> b) -> a -> b
$ Music -> MusicContextType
music'ctxType Music
music) (Music -> Ptr ()
music'ctxData Music
music) WindowResources
wr
  forall (m :: * -> *) a. Monad m => a -> m a
return Music
music

loadMusicStreamFromMemory :: String -> [Integer] -> WindowResources -> IO Music
loadMusicStreamFromMemory :: String -> [Integer] -> WindowResources -> IO Music
loadMusicStreamFromMemory String
fileType [Integer]
streamData WindowResources
wr = do
  Music
music <- forall a. String -> (CString -> IO a) -> IO a
withCString String
fileType (\CString
t -> forall a b.
(Freeable a, Storable a) =>
[a] -> (Int -> Ptr a -> IO b) -> IO b
withFreeableArrayLen (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral [Integer]
streamData) (\Int
size Ptr CUChar
d -> CString -> Ptr CUChar -> CInt -> IO (Ptr Music)
c'loadMusicStreamFromMemory CString
t Ptr CUChar
d (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
size forall a. Num a => a -> a -> a
* forall a. Storable a => a -> Int
sizeOf (CUChar
0 :: CUChar)))) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
  Ptr () -> WindowResources -> IO ()
addAudioBuffer (forall a b. Ptr a -> Ptr b
castPtr (AudioStream -> Ptr RAudioBuffer
audioStream'buffer forall a b. (a -> b) -> a -> b
$ Music -> AudioStream
music'stream Music
music)) WindowResources
wr
  forall a. Integral a => a -> Ptr () -> WindowResources -> IO ()
addCtxData (forall a. Enum a => a -> Int
fromEnum forall a b. (a -> b) -> a -> b
$ Music -> MusicContextType
music'ctxType Music
music) (Music -> Ptr ()
music'ctxData Music
music) WindowResources
wr
  forall (m :: * -> *) a. Monad m => a -> m a
return Music
music

-- | Unloads a music stream from RAM. Music streams are automatically unloaded

-- when `closeAudioDevice` is called, so manually unloading music streams is

-- not required. In larger projects, you may want to manually unload music

-- streams to avoid having them in RAM for too long.

unloadMusicStream :: Music -> WindowResources -> IO ()
unloadMusicStream :: Music -> WindowResources -> IO ()
unloadMusicStream Music
music = forall a. Integral a => a -> Ptr () -> WindowResources -> IO ()
unloadSingleCtxDataPtr (forall a. Enum a => a -> Int
fromEnum forall a b. (a -> b) -> a -> b
$ Music -> MusicContextType
music'ctxType Music
music) (Music -> Ptr ()
music'ctxData Music
music)

isMusicReady :: Music -> IO Bool
isMusicReady :: Music -> IO Bool
isMusicReady Music
music = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO CBool
c'isMusicReady

playMusicStream :: Music -> IO ()
playMusicStream :: Music -> IO ()
playMusicStream Music
music = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO ()
c'playMusicStream

isMusicStreamPlaying :: Music -> IO Bool
isMusicStreamPlaying :: Music -> IO Bool
isMusicStreamPlaying Music
music = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO CBool
c'isMusicStreamPlaying

updateMusicStream :: Music -> IO ()
updateMusicStream :: Music -> IO ()
updateMusicStream Music
music = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO ()
c'updateMusicStream

stopMusicStream :: Music -> IO ()
stopMusicStream :: Music -> IO ()
stopMusicStream Music
music = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO ()
c'stopMusicStream

pauseMusicStream :: Music -> IO ()
pauseMusicStream :: Music -> IO ()
pauseMusicStream Music
music = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO ()
c'pauseMusicStream

resumeMusicStream :: Music -> IO ()
resumeMusicStream :: Music -> IO ()
resumeMusicStream Music
music = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO ()
c'resumeMusicStream

seekMusicStream :: Music -> Float -> IO ()
seekMusicStream :: Music -> Float -> IO ()
seekMusicStream Music
music Float
position = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music (\Ptr Music
m -> Ptr Music -> CFloat -> IO ()
c'seekMusicStream Ptr Music
m (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
position))

setMusicVolume :: Music -> Float -> IO ()
setMusicVolume :: Music -> Float -> IO ()
setMusicVolume Music
music Float
volume = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music (\Ptr Music
m -> Ptr Music -> CFloat -> IO ()
c'setMusicVolume Ptr Music
m (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
volume))

setMusicPitch :: Music -> Float -> IO ()
setMusicPitch :: Music -> Float -> IO ()
setMusicPitch Music
music Float
pitch = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music (\Ptr Music
m -> Ptr Music -> CFloat -> IO ()
c'setMusicPitch Ptr Music
m (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
pitch))

setMusicPan :: Music -> Float -> IO ()
setMusicPan :: Music -> Float -> IO ()
setMusicPan Music
music Float
pan = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music (\Ptr Music
m -> Ptr Music -> CFloat -> IO ()
c'setMusicPan Ptr Music
m (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
pan))

getMusicTimeLength :: Music -> IO Float
getMusicTimeLength :: Music -> IO Float
getMusicTimeLength Music
music = forall a b. (Real a, Fractional b) => a -> b
realToFrac forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO CFloat
c'getMusicTimeLength

getMusicTimePlayed :: Music -> IO Float
getMusicTimePlayed :: Music -> IO Float
getMusicTimePlayed Music
music = forall a b. (Real a, Fractional b) => a -> b
realToFrac forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Music
music Ptr Music -> IO CFloat
c'getMusicTimePlayed

loadAudioStream :: Integer -> Integer -> Integer -> WindowResources -> IO AudioStream
loadAudioStream :: Integer -> Integer -> Integer -> WindowResources -> IO AudioStream
loadAudioStream Integer
sampleRate Integer
sampleSize Integer
channels WindowResources
wr = do
  AudioStream
stream <- CUInt -> CUInt -> CUInt -> IO (Ptr AudioStream)
c'loadAudioStream (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
sampleRate) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
sampleSize) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
channels) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
  Ptr () -> WindowResources -> IO ()
addAudioBuffer (forall a b. Ptr a -> Ptr b
castPtr (AudioStream -> Ptr RAudioBuffer
audioStream'buffer AudioStream
stream)) WindowResources
wr
  forall (m :: * -> *) a. Monad m => a -> m a
return AudioStream
stream

-- | Unloads an audio stream from RAM. Audio streams are automatically unloaded

-- when `closeAudioDevice` is called, so manually unloading audio streams is

-- not required. In larger projects, you may want to manually unload audio

-- streams to avoid having them in RAM for too long.

unloadAudioStream :: AudioStream -> WindowResources -> IO ()
unloadAudioStream :: AudioStream -> WindowResources -> IO ()
unloadAudioStream AudioStream
stream = Ptr () -> WindowResources -> IO ()
unloadSingleAudioBuffer (forall a b. Ptr a -> Ptr b
castPtr forall a b. (a -> b) -> a -> b
$ AudioStream -> Ptr RAudioBuffer
audioStream'buffer AudioStream
stream)

isAudioStreamReady :: AudioStream -> IO Bool
isAudioStreamReady :: AudioStream -> IO Bool
isAudioStreamReady AudioStream
stream = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream Ptr AudioStream -> IO CBool
c'isAudioStreamReady

updateAudioStream :: AudioStream -> Ptr () -> Int -> IO ()
updateAudioStream :: AudioStream -> Ptr () -> Int -> IO ()
updateAudioStream AudioStream
stream Ptr ()
value Int
frameCount = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream (\Ptr AudioStream
s -> Ptr AudioStream -> Ptr () -> CInt -> IO ()
c'updateAudioStream Ptr AudioStream
s Ptr ()
value (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
frameCount))

isAudioStreamProcessed :: AudioStream -> IO Bool
isAudioStreamProcessed :: AudioStream -> IO Bool
isAudioStreamProcessed AudioStream
stream = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream Ptr AudioStream -> IO CBool
c'isAudioStreamProcessed

playAudioStream :: AudioStream -> IO ()
playAudioStream :: AudioStream -> IO ()
playAudioStream AudioStream
stream = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream Ptr AudioStream -> IO ()
c'playAudioStream

pauseAudioStream :: AudioStream -> IO ()
pauseAudioStream :: AudioStream -> IO ()
pauseAudioStream AudioStream
stream = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream Ptr AudioStream -> IO ()
c'pauseAudioStream

resumeAudioStream :: AudioStream -> IO ()
resumeAudioStream :: AudioStream -> IO ()
resumeAudioStream AudioStream
stream = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream Ptr AudioStream -> IO ()
c'resumeAudioStream

isAudioStreamPlaying :: AudioStream -> IO Bool
isAudioStreamPlaying :: AudioStream -> IO Bool
isAudioStreamPlaying AudioStream
stream = forall a. (Eq a, Num a) => a -> Bool
toBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream Ptr AudioStream -> IO CBool
c'isAudioStreamPlaying

stopAudioStream :: AudioStream -> IO ()
stopAudioStream :: AudioStream -> IO ()
stopAudioStream AudioStream
stream = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream Ptr AudioStream -> IO ()
c'stopAudioStream

setAudioStreamVolume :: AudioStream -> Float -> IO ()
setAudioStreamVolume :: AudioStream -> Float -> IO ()
setAudioStreamVolume AudioStream
stream Float
volume = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream (\Ptr AudioStream
s -> Ptr AudioStream -> CFloat -> IO ()
c'setAudioStreamVolume Ptr AudioStream
s (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
volume))

setAudioStreamPitch :: AudioStream -> Float -> IO ()
setAudioStreamPitch :: AudioStream -> Float -> IO ()
setAudioStreamPitch AudioStream
stream Float
pitch = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream (\Ptr AudioStream
s -> Ptr AudioStream -> CFloat -> IO ()
c'setAudioStreamPitch Ptr AudioStream
s (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
pitch))

setAudioStreamPan :: AudioStream -> Float -> IO ()
setAudioStreamPan :: AudioStream -> Float -> IO ()
setAudioStreamPan AudioStream
stream Float
pan = forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable AudioStream
stream (\Ptr AudioStream
s -> Ptr AudioStream -> CFloat -> IO ()
c'setAudioStreamPan Ptr AudioStream
s (forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
pan))

setAudioStreamBufferSizeDefault :: Int -> IO ()
setAudioStreamBufferSizeDefault :: Int -> IO ()
setAudioStreamBufferSizeDefault = Int -> IO ()
setAudioStreamBufferSizeDefault forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral