{-# LANGUAGE ForeignFunctionInterface #-}
{-# INCLUDE "cal3d_c.h" #-}

module Graphics.Animation.Cal3D.Mixer
    (newMixer, deleteMixer
    , blendCycle, clearCycle, executeAction
    )

where

import Foreign
import Foreign.C.Types
import Foreign.C.String

import Graphics.Animation.Cal3D.Types
import Graphics.Animation.Cal3D.Error

-- | Create a Mixer.
foreign import ccall safe "newMixer"
        newMixer :: IO Mixer

-- | Destroy a Mixer.
foreign import ccall safe "deleteMixer"
        deleteMixer :: Mixer -> IO ()

-- | Add an animation to be "cycled" (repeated) to the current mix.
-- The animation will continue playing until removed by 'clearCycle'.

blendCycle :: Mixer 
           -> AnimationId 
           -> Float -- ^ weight of this animation; weights should sum to 1.0
           -> Float -- ^ delay in seconds before the animation starts
           -> IO (Either String ())
blendCycle mixer (AnimationId id) weight delay =
    checkError (c_blendCycle mixer id 
                (realToFrac weight) 
                (realToFrac delay)) 
               0 "blendCycle failed"

foreign import ccall safe "blendCycle"
        c_blendCycle :: Mixer -> CInt -> CFloat -> CFloat -> IO CInt

-- | Remove a "cycled" animation from the current mix.

clearCycle :: Mixer 
           -> AnimationId 
           -> Float -- ^ delay in seconds before the animation ends
           -> IO (Either String ())
clearCycle mixer (AnimationId id) delay =
    checkError (c_clearCycle mixer id (realToFrac delay))
               0 "clearCycle failed"

foreign import ccall safe "clearCycle"
        c_clearCycle :: Mixer -> CInt -> CFloat -> IO CInt

-- | Execute an animation once, instead of repeating it.
executeAction :: Mixer 
              -> AnimationId 
              -> Float          -- ^ delay in
              -> Float          -- ^ delay out
              -> Float          -- ^ weight target
              -> Bool           -- ^ autolock?
              -> IO (Either String ())
executeAction mixer (AnimationId id) delayIn delayOut weightTarget autoLock =
    checkError (c_executeAction mixer id 
                (realToFrac delayIn)
                (realToFrac delayOut)
                (realToFrac weightTarget)
                (fromBool autoLock))
               0 "executeAction failed"

foreign import ccall safe "executeAction"
        c_executeAction :: Mixer -> CInt -> CFloat -> CFloat -> CFloat ->
                           CInt -> IO CInt