-- 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\\ClassItemListbox.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. -- -- ClassItemListbox.chs -- module HGamer3D.Bindings.CEGUI.ClassItemListbox 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\\ClassItemListbox.chs" #-} import HGamer3D.Bindings.CEGUI.ClassPtr {-# LINE 41 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} import HGamer3D.Bindings.CEGUI.StructHG3DClass {-# LINE 42 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Returns the number of selected items in this ItemListbox getSelectedCount :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ getSelectedCount a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSelectedCount'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 48 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Returns a pointer to the last selected item. getLastSelectedItem :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (HG3DClass) -- ^ return value - A pointer to the last selected item, 0 is none. getLastSelectedItem a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getLastSelectedItem'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 53 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Returns a pointer to the first selected item. - Details: If multiselect is disabled then this does the equivalent of calling getLastSelectedItem. If multiselect is enabled it will search the array starting at start_index getFirstSelectedItem :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ start_index - The index where the search should begin. If omitted the search will begin with the first item. -> IO (HG3DClass) -- ^ return value - A pointer to the first selected item in the listbox. If no item is selected the return value is 0. If getFirstSelectedItem a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getFirstSelectedItem'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 59 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Returns a pointer to the next seleced item relative to a previous call to getFirstSelectedItem or getNextSelectedItem. - Details: This member function will take on from where the last call to getFirstSelectedItem or getNextSelectedItem returned. So be sure to start with a call to getFirstSelectedItem. getNextSelectedItem :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (HG3DClass) -- ^ return value - A pointer to the next seleced item. If there are no further selected items the return value is 0. If multiselect is disabled the return value is 0. getNextSelectedItem a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getNextSelectedItem'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 64 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Returns a pointer to the next selected item after the item 'start_item' given. - Details: This member function will search the array from the beginning and will be slow for large lists, it will not advance the internal counter used by getFirstSelectedItem and getNextSelectedItem either. getNextSelectedItemAfter :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ start_item -> IO (HG3DClass) -- ^ getNextSelectedItemAfter a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> alloca $ \a3' -> getNextSelectedItemAfter'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 70 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Returns 'true' if multiple selections are allowed. 'false' if not. isMultiSelectEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isMultiSelectEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isMultiSelectEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 75 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Returns 'true' if the item at the given index is selectable and currently selected. isItemSelected :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ index -> IO (Bool) -- ^ isItemSelected a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> isItemSelected'_ a1' a2' a3' >>= \res -> peekBoolUtil a3'>>= \a3'' -> return (a3'') {-# LINE 81 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | initialiseComponents :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ initialiseComponents a1 = withHG3DClass a1 $ \a1' -> initialiseComponents'_ a1' >>= \res -> return () {-# LINE 85 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Set whether or not multiple selections should be allowed. setMultiSelectEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ state -> IO () -- ^ setMultiSelectEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setMultiSelectEnabled'_ a1' a2' >>= \res -> return () {-# LINE 90 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Clears all selections. clearAllSelections :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ clearAllSelections a1 = withHG3DClass a1 $ \a1' -> clearAllSelections'_ a1' >>= \res -> return () {-# LINE 94 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Select a range of items. selectRange :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ a - Start item. (inclusive) -> Int -- ^ z - End item. (inclusive) -> IO () -- ^ selectRange a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromIntegral a3} in selectRange'_ a1' a2' a3' >>= \res -> return () {-# LINE 100 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Select all items. Does nothing if multiselect is disabled. selectAllItems :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ selectAllItems a1 = withHG3DClass a1 $ \a1' -> selectAllItems'_ a1' >>= \res -> return () {-# LINE 104 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Constructor for the ItemListbox new :: String -- ^ type -> String -- ^ name -> IO (HG3DClass) -- ^ new a1 a2 = withCString a1 $ \a1' -> withCString a2 $ \a2' -> alloca $ \a3' -> new'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 110 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Destructor for the ItemListbox delete :: HG3DClass -- ^ classpointer - pointer of Class instance which is going to be deleted. -> IO () -- ^ delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 114 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Setup size and position for the item widgets attached to this ItemListbox layoutItemWidgets :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ layoutItemWidgets a1 = withHG3DClass a1 $ \a1' -> layoutItemWidgets'_ a1' >>= \res -> return () {-# LINE 118 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Return whether this window was inherited from the given class name at some point in the inheritance hierarchy. testClassNameImpl :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ class_name - The class name that is to be checked. -> IO (Bool) -- ^ return value - true if this window was inherited from testClassNameImpl a1 a2 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> alloca $ \a3' -> testClassNameImpl'_ a1' a2' a3' >>= \res -> peekBoolUtil a3'>>= \a3'' -> return (a3'') {-# LINE 124 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Notify this ItemListbox notifyItemClicked :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ li -> IO () -- ^ notifyItemClicked a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> notifyItemClicked'_ a1' a2' >>= \res -> return () {-# LINE 129 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} -- | Notify this ItemListbox notifyItemSelectState :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ li -> Bool -- ^ state -> IO () -- ^ notifyItemSelectState a1 a2 a3 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> let {a3' = fromBool a3} in notifyItemSelectState'_ a1' a2' a3' >>= \res -> return () {-# LINE 135 ".\\HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_getSelectedCount" getSelectedCount'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_getLastSelectedItem" getLastSelectedItem'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_getFirstSelectedItem" getFirstSelectedItem'_ :: ((HG3DClassPtr) -> (CInt -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_getNextSelectedItem" getNextSelectedItem'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_getNextSelectedItemAfter" getNextSelectedItemAfter'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_isMultiSelectEnabled" isMultiSelectEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_isItemSelected" isItemSelected'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_initialiseComponents" initialiseComponents'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_setMultiSelectEnabled" setMultiSelectEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_clearAllSelections" clearAllSelections'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_selectRange" selectRange'_ :: ((HG3DClassPtr) -> (CInt -> (CInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_selectAllItems" selectAllItems'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_construct" new'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_layoutItemWidgets" layoutItemWidgets'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_testClassName_impl" testClassNameImpl'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_notifyItemClicked" notifyItemClicked'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassItemListbox.chs.h cegui_itmlstbx_notifyItemSelectState" notifyItemSelectState'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CInt -> (IO ()))))