-- 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\\CEGUI\\ClassSystem.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.
-- 


-- ClassSystem.chs

-- 

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

{- function create -}
create :: HG3DClass -> HG3DClass -> HG3DClass -> HG3DClass -> HG3DClass -> String -> String -> IO (HG3DClass)
create a1 a2 a3 a4 a5 a6 a7 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  withHG3DClass a3 $ \a3' -> 
  withHG3DClass a4 $ \a4' -> 
  withHG3DClass a5 $ \a5' -> 
  withCString a6 $ \a6' -> 
  withCString a7 $ \a7' -> 
  alloca $ \a8' -> 
  create'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  peek  a8'>>= \a8'' -> 
  return (a8'')
{-# LINE 55 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function destroy -}
destroy :: IO ()
destroy =
  destroy'_ >>= \res ->
  return ()
{-# LINE 59 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getSingleton -}
getSingleton :: IO (HG3DClass)
getSingleton =
  alloca $ \a1' -> 
  getSingleton'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 63 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getSingletonPtr -}
getSingletonPtr :: IO (HG3DClass)
getSingletonPtr =
  alloca $ \a1' -> 
  getSingletonPtr'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 67 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setDefaultXMLParserName -}
setDefaultXMLParserName :: String -> IO ()
setDefaultXMLParserName a1 =
  withCString a1 $ \a1' -> 
  setDefaultXMLParserName'_ a1' >>= \res ->
  return ()
{-# LINE 71 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getDefaultXMLParserName -}
getDefaultXMLParserName :: IO (String)
getDefaultXMLParserName =
  alloc64k $ \a1' -> 
  getDefaultXMLParserName'_ a1' >>= \res ->
  peekCString  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 75 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setDefaultImageCodecName -}
setDefaultImageCodecName :: String -> IO ()
setDefaultImageCodecName a1 =
  withCString a1 $ \a1' -> 
  setDefaultImageCodecName'_ a1' >>= \res ->
  return ()
{-# LINE 79 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getDefaultImageCodecName -}
getDefaultImageCodecName :: IO (String)
getDefaultImageCodecName =
  alloc64k $ \a1' -> 
  getDefaultImageCodecName'_ a1' >>= \res ->
  peekCString  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 83 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getRenderer -}
getRenderer :: HG3DClass -> IO (HG3DClass)
getRenderer a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRenderer'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 88 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setDefaultFont -}
setDefaultFont :: HG3DClass -> String -> IO ()
setDefaultFont a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  setDefaultFont'_ a1' a2' >>= \res ->
  return ()
{-# LINE 93 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setDefaultFont2 -}
setDefaultFont2 :: HG3DClass -> HG3DClass -> IO ()
setDefaultFont2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setDefaultFont2'_ a1' a2' >>= \res ->
  return ()
{-# LINE 98 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getDefaultFont -}
getDefaultFont :: HG3DClass -> IO (HG3DClass)
getDefaultFont a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDefaultFont'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 103 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function signalRedraw -}
signalRedraw :: HG3DClass -> IO ()
signalRedraw a1 =
  withHG3DClass a1 $ \a1' -> 
  signalRedraw'_ a1' >>= \res ->
  return ()
{-# LINE 107 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function isRedrawRequested -}
isRedrawRequested :: HG3DClass -> IO (Bool)
isRedrawRequested a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isRedrawRequested'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 112 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function renderGUI -}
renderGUI :: HG3DClass -> IO ()
renderGUI a1 =
  withHG3DClass a1 $ \a1' -> 
  renderGUI'_ a1' >>= \res ->
  return ()
{-# LINE 116 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setGUISheet -}
setGUISheet :: HG3DClass -> HG3DClass -> IO (HG3DClass)
setGUISheet a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  alloca $ \a3' -> 
  setGUISheet'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 122 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getGUISheet -}
getGUISheet :: HG3DClass -> IO (HG3DClass)
getGUISheet a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getGUISheet'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 127 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getSingleClickTimeout -}
getSingleClickTimeout :: HG3DClass -> IO (Double)
getSingleClickTimeout a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSingleClickTimeout'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 132 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getMultiClickTimeout -}
getMultiClickTimeout :: HG3DClass -> IO (Double)
getMultiClickTimeout a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getMultiClickTimeout'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 137 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setSingleClickTimeout -}
setSingleClickTimeout :: HG3DClass -> Double -> IO ()
setSingleClickTimeout a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setSingleClickTimeout'_ a1' a2' >>= \res ->
  return ()
{-# LINE 142 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setMultiClickTimeout -}
setMultiClickTimeout :: HG3DClass -> Double -> IO ()
setMultiClickTimeout a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setMultiClickTimeout'_ a1' a2' >>= \res ->
  return ()
{-# LINE 147 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function isMouseClickEventGenerationEnabled -}
isMouseClickEventGenerationEnabled :: HG3DClass -> IO (Bool)
isMouseClickEventGenerationEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isMouseClickEventGenerationEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 152 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setMouseClickEventGenerationEnabled -}
setMouseClickEventGenerationEnabled :: HG3DClass -> Bool -> IO ()
setMouseClickEventGenerationEnabled a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setMouseClickEventGenerationEnabled'_ a1' a2' >>= \res ->
  return ()
{-# LINE 157 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setDefaultMouseCursor3 -}
setDefaultMouseCursor3 :: HG3DClass -> String -> String -> IO ()
setDefaultMouseCursor3 a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  setDefaultMouseCursor3'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 163 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getWindowContainingMouse -}
getWindowContainingMouse :: HG3DClass -> IO (HG3DClass)
getWindowContainingMouse a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getWindowContainingMouse'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 168 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getScriptingModule -}
getScriptingModule :: HG3DClass -> IO (HG3DClass)
getScriptingModule a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getScriptingModule'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 173 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setScriptingModule -}
setScriptingModule :: HG3DClass -> HG3DClass -> IO ()
setScriptingModule a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setScriptingModule'_ a1' a2' >>= \res ->
  return ()
{-# LINE 178 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getResourceProvider -}
getResourceProvider :: HG3DClass -> IO (HG3DClass)
getResourceProvider a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getResourceProvider'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 183 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function executeScriptFile -}
executeScriptFile :: HG3DClass -> String -> String -> IO ()
executeScriptFile a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  executeScriptFile'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 189 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function executeScriptGlobal -}
executeScriptGlobal :: HG3DClass -> String -> IO (Int)
executeScriptGlobal a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  executeScriptGlobal'_ a1' a2' a3' >>= \res ->
  peekIntConv  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 195 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function executeScriptString -}
executeScriptString :: HG3DClass -> String -> IO ()
executeScriptString a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  executeScriptString'_ a1' a2' >>= \res ->
  return ()
{-# LINE 200 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getMouseMoveScaling -}
getMouseMoveScaling :: HG3DClass -> IO (Float)
getMouseMoveScaling a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getMouseMoveScaling'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 205 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setMouseMoveScaling -}
setMouseMoveScaling :: HG3DClass -> Float -> IO ()
setMouseMoveScaling a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setMouseMoveScaling'_ a1' a2' >>= \res ->
  return ()
{-# LINE 210 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function notifyWindowDestroyed -}
notifyWindowDestroyed :: HG3DClass -> HG3DClass -> IO ()
notifyWindowDestroyed a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  notifyWindowDestroyed'_ a1' a2' >>= \res ->
  return ()
{-# LINE 215 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getSystemKeys -}
getSystemKeys :: HG3DClass -> IO (Int)
getSystemKeys a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSystemKeys'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 220 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setXMLParser -}
setXMLParser :: HG3DClass -> String -> IO ()
setXMLParser a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  setXMLParser'_ a1' a2' >>= \res ->
  return ()
{-# LINE 225 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setXMLParser2 -}
setXMLParser2 :: HG3DClass -> HG3DClass -> IO ()
setXMLParser2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setXMLParser2'_ a1' a2' >>= \res ->
  return ()
{-# LINE 230 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getXMLParser -}
getXMLParser :: HG3DClass -> IO (HG3DClass)
getXMLParser a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getXMLParser'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 235 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setDefaultTooltip -}
setDefaultTooltip :: HG3DClass -> HG3DClass -> IO ()
setDefaultTooltip a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setDefaultTooltip'_ a1' a2' >>= \res ->
  return ()
{-# LINE 240 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setDefaultTooltip2 -}
setDefaultTooltip2 :: HG3DClass -> String -> IO ()
setDefaultTooltip2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  setDefaultTooltip2'_ a1' a2' >>= \res ->
  return ()
{-# LINE 245 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getDefaultTooltip -}
getDefaultTooltip :: HG3DClass -> IO (HG3DClass)
getDefaultTooltip a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDefaultTooltip'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 250 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setModalTarget -}
setModalTarget :: HG3DClass -> HG3DClass -> IO ()
setModalTarget a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setModalTarget'_ a1' a2' >>= \res ->
  return ()
{-# LINE 255 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getModalTarget -}
getModalTarget :: HG3DClass -> IO (HG3DClass)
getModalTarget a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getModalTarget'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 260 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function updateWindowContainingMouse -}
updateWindowContainingMouse :: HG3DClass -> IO (Bool)
updateWindowContainingMouse a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  updateWindowContainingMouse'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 265 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function getImageCodec -}
getImageCodec :: HG3DClass -> IO (HG3DClass)
getImageCodec a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getImageCodec'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 270 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setImageCodec -}
setImageCodec :: HG3DClass -> String -> IO ()
setImageCodec a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  setImageCodec'_ a1' a2' >>= \res ->
  return ()
{-# LINE 275 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function setImageCodec2 -}
setImageCodec2 :: HG3DClass -> HG3DClass -> IO ()
setImageCodec2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setImageCodec2'_ a1' a2' >>= \res ->
  return ()
{-# LINE 280 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function invalidateAllCachedRendering -}
invalidateAllCachedRendering :: HG3DClass -> IO ()
invalidateAllCachedRendering a1 =
  withHG3DClass a1 $ \a1' -> 
  invalidateAllCachedRendering'_ a1' >>= \res ->
  return ()
{-# LINE 284 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMouseMove -}
injectMouseMove :: HG3DClass -> Float -> Float -> IO (Bool)
injectMouseMove a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  alloca $ \a4' -> 
  injectMouseMove'_ a1' a2' a3' a4' >>= \res ->
  peekBoolUtil  a4'>>= \a4'' -> 
  return (a4'')
{-# LINE 291 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMouseLeaves -}
injectMouseLeaves :: HG3DClass -> IO (Bool)
injectMouseLeaves a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  injectMouseLeaves'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 296 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMouseButtonDown -}
injectMouseButtonDown :: HG3DClass -> EnumMouseButton -> IO (Bool)
injectMouseButtonDown a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = cIntFromEnum a2} in 
  alloca $ \a3' -> 
  injectMouseButtonDown'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 302 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMouseButtonUp -}
injectMouseButtonUp :: HG3DClass -> EnumMouseButton -> IO (Bool)
injectMouseButtonUp a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = cIntFromEnum a2} in 
  alloca $ \a3' -> 
  injectMouseButtonUp'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 308 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectKeyDown -}
injectKeyDown :: HG3DClass -> Int -> IO (Bool)
injectKeyDown a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  injectKeyDown'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 314 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectKeyUp -}
injectKeyUp :: HG3DClass -> Int -> IO (Bool)
injectKeyUp a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  injectKeyUp'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 320 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectChar -}
injectChar :: HG3DClass -> Int -> IO (Bool)
injectChar a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  injectChar'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 326 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMouseWheelChange -}
injectMouseWheelChange :: HG3DClass -> Float -> IO (Bool)
injectMouseWheelChange a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  alloca $ \a3' -> 
  injectMouseWheelChange'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 332 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMousePosition -}
injectMousePosition :: HG3DClass -> Float -> Float -> IO (Bool)
injectMousePosition a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  alloca $ \a4' -> 
  injectMousePosition'_ a1' a2' a3' a4' >>= \res ->
  peekBoolUtil  a4'>>= \a4'' -> 
  return (a4'')
{-# LINE 339 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectTimePulse -}
injectTimePulse :: HG3DClass -> Float -> IO (Bool)
injectTimePulse a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  alloca $ \a3' -> 
  injectTimePulse'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 345 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMouseButtonClick -}
injectMouseButtonClick :: HG3DClass -> EnumMouseButton -> IO (Bool)
injectMouseButtonClick a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = cIntFromEnum a2} in 
  alloca $ \a3' -> 
  injectMouseButtonClick'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 351 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMouseButtonDoubleClick -}
injectMouseButtonDoubleClick :: HG3DClass -> EnumMouseButton -> IO (Bool)
injectMouseButtonDoubleClick a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = cIntFromEnum a2} in 
  alloca $ \a3' -> 
  injectMouseButtonDoubleClick'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 357 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}

{- function injectMouseButtonTripleClick -}
injectMouseButtonTripleClick :: HG3DClass -> EnumMouseButton -> IO (Bool)
injectMouseButtonTripleClick a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = cIntFromEnum a2} in 
  alloca $ \a3' -> 
  injectMouseButtonTripleClick'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 363 ".\\HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs" #-}


foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_create"
  create'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))))))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_destroy"
  destroy'_ :: (IO ())

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getSingleton"
  getSingleton'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getSingletonPtr"
  getSingletonPtr'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setDefaultXMLParserName"
  setDefaultXMLParserName'_ :: ((Ptr CChar) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getDefaultXMLParserName"
  getDefaultXMLParserName'_ :: ((Ptr CChar) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setDefaultImageCodecName"
  setDefaultImageCodecName'_ :: ((Ptr CChar) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getDefaultImageCodecName"
  getDefaultImageCodecName'_ :: ((Ptr CChar) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getRenderer"
  getRenderer'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setDefaultFont"
  setDefaultFont'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setDefaultFont2"
  setDefaultFont2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getDefaultFont"
  getDefaultFont'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_signalRedraw"
  signalRedraw'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_isRedrawRequested"
  isRedrawRequested'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_renderGUI"
  renderGUI'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setGUISheet"
  setGUISheet'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getGUISheet"
  getGUISheet'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getSingleClickTimeout"
  getSingleClickTimeout'_ :: ((HG3DClassPtr) -> ((Ptr CDouble) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getMultiClickTimeout"
  getMultiClickTimeout'_ :: ((HG3DClassPtr) -> ((Ptr CDouble) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setSingleClickTimeout"
  setSingleClickTimeout'_ :: ((HG3DClassPtr) -> (CDouble -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setMultiClickTimeout"
  setMultiClickTimeout'_ :: ((HG3DClassPtr) -> (CDouble -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_isMouseClickEventGenerationEnabled"
  isMouseClickEventGenerationEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setMouseClickEventGenerationEnabled"
  setMouseClickEventGenerationEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setDefaultMouseCursor3"
  setDefaultMouseCursor3'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getWindowContainingMouse"
  getWindowContainingMouse'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getScriptingModule"
  getScriptingModule'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setScriptingModule"
  setScriptingModule'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getResourceProvider"
  getResourceProvider'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_executeScriptFile"
  executeScriptFile'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_executeScriptGlobal"
  executeScriptGlobal'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_executeScriptString"
  executeScriptString'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getMouseMoveScaling"
  getMouseMoveScaling'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setMouseMoveScaling"
  setMouseMoveScaling'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_notifyWindowDestroyed"
  notifyWindowDestroyed'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getSystemKeys"
  getSystemKeys'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setXMLParser"
  setXMLParser'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setXMLParser2"
  setXMLParser2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getXMLParser"
  getXMLParser'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setDefaultTooltip"
  setDefaultTooltip'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setDefaultTooltip2"
  setDefaultTooltip2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getDefaultTooltip"
  getDefaultTooltip'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setModalTarget"
  setModalTarget'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getModalTarget"
  getModalTarget'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_updateWindowContainingMouse"
  updateWindowContainingMouse'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_getImageCodec"
  getImageCodec'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setImageCodec"
  setImageCodec'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_setImageCodec2"
  setImageCodec2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_invalidateAllCachedRendering"
  invalidateAllCachedRendering'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMouseMove"
  injectMouseMove'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> ((Ptr CInt) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMouseLeaves"
  injectMouseLeaves'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMouseButtonDown"
  injectMouseButtonDown'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMouseButtonUp"
  injectMouseButtonUp'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectKeyDown"
  injectKeyDown'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectKeyUp"
  injectKeyUp'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectChar"
  injectChar'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMouseWheelChange"
  injectMouseWheelChange'_ :: ((HG3DClassPtr) -> (CFloat -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMousePosition"
  injectMousePosition'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> ((Ptr CInt) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectTimePulse"
  injectTimePulse'_ :: ((HG3DClassPtr) -> (CFloat -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMouseButtonClick"
  injectMouseButtonClick'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMouseButtonDoubleClick"
  injectMouseButtonDoubleClick'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassSystem.chs.h cegui_sstm_injectMouseButtonTripleClick"
  injectMouseButtonTripleClick'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ()))))