-- 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\\ClassHG3DWindowStaticFunctions.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.
-- 


-- ClassHG3DWindowStaticFunctions.chs

-- 

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

-- | 
castWindowToPushButton :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToPushButton a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToPushButton'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 48 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToListbox :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToListbox a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToListbox'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 53 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToCombobox :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToCombobox a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToCombobox'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 58 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToCheckbox :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToCheckbox a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToCheckbox'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 63 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToRadioButton :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToRadioButton a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToRadioButton'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 68 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToEditbox :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToEditbox a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToEditbox'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 73 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToMultiLineEditbox :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToMultiLineEditbox a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToMultiLineEditbox'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 78 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToFrameWindow :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToFrameWindow a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToFrameWindow'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 83 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToProgressBar :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToProgressBar a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToProgressBar'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 88 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToSlider :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToSlider a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToSlider'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 93 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToSpinner :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToSpinner a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToSpinner'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 98 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}

-- | 
castWindowToMultiColumnList :: HG3DClass  -- ^ window
  ->  IO (HG3DClass)
 -- ^ 
castWindowToMultiColumnList a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  castWindowToMultiColumnList'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 103 ".\\HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs" #-}


foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToPushButton"
  castWindowToPushButton'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToListbox"
  castWindowToListbox'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToCombobox"
  castWindowToCombobox'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToCheckbox"
  castWindowToCheckbox'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToRadioButton"
  castWindowToRadioButton'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToEditbox"
  castWindowToEditbox'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToMultiLineEditbox"
  castWindowToMultiLineEditbox'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToFrameWindow"
  castWindowToFrameWindow'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToProgressBar"
  castWindowToProgressBar'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToSlider"
  castWindowToSlider'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToSpinner"
  castWindowToSpinner'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassHG3DWindowStaticFunctions.chs.h cegui_hg3dwsfs_castWindowToMultiColumnList"
  castWindowToMultiColumnList'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))