-- 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\\ClassRenderWindow.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. -- -- ClassRenderWindow.chs -- module HGamer3D.Bindings.Ogre.ClassRenderWindow 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\\ClassRenderWindow.chs" #-} import HGamer3D.Bindings.Ogre.ClassPtr {-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} import HGamer3D.Bindings.Ogre.StructHG3DClass {-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function setFullscreen -} setFullscreen :: HG3DClass -> Bool -> Int -> Int -> IO () setFullscreen a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in let {a3' = fromIntegral a3} in let {a4' = fromIntegral a4} in setFullscreen'_ a1' a2' a3' a4' >>= \res -> return () {-# LINE 52 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function destroy -} destroy :: HG3DClass -> IO () destroy a1 = withHG3DClass a1 $ \a1' -> destroy'_ a1' >>= \res -> return () {-# LINE 56 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function resize -} resize :: HG3DClass -> Int -> Int -> IO () resize a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromIntegral a3} in resize'_ a1' a2' a3' >>= \res -> return () {-# LINE 62 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function windowMovedOrResized -} windowMovedOrResized :: HG3DClass -> IO () windowMovedOrResized a1 = withHG3DClass a1 $ \a1' -> windowMovedOrResized'_ a1' >>= \res -> return () {-# LINE 66 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function reposition -} reposition :: HG3DClass -> Int -> Int -> IO () reposition a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromIntegral a3} in reposition'_ a1' a2' a3' >>= \res -> return () {-# LINE 72 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function isVisible -} isVisible :: HG3DClass -> IO (Bool) isVisible a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isVisible'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 77 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function setVisible -} setVisible :: HG3DClass -> Bool -> IO () setVisible a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setVisible'_ a1' a2' >>= \res -> return () {-# LINE 82 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function isHidden -} isHidden :: HG3DClass -> IO (Bool) isHidden a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isHidden'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 87 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function setHidden -} setHidden :: HG3DClass -> Bool -> IO () setHidden a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setHidden'_ a1' a2' >>= \res -> return () {-# LINE 92 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function setVSyncEnabled -} setVSyncEnabled :: HG3DClass -> Bool -> IO () setVSyncEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setVSyncEnabled'_ a1' a2' >>= \res -> return () {-# LINE 97 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function isVSyncEnabled -} isVSyncEnabled :: HG3DClass -> IO (Bool) isVSyncEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isVSyncEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 102 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function setVSyncInterval -} setVSyncInterval :: HG3DClass -> Int -> IO () setVSyncInterval a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setVSyncInterval'_ a1' a2' >>= \res -> return () {-# LINE 107 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function getVSyncInterval -} getVSyncInterval :: HG3DClass -> IO (Int) getVSyncInterval a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getVSyncInterval'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 112 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function isActive -} isActive :: HG3DClass -> IO (Bool) isActive a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isActive'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 117 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function isClosed -} isClosed :: HG3DClass -> IO (Bool) isClosed a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isClosed'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 122 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function isPrimary -} isPrimary :: HG3DClass -> IO (Bool) isPrimary a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isPrimary'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 127 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function isFullScreen -} isFullScreen :: HG3DClass -> IO (Bool) isFullScreen a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isFullScreen'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 132 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function getMetrics -} getMetrics :: HG3DClass -> IO (Int, Int, Int, Int, Int) getMetrics a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> alloca $ \a3' -> alloca $ \a4' -> alloca $ \a5' -> alloca $ \a6' -> getMetrics'_ a1' a2' a3' a4' a5' a6' >>= \res -> peekIntConv a2'>>= \a2'' -> peekIntConv a3'>>= \a3'' -> peekIntConv a4'>>= \a4'' -> peekIntConv a5'>>= \a5'' -> peekIntConv a6'>>= \a6'' -> return (a2'', a3'', a4'', a5'', a6'') {-# LINE 141 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function isDeactivatedOnFocusChange -} isDeactivatedOnFocusChange :: HG3DClass -> IO (Bool) isDeactivatedOnFocusChange a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isDeactivatedOnFocusChange'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 146 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} {- function setDeactivateOnFocusChange -} setDeactivateOnFocusChange :: HG3DClass -> Bool -> IO () setDeactivateOnFocusChange a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setDeactivateOnFocusChange'_ a1' a2' >>= \res -> return () {-# LINE 151 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_setFullscreen" setFullscreen'_ :: ((HG3DClassPtr) -> (CInt -> (CUInt -> (CUInt -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_destroy" destroy'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_resize" resize'_ :: ((HG3DClassPtr) -> (CUInt -> (CUInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_windowMovedOrResized" windowMovedOrResized'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_reposition" reposition'_ :: ((HG3DClassPtr) -> (CInt -> (CInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_isVisible" isVisible'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_setVisible" setVisible'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_isHidden" isHidden'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_setHidden" setHidden'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_setVSyncEnabled" setVSyncEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_isVSyncEnabled" isVSyncEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_setVSyncInterval" setVSyncInterval'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_getVSyncInterval" getVSyncInterval'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_isActive" isActive'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_isClosed" isClosed'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_isPrimary" isPrimary'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_isFullScreen" isFullScreen'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_getMetrics" getMetrics'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> ((Ptr CUInt) -> ((Ptr CUInt) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ()))))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_isDeactivatedOnFocusChange" isDeactivatedOnFocusChange'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs.h ogre_rw_setDeactivateOnFocusChange" setDeactivateOnFocusChange'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))