module Graphics.UI.SDL.MPEG.General where
import Foreign
import Foreign.C.String
import Graphics.UI.SDL
import Graphics.UI.SDL.MPEG.Types

mkFinalizedMPEG :: Ptr MPEGStruct -> IO MPEG
mkFinalizedMPEG = newForeignPtr _SMPEG_delete

foreign import ccall unsafe "&SMPEG_delete" _SMPEG_delete
    :: FunPtr (Ptr MPEGStruct -> IO ())

foreign import ccall unsafe "SMPEG_new" _SMPEG_new
    :: CString -> (Ptr InfoStruct) -> Int -> IO (Ptr MPEGStruct)

foreign import ccall unsafe "SMPEG_new_descr" _SMPEG_new_descr
    :: Int -> (Ptr InfoStruct) -> Int -> IO (Ptr MPEGStruct)

foreign import ccall unsafe "SMPEG_new_data" _SMPEG_new_data
    :: Ptr () -> Int -> (Ptr InfoStruct) -> Int -> IO (Ptr MPEGStruct)

foreign import ccall unsafe "SMPEG_new_rwops" _SMPEG_new_rwops
    :: Ptr RWopsStruct -> (Ptr InfoStruct) -> Int -> IO (Ptr MPEGStruct)

foreign import ccall unsafe "SMPEG_renderFrame" _SMPEG_renderFrame
    :: Ptr MPEGStruct -> Int -> IO ()

foreign import ccall unsafe "SMPEG_play" _SMPEG_play
    :: Ptr MPEGStruct -> IO ()

foreign import ccall unsafe "SMPEG_pause" _SMPEG_pause
    :: Ptr MPEGStruct -> IO ()

foreign import ccall unsafe "SMPEG_stop" _SMPEG_stop
    :: Ptr MPEGStruct -> IO ()

foreign import ccall unsafe "SMPEG_rewind" _SMPEG_rewind
    :: Ptr MPEGStruct -> IO ()

foreign import ccall unsafe "SMPEG_setdisplay" _SMPEG_setdisplay
    :: Ptr MPEGStruct -> (Ptr SurfaceStruct) -> (Ptr MutexStruct) -> FunPtr DisplayCallback -> IO ()

foreign import ccall unsafe "SMPEG_setdisplayregion" _SMPEG_setdisplayregion
    :: Ptr MPEGStruct -> Int -> Int -> Int -> Int -> IO ()

foreign import ccall unsafe "SMPEG_move" _SMPEG_move
    :: Ptr MPEGStruct -> Int -> Int -> IO ()

foreign import ccall "wrapper"
    mkDisplayCallback :: DisplayCallback -> IO (FunPtr DisplayCallback)

foreign import ccall unsafe "SMPEG_getinfo" _SMPEG_getinfo
    :: Ptr MPEGStruct -> Ptr InfoStruct -> IO ()

foreign import ccall unsafe "SMPEG_enableaudio" _SMPEG_enableaudio
    :: Ptr MPEGStruct -> Int -> IO ()

foreign import ccall unsafe "SMPEG_enablevideo" _SMPEG_enablevideo
    :: Ptr MPEGStruct -> Int -> IO ()

foreign import ccall unsafe "SMPEG_status" _SMPEG_status
    :: Ptr MPEGStruct -> IO Int

foreign import ccall unsafe "SMPEG_setvolume" _SMPEG_setvolume
    :: Ptr MPEGStruct -> Int -> IO ()

foreign import ccall unsafe "SMPEG_loop" _SMPEG_loop
    :: Ptr MPEGStruct -> Int -> IO ()

foreign import ccall unsafe "SMPEG_scaleXY" _SMPEG_scaleXY
    :: Ptr MPEGStruct -> Int -> Int -> IO ()

foreign import ccall unsafe "SMPEG_scale" _SMPEG_scale
    :: Ptr MPEGStruct -> Int -> IO ()

foreign import ccall unsafe "SMPEG_seek" _SMPEG_seek
    :: Ptr MPEGStruct -> Int -> IO ()

foreign import ccall unsafe "SMPEG_skip" _SMPEG_skip
    :: Ptr MPEGStruct -> Float -> IO ()

foreign import ccall unsafe "SMPEG_renderFinal" _SMPEG_renderFinal
    :: Ptr MPEGStruct -> Ptr SurfaceStruct -> Int -> Int -> IO ()

foreign import ccall unsafe "SMPEG_filter" _SMPEG_filter
    :: Ptr MPEGStruct -> Ptr FilterStruct -> IO (Ptr FilterStruct)

foreign import ccall unsafe "SMPEG_error" _SMPEG_error
    :: Ptr MPEGStruct -> IO CString

foreign import ccall unsafe "SMPEG_playAudio" _SMPEG_playAudio
    :: Ptr MPEGStruct -> CString -> Int -> IO Int

foreign import ccall unsafe "SMPEG_playAudioSDL" _SMPEG_playAudioSDL
    :: Ptr MPEGStruct -> CString -> Int -> IO ()

foreign import ccall unsafe "SMPEG_wantedSpec" _SMPEG_wantedSpec
    :: Ptr MPEGStruct -> Ptr AudioSpecStruct -> IO Int

foreign import ccall unsafe "SMPEG_actualSpec" _SMPEG_actualSpec
    :: Ptr MPEGStruct -> Ptr AudioSpecStruct -> IO ()