{-# LANGUAGE DeriveAnyClass #-}

{-# OPTIONS -Wall #-}

-- | Bindings for types used in @raudio@
module Raylib.Types.Core.Audio
  ( -- * Enumerations
    MusicContextType (..),
    AudioBufferUsage (..),

    -- * Structures
    Wave (..),
    RAudioBuffer (..),
    RAudioProcessor (..),
    AudioStream (..),
    Sound (..),
    Music (..),

    -- * Pointer utilities
    p'wave'frameCount,
    p'wave'sampleRate,
    p'wave'sampleSize,
    p'wave'channels,
    p'wave'data,
    p'rAudioBuffer'converter,
    p'rAudioBuffer'callback,
    p'rAudioBuffer'processor,
    p'rAudioBuffer'volume,
    p'rAudioBuffer'pitch,
    p'rAudioBuffer'pan,
    p'rAudioBuffer'playing,
    p'rAudioBuffer'paused,
    p'rAudioBuffer'looping,
    p'rAudioBuffer'usage,
    p'rAudioBuffer'isSubBufferProcessed,
    p'rAudioBuffer'sizeInFrames,
    p'rAudioBuffer'frameCursorPos,
    p'rAudioBuffer'framesProcessed,
    p'rAudioBuffer'data,
    p'rAudioBuffer'next,
    p'rAudioBuffer'prev,
    p'rAudioProcessor'process,
    p'rAudioProcessor'next,
    p'rAudioProcessor'prev,
    p'audioStream'buffer,
    p'audioStream'processor,
    p'audioStream'sampleRate,
    p'audioStream'sampleSize,
    p'audioStream'channels,
    p'sound'stream,
    p'sound'frameCount,
    p'music'stream,
    p'music'frameCount,
    p'music'looping,
    p'music'ctxType,
    p'music'ctxData,

    -- * Callbacks
    AudioCallback,
    C'AudioCallback,
  )
where

import Data.Maybe (fromMaybe)
import Foreign
  ( FunPtr,
    Ptr,
    Storable (alignment, peek, poke, sizeOf),
    Word8,
    castPtr,
    fromBool,
    malloc,
    newArray,
    nullFunPtr,
    nullPtr,
    peekArray,
    plusPtr,
    toBool,
  )
import Foreign.C
  ( CBool,
    CFloat,
    CInt (..),
    CShort,
    CUChar,
    CUInt,
  )
import Raylib.Internal.Foreign (Freeable (rlFreeDependents), c'free, peekMaybe, peekStaticArray, pokeMaybe, pokeStaticArray)

---------------------------------------
-- audio enums ------------------------
---------------------------------------

data MusicContextType
  = MusicAudioNone
  | MusicAudioWAV
  | MusicAudioOGG
  | MusicAudioFLAC
  | MusicAudioMP3
  | MusicAudioQOA
  | MusicModuleXM
  | MusicModuleMOD
  deriving (MusicContextType -> MusicContextType -> Bool
(MusicContextType -> MusicContextType -> Bool)
-> (MusicContextType -> MusicContextType -> Bool)
-> Eq MusicContextType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MusicContextType -> MusicContextType -> Bool
== :: MusicContextType -> MusicContextType -> Bool
$c/= :: MusicContextType -> MusicContextType -> Bool
/= :: MusicContextType -> MusicContextType -> Bool
Eq, Int -> MusicContextType -> ShowS
[MusicContextType] -> ShowS
MusicContextType -> String
(Int -> MusicContextType -> ShowS)
-> (MusicContextType -> String)
-> ([MusicContextType] -> ShowS)
-> Show MusicContextType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MusicContextType -> ShowS
showsPrec :: Int -> MusicContextType -> ShowS
$cshow :: MusicContextType -> String
show :: MusicContextType -> String
$cshowList :: [MusicContextType] -> ShowS
showList :: [MusicContextType] -> ShowS
Show, Int -> MusicContextType
MusicContextType -> Int
MusicContextType -> [MusicContextType]
MusicContextType -> MusicContextType
MusicContextType -> MusicContextType -> [MusicContextType]
MusicContextType
-> MusicContextType -> MusicContextType -> [MusicContextType]
(MusicContextType -> MusicContextType)
-> (MusicContextType -> MusicContextType)
-> (Int -> MusicContextType)
-> (MusicContextType -> Int)
-> (MusicContextType -> [MusicContextType])
-> (MusicContextType -> MusicContextType -> [MusicContextType])
-> (MusicContextType -> MusicContextType -> [MusicContextType])
-> (MusicContextType
    -> MusicContextType -> MusicContextType -> [MusicContextType])
-> Enum MusicContextType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: MusicContextType -> MusicContextType
succ :: MusicContextType -> MusicContextType
$cpred :: MusicContextType -> MusicContextType
pred :: MusicContextType -> MusicContextType
$ctoEnum :: Int -> MusicContextType
toEnum :: Int -> MusicContextType
$cfromEnum :: MusicContextType -> Int
fromEnum :: MusicContextType -> Int
$cenumFrom :: MusicContextType -> [MusicContextType]
enumFrom :: MusicContextType -> [MusicContextType]
$cenumFromThen :: MusicContextType -> MusicContextType -> [MusicContextType]
enumFromThen :: MusicContextType -> MusicContextType -> [MusicContextType]
$cenumFromTo :: MusicContextType -> MusicContextType -> [MusicContextType]
enumFromTo :: MusicContextType -> MusicContextType -> [MusicContextType]
$cenumFromThenTo :: MusicContextType
-> MusicContextType -> MusicContextType -> [MusicContextType]
enumFromThenTo :: MusicContextType
-> MusicContextType -> MusicContextType -> [MusicContextType]
Enum)

instance Storable MusicContextType where
  sizeOf :: MusicContextType -> Int
sizeOf MusicContextType
_ = Int
4
  alignment :: MusicContextType -> Int
alignment MusicContextType
_ = Int
4
  peek :: Ptr MusicContextType -> IO MusicContextType
peek Ptr MusicContextType
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr MusicContextType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr MusicContextType
ptr)
    MusicContextType -> IO MusicContextType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (MusicContextType -> IO MusicContextType)
-> MusicContextType -> IO MusicContextType
forall a b. (a -> b) -> a -> b
$ Int -> MusicContextType
forall a. Enum a => Int -> a
toEnum (Int -> MusicContextType) -> Int -> MusicContextType
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr MusicContextType -> MusicContextType -> IO ()
poke Ptr MusicContextType
ptr MusicContextType
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MusicContextType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr MusicContextType
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (MusicContextType -> Int
forall a. Enum a => a -> Int
fromEnum MusicContextType
v) :: CInt)

data AudioBufferUsage
  = AudioBufferUsageStatic
  | AudioBufferUsageStream
  deriving (AudioBufferUsage -> AudioBufferUsage -> Bool
(AudioBufferUsage -> AudioBufferUsage -> Bool)
-> (AudioBufferUsage -> AudioBufferUsage -> Bool)
-> Eq AudioBufferUsage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AudioBufferUsage -> AudioBufferUsage -> Bool
== :: AudioBufferUsage -> AudioBufferUsage -> Bool
$c/= :: AudioBufferUsage -> AudioBufferUsage -> Bool
/= :: AudioBufferUsage -> AudioBufferUsage -> Bool
Eq, Int -> AudioBufferUsage -> ShowS
[AudioBufferUsage] -> ShowS
AudioBufferUsage -> String
(Int -> AudioBufferUsage -> ShowS)
-> (AudioBufferUsage -> String)
-> ([AudioBufferUsage] -> ShowS)
-> Show AudioBufferUsage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AudioBufferUsage -> ShowS
showsPrec :: Int -> AudioBufferUsage -> ShowS
$cshow :: AudioBufferUsage -> String
show :: AudioBufferUsage -> String
$cshowList :: [AudioBufferUsage] -> ShowS
showList :: [AudioBufferUsage] -> ShowS
Show, Int -> AudioBufferUsage
AudioBufferUsage -> Int
AudioBufferUsage -> [AudioBufferUsage]
AudioBufferUsage -> AudioBufferUsage
AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage]
AudioBufferUsage
-> AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage]
(AudioBufferUsage -> AudioBufferUsage)
-> (AudioBufferUsage -> AudioBufferUsage)
-> (Int -> AudioBufferUsage)
-> (AudioBufferUsage -> Int)
-> (AudioBufferUsage -> [AudioBufferUsage])
-> (AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage])
-> (AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage])
-> (AudioBufferUsage
    -> AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage])
-> Enum AudioBufferUsage
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: AudioBufferUsage -> AudioBufferUsage
succ :: AudioBufferUsage -> AudioBufferUsage
$cpred :: AudioBufferUsage -> AudioBufferUsage
pred :: AudioBufferUsage -> AudioBufferUsage
$ctoEnum :: Int -> AudioBufferUsage
toEnum :: Int -> AudioBufferUsage
$cfromEnum :: AudioBufferUsage -> Int
fromEnum :: AudioBufferUsage -> Int
$cenumFrom :: AudioBufferUsage -> [AudioBufferUsage]
enumFrom :: AudioBufferUsage -> [AudioBufferUsage]
$cenumFromThen :: AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage]
enumFromThen :: AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage]
$cenumFromTo :: AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage]
enumFromTo :: AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage]
$cenumFromThenTo :: AudioBufferUsage
-> AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage]
enumFromThenTo :: AudioBufferUsage
-> AudioBufferUsage -> AudioBufferUsage -> [AudioBufferUsage]
Enum)

instance Storable AudioBufferUsage where
  sizeOf :: AudioBufferUsage -> Int
sizeOf AudioBufferUsage
_ = Int
4
  alignment :: AudioBufferUsage -> Int
alignment AudioBufferUsage
_ = Int
4
  peek :: Ptr AudioBufferUsage -> IO AudioBufferUsage
peek Ptr AudioBufferUsage
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr AudioBufferUsage -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr AudioBufferUsage
ptr)
    AudioBufferUsage -> IO AudioBufferUsage
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioBufferUsage -> IO AudioBufferUsage)
-> AudioBufferUsage -> IO AudioBufferUsage
forall a b. (a -> b) -> a -> b
$ Int -> AudioBufferUsage
forall a. Enum a => Int -> a
toEnum (Int -> AudioBufferUsage) -> Int -> AudioBufferUsage
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr AudioBufferUsage -> AudioBufferUsage -> IO ()
poke Ptr AudioBufferUsage
ptr AudioBufferUsage
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AudioBufferUsage -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr AudioBufferUsage
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (AudioBufferUsage -> Int
forall a. Enum a => a -> Int
fromEnum AudioBufferUsage
v) :: CInt)

---------------------------------------
-- audio structures -------------------
---------------------------------------

data Wave = Wave
  { Wave -> Integer
wave'frameCount :: Integer,
    Wave -> Integer
wave'sampleRate :: Integer,
    Wave -> Integer
wave'sampleSize :: Integer,
    Wave -> Integer
wave'channels :: Integer,
    Wave -> [Int]
wave'data :: [Int]
  }
  deriving (Wave -> Wave -> Bool
(Wave -> Wave -> Bool) -> (Wave -> Wave -> Bool) -> Eq Wave
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Wave -> Wave -> Bool
== :: Wave -> Wave -> Bool
$c/= :: Wave -> Wave -> Bool
/= :: Wave -> Wave -> Bool
Eq, Int -> Wave -> ShowS
[Wave] -> ShowS
Wave -> String
(Int -> Wave -> ShowS)
-> (Wave -> String) -> ([Wave] -> ShowS) -> Show Wave
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Wave -> ShowS
showsPrec :: Int -> Wave -> ShowS
$cshow :: Wave -> String
show :: Wave -> String
$cshowList :: [Wave] -> ShowS
showList :: [Wave] -> ShowS
Show)

instance Storable Wave where
  sizeOf :: Wave -> Int
sizeOf Wave
_ = Int
24
  alignment :: Wave -> Int
alignment Wave
_ = Int
4
  peek :: Ptr Wave -> IO Wave
peek Ptr Wave
_p = do
    Integer
frameCount <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Wave -> Ptr CUInt
p'wave'frameCount Ptr Wave
_p)
    Integer
sampleRate <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Wave -> Ptr CUInt
p'wave'sampleRate Ptr Wave
_p)
    Integer
sampleSize <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Wave -> Ptr CUInt
p'wave'sampleSize Ptr Wave
_p)
    Integer
channels <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Wave -> Ptr CUInt
p'wave'channels Ptr Wave
_p)
    Ptr CShort
wDataPtr <- Ptr (Ptr CShort) -> IO (Ptr CShort)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Wave -> Ptr (Ptr CShort)
p'wave'data Ptr Wave
_p)
    [Int]
wData <- (CShort -> Int) -> [CShort] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map CShort -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([CShort] -> [Int]) -> IO [CShort] -> IO [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr CShort -> IO [CShort]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Integer
frameCount Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
channels) Ptr CShort
wDataPtr
    Wave -> IO Wave
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Wave -> IO Wave) -> Wave -> IO Wave
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer -> Integer -> [Int] -> Wave
Wave Integer
frameCount Integer
sampleRate Integer
sampleSize Integer
channels [Int]
wData
  poke :: Ptr Wave -> Wave -> IO ()
poke Ptr Wave
_p (Wave Integer
frameCount Integer
sampleRate Integer
sampleSize Integer
channels [Int]
wData) = do
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Wave -> Ptr CUInt
p'wave'frameCount Ptr Wave
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
frameCount)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Wave -> Ptr CUInt
p'wave'sampleRate Ptr Wave
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
sampleRate)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Wave -> Ptr CUInt
p'wave'sampleSize Ptr Wave
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
sampleSize)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Wave -> Ptr CUInt
p'wave'channels Ptr Wave
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
channels)
    Ptr (Ptr CShort) -> Ptr CShort -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Wave -> Ptr (Ptr CShort)
p'wave'data Ptr Wave
_p) (Ptr CShort -> IO ()) -> IO (Ptr CShort) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [CShort] -> IO (Ptr CShort)
forall a. Storable a => [a] -> IO (Ptr a)
newArray ((Int -> CShort) -> [Int] -> [CShort]
forall a b. (a -> b) -> [a] -> [b]
map Int -> CShort
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Int]
wData)
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

p'wave'frameCount :: Ptr Wave -> Ptr CUInt
p'wave'frameCount :: Ptr Wave -> Ptr CUInt
p'wave'frameCount = (Ptr Wave -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

p'wave'sampleRate :: Ptr Wave -> Ptr CUInt
p'wave'sampleRate :: Ptr Wave -> Ptr CUInt
p'wave'sampleRate = (Ptr Wave -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4)

p'wave'sampleSize :: Ptr Wave -> Ptr CUInt
p'wave'sampleSize :: Ptr Wave -> Ptr CUInt
p'wave'sampleSize = (Ptr Wave -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)

p'wave'channels :: Ptr Wave -> Ptr CUInt
p'wave'channels :: Ptr Wave -> Ptr CUInt
p'wave'channels = (Ptr Wave -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12)

-- array (wave'frameCount *  wave'channels)
p'wave'data :: Ptr Wave -> Ptr (Ptr CShort)
p'wave'data :: Ptr Wave -> Ptr (Ptr CShort)
p'wave'data = (Ptr Wave -> Int -> Ptr (Ptr CShort)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16)

instance Freeable Wave where
  rlFreeDependents :: Wave -> Ptr Wave -> IO ()
rlFreeDependents Wave
_ Ptr Wave
ptr = do
    Ptr CShort
dataPtr <- Ptr (Ptr CShort) -> IO (Ptr CShort)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Wave -> Ptr (Ptr CShort)
p'wave'data Ptr Wave
ptr)
    Ptr () -> IO ()
c'free (Ptr () -> IO ()) -> Ptr () -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CShort -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CShort
dataPtr

-- RAudioBuffer/Processor are bound weirdly. They are currently used as `Ptr`s
-- because peeking/poking them every time an audio function is called doesn't
-- work properly (they are stored in a linked list in C, which makes it very
-- difficult to properly marshal them).
--
-- The types defined here are actually unnecessary because the pointers are
-- never dereferenced.
data RAudioBuffer = RAudioBuffer
  { RAudioBuffer -> [Int]
rAudioBuffer'converter :: [Int], -- Implemented as an array of 78 integers because the entire `ma_data_converter` type is too complex
    RAudioBuffer -> Maybe C'AudioCallback
rAudioBuffer'callback :: Maybe C'AudioCallback,
    RAudioBuffer -> Maybe RAudioProcessor
rAudioBuffer'processor :: Maybe RAudioProcessor,
    RAudioBuffer -> Float
rAudioBuffer'volume :: Float,
    RAudioBuffer -> Float
rAudioBuffer'pitch :: Float,
    RAudioBuffer -> Float
rAudioBuffer'pan :: Float,
    RAudioBuffer -> Bool
rAudioBuffer'playing :: Bool,
    RAudioBuffer -> Bool
rAudioBuffer'paused :: Bool,
    RAudioBuffer -> Bool
rAudioBuffer'looping :: Bool,
    RAudioBuffer -> AudioBufferUsage
rAudioBuffer'usage :: AudioBufferUsage,
    RAudioBuffer -> [Bool]
rAudioBuffer'isSubBufferProcessed :: [Bool],
    RAudioBuffer -> Integer
rAudioBuffer'sizeInFrames :: Integer,
    RAudioBuffer -> Integer
rAudioBuffer'frameCursorPos :: Integer,
    RAudioBuffer -> Integer
rAudioBuffer'framesProcessed :: Integer,
    RAudioBuffer -> [Word8]
rAudioBuffer'data :: [Word8],
    RAudioBuffer -> Maybe RAudioBuffer
rAudioBuffer'next :: Maybe RAudioBuffer,
    RAudioBuffer -> Maybe RAudioBuffer
rAudioBuffer'prev :: Maybe RAudioBuffer
  }
  deriving (RAudioBuffer -> RAudioBuffer -> Bool
(RAudioBuffer -> RAudioBuffer -> Bool)
-> (RAudioBuffer -> RAudioBuffer -> Bool) -> Eq RAudioBuffer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RAudioBuffer -> RAudioBuffer -> Bool
== :: RAudioBuffer -> RAudioBuffer -> Bool
$c/= :: RAudioBuffer -> RAudioBuffer -> Bool
/= :: RAudioBuffer -> RAudioBuffer -> Bool
Eq, Int -> RAudioBuffer -> ShowS
[RAudioBuffer] -> ShowS
RAudioBuffer -> String
(Int -> RAudioBuffer -> ShowS)
-> (RAudioBuffer -> String)
-> ([RAudioBuffer] -> ShowS)
-> Show RAudioBuffer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RAudioBuffer -> ShowS
showsPrec :: Int -> RAudioBuffer -> ShowS
$cshow :: RAudioBuffer -> String
show :: RAudioBuffer -> String
$cshowList :: [RAudioBuffer] -> ShowS
showList :: [RAudioBuffer] -> ShowS
Show, RAudioBuffer -> Ptr RAudioBuffer -> IO ()
(RAudioBuffer -> Ptr RAudioBuffer -> IO ())
-> (RAudioBuffer -> Ptr RAudioBuffer -> IO ())
-> Freeable RAudioBuffer
forall a.
(a -> Ptr a -> IO ()) -> (a -> Ptr a -> IO ()) -> Freeable a
$crlFreeDependents :: RAudioBuffer -> Ptr RAudioBuffer -> IO ()
rlFreeDependents :: RAudioBuffer -> Ptr RAudioBuffer -> IO ()
$crlFree :: RAudioBuffer -> Ptr RAudioBuffer -> IO ()
rlFree :: RAudioBuffer -> Ptr RAudioBuffer -> IO ()
Freeable)

instance Storable RAudioBuffer where
  sizeOf :: RAudioBuffer -> Int
sizeOf RAudioBuffer
_ = Int
392
  alignment :: RAudioBuffer -> Int
alignment RAudioBuffer
_ = Int
8
  peek :: Ptr RAudioBuffer -> IO RAudioBuffer
peek Ptr RAudioBuffer
_p = do
    Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer
base <- Ptr RAudioBuffer
-> IO (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
loadBase Ptr RAudioBuffer
_p
    Ptr RAudioBuffer
nextPtr <- Ptr (Ptr RAudioBuffer) -> IO (Ptr RAudioBuffer)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'next Ptr RAudioBuffer
_p)
    Maybe RAudioBuffer
next <- Ptr RAudioBuffer -> IO (Maybe RAudioBuffer)
loadNext Ptr RAudioBuffer
nextPtr
    Ptr RAudioBuffer
prevPtr <- Ptr (Ptr RAudioBuffer) -> IO (Ptr RAudioBuffer)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'prev Ptr RAudioBuffer
_p)
    Maybe RAudioBuffer
prev <- Ptr RAudioBuffer -> IO (Maybe RAudioBuffer)
loadPrev Ptr RAudioBuffer
prevPtr
    RAudioBuffer -> IO RAudioBuffer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RAudioBuffer -> IO RAudioBuffer)
-> RAudioBuffer -> IO RAudioBuffer
forall a b. (a -> b) -> a -> b
$
      let p :: RAudioBuffer
p =
            Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer
base
              ((\RAudioBuffer
a -> RAudioBuffer
a {rAudioBuffer'prev = Just p}) (RAudioBuffer -> RAudioBuffer)
-> Maybe RAudioBuffer -> Maybe RAudioBuffer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RAudioBuffer
next)
              ((\RAudioBuffer
a -> RAudioBuffer
a {rAudioBuffer'next = Just p}) (RAudioBuffer -> RAudioBuffer)
-> Maybe RAudioBuffer -> Maybe RAudioBuffer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RAudioBuffer
prev)
       in RAudioBuffer
p
    where
      getBytesPerSample :: Int -> Integer
getBytesPerSample = ([Integer
0, Integer
1, Integer
2, Integer
3, Integer
4, Integer
4] [Integer] -> Int -> Integer
forall a. HasCallStack => [a] -> Int -> a
!!)
      loadBase :: Ptr RAudioBuffer
-> IO (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
loadBase Ptr RAudioBuffer
ptr = do
        [Int]
converter <- (CInt -> Int) -> [CInt] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([CInt] -> [Int]) -> IO [CInt] -> IO [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekStaticArray Int
78 (Ptr () -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr (Ptr RAudioBuffer -> Ptr ()
p'rAudioBuffer'converter Ptr RAudioBuffer
ptr) :: Ptr CInt)
        let formatIn :: Int
formatIn =
              case [Int]
converter of
                [] -> String -> Int
forall a. HasCallStack => String -> a
error String
"invalid miniaudio converter"
                Int
x:[Int]
_ -> Int
x
        C'AudioCallback
funPtr <- Ptr C'AudioCallback -> IO C'AudioCallback
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr C'AudioCallback
p'rAudioBuffer'callback Ptr RAudioBuffer
ptr)
        let callback :: Maybe C'AudioCallback
callback = if C'AudioCallback
funPtr C'AudioCallback -> C'AudioCallback -> Bool
forall a. Eq a => a -> a -> Bool
== C'AudioCallback
forall a. FunPtr a
nullFunPtr then Maybe C'AudioCallback
forall a. Maybe a
Nothing else C'AudioCallback -> Maybe C'AudioCallback
forall a. a -> Maybe a
Just C'AudioCallback
funPtr
        Maybe RAudioProcessor
processor <- Ptr (Ptr RAudioProcessor) -> IO (Maybe RAudioProcessor)
forall a. Storable a => Ptr (Ptr a) -> IO (Maybe a)
peekMaybe (Ptr RAudioBuffer -> Ptr (Ptr RAudioProcessor)
p'rAudioBuffer'processor Ptr RAudioBuffer
ptr)

        Float
volume <- CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CFloat -> Float) -> IO CFloat -> IO Float
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'volume Ptr RAudioBuffer
ptr)
        Float
pitch <- CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CFloat -> Float) -> IO CFloat -> IO Float
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'pitch Ptr RAudioBuffer
ptr)
        Float
pan <- CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CFloat -> Float) -> IO CFloat -> IO Float
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'pan Ptr RAudioBuffer
ptr)

        Bool
playing <- CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CBool -> IO CBool
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'playing Ptr RAudioBuffer
ptr)
        Bool
paused <- CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CBool -> IO CBool
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'paused Ptr RAudioBuffer
ptr)
        Bool
looping <- CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CBool -> IO CBool
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'looping Ptr RAudioBuffer
ptr)
        AudioBufferUsage
usage <- Ptr AudioBufferUsage -> IO AudioBufferUsage
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr AudioBufferUsage
p'rAudioBuffer'usage Ptr RAudioBuffer
ptr)

        [Bool]
isSubBufferProcessed <- (CBool -> Bool) -> [CBool] -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
map CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool ([CBool] -> [Bool]) -> IO [CBool] -> IO [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr CBool -> IO [CBool]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekStaticArray Int
2 (Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'isSubBufferProcessed Ptr RAudioBuffer
ptr)
        Integer
sizeInFrames <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'sizeInFrames Ptr RAudioBuffer
ptr)
        Integer
frameCursorPos <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'frameCursorPos Ptr RAudioBuffer
ptr)
        Integer
framesProcessed <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'framesProcessed Ptr RAudioBuffer
ptr)

        [Word8]
bData <- (CUChar -> Word8) -> [CUChar] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map CUChar -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([CUChar] -> [Word8]) -> IO [CUChar] -> IO [Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int -> Ptr CUChar -> IO [CUChar]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Integer
sizeInFrames Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
2 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int -> Integer
getBytesPerSample Int
formatIn) (Ptr CUChar -> IO [CUChar]) -> IO (Ptr CUChar) -> IO [CUChar]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr CUChar) -> IO (Ptr CUChar)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr (Ptr CUChar)
p'rAudioBuffer'data Ptr RAudioBuffer
ptr))

        (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
-> IO (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
 -> IO (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer))
-> (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
-> IO (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
forall a b. (a -> b) -> a -> b
$ [Int]
-> Maybe C'AudioCallback
-> Maybe RAudioProcessor
-> Float
-> Float
-> Float
-> Bool
-> Bool
-> Bool
-> AudioBufferUsage
-> [Bool]
-> Integer
-> Integer
-> Integer
-> [Word8]
-> Maybe RAudioBuffer
-> Maybe RAudioBuffer
-> RAudioBuffer
RAudioBuffer [Int]
converter Maybe C'AudioCallback
callback Maybe RAudioProcessor
processor Float
volume Float
pitch Float
pan Bool
playing Bool
paused Bool
looping AudioBufferUsage
usage [Bool]
isSubBufferProcessed Integer
sizeInFrames Integer
frameCursorPos Integer
framesProcessed [Word8]
bData
      loadNext :: Ptr RAudioBuffer -> IO (Maybe RAudioBuffer)
loadNext Ptr RAudioBuffer
ptr =
        if Ptr RAudioBuffer
ptr Ptr RAudioBuffer -> Ptr RAudioBuffer -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr RAudioBuffer
forall a. Ptr a
nullPtr
          then Maybe RAudioBuffer -> IO (Maybe RAudioBuffer)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RAudioBuffer
forall a. Maybe a
Nothing
          else do
            Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer
base <- Ptr RAudioBuffer
-> IO (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
loadBase Ptr RAudioBuffer
ptr
            Ptr RAudioBuffer
nextPtr <- Ptr (Ptr RAudioBuffer) -> IO (Ptr RAudioBuffer)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'next Ptr RAudioBuffer
ptr)
            Maybe RAudioBuffer
next <- Ptr RAudioBuffer -> IO (Maybe RAudioBuffer)
loadNext Ptr RAudioBuffer
nextPtr
            let p :: RAudioBuffer
p = Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer
base ((\RAudioBuffer
a -> RAudioBuffer
a {rAudioBuffer'prev = Just p}) (RAudioBuffer -> RAudioBuffer)
-> Maybe RAudioBuffer -> Maybe RAudioBuffer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RAudioBuffer
next) Maybe RAudioBuffer
forall a. Maybe a
Nothing
             in Maybe RAudioBuffer -> IO (Maybe RAudioBuffer)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RAudioBuffer -> Maybe RAudioBuffer
forall a. a -> Maybe a
Just RAudioBuffer
p)

      loadPrev :: Ptr RAudioBuffer -> IO (Maybe RAudioBuffer)
loadPrev Ptr RAudioBuffer
ptr =
        if Ptr RAudioBuffer
ptr Ptr RAudioBuffer -> Ptr RAudioBuffer -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr RAudioBuffer
forall a. Ptr a
nullPtr
          then Maybe RAudioBuffer -> IO (Maybe RAudioBuffer)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RAudioBuffer
forall a. Maybe a
Nothing
          else do
            Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer
base <- Ptr RAudioBuffer
-> IO (Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer)
loadBase Ptr RAudioBuffer
ptr
            Ptr RAudioBuffer
prevPtr <- Ptr (Ptr RAudioBuffer) -> IO (Ptr RAudioBuffer)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'prev Ptr RAudioBuffer
ptr)
            Maybe RAudioBuffer
prev <- Ptr RAudioBuffer -> IO (Maybe RAudioBuffer)
loadPrev Ptr RAudioBuffer
prevPtr
            let p :: RAudioBuffer
p = Maybe RAudioBuffer -> Maybe RAudioBuffer -> RAudioBuffer
base Maybe RAudioBuffer
forall a. Maybe a
Nothing ((\RAudioBuffer
a -> RAudioBuffer
a {rAudioBuffer'next = Just p}) (RAudioBuffer -> RAudioBuffer)
-> Maybe RAudioBuffer -> Maybe RAudioBuffer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RAudioBuffer
prev)
             in Maybe RAudioBuffer -> IO (Maybe RAudioBuffer)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RAudioBuffer -> Maybe RAudioBuffer
forall a. a -> Maybe a
Just RAudioBuffer
p)
  poke :: Ptr RAudioBuffer -> RAudioBuffer -> IO ()
poke Ptr RAudioBuffer
_p RAudioBuffer
a = do
    Ptr RAudioBuffer -> RAudioBuffer -> IO ()
pokeBase Ptr RAudioBuffer
_p RAudioBuffer
a
    Ptr RAudioBuffer -> Maybe RAudioBuffer -> IO ()
pokeNext Ptr RAudioBuffer
_p (Maybe RAudioBuffer -> IO ()) -> Maybe RAudioBuffer -> IO ()
forall a b. (a -> b) -> a -> b
$ RAudioBuffer -> Maybe RAudioBuffer
rAudioBuffer'next RAudioBuffer
a
    Ptr RAudioBuffer -> Maybe RAudioBuffer -> IO ()
pokePrev Ptr RAudioBuffer
_p (Maybe RAudioBuffer -> IO ()) -> Maybe RAudioBuffer -> IO ()
forall a b. (a -> b) -> a -> b
$ RAudioBuffer -> Maybe RAudioBuffer
rAudioBuffer'prev RAudioBuffer
a
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    where
      pokeBase :: Ptr RAudioBuffer -> RAudioBuffer -> IO ()
pokeBase Ptr RAudioBuffer
ptr (RAudioBuffer [Int]
converter Maybe C'AudioCallback
callback Maybe RAudioProcessor
processor Float
volume Float
pitch Float
pan Bool
playing Bool
paused Bool
looping AudioBufferUsage
usage [Bool]
isSubBufferProcessed Integer
sizeInFrames Integer
frameCursorPos Integer
framesProcessed [Word8]
bData Maybe RAudioBuffer
_ Maybe RAudioBuffer
_) = do
        Ptr CInt -> [CInt] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeStaticArray (Ptr () -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr (Ptr RAudioBuffer -> Ptr ()
p'rAudioBuffer'converter Ptr RAudioBuffer
ptr) :: Ptr CInt) ((Int -> CInt) -> [Int] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Int]
converter)
        Ptr C'AudioCallback -> C'AudioCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr C'AudioCallback
p'rAudioBuffer'callback Ptr RAudioBuffer
ptr) (C'AudioCallback -> Maybe C'AudioCallback -> C'AudioCallback
forall a. a -> Maybe a -> a
fromMaybe C'AudioCallback
forall a. FunPtr a
nullFunPtr Maybe C'AudioCallback
callback)
        Ptr (Ptr RAudioProcessor) -> Maybe RAudioProcessor -> IO ()
forall a. Storable a => Ptr (Ptr a) -> Maybe a -> IO ()
pokeMaybe (Ptr RAudioBuffer -> Ptr (Ptr RAudioProcessor)
p'rAudioBuffer'processor Ptr RAudioBuffer
ptr) Maybe RAudioProcessor
processor

        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'volume Ptr RAudioBuffer
ptr) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
volume)
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'pitch Ptr RAudioBuffer
ptr) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
pitch)
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'pan Ptr RAudioBuffer
ptr) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
pan)

        Ptr CBool -> CBool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'playing Ptr RAudioBuffer
ptr) (Bool -> CBool
forall a. Num a => Bool -> a
fromBool Bool
playing)
        Ptr CBool -> CBool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'paused Ptr RAudioBuffer
ptr) (Bool -> CBool
forall a. Num a => Bool -> a
fromBool Bool
paused)
        Ptr CBool -> CBool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'looping Ptr RAudioBuffer
ptr) (Bool -> CBool
forall a. Num a => Bool -> a
fromBool Bool
looping)
        Ptr AudioBufferUsage -> AudioBufferUsage -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr AudioBufferUsage
p'rAudioBuffer'usage Ptr RAudioBuffer
ptr) AudioBufferUsage
usage

        Ptr CBool -> [CBool] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeStaticArray (Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'isSubBufferProcessed Ptr RAudioBuffer
ptr) ((Bool -> CBool) -> [Bool] -> [CBool]
forall a b. (a -> b) -> [a] -> [b]
map Bool -> CBool
forall a. Num a => Bool -> a
fromBool [Bool]
isSubBufferProcessed)
        Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'sizeInFrames Ptr RAudioBuffer
ptr) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
sizeInFrames)
        Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'frameCursorPos Ptr RAudioBuffer
ptr) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
frameCursorPos)
        Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'framesProcessed Ptr RAudioBuffer
ptr) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
framesProcessed)

        Ptr (Ptr CUChar) -> Ptr CUChar -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr (Ptr CUChar)
p'rAudioBuffer'data Ptr RAudioBuffer
ptr) (Ptr CUChar -> IO ()) -> IO (Ptr CUChar) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [CUChar] -> IO (Ptr CUChar)
forall a. Storable a => [a] -> IO (Ptr a)
newArray ((Word8 -> CUChar) -> [Word8] -> [CUChar]
forall a b. (a -> b) -> [a] -> [b]
map Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Word8]
bData :: [CUChar])

        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      pokeNext :: Ptr RAudioBuffer -> Maybe RAudioBuffer -> IO ()
pokeNext Ptr RAudioBuffer
basePtr Maybe RAudioBuffer
pNext =
        case Maybe RAudioBuffer
pNext of
          Maybe RAudioBuffer
Nothing -> Ptr (Ptr RAudioBuffer) -> Ptr RAudioBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'next Ptr RAudioBuffer
basePtr) Ptr RAudioBuffer
forall a. Ptr a
nullPtr
          Just RAudioBuffer
val -> do
            Ptr RAudioBuffer
nextPtr <- IO (Ptr RAudioBuffer)
forall a. Storable a => IO (Ptr a)
malloc
            Ptr RAudioBuffer -> RAudioBuffer -> IO ()
pokeBase Ptr RAudioBuffer
nextPtr RAudioBuffer
val
            Ptr RAudioBuffer -> Maybe RAudioBuffer -> IO ()
pokeNext Ptr RAudioBuffer
nextPtr (RAudioBuffer -> Maybe RAudioBuffer
rAudioBuffer'next RAudioBuffer
val)
            Ptr (Ptr RAudioBuffer) -> Ptr RAudioBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'prev Ptr RAudioBuffer
nextPtr) Ptr RAudioBuffer
basePtr
            Ptr (Ptr RAudioBuffer) -> Ptr RAudioBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'next Ptr RAudioBuffer
basePtr) Ptr RAudioBuffer
nextPtr
      pokePrev :: Ptr RAudioBuffer -> Maybe RAudioBuffer -> IO ()
pokePrev Ptr RAudioBuffer
basePtr Maybe RAudioBuffer
pPrev =
        case Maybe RAudioBuffer
pPrev of
          Maybe RAudioBuffer
Nothing -> Ptr (Ptr RAudioBuffer) -> Ptr RAudioBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'prev Ptr RAudioBuffer
basePtr) Ptr RAudioBuffer
forall a. Ptr a
nullPtr
          Just RAudioBuffer
val -> do
            Ptr RAudioBuffer
prevPtr <- IO (Ptr RAudioBuffer)
forall a. Storable a => IO (Ptr a)
malloc
            Ptr RAudioBuffer -> RAudioBuffer -> IO ()
pokeBase Ptr RAudioBuffer
prevPtr RAudioBuffer
val
            Ptr (Ptr RAudioBuffer) -> Ptr RAudioBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'next Ptr RAudioBuffer
prevPtr) Ptr RAudioBuffer
basePtr
            Ptr RAudioBuffer -> Maybe RAudioBuffer -> IO ()
pokePrev Ptr RAudioBuffer
prevPtr (RAudioBuffer -> Maybe RAudioBuffer
rAudioBuffer'prev RAudioBuffer
val)
            Ptr (Ptr RAudioBuffer) -> Ptr RAudioBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'prev Ptr RAudioBuffer
basePtr) Ptr RAudioBuffer
prevPtr

-- bytes (312)
p'rAudioBuffer'converter :: Ptr RAudioBuffer -> Ptr ()
p'rAudioBuffer'converter :: Ptr RAudioBuffer -> Ptr ()
p'rAudioBuffer'converter = (Ptr RAudioBuffer -> Int -> Ptr ()
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

-- maybe funptr
p'rAudioBuffer'callback :: Ptr RAudioBuffer -> Ptr C'AudioCallback
p'rAudioBuffer'callback :: Ptr RAudioBuffer -> Ptr C'AudioCallback
p'rAudioBuffer'callback = (Ptr RAudioBuffer -> Int -> Ptr C'AudioCallback
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
312)

-- maybe
p'rAudioBuffer'processor :: Ptr RAudioBuffer -> Ptr (Ptr RAudioProcessor)
p'rAudioBuffer'processor :: Ptr RAudioBuffer -> Ptr (Ptr RAudioProcessor)
p'rAudioBuffer'processor = (Ptr RAudioBuffer -> Int -> Ptr (Ptr RAudioProcessor)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
320)

p'rAudioBuffer'volume :: Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'volume :: Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'volume = (Ptr RAudioBuffer -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
328)

p'rAudioBuffer'pitch :: Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'pitch :: Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'pitch = (Ptr RAudioBuffer -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
332)

p'rAudioBuffer'pan :: Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'pan :: Ptr RAudioBuffer -> Ptr CFloat
p'rAudioBuffer'pan = (Ptr RAudioBuffer -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
336)

p'rAudioBuffer'playing :: Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'playing :: Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'playing = (Ptr RAudioBuffer -> Int -> Ptr CBool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
340)

p'rAudioBuffer'paused :: Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'paused :: Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'paused = (Ptr RAudioBuffer -> Int -> Ptr CBool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
341)

p'rAudioBuffer'looping :: Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'looping :: Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'looping = (Ptr RAudioBuffer -> Int -> Ptr CBool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
342)

p'rAudioBuffer'usage :: Ptr RAudioBuffer -> Ptr AudioBufferUsage
p'rAudioBuffer'usage :: Ptr RAudioBuffer -> Ptr AudioBufferUsage
p'rAudioBuffer'usage = (Ptr RAudioBuffer -> Int -> Ptr AudioBufferUsage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
344)

-- static array (2)
p'rAudioBuffer'isSubBufferProcessed :: Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'isSubBufferProcessed :: Ptr RAudioBuffer -> Ptr CBool
p'rAudioBuffer'isSubBufferProcessed = (Ptr RAudioBuffer -> Int -> Ptr CBool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
348)

p'rAudioBuffer'sizeInFrames :: Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'sizeInFrames :: Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'sizeInFrames = (Ptr RAudioBuffer -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
352)

p'rAudioBuffer'frameCursorPos :: Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'frameCursorPos :: Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'frameCursorPos = (Ptr RAudioBuffer -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
356)

p'rAudioBuffer'framesProcessed :: Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'framesProcessed :: Ptr RAudioBuffer -> Ptr CUInt
p'rAudioBuffer'framesProcessed = (Ptr RAudioBuffer -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
360)

-- array (rAudioBuffer'sizeInFrames * 2 * ([0, 1, 2, 3, 4, 4] !! (peek (rAudioBuffer'converter :: Ptr CInt))))
p'rAudioBuffer'data :: Ptr RAudioBuffer -> Ptr (Ptr CUChar)
p'rAudioBuffer'data :: Ptr RAudioBuffer -> Ptr (Ptr CUChar)
p'rAudioBuffer'data = (Ptr RAudioBuffer -> Int -> Ptr (Ptr CUChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
368)

-- maybe
p'rAudioBuffer'next :: Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'next :: Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'next = (Ptr RAudioBuffer -> Int -> Ptr (Ptr RAudioBuffer)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
376)

-- maybe
p'rAudioBuffer'prev :: Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'prev :: Ptr RAudioBuffer -> Ptr (Ptr RAudioBuffer)
p'rAudioBuffer'prev = (Ptr RAudioBuffer -> Int -> Ptr (Ptr RAudioBuffer)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
384)

data RAudioProcessor = RAudioProcessor
  { RAudioProcessor -> Maybe C'AudioCallback
rAudioProcessor'process :: Maybe C'AudioCallback,
    RAudioProcessor -> Maybe RAudioProcessor
rAudioProcessor'next :: Maybe RAudioProcessor,
    RAudioProcessor -> Maybe RAudioProcessor
rAudioProcessor'prev :: Maybe RAudioProcessor
  }
  deriving (RAudioProcessor -> RAudioProcessor -> Bool
(RAudioProcessor -> RAudioProcessor -> Bool)
-> (RAudioProcessor -> RAudioProcessor -> Bool)
-> Eq RAudioProcessor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RAudioProcessor -> RAudioProcessor -> Bool
== :: RAudioProcessor -> RAudioProcessor -> Bool
$c/= :: RAudioProcessor -> RAudioProcessor -> Bool
/= :: RAudioProcessor -> RAudioProcessor -> Bool
Eq, Int -> RAudioProcessor -> ShowS
[RAudioProcessor] -> ShowS
RAudioProcessor -> String
(Int -> RAudioProcessor -> ShowS)
-> (RAudioProcessor -> String)
-> ([RAudioProcessor] -> ShowS)
-> Show RAudioProcessor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RAudioProcessor -> ShowS
showsPrec :: Int -> RAudioProcessor -> ShowS
$cshow :: RAudioProcessor -> String
show :: RAudioProcessor -> String
$cshowList :: [RAudioProcessor] -> ShowS
showList :: [RAudioProcessor] -> ShowS
Show, RAudioProcessor -> Ptr RAudioProcessor -> IO ()
(RAudioProcessor -> Ptr RAudioProcessor -> IO ())
-> (RAudioProcessor -> Ptr RAudioProcessor -> IO ())
-> Freeable RAudioProcessor
forall a.
(a -> Ptr a -> IO ()) -> (a -> Ptr a -> IO ()) -> Freeable a
$crlFreeDependents :: RAudioProcessor -> Ptr RAudioProcessor -> IO ()
rlFreeDependents :: RAudioProcessor -> Ptr RAudioProcessor -> IO ()
$crlFree :: RAudioProcessor -> Ptr RAudioProcessor -> IO ()
rlFree :: RAudioProcessor -> Ptr RAudioProcessor -> IO ()
Freeable)

instance Storable RAudioProcessor where
  sizeOf :: RAudioProcessor -> Int
sizeOf RAudioProcessor
_ = Int
24
  alignment :: RAudioProcessor -> Int
alignment RAudioProcessor
_ = Int
8
  peek :: Ptr RAudioProcessor -> IO RAudioProcessor
peek Ptr RAudioProcessor
_p = do
    Maybe C'AudioCallback
process <- Ptr RAudioProcessor -> IO (Maybe C'AudioCallback)
loadProcess Ptr RAudioProcessor
_p
    Ptr RAudioProcessor
nextPtr <- Ptr (Ptr RAudioProcessor) -> IO (Ptr RAudioProcessor)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'next Ptr RAudioProcessor
_p)
    Maybe RAudioProcessor
next <- Ptr RAudioProcessor -> IO (Maybe RAudioProcessor)
loadNext Ptr RAudioProcessor
nextPtr
    Ptr RAudioProcessor
prevPtr <- Ptr (Ptr RAudioProcessor) -> IO (Ptr RAudioProcessor)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'prev Ptr RAudioProcessor
_p)
    Maybe RAudioProcessor
prev <- Ptr RAudioProcessor -> IO (Maybe RAudioProcessor)
loadPrev Ptr RAudioProcessor
prevPtr
    RAudioProcessor -> IO RAudioProcessor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RAudioProcessor -> IO RAudioProcessor)
-> RAudioProcessor -> IO RAudioProcessor
forall a b. (a -> b) -> a -> b
$ let p :: RAudioProcessor
p = Maybe C'AudioCallback
-> Maybe RAudioProcessor
-> Maybe RAudioProcessor
-> RAudioProcessor
RAudioProcessor Maybe C'AudioCallback
process ((\RAudioProcessor
a -> RAudioProcessor
a {rAudioProcessor'prev = Just p}) (RAudioProcessor -> RAudioProcessor)
-> Maybe RAudioProcessor -> Maybe RAudioProcessor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RAudioProcessor
next) ((\RAudioProcessor
a -> RAudioProcessor
a {rAudioProcessor'next = Just p}) (RAudioProcessor -> RAudioProcessor)
-> Maybe RAudioProcessor -> Maybe RAudioProcessor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RAudioProcessor
prev) in RAudioProcessor
p
    where
      loadProcess :: Ptr RAudioProcessor -> IO (Maybe C'AudioCallback)
loadProcess Ptr RAudioProcessor
ptr = do
        C'AudioCallback
funPtr <- Ptr C'AudioCallback -> IO C'AudioCallback
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioProcessor -> Ptr C'AudioCallback
p'rAudioProcessor'process Ptr RAudioProcessor
ptr)
        if C'AudioCallback
funPtr C'AudioCallback -> C'AudioCallback -> Bool
forall a. Eq a => a -> a -> Bool
== C'AudioCallback
forall a. FunPtr a
nullFunPtr then Maybe C'AudioCallback -> IO (Maybe C'AudioCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe C'AudioCallback
forall a. Maybe a
Nothing else Maybe C'AudioCallback -> IO (Maybe C'AudioCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (C'AudioCallback -> Maybe C'AudioCallback
forall a. a -> Maybe a
Just C'AudioCallback
funPtr)
      loadNext :: Ptr RAudioProcessor -> IO (Maybe RAudioProcessor)
loadNext Ptr RAudioProcessor
ptr =
        if Ptr RAudioProcessor
ptr Ptr RAudioProcessor -> Ptr RAudioProcessor -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr RAudioProcessor
forall a. Ptr a
nullPtr
          then Maybe RAudioProcessor -> IO (Maybe RAudioProcessor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RAudioProcessor
forall a. Maybe a
Nothing
          else do
            Maybe C'AudioCallback
process <- Ptr RAudioProcessor -> IO (Maybe C'AudioCallback)
loadProcess Ptr RAudioProcessor
ptr
            Ptr RAudioProcessor
nextPtr <- Ptr (Ptr RAudioProcessor) -> IO (Ptr RAudioProcessor)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'next Ptr RAudioProcessor
ptr)
            Maybe RAudioProcessor
next <- Ptr RAudioProcessor -> IO (Maybe RAudioProcessor)
loadNext Ptr RAudioProcessor
nextPtr
            let p :: RAudioProcessor
p = Maybe C'AudioCallback
-> Maybe RAudioProcessor
-> Maybe RAudioProcessor
-> RAudioProcessor
RAudioProcessor Maybe C'AudioCallback
process ((\RAudioProcessor
a -> RAudioProcessor
a {rAudioProcessor'prev = Just p}) (RAudioProcessor -> RAudioProcessor)
-> Maybe RAudioProcessor -> Maybe RAudioProcessor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RAudioProcessor
next) Maybe RAudioProcessor
forall a. Maybe a
Nothing
             in Maybe RAudioProcessor -> IO (Maybe RAudioProcessor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RAudioProcessor -> Maybe RAudioProcessor
forall a. a -> Maybe a
Just RAudioProcessor
p)

      loadPrev :: Ptr RAudioProcessor -> IO (Maybe RAudioProcessor)
loadPrev Ptr RAudioProcessor
ptr =
        if Ptr RAudioProcessor
ptr Ptr RAudioProcessor -> Ptr RAudioProcessor -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr RAudioProcessor
forall a. Ptr a
nullPtr
          then Maybe RAudioProcessor -> IO (Maybe RAudioProcessor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RAudioProcessor
forall a. Maybe a
Nothing
          else do
            Maybe C'AudioCallback
process <- Ptr RAudioProcessor -> IO (Maybe C'AudioCallback)
loadProcess Ptr RAudioProcessor
ptr
            Ptr RAudioProcessor
prevPtr <- Ptr (Ptr RAudioProcessor) -> IO (Ptr RAudioProcessor)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'prev Ptr RAudioProcessor
ptr)
            Maybe RAudioProcessor
prev <- Ptr RAudioProcessor -> IO (Maybe RAudioProcessor)
loadPrev Ptr RAudioProcessor
prevPtr
            let p :: RAudioProcessor
p = Maybe C'AudioCallback
-> Maybe RAudioProcessor
-> Maybe RAudioProcessor
-> RAudioProcessor
RAudioProcessor Maybe C'AudioCallback
process Maybe RAudioProcessor
forall a. Maybe a
Nothing ((\RAudioProcessor
a -> RAudioProcessor
a {rAudioProcessor'next = Just p}) (RAudioProcessor -> RAudioProcessor)
-> Maybe RAudioProcessor -> Maybe RAudioProcessor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RAudioProcessor
prev)
             in Maybe RAudioProcessor -> IO (Maybe RAudioProcessor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RAudioProcessor -> Maybe RAudioProcessor
forall a. a -> Maybe a
Just RAudioProcessor
p)
  poke :: Ptr RAudioProcessor -> RAudioProcessor -> IO ()
poke Ptr RAudioProcessor
_p (RAudioProcessor Maybe C'AudioCallback
process Maybe RAudioProcessor
next Maybe RAudioProcessor
prev) = do
    Ptr C'AudioCallback -> C'AudioCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr C'AudioCallback
p'rAudioProcessor'process Ptr RAudioProcessor
_p) (C'AudioCallback -> Maybe C'AudioCallback -> C'AudioCallback
forall a. a -> Maybe a -> a
fromMaybe C'AudioCallback
forall a. FunPtr a
nullFunPtr Maybe C'AudioCallback
process)
    Ptr RAudioProcessor -> Maybe RAudioProcessor -> IO ()
pokeNext Ptr RAudioProcessor
_p Maybe RAudioProcessor
next
    Ptr RAudioProcessor -> Maybe RAudioProcessor -> IO ()
pokePrev (Ptr RAudioProcessor -> Ptr RAudioProcessor
forall a b. Ptr a -> Ptr b
castPtr Ptr RAudioProcessor
_p) Maybe RAudioProcessor
prev
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    where
      pokeNext :: Ptr RAudioProcessor -> Maybe RAudioProcessor -> IO ()
pokeNext Ptr RAudioProcessor
basePtr Maybe RAudioProcessor
pNext =
        case Maybe RAudioProcessor
pNext of
          Maybe RAudioProcessor
Nothing -> Ptr (Ptr RAudioProcessor) -> Ptr RAudioProcessor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'next Ptr RAudioProcessor
basePtr) Ptr RAudioProcessor
forall a. Ptr a
nullPtr
          Just RAudioProcessor
val -> do
            Ptr RAudioProcessor
nextPtr <- IO (Ptr RAudioProcessor)
forall a. Storable a => IO (Ptr a)
malloc
            Ptr C'AudioCallback -> C'AudioCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr C'AudioCallback
p'rAudioProcessor'process Ptr RAudioProcessor
nextPtr) (C'AudioCallback -> Maybe C'AudioCallback -> C'AudioCallback
forall a. a -> Maybe a -> a
fromMaybe C'AudioCallback
forall a. FunPtr a
nullFunPtr (RAudioProcessor -> Maybe C'AudioCallback
rAudioProcessor'process RAudioProcessor
val))
            Ptr RAudioProcessor -> Maybe RAudioProcessor -> IO ()
pokeNext Ptr RAudioProcessor
nextPtr (RAudioProcessor -> Maybe RAudioProcessor
rAudioProcessor'next RAudioProcessor
val)
            Ptr (Ptr RAudioProcessor) -> Ptr RAudioProcessor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'prev Ptr RAudioProcessor
nextPtr) Ptr RAudioProcessor
basePtr
            Ptr (Ptr RAudioProcessor) -> Ptr RAudioProcessor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'next Ptr RAudioProcessor
basePtr) Ptr RAudioProcessor
nextPtr
      pokePrev :: Ptr RAudioProcessor -> Maybe RAudioProcessor -> IO ()
pokePrev Ptr RAudioProcessor
basePtr Maybe RAudioProcessor
pPrev =
        case Maybe RAudioProcessor
pPrev of
          Maybe RAudioProcessor
Nothing -> Ptr (Ptr RAudioProcessor) -> Ptr RAudioProcessor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'prev Ptr RAudioProcessor
basePtr) Ptr RAudioProcessor
forall a. Ptr a
nullPtr
          Just RAudioProcessor
val -> do
            Ptr RAudioProcessor
prevPtr <- IO (Ptr RAudioProcessor)
forall a. Storable a => IO (Ptr a)
malloc
            Ptr C'AudioCallback -> C'AudioCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr C'AudioCallback
p'rAudioProcessor'process Ptr RAudioProcessor
prevPtr) (C'AudioCallback -> Maybe C'AudioCallback -> C'AudioCallback
forall a. a -> Maybe a -> a
fromMaybe C'AudioCallback
forall a. FunPtr a
nullFunPtr (RAudioProcessor -> Maybe C'AudioCallback
rAudioProcessor'process RAudioProcessor
val))
            Ptr (Ptr RAudioProcessor) -> Ptr RAudioProcessor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'next Ptr RAudioProcessor
prevPtr) Ptr RAudioProcessor
basePtr
            Ptr RAudioProcessor -> Maybe RAudioProcessor -> IO ()
pokePrev Ptr RAudioProcessor
prevPtr (RAudioProcessor -> Maybe RAudioProcessor
rAudioProcessor'prev RAudioProcessor
val)
            Ptr (Ptr RAudioProcessor) -> Ptr RAudioProcessor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'prev Ptr RAudioProcessor
basePtr) Ptr RAudioProcessor
prevPtr

-- maybe funptr
p'rAudioProcessor'process :: Ptr RAudioProcessor -> Ptr C'AudioCallback
p'rAudioProcessor'process :: Ptr RAudioProcessor -> Ptr C'AudioCallback
p'rAudioProcessor'process = (Ptr RAudioProcessor -> Int -> Ptr C'AudioCallback
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

-- maybe
p'rAudioProcessor'next :: Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'next :: Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'next = (Ptr RAudioProcessor -> Int -> Ptr (Ptr RAudioProcessor)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)

-- maybe
p'rAudioProcessor'prev :: Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'prev :: Ptr RAudioProcessor -> Ptr (Ptr RAudioProcessor)
p'rAudioProcessor'prev = (Ptr RAudioProcessor -> Int -> Ptr (Ptr RAudioProcessor)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16)

data AudioStream = AudioStream
  { AudioStream -> Ptr RAudioBuffer
audioStream'buffer :: Ptr RAudioBuffer,
    AudioStream -> Ptr RAudioProcessor
audioStream'processor :: Ptr RAudioProcessor,
    AudioStream -> Integer
audioStream'sampleRate :: Integer,
    AudioStream -> Integer
audioStream'sampleSize :: Integer,
    AudioStream -> Integer
audioStream'channels :: Integer
  }
  deriving (AudioStream -> AudioStream -> Bool
(AudioStream -> AudioStream -> Bool)
-> (AudioStream -> AudioStream -> Bool) -> Eq AudioStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AudioStream -> AudioStream -> Bool
== :: AudioStream -> AudioStream -> Bool
$c/= :: AudioStream -> AudioStream -> Bool
/= :: AudioStream -> AudioStream -> Bool
Eq, Int -> AudioStream -> ShowS
[AudioStream] -> ShowS
AudioStream -> String
(Int -> AudioStream -> ShowS)
-> (AudioStream -> String)
-> ([AudioStream] -> ShowS)
-> Show AudioStream
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AudioStream -> ShowS
showsPrec :: Int -> AudioStream -> ShowS
$cshow :: AudioStream -> String
show :: AudioStream -> String
$cshowList :: [AudioStream] -> ShowS
showList :: [AudioStream] -> ShowS
Show, AudioStream -> Ptr AudioStream -> IO ()
(AudioStream -> Ptr AudioStream -> IO ())
-> (AudioStream -> Ptr AudioStream -> IO ())
-> Freeable AudioStream
forall a.
(a -> Ptr a -> IO ()) -> (a -> Ptr a -> IO ()) -> Freeable a
$crlFreeDependents :: AudioStream -> Ptr AudioStream -> IO ()
rlFreeDependents :: AudioStream -> Ptr AudioStream -> IO ()
$crlFree :: AudioStream -> Ptr AudioStream -> IO ()
rlFree :: AudioStream -> Ptr AudioStream -> IO ()
Freeable)

instance Storable AudioStream where
  sizeOf :: AudioStream -> Int
sizeOf AudioStream
_ = Int
32
  alignment :: AudioStream -> Int
alignment AudioStream
_ = Int
8
  peek :: Ptr AudioStream -> IO AudioStream
peek Ptr AudioStream
_p = do
    Ptr RAudioBuffer
buffer <- Ptr (Ptr RAudioBuffer) -> IO (Ptr RAudioBuffer)
forall a. Storable a => Ptr a -> IO a
peek (Ptr AudioStream -> Ptr (Ptr RAudioBuffer)
p'audioStream'buffer Ptr AudioStream
_p)
    Ptr RAudioProcessor
processor <- Ptr (Ptr RAudioProcessor) -> IO (Ptr RAudioProcessor)
forall a. Storable a => Ptr a -> IO a
peek (Ptr AudioStream -> Ptr (Ptr RAudioProcessor)
p'audioStream'processor Ptr AudioStream
_p)
    Integer
sampleRate <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr AudioStream -> Ptr CUInt
p'audioStream'sampleRate Ptr AudioStream
_p)
    Integer
sampleSize <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr AudioStream -> Ptr CUInt
p'audioStream'sampleSize Ptr AudioStream
_p)
    Integer
channels <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr AudioStream -> Ptr CUInt
p'audioStream'channels Ptr AudioStream
_p)
    AudioStream -> IO AudioStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioStream -> IO AudioStream) -> AudioStream -> IO AudioStream
forall a b. (a -> b) -> a -> b
$ Ptr RAudioBuffer
-> Ptr RAudioProcessor
-> Integer
-> Integer
-> Integer
-> AudioStream
AudioStream Ptr RAudioBuffer
buffer Ptr RAudioProcessor
processor Integer
sampleRate Integer
sampleSize Integer
channels
  poke :: Ptr AudioStream -> AudioStream -> IO ()
poke Ptr AudioStream
_p (AudioStream Ptr RAudioBuffer
buffer Ptr RAudioProcessor
processor Integer
sampleRate Integer
sampleSize Integer
channels) = do
    Ptr (Ptr RAudioBuffer) -> Ptr RAudioBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AudioStream -> Ptr (Ptr RAudioBuffer)
p'audioStream'buffer Ptr AudioStream
_p) Ptr RAudioBuffer
buffer
    Ptr (Ptr RAudioProcessor) -> Ptr RAudioProcessor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AudioStream -> Ptr (Ptr RAudioProcessor)
p'audioStream'processor Ptr AudioStream
_p) Ptr RAudioProcessor
processor
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AudioStream -> Ptr CUInt
p'audioStream'sampleRate Ptr AudioStream
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
sampleRate)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AudioStream -> Ptr CUInt
p'audioStream'sampleSize Ptr AudioStream
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
sampleSize)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AudioStream -> Ptr CUInt
p'audioStream'channels Ptr AudioStream
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
channels)
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- maybe
p'audioStream'buffer :: Ptr AudioStream -> Ptr (Ptr RAudioBuffer)
p'audioStream'buffer :: Ptr AudioStream -> Ptr (Ptr RAudioBuffer)
p'audioStream'buffer = (Ptr AudioStream -> Int -> Ptr (Ptr RAudioBuffer)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

-- maybe
p'audioStream'processor :: Ptr AudioStream -> Ptr (Ptr RAudioProcessor)
p'audioStream'processor :: Ptr AudioStream -> Ptr (Ptr RAudioProcessor)
p'audioStream'processor = (Ptr AudioStream -> Int -> Ptr (Ptr RAudioProcessor)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)

p'audioStream'sampleRate :: Ptr AudioStream -> Ptr CUInt
p'audioStream'sampleRate :: Ptr AudioStream -> Ptr CUInt
p'audioStream'sampleRate = (Ptr AudioStream -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16)

p'audioStream'sampleSize :: Ptr AudioStream -> Ptr CUInt
p'audioStream'sampleSize :: Ptr AudioStream -> Ptr CUInt
p'audioStream'sampleSize = (Ptr AudioStream -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20)

p'audioStream'channels :: Ptr AudioStream -> Ptr CUInt
p'audioStream'channels :: Ptr AudioStream -> Ptr CUInt
p'audioStream'channels = (Ptr AudioStream -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24)

data Sound = Sound
  { Sound -> AudioStream
sound'stream :: AudioStream,
    Sound -> Integer
sound'frameCount :: Integer
  }
  deriving (Sound -> Sound -> Bool
(Sound -> Sound -> Bool) -> (Sound -> Sound -> Bool) -> Eq Sound
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Sound -> Sound -> Bool
== :: Sound -> Sound -> Bool
$c/= :: Sound -> Sound -> Bool
/= :: Sound -> Sound -> Bool
Eq, Int -> Sound -> ShowS
[Sound] -> ShowS
Sound -> String
(Int -> Sound -> ShowS)
-> (Sound -> String) -> ([Sound] -> ShowS) -> Show Sound
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Sound -> ShowS
showsPrec :: Int -> Sound -> ShowS
$cshow :: Sound -> String
show :: Sound -> String
$cshowList :: [Sound] -> ShowS
showList :: [Sound] -> ShowS
Show, Sound -> Ptr Sound -> IO ()
(Sound -> Ptr Sound -> IO ())
-> (Sound -> Ptr Sound -> IO ()) -> Freeable Sound
forall a.
(a -> Ptr a -> IO ()) -> (a -> Ptr a -> IO ()) -> Freeable a
$crlFreeDependents :: Sound -> Ptr Sound -> IO ()
rlFreeDependents :: Sound -> Ptr Sound -> IO ()
$crlFree :: Sound -> Ptr Sound -> IO ()
rlFree :: Sound -> Ptr Sound -> IO ()
Freeable)

instance Storable Sound where
  sizeOf :: Sound -> Int
sizeOf Sound
_ = Int
40
  alignment :: Sound -> Int
alignment Sound
_ = Int
8
  peek :: Ptr Sound -> IO Sound
peek Ptr Sound
_p = do
    AudioStream
stream <- Ptr AudioStream -> IO AudioStream
forall a. Storable a => Ptr a -> IO a
peek (Ptr Sound -> Ptr AudioStream
p'sound'stream Ptr Sound
_p)
    Integer
frameCount <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Sound -> Ptr CUInt
p'sound'frameCount Ptr Sound
_p)
    Sound -> IO Sound
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Sound -> IO Sound) -> Sound -> IO Sound
forall a b. (a -> b) -> a -> b
$ AudioStream -> Integer -> Sound
Sound AudioStream
stream Integer
frameCount
  poke :: Ptr Sound -> Sound -> IO ()
poke Ptr Sound
_p (Sound AudioStream
stream Integer
frameCount) = do
    Ptr AudioStream -> AudioStream -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Sound -> Ptr AudioStream
p'sound'stream Ptr Sound
_p) AudioStream
stream
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Sound -> Ptr CUInt
p'sound'frameCount Ptr Sound
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
frameCount)
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

p'sound'stream :: Ptr Sound -> Ptr AudioStream
p'sound'stream :: Ptr Sound -> Ptr AudioStream
p'sound'stream = (Ptr Sound -> Int -> Ptr AudioStream
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

p'sound'frameCount :: Ptr Sound -> Ptr CUInt
p'sound'frameCount :: Ptr Sound -> Ptr CUInt
p'sound'frameCount = (Ptr Sound -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32)

data Music = Music
  { Music -> AudioStream
music'stream :: AudioStream,
    Music -> Integer
music'frameCount :: Integer,
    Music -> Bool
music'looping :: Bool,
    Music -> MusicContextType
music'ctxType :: MusicContextType,
    Music -> Ptr ()
music'ctxData :: Ptr ()
  }
  deriving (Music -> Music -> Bool
(Music -> Music -> Bool) -> (Music -> Music -> Bool) -> Eq Music
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Music -> Music -> Bool
== :: Music -> Music -> Bool
$c/= :: Music -> Music -> Bool
/= :: Music -> Music -> Bool
Eq, Int -> Music -> ShowS
[Music] -> ShowS
Music -> String
(Int -> Music -> ShowS)
-> (Music -> String) -> ([Music] -> ShowS) -> Show Music
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Music -> ShowS
showsPrec :: Int -> Music -> ShowS
$cshow :: Music -> String
show :: Music -> String
$cshowList :: [Music] -> ShowS
showList :: [Music] -> ShowS
Show, Music -> Ptr Music -> IO ()
(Music -> Ptr Music -> IO ())
-> (Music -> Ptr Music -> IO ()) -> Freeable Music
forall a.
(a -> Ptr a -> IO ()) -> (a -> Ptr a -> IO ()) -> Freeable a
$crlFreeDependents :: Music -> Ptr Music -> IO ()
rlFreeDependents :: Music -> Ptr Music -> IO ()
$crlFree :: Music -> Ptr Music -> IO ()
rlFree :: Music -> Ptr Music -> IO ()
Freeable)

instance Storable Music where
  sizeOf :: Music -> Int
sizeOf Music
_ = Int
56
  alignment :: Music -> Int
alignment Music
_ = Int
4
  peek :: Ptr Music -> IO Music
peek Ptr Music
_p = do
    AudioStream
stream <- Ptr AudioStream -> IO AudioStream
forall a. Storable a => Ptr a -> IO a
peek (Ptr Music -> Ptr AudioStream
p'music'stream Ptr Music
_p)
    Integer
frameCount <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Music -> Ptr CUInt
p'music'frameCount Ptr Music
_p)
    Bool
looping <- CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CBool -> IO CBool
forall a. Storable a => Ptr a -> IO a
peek (Ptr Music -> Ptr CBool
p'music'looping Ptr Music
_p)
    MusicContextType
ctxType <- Ptr MusicContextType -> IO MusicContextType
forall a. Storable a => Ptr a -> IO a
peek (Ptr Music -> Ptr MusicContextType
p'music'ctxType Ptr Music
_p)
    Ptr ()
ctxData <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr Music -> Ptr (Ptr ())
p'music'ctxData Ptr Music
_p)
    Music -> IO Music
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Music -> IO Music) -> Music -> IO Music
forall a b. (a -> b) -> a -> b
$ AudioStream
-> Integer -> Bool -> MusicContextType -> Ptr () -> Music
Music AudioStream
stream Integer
frameCount Bool
looping MusicContextType
ctxType Ptr ()
ctxData
  poke :: Ptr Music -> Music -> IO ()
poke Ptr Music
_p (Music AudioStream
stream Integer
frameCount Bool
looping MusicContextType
ctxType Ptr ()
ctxData) = do
    Ptr AudioStream -> AudioStream -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Music -> Ptr AudioStream
p'music'stream Ptr Music
_p) AudioStream
stream
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Music -> Ptr CUInt
p'music'frameCount Ptr Music
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
frameCount)
    Ptr CBool -> CBool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Music -> Ptr CBool
p'music'looping Ptr Music
_p) (Bool -> CBool
forall a. Num a => Bool -> a
fromBool Bool
looping)
    Ptr MusicContextType -> MusicContextType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Music -> Ptr MusicContextType
p'music'ctxType Ptr Music
_p) MusicContextType
ctxType
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Music -> Ptr (Ptr ())
p'music'ctxData Ptr Music
_p) Ptr ()
ctxData
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

p'music'stream :: Ptr Music -> Ptr AudioStream
p'music'stream :: Ptr Music -> Ptr AudioStream
p'music'stream = (Ptr Music -> Int -> Ptr AudioStream
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

p'music'frameCount :: Ptr Music -> Ptr CUInt
p'music'frameCount :: Ptr Music -> Ptr CUInt
p'music'frameCount = (Ptr Music -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32)

p'music'looping :: Ptr Music -> Ptr CBool
p'music'looping :: Ptr Music -> Ptr CBool
p'music'looping = (Ptr Music -> Int -> Ptr CBool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36)

p'music'ctxType :: Ptr Music -> Ptr MusicContextType
p'music'ctxType :: Ptr Music -> Ptr MusicContextType
p'music'ctxType = (Ptr Music -> Int -> Ptr MusicContextType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40)

-- bytes (?)
p'music'ctxData :: Ptr Music -> Ptr (Ptr ())
p'music'ctxData :: Ptr Music -> Ptr (Ptr ())
p'music'ctxData = (Ptr Music -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48)

---------------------------------------
-- audio callbacks --------------------
---------------------------------------

type AudioCallback = Ptr () -> Integer -> IO ()

type C'AudioCallback = FunPtr (Ptr () -> CUInt -> IO ())