-- 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\\Ogre\\ClassControllerManager.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.
-- 


-- ClassControllerManager.chs

-- 

module HGamer3D.Bindings.Ogre.ClassControllerManager 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.Ogre.Utils
{-# LINE 40 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}
import HGamer3D.Bindings.Ogre.ClassPtr
{-# LINE 41 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}
import HGamer3D.Bindings.Ogre.StructHG3DClass
{-# LINE 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | 
new :: IO (HG3DClass)
 -- ^ 
new =
  alloca $ \a1' -> 
  new'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

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

-- | Destroys all the controllers in existence. 
clearControllers :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
clearControllers a1 =
  withHG3DClass a1 $ \a1' -> 
  clearControllers'_ a1' >>= \res ->
  return ()
{-# LINE 55 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | Updates all the registered controllers. 
updateAllControllers :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
updateAllControllers a1 =
  withHG3DClass a1 $ \a1' -> 
  updateAllControllers'_ a1' >>= \res ->
  return ()
{-# LINE 59 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | Return relative speed of time as perceived by time based controllers. See setTimeFactor for full information on the meaning of this value. 
getTimeFactor :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getTimeFactor a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getTimeFactor'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 64 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | Set the relative speed to update frame time based controllers. Normally any controllers which use time as an input (FrameTimeController) are updated automatically in line with the real passage of time. This method allows you to change that, so that controllers are told that the time is passing slower or faster than it actually is. Use this to globally speed up / slow down the effect of time-based controllers. 
setTimeFactor :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ tf - The virtual speed of time (1.0 is real time). 
  ->  IO ()
 -- ^ 
setTimeFactor a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setTimeFactor'_ a1' a2' >>= \res ->
  return ()
{-# LINE 69 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | Gets the constant that is added to time lapsed between each frame. See setFrameDelay for full information on the meaning of this value. 
getFrameDelay :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getFrameDelay a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getFrameDelay'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 74 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | Sets a constant frame rate. This function is useful when rendering a sequence to files that should create a film clip with constant frame rate. It will ensure that scrolling textures and animations move at a constant frame rate. 
setFrameDelay :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ fd - The delay in seconds wanted between each frame (1.0f / 25.0f means a seconds worth of animation is done in 25 frames). 
  ->  IO ()
 -- ^ 
setFrameDelay a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setFrameDelay'_ a1' a2' >>= \res ->
  return ()
{-# LINE 79 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | Return the elapsed time. See setElapsedTime for full information on the meaning of this value. 
getElapsedTime :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getElapsedTime a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getElapsedTime'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 84 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | Set the elapsed time. Normally elapsed time accumulated all frames time (which speed relative to time factor) since the rendering loop started. This method allows your to change that to special time, so some elapsed-time-based globally effect is repeatable. 
setElapsedTime :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ elapsedTime - The new elapsed time 
  ->  IO ()
 -- ^ 
setElapsedTime a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setElapsedTime'_ a1' a2' >>= \res ->
  return ()
{-# LINE 89 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}

-- | Override standard Singleton retrieval. Why do we do this? Well, it's because the Singleton implementation is in a .h file, which means it gets compiled into anybody who includes it. This is needed for the Singleton template to work, but we actually only want it compiled into the implementation of the class based on the Singleton, not all of them. If we don't change this, we get link errors when trying to use the Singleton-based class from an outside dll. This method just delegates to the template version anyway, but the implementation stays in this single compilation unit, preventing link errors. 
getSingletonPtr :: IO (HG3DClass)
 -- ^ 
getSingletonPtr =
  alloca $ \a1' -> 
  getSingletonPtr'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 93 ".\\HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs" #-}


foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_construct"
  new'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_clearControllers"
  clearControllers'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_updateAllControllers"
  updateAllControllers'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_getTimeFactor"
  getTimeFactor'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_setTimeFactor"
  setTimeFactor'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_getFrameDelay"
  getFrameDelay'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_setFrameDelay"
  setFrameDelay'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_getElapsedTime"
  getElapsedTime'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_setElapsedTime"
  setElapsedTime'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassControllerManager.chs.h ogre_cmgr_getSingletonPtr"
  getSingletonPtr'_ :: ((HG3DClassPtr) -> (IO ()))