-- 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, 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. -- -- 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 40 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} import HGamer3D.Bindings.Ogre.ClassPtr {-# LINE 41 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} import HGamer3D.Bindings.Ogre.StructHG3DClass {-# LINE 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Alter fullscreen mode options. Nothing will happen unless the settings here are different from the current settings. setFullscreen :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ fullScreen - Whether to use fullscreen mode or not. -> Int -- ^ width - The new width to use -> Int -- ^ height - The new height to use -> 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 50 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Destroys the window. destroy :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ destroy a1 = withHG3DClass a1 $ \a1' -> destroy'_ a1' >>= \res -> return () {-# LINE 54 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Alter the size of the window. resize :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ width -> Int -- ^ height -> 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 60 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Notify that the window has been resized You don't need to call this unless you created the window externally. windowMovedOrResized :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ windowMovedOrResized a1 = withHG3DClass a1 $ \a1' -> windowMovedOrResized'_ a1' >>= \res -> return () {-# LINE 64 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Reposition the window. reposition :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ left -> Int -- ^ top -> 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 70 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Indicates whether the window is visible (not minimized or obscured) isVisible :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isVisible a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isVisible'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 75 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Set the visibility state setVisible :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ visible -> IO () -- ^ setVisible a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setVisible'_ a1' a2' >>= \res -> return () {-# LINE 80 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Overridden from RenderTarget isActive :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isActive a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isActive'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 85 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Indicates whether the window has been closed by the user. isClosed :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isClosed a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isClosed'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 90 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Indicates whether the window is the primary window. The primary window is special in that it is destroyed when ogre is shut down, and cannot be destroyed directly. This is the case because it holds the context for vertex, index buffers and textures. isPrimary :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isPrimary a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isPrimary'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 95 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Returns true if window is running in fullscreen mode. isFullScreen :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isFullScreen a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isFullScreen'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 100 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Overloaded version of getMetrics from RenderTarget getMetrics :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int, Int, Int, Int, Int) -- ^ width 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 109 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Returns true if the window will automatically de-activate itself when it loses focus. isDeactivatedOnFocusChange :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isDeactivatedOnFocusChange a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isDeactivatedOnFocusChange'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 114 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderWindow.chs" #-} -- | Indicates whether the window will automatically deactivate itself when it loses focus. 'true' is the default behavior. setDeactivateOnFocusChange :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ deactivate - a value of 'true' will cause the window to deactivate itself when it loses focus. 'false' will allow it to continue to render even when window focus is lost. -> IO () -- ^ setDeactivateOnFocusChange a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setDeactivateOnFocusChange'_ a1' a2' >>= \res -> return () {-# LINE 119 ".\\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_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 ())))