-- GENERATED by C->Haskell Compiler, version 0.16.3 Crystal Seed, 24 Jan 2009 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TypeSynonymInstances #-}

-- This source file is part of HGamer3D
-- (A project to enable 3D game development in Haskell)
-- For the latest info, see http://www.althainz.de/HGamer3D.html
-- 

-- (c) 2011, 2012 Peter Althainz
-- 
-- Licensed under the Apache License, Version 2.0 (the "License");
-- you may not use this file except in compliance with the License.
-- You may obtain a copy of the License at
-- 
--     http://www.apache.org/licenses/LICENSE-2.0
-- 
-- Unless required by applicable law or agreed to in writing, software
-- distributed under the License is distributed on an "AS IS" BASIS,
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-- See the License for the specific language governing permissions and
-- limitations under the License.
-- 


-- ClassSoundStream.chs

-- 

module HGamer3D.Bindings.SFML.ClassSoundStream where

import Foreign
import Foreign.Ptr
import Foreign.C

import HGamer3D.Data.HG3DClass
import HGamer3D.Data.Vector
import HGamer3D.Data.Colour
import HGamer3D.Data.Angle

import HGamer3D.Bindings.SFML.Utils
{-# LINE 40 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}
import HGamer3D.Bindings.SFML.ClassPtr
{-# LINE 41 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}
import HGamer3D.Bindings.SFML.StructHG3DClass
{-# LINE 42 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}

-- | Destructor. 
delete :: HG3DClass  -- ^ classpointer - pointer of Class instance which is going to be deleted.
  ->  IO ()
 -- ^ 
delete a1 =
  withHG3DClass a1 $ \a1' -> 
  delete'_ a1' >>= \res ->
  return ()
{-# LINE 47 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}

-- | Start or resume playing the audio stream.  - Details: This function starts the stream if it was stopped, resumes it if it was paused, and restarts it from beginning if it was it already playing. This function uses its own thread so that it doesn't block the rest of the program while the stream is played.
play :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
play a1 =
  withHG3DClass a1 $ \a1' -> 
  play'_ a1' >>= \res ->
  return ()
{-# LINE 51 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}

-- | Pause the audio stream.  - Details: This function pauses the stream if it was playing, otherwise (stream already paused or stopped) it has no effect.
pause :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
pause a1 =
  withHG3DClass a1 $ \a1' -> 
  pause'_ a1' >>= \res ->
  return ()
{-# LINE 55 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}

-- | Stop playing the audio stream.  - Details: This function stops the stream if it was playing or paused, and does nothing if it was already stopped. It also resets the playing position (unlike pause()
stop :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
stop a1 =
  withHG3DClass a1 $ \a1' -> 
  stop'_ a1' >>= \res ->
  return ()
{-# LINE 59 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}

-- | Return the number of channels of the stream.  - Details: 1 channel means a mono sound, 2 means stereo, etc.
getChannelCount :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getChannelCount a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getChannelCount'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 64 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}

-- | Get the stream sample rate of the stream.  - Details: The sample rate is the number of audio samples played per second. The higher, the better the quality.
getSampleRate :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getSampleRate a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSampleRate'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 69 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}

-- | Set whether or not the stream should loop after reaching the end.  - Details: If set, the stream will restart from beginning after reaching the end and so on, until it is stopped or setLoop(false) is called. The default looping state for streams is false.
setLoop :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ loop
  ->  IO ()
 -- ^ 
setLoop a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setLoop'_ a1' a2' >>= \res ->
  return ()
{-# LINE 74 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}

-- | Tell whether or not the stream is in loop mode.  - Details: setLoop
getLoop :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ return value - True if the stream is looping, false otherwise    
getLoop a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getLoop'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 79 ".\\HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs" #-}


foreign import ccall safe "HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs.h sfml_snst_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs.h sfml_snst_play"
  play'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs.h sfml_snst_pause"
  pause'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs.h sfml_snst_stop"
  stop'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs.h sfml_snst_getChannelCount"
  getChannelCount'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs.h sfml_snst_getSampleRate"
  getSampleRate'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs.h sfml_snst_setLoop"
  setLoop'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\SFML\\ClassSoundStream.chs.h sfml_snst_getLoop"
  getLoop'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))