-- 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\\ClassViewport.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-2013 Peter Althainz -- -- The files are part of HGamer3D (www.hgamer3d.org) -- -- 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. -- -- ClassViewport.chs -- module HGamer3D.Bindings.Ogre.ClassViewport 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 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} import HGamer3D.Bindings.Ogre.ClassPtr {-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} import HGamer3D.Bindings.Ogre.StructHG3DClass {-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} import HGamer3D.Bindings.Ogre.StructColour {-# LINE 45 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} import HGamer3D.Bindings.Ogre.EnumOrientationMode {-# LINE 46 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} import HGamer3D.Bindings.Ogre.StructVec2 {-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function Viewport -} new :: HG3DClass -> HG3DClass -> Float -> Float -> Float -> Float -> Int -> IO (HG3DClass) new a1 a2 a3 a4 a5 a6 a7 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> let {a3' = realToFrac a3} in let {a4' = realToFrac a4} in let {a5' = realToFrac a5} in let {a6' = realToFrac a6} in let {a7' = fromIntegral a7} in alloca $ \a8' -> new'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res -> peek a8'>>= \a8'' -> return (a8'') {-# LINE 59 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function ~Viewport -} delete :: HG3DClass -> IO () delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 63 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function update -} update :: HG3DClass -> IO () update a1 = withHG3DClass a1 $ \a1' -> update'_ a1' >>= \res -> return () {-# LINE 67 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function clear -} clear :: HG3DClass -> Int -> Colour -> Float -> Int -> IO () clear a1 a2 a3 a4 a5 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in withColour a3 $ \a3' -> let {a4' = realToFrac a4} in let {a5' = fromIntegral a5} in clear'_ a1' a2' a3' a4' a5' >>= \res -> return () {-# LINE 75 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getTarget -} getTarget :: HG3DClass -> IO (HG3DClass) getTarget a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getTarget'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 80 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getCamera -} getCamera :: HG3DClass -> IO (HG3DClass) getCamera a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCamera'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 85 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setCamera -} setCamera :: HG3DClass -> HG3DClass -> IO () setCamera a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> setCamera'_ a1' a2' >>= \res -> return () {-# LINE 90 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getZOrder -} getZOrder :: HG3DClass -> IO (Int) getZOrder a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getZOrder'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 95 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getLeft -} getLeft :: HG3DClass -> IO (Float) getLeft a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getLeft'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 100 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getTop -} getTop :: HG3DClass -> IO (Float) getTop a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getTop'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 105 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getWidth -} getWidth :: HG3DClass -> IO (Float) getWidth a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getWidth'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 110 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getHeight -} getHeight :: HG3DClass -> IO (Float) getHeight a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getHeight'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 115 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getActualLeft -} getActualLeft :: HG3DClass -> IO (Int) getActualLeft a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getActualLeft'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 120 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getActualTop -} getActualTop :: HG3DClass -> IO (Int) getActualTop a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getActualTop'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 125 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getActualWidth -} getActualWidth :: HG3DClass -> IO (Int) getActualWidth a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getActualWidth'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 130 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getActualHeight -} getActualHeight :: HG3DClass -> IO (Int) getActualHeight a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getActualHeight'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 135 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setDimensions -} setDimensions :: HG3DClass -> Float -> Float -> Float -> Float -> IO () setDimensions a1 a2 a3 a4 a5 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in let {a3' = realToFrac a3} in let {a4' = realToFrac a4} in let {a5' = realToFrac a5} in setDimensions'_ a1' a2' a3' a4' a5' >>= \res -> return () {-# LINE 143 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setOrientationMode -} setOrientationMode :: HG3DClass -> EnumOrientationMode -> Bool -> IO () setOrientationMode a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in let {a3' = fromBool a3} in setOrientationMode'_ a1' a2' a3' >>= \res -> return () {-# LINE 149 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getOrientationMode -} getOrientationMode :: HG3DClass -> IO (EnumOrientationMode) getOrientationMode a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getOrientationMode'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 154 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setBackgroundColour -} setBackgroundColour :: HG3DClass -> Colour -> IO () setBackgroundColour a1 a2 = withHG3DClass a1 $ \a1' -> withColour a2 $ \a2' -> setBackgroundColour'_ a1' a2' >>= \res -> return () {-# LINE 159 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getBackgroundColour -} getBackgroundColour :: HG3DClass -> IO (Colour) getBackgroundColour a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBackgroundColour'_ a1' a2' >>= \res -> peekColour a2'>>= \a2'' -> return (a2'') {-# LINE 164 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setDepthClear -} setDepthClear :: HG3DClass -> Float -> IO () setDepthClear a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in setDepthClear'_ a1' a2' >>= \res -> return () {-# LINE 169 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getDepthClear -} getDepthClear :: HG3DClass -> IO (Float) getDepthClear a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getDepthClear'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 174 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setClearEveryFrame -} setClearEveryFrame :: HG3DClass -> Bool -> Int -> IO () setClearEveryFrame a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in let {a3' = fromIntegral a3} in setClearEveryFrame'_ a1' a2' a3' >>= \res -> return () {-# LINE 180 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getClearEveryFrame -} getClearEveryFrame :: HG3DClass -> IO (Bool) getClearEveryFrame a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getClearEveryFrame'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 185 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getClearBuffers -} getClearBuffers :: HG3DClass -> IO (Int) getClearBuffers a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getClearBuffers'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 190 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setAutoUpdated -} setAutoUpdated :: HG3DClass -> Bool -> IO () setAutoUpdated a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setAutoUpdated'_ a1' a2' >>= \res -> return () {-# LINE 195 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function isAutoUpdated -} isAutoUpdated :: HG3DClass -> IO (Bool) isAutoUpdated a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isAutoUpdated'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 200 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setMaterialScheme -} setMaterialScheme :: HG3DClass -> String -> IO () setMaterialScheme a1 a2 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> setMaterialScheme'_ a1' a2' >>= \res -> return () {-# LINE 205 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getMaterialScheme -} getMaterialScheme :: HG3DClass -> IO (String) getMaterialScheme a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getMaterialScheme'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 210 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getActualDimensions -} getActualDimensions :: HG3DClass -> IO (Int, Int, Int, Int) getActualDimensions a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> alloca $ \a3' -> alloca $ \a4' -> alloca $ \a5' -> getActualDimensions'_ a1' a2' a3' a4' a5' >>= \res -> peekIntConv a2'>>= \a2'' -> peekIntConv a3'>>= \a3'' -> peekIntConv a4'>>= \a4'' -> peekIntConv a5'>>= \a5'' -> return (a2'', a3'', a4'', a5'') {-# LINE 218 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setOverlaysEnabled -} setOverlaysEnabled :: HG3DClass -> Bool -> IO () setOverlaysEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setOverlaysEnabled'_ a1' a2' >>= \res -> return () {-# LINE 223 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getOverlaysEnabled -} getOverlaysEnabled :: HG3DClass -> IO (Bool) getOverlaysEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getOverlaysEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 228 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setSkiesEnabled -} setSkiesEnabled :: HG3DClass -> Bool -> IO () setSkiesEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setSkiesEnabled'_ a1' a2' >>= \res -> return () {-# LINE 233 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getSkiesEnabled -} getSkiesEnabled :: HG3DClass -> IO (Bool) getSkiesEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSkiesEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 238 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setShadowsEnabled -} setShadowsEnabled :: HG3DClass -> Bool -> IO () setShadowsEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setShadowsEnabled'_ a1' a2' >>= \res -> return () {-# LINE 243 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getShadowsEnabled -} getShadowsEnabled :: HG3DClass -> IO (Bool) getShadowsEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getShadowsEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 248 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setVisibilityMask -} setVisibilityMask :: HG3DClass -> Int -> IO () setVisibilityMask a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setVisibilityMask'_ a1' a2' >>= \res -> return () {-# LINE 253 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getVisibilityMask -} getVisibilityMask :: HG3DClass -> IO (Int) getVisibilityMask a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getVisibilityMask'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 258 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setRenderQueueInvocationSequenceName -} setRenderQueueInvocationSequenceName :: HG3DClass -> String -> IO () setRenderQueueInvocationSequenceName a1 a2 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> setRenderQueueInvocationSequenceName'_ a1' a2' >>= \res -> return () {-# LINE 263 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getRenderQueueInvocationSequenceName -} getRenderQueueInvocationSequenceName :: HG3DClass -> IO (String) getRenderQueueInvocationSequenceName a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getRenderQueueInvocationSequenceName'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 268 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function pointOrientedToScreen -} pointOrientedToScreen :: HG3DClass -> Vec2 -> Int -> IO (Vec2) pointOrientedToScreen a1 a2 a3 = withHG3DClass a1 $ \a1' -> withVec2 a2 $ \a2' -> let {a3' = fromIntegral a3} in alloca $ \a4' -> pointOrientedToScreen'_ a1' a2' a3' a4' >>= \res -> peekVec2 a4'>>= \a4'' -> return (a4'') {-# LINE 275 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function pointOrientedToScreen2 -} pointOrientedToScreen2 :: HG3DClass -> Float -> Float -> Int -> IO (Float, Float) pointOrientedToScreen2 a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in let {a3' = realToFrac a3} in let {a4' = fromIntegral a4} in alloca $ \a5' -> alloca $ \a6' -> pointOrientedToScreen2'_ a1' a2' a3' a4' a5' a6' >>= \res -> peekFloatConv a5'>>= \a5'' -> peekFloatConv a6'>>= \a6'' -> return (a5'', a6'') {-# LINE 284 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function setDefaultOrientationMode -} setDefaultOrientationMode :: EnumOrientationMode -> IO () setDefaultOrientationMode a1 = let {a1' = cIntFromEnum a1} in setDefaultOrientationMode'_ a1' >>= \res -> return () {-# LINE 288 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} {- function getDefaultOrientationMode -} getDefaultOrientationMode :: IO (EnumOrientationMode) getDefaultOrientationMode = alloca $ \a1' -> getDefaultOrientationMode'_ a1' >>= \res -> peekEnumUtil a1'>>= \a1'' -> return (a1'') {-# LINE 292 ".\\HGamer3D\\Bindings\\Ogre\\ClassViewport.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_construct" new'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (CInt -> ((HG3DClassPtr) -> (IO ()))))))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_update" update'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_clear" clear'_ :: ((HG3DClassPtr) -> (CUInt -> ((ColourPtr) -> (CFloat -> (CUShort -> (IO ())))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getTarget" getTarget'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getCamera" getCamera'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setCamera" setCamera'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getZOrder" getZOrder'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getLeft" getLeft'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getTop" getTop'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getWidth" getWidth'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getHeight" getHeight'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getActualLeft" getActualLeft'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getActualTop" getActualTop'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getActualWidth" getActualWidth'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getActualHeight" getActualHeight'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setDimensions" setDimensions'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setOrientationMode" setOrientationMode'_ :: ((HG3DClassPtr) -> (CInt -> (CInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getOrientationMode" getOrientationMode'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setBackgroundColour" setBackgroundColour'_ :: ((HG3DClassPtr) -> ((ColourPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getBackgroundColour" getBackgroundColour'_ :: ((HG3DClassPtr) -> ((ColourPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setDepthClear" setDepthClear'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getDepthClear" getDepthClear'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setClearEveryFrame" setClearEveryFrame'_ :: ((HG3DClassPtr) -> (CInt -> (CUInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getClearEveryFrame" getClearEveryFrame'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getClearBuffers" getClearBuffers'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setAutoUpdated" setAutoUpdated'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_isAutoUpdated" isAutoUpdated'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setMaterialScheme" setMaterialScheme'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getMaterialScheme" getMaterialScheme'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getActualDimensions" getActualDimensions'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ())))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setOverlaysEnabled" setOverlaysEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getOverlaysEnabled" getOverlaysEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setSkiesEnabled" setSkiesEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getSkiesEnabled" getSkiesEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setShadowsEnabled" setShadowsEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getShadowsEnabled" getShadowsEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setVisibilityMask" setVisibilityMask'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getVisibilityMask" getVisibilityMask'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setRenderQueueInvocationSequenceName" setRenderQueueInvocationSequenceName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getRenderQueueInvocationSequenceName" getRenderQueueInvocationSequenceName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_pointOrientedToScreen" pointOrientedToScreen'_ :: ((HG3DClassPtr) -> ((Vec2Ptr) -> (CInt -> ((Vec2Ptr) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_pointOrientedToScreen2" pointOrientedToScreen2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_setDefaultOrientationMode" setDefaultOrientationMode'_ :: (CInt -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassViewport.chs.h ogre_vprt_getDefaultOrientationMode" getDefaultOrientationMode'_ :: ((Ptr CInt) -> (IO ()))