-- 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\\ClassMultiColumnList.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. -- -- ClassMultiColumnList.chs -- module HGamer3D.Bindings.CEGUI.ClassMultiColumnList 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\\ClassMultiColumnList.chs" #-} import HGamer3D.Bindings.CEGUI.ClassPtr {-# LINE 41 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} import HGamer3D.Bindings.CEGUI.StructHG3DClass {-# LINE 42 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} import HGamer3D.Bindings.CEGUI.EnumSortDirection {-# LINE 43 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} import HGamer3D.Bindings.CEGUI.EnumSelectionMode {-# LINE 44 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return whether user manipulation of the sort column and direction are enabled. isUserSortControlEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ return value - true if the user may interactively modify the sort column and direction. false if the user may not modify the sort column and direction (these can still be set programmatically). isUserSortControlEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isUserSortControlEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 50 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return whether the user may size column segments. isUserColumnSizingEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ return value - true if the user may interactively modify the width of columns, false if they may not. isUserColumnSizingEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isUserColumnSizingEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 55 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return whether the user may modify the order of the columns. isUserColumnDraggingEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ return value - true if the user may interactively modify the order of the columns, false if they may not. isUserColumnDraggingEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isUserColumnDraggingEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 60 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the number of columns in the multi-column list. getColumnCount :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - uint value equal to the number of columns in the list. getColumnCount a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getColumnCount'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 65 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the number of rows in the multi-column list. getRowCount :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - uint value equal to the number of rows currently in the list. getRowCount a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getRowCount'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 70 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the zero based index of the current sort column. There must be at least one column to successfully call this method. getSortColumn :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - Zero based column index that is the current sort column. getSortColumn a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSortColumn'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 75 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the zero based column index of the column with the specified ID. getColumnWithID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_id - ID code of the column whos index is to be returned. -> IO (Int) -- ^ return value - Zero based column index of the first column whos ID matches getColumnWithID a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getColumnWithID'_ a1' a2' a3' >>= \res -> peekIntConv a3'>>= \a3'' -> return (a3'') {-# LINE 81 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the zero based index of the column whos header text matches the specified text. getColumnWithHeaderText :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ text - String object containing the text to be searched for. -> IO (Int) -- ^ return value - Zero based column index of the column whos header has the specified text. getColumnWithHeaderText a1 a2 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> alloca $ \a3' -> getColumnWithHeaderText'_ a1' a2' a3' >>= \res -> peekIntConv a3'>>= \a3'' -> return (a3'') {-# LINE 87 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the currently set sort direction. getSortDirection :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (EnumSortDirection) -- ^ return value - One of the getSortDirection a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSortDirection'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 92 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the ListHeaderSegment getHeaderSegmentForColumn :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_idx - zero based index of the column whos ListHeaderSegment is to be returned. -> IO (HG3DClass) -- ^ getHeaderSegmentForColumn a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getHeaderSegmentForColumn'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 98 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the zero based index of the Row that contains item getItemRowIndex :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to the ListboxItem that the row index is to returned for. -> IO (Int) -- ^ return value - Zero based index of the row that contains getItemRowIndex a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> alloca $ \a3' -> getItemRowIndex'_ a1' a2' a3' >>= \res -> peekIntConv a3'>>= \a3'' -> return (a3'') {-# LINE 104 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the current zero based index of the column that contains item getItemColumnIndex :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to the ListboxItem that the column index is to returned for. -> IO (Int) -- ^ return value - Zero based index of the column that contains getItemColumnIndex a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> alloca $ \a3' -> getItemColumnIndex'_ a1' a2' a3' >>= \res -> peekIntConv a3'>>= \a3'' -> return (a3'') {-# LINE 110 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | return whether ListboxItemitemcol_idx isListboxItemInColumn :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to the ListboxItem to look for. -> Int -- ^ col_idx - Zero based index of the column that is to be searched. -> IO (Bool) -- ^ isListboxItemInColumn a1 a2 a3 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> let {a3' = fromIntegral a3} in alloca $ \a4' -> isListboxItemInColumn'_ a1' a2' a3' a4' >>= \res -> peekBoolUtil a4'>>= \a4'' -> return (a4'') {-# LINE 117 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | return whether ListboxItemitemrow_idx isListboxItemInRow :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to the ListboxItem to look for. -> Int -- ^ row_idx - Zero based index of the row that is to be searched. -> IO (Bool) -- ^ isListboxItemInRow a1 a2 a3 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> let {a3' = fromIntegral a3} in alloca $ \a4' -> isListboxItemInRow'_ a1' a2' a3' a4' >>= \res -> peekBoolUtil a4'>>= \a4'' -> return (a4'') {-# LINE 124 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | return whether ListboxItemitem isListboxItemInList :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to the ListboxItem to look for. -> IO (Bool) -- ^ isListboxItemInList a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> alloca $ \a3' -> isListboxItemInList'_ a1' a2' a3' >>= \res -> peekBoolUtil a3'>>= \a3'' -> return (a3'') {-# LINE 130 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the ListboxItemcol_idxtext findColumnItemWithText :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ text - String object containing the text to be searched for. -> Int -- ^ col_idx - Zero based index of the column to be searched. -> HG3DClass -- ^ start_item - Pointer to the ListboxItem where the exclusive search is to start, or NULL to search from the top of the column. -> IO (HG3DClass) -- ^ return value - Pointer to the first findColumnItemWithText a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> let {a3' = fromIntegral a3} in withHG3DClass a4 $ \a4' -> alloca $ \a5' -> findColumnItemWithText'_ a1' a2' a3' a4' a5' >>= \res -> peek a5'>>= \a5'' -> return (a5'') {-# LINE 138 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the ListboxItemrow_idxtext findRowItemWithText :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ text - String object containing the text to be searched for. -> Int -- ^ row_idx - Zero based index of the row to be searched. -> HG3DClass -- ^ start_item - Pointer to the ListboxItem where the exclusive search is to start, or NULL to search from the start of the row. -> IO (HG3DClass) -- ^ return value - Pointer to the first findRowItemWithText a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> let {a3' = fromIntegral a3} in withHG3DClass a4 $ \a4' -> alloca $ \a5' -> findRowItemWithText'_ a1' a2' a3' a4' a5' >>= \res -> peek a5'>>= \a5'' -> return (a5'') {-# LINE 146 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the ListboxItemtext - Details: List box searching progresses across the columns in each row. findListItemWithText :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ text - String object containing the text to be searched for. -> HG3DClass -- ^ start_item - Pointer to the ListboxItem where the exclusive search is to start, or NULL to search the whole list box. -> IO (HG3DClass) -- ^ return value - Pointer to the first findListItemWithText a1 a2 a3 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> withHG3DClass a3 $ \a3' -> alloca $ \a4' -> findListItemWithText'_ a1' a2' a3' a4' >>= \res -> peek a4'>>= \a4'' -> return (a4'') {-# LINE 153 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return a pointer to the first selected ListboxItem - Details: List box searching progresses across the columns in each row. getFirstSelectedItem :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (HG3DClass) -- ^ return value - Pointer to the first getFirstSelectedItem a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getFirstSelectedItem'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 158 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return a pointer to the next selected ListboxItemstart_item - Details: List box searching progresses across the columns in each row. getNextSelected :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ start_item - Pointer to the ListboxItem where the exclusive search is to start, or NULL to search the whole list box. -> IO (HG3DClass) -- ^ return value - Pointer to the first selected getNextSelected a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> alloca $ \a3' -> getNextSelected'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 164 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the number of selected ListboxItems attached to this list box. - Details: return uint value equal to the number of ListboxItems attached to this list box that are currently selected. 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 169 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the ID of the currently set nominated selection column to be used when in one of the NominatedColumn* selection modes. There must be at least one column to successfully call this method. - Details: You should only ever call this when getColumnCount() getNominatedSelectionColumnID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - ID code of the nominated selection column. getNominatedSelectionColumnID a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getNominatedSelectionColumnID'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 174 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the index of the currently set nominated selection column to be used when in one of the NominatedColumn* selection modes. getNominatedSelectionColumn :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - Zero based index of the nominated selection column. getNominatedSelectionColumn a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getNominatedSelectionColumn'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 179 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the index of the currently set nominated selection row to be used when in one of the NominatedRow* selection modes. getNominatedSelectionRow :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - Zero based index of the nominated selection column. getNominatedSelectionRow a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getNominatedSelectionRow'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 184 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the currently set selection mode. getSelectionMode :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (EnumSelectionMode) -- ^ return value - One of the getSelectionMode a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSelectionMode'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 189 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return whether the vertical scroll bar is always shown. isVertScrollbarAlwaysShown :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isVertScrollbarAlwaysShown a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isVertScrollbarAlwaysShown'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 194 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return whether the horizontal scroll bar is always shown. isHorzScrollbarAlwaysShown :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isHorzScrollbarAlwaysShown a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isHorzScrollbarAlwaysShown'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 199 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the ID code assigned to the requested column. getColumnID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_idx - Zero based index of the column whos ID code is to be returned. -> IO (Int) -- ^ return value - Current ID code assigned to the column at the requested index. getColumnID a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getColumnID'_ a1' a2' a3' >>= \res -> peekIntConv a3'>>= \a3'' -> return (a3'') {-# LINE 205 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the ID code assigned to the requested row. getRowID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ row_idx - Zero based index of the row who's ID code is to be returned. -> IO (Int) -- ^ return value - Current ID code assigned to the row at the requested index. getRowID a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getRowID'_ a1' a2' a3' >>= \res -> peekIntConv a3'>>= \a3'' -> return (a3'') {-# LINE 211 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the zero based row index of the row with the specified ID. getRowWithID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ row_id - ID code of the row who's index is to be returned. -> IO (Int) -- ^ return value - Zero based row index of the first row who's ID matches getRowWithID a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getRowWithID'_ a1' a2' a3' >>= \res -> peekIntConv a3'>>= \a3'' -> return (a3'') {-# LINE 217 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return a pointer to the vertical scrollbar component widget for this MultiColumnList getVertScrollbar :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (HG3DClass) -- ^ return value - Pointer to a getVertScrollbar a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getVertScrollbar'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 222 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return a pointer to the horizontal scrollbar component widget for this MultiColumnList getHorzScrollbar :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (HG3DClass) -- ^ return value - Pointer to a getHorzScrollbar a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getHorzScrollbar'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 227 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return a pointer to the list header component widget for this MultiColumnList getListHeader :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (HG3DClass) -- ^ return value - Pointer to a getListHeader a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getListHeader'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 232 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the sum of all row heights in pixels. getTotalRowsHeight :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Float) -- ^ getTotalRowsHeight a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getTotalRowsHeight'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 237 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return the pixel width of the widest item in the given column. getWidestColumnItemWidth :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_idx -> IO (Float) -- ^ getWidestColumnItemWidth a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getWidestColumnItemWidth'_ a1' a2' a3' >>= \res -> peekFloatConv a3'>>= \a3'' -> return (a3'') {-# LINE 243 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Return, in pixels, the height of the highest item in the given row. getHighestRowItemHeight :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ row_idx -> IO (Float) -- ^ getHighestRowItemHeight a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getHighestRowItemHeight'_ a1' a2' a3' >>= \res -> peekFloatConv a3'>>= \a3'' -> return (a3'') {-# LINE 249 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Initialise the Window - Details: This must be called for every window created. Normally this is handled automatically by the WindowFactory for each Window initialiseComponents :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ return value - Nothing initialiseComponents a1 = withHG3DClass a1 $ \a1' -> initialiseComponents'_ a1' >>= \res -> return () {-# LINE 253 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Remove all items from the list. - Details: Note that this will cause 'AutoDelete' items to be deleted. resetList :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ resetList a1 = withHG3DClass a1 $ \a1' -> resetList'_ a1' >>= \res -> return () {-# LINE 257 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Removes a column from the list box. This will cause any ListboxItem removeColumn :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_idx - Zero based index of the column to be removed. -> IO () -- ^ return value - Nothing. removeColumn a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in removeColumn'_ a1' a2' >>= \res -> return () {-# LINE 262 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Removes a column from the list box. This will cause any ListboxItem removeColumnWithID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_id - ID code of the column to be deleted. -> IO () -- ^ return value - Nothing. removeColumnWithID a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in removeColumnWithID'_ a1' a2' >>= \res -> return () {-# LINE 267 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Move the column at index col_idxposition moveColumn :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_idx - Zero based index of the column to be moved. -> Int -- ^ position - Zero based index of the new position for the column. -> IO () -- ^ return value - Nothing. moveColumn a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromIntegral a3} in moveColumn'_ a1' a2' a3' >>= \res -> return () {-# LINE 273 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Move the column with ID col_idposition moveColumnWithID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_id - ID code of the column to be moved. -> Int -- ^ position - Zero based index of the new position for the column. -> IO () -- ^ return value - Nothing. moveColumnWithID a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromIntegral a3} in moveColumnWithID'_ a1' a2' a3' >>= \res -> return () {-# LINE 279 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Add an empty row to the list box. - Details: If the list is being sorted, the new row will appear at an appropriate position according to the sorting being applied. If no sorting is being done, the new row will appear at the bottom of the list. addRow :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ row_id - ID code to be assigned to the new row. -> IO (Int) -- ^ return value - Initial zero based index of the new row. addRow a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> addRow'_ a1' a2' a3' >>= \res -> peekIntConv a3'>>= \a3'' -> return (a3'') {-# LINE 285 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Add a row to the list box, and set the item in the column with ID col_iditem - Details: If the list is being sorted, the new row will appear at an appropriate position according to the sorting being applied. If no sorting is being done, the new row will appear at the bottom of the list. addRow2 :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to a ListboxItem to be used as the initial contents for the column with ID col_id. -> Int -- ^ col_id - ID code of the column whos initial item is to be set to item. -> Int -- ^ row_id - ID code to be assigned to the new row. -> IO (Int) -- ^ return value - Initial zero based index of the new row. addRow2 a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> let {a3' = fromIntegral a3} in let {a4' = fromIntegral a4} in alloca $ \a5' -> addRow2'_ a1' a2' a3' a4' a5' >>= \res -> peekIntConv a5'>>= \a5'' -> return (a5'') {-# LINE 293 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Insert an empty row into the list box. - Details: If the list is being sorted, the new row will appear at an appropriate position according to the sorting being applied. If no sorting is being done, the new row will appear at the specified index. insertRow :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ row_idx - Zero based index where the row should be inserted. If this is greater than the current number of rows, the row is appended to the list. -> Int -- ^ row_id - ID code to be assigned to the new row. -> IO (Int) -- ^ return value - Zero based index where the row was actually inserted. insertRow a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromIntegral a3} in alloca $ \a4' -> insertRow'_ a1' a2' a3' a4' >>= \res -> peekIntConv a4'>>= \a4'' -> return (a4'') {-# LINE 300 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Insert a row into the list box, and set the item in the column with ID col_iditem - Details: If the list is being sorted, the new row will appear at an appropriate position according to the sorting being applied. If no sorting is being done, the new row will appear at the specified index. insertRow2 :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to a ListboxItem to be used as the initial contents for the column with ID col_id. -> Int -- ^ col_id - ID code of the column whos initial item is to be set to item. -> Int -- ^ row_idx - Zero based index where the row should be inserted. If this is greater than the current number of rows, the row is appended to the list. -> Int -- ^ row_id - ID code to be assigned to the new row. -> IO (Int) -- ^ return value - Zero based index where the row was actually inserted. insertRow2 a1 a2 a3 a4 a5 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> let {a3' = fromIntegral a3} in let {a4' = fromIntegral a4} in let {a5' = fromIntegral a5} in alloca $ \a6' -> insertRow2'_ a1' a2' a3' a4' a5' a6' >>= \res -> peekIntConv a6'>>= \a6'' -> return (a6'') {-# LINE 309 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Remove the list box row with index row_idxListboxItemrow_idx removeRow :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ row_idx - Zero based index of the row to be removed. -> IO () -- ^ return value - Nothing. removeRow a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in removeRow'_ a1' a2' >>= \res -> return () {-# LINE 314 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the ListboxItemcol_idrow_idx setItem2 :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to the ListboxItem to be set into the list. -> Int -- ^ col_id - ID code of the column to receive item. -> Int -- ^ row_idx - Zero based index of the row to receive item. -> IO () -- ^ return value - Nothing. setItem2 a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> let {a3' = fromIntegral a3} in let {a4' = fromIntegral a4} in setItem2'_ a1' a2' a3' a4' >>= \res -> return () {-# LINE 321 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the selection mode for the list box. setSelectionMode :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> EnumSelectionMode -- ^ sel_mode - One of the MultiColumnList::SelectionMode enumerated values specifying the selection mode to be used. -> IO () -- ^ return value - Nothing. setSelectionMode a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in setSelectionMode'_ a1' a2' >>= \res -> return () {-# LINE 326 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the column to be used for the NominatedColumn* selection modes. setNominatedSelectionColumnID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_id - ID code of the column to be used in NominatedColumn* selection modes. -> IO () -- ^ return value - Nothing. setNominatedSelectionColumnID a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setNominatedSelectionColumnID'_ a1' a2' >>= \res -> return () {-# LINE 331 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the column to be used for the NominatedColumn* selection modes. setNominatedSelectionColumn :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_idx - zero based index of the column to be used in NominatedColumn* selection modes. -> IO () -- ^ return value - Nothing. setNominatedSelectionColumn a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setNominatedSelectionColumn'_ a1' a2' >>= \res -> return () {-# LINE 336 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the row to be used for the NominatedRow* selection modes. setNominatedSelectionRow :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ row_idx - zero based index of the row to be used in NominatedRow* selection modes. -> IO () -- ^ return value - Nothing. setNominatedSelectionRow a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setNominatedSelectionRow'_ a1' a2' >>= \res -> return () {-# LINE 341 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the sort direction to be used. setSortDirection :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> EnumSortDirection -- ^ direction - One of the ListHeaderSegment::SortDirection enumerated values specifying the sort direction to be used. -> IO () -- ^ return value - Nothing. setSortDirection a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in setSortDirection'_ a1' a2' >>= \res -> return () {-# LINE 346 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the column to be used as the sort key. setSortColumn :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_idx - Zero based index of the column to use as the key when sorting the list items. -> IO () -- ^ return value - Nothing. setSortColumn a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setSortColumn'_ a1' a2' >>= \res -> return () {-# LINE 351 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the column to be used as the sort key. setSortColumnByID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_id - ID code of the column to use as the key when sorting the list items. -> IO () -- ^ return value - Nothing. setSortColumnByID a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setSortColumnByID'_ a1' a2' >>= \res -> return () {-# LINE 356 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set whether the vertical scroll bar should always be shown, or just when needed. setShowVertScrollbar :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ setting - -- -- -> IO () -- ^ return value - Nothing. setShowVertScrollbar a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setShowVertScrollbar'_ a1' a2' >>= \res -> return () {-# LINE 361 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set whether the horizontal scroll bar should always be shown, or just when needed. setShowHorzScrollbar :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ setting - -- -- -> IO () -- ^ return value - Nothing. setShowHorzScrollbar a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setShowHorzScrollbar'_ a1' a2' >>= \res -> return () {-# LINE 366 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Removed the selected state from any currently selected ListboxItem clearAllSelections :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ return value - Nothing. clearAllSelections a1 = withHG3DClass a1 $ \a1' -> clearAllSelections'_ a1' >>= \res -> return () {-# LINE 370 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Sets or clears the selected state of the given ListboxItem - Details: Depending upon the current selection mode, this may cause other items to be selected, other items to be deselected, or for nothing to actually happen at all. setItemSelectState :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ item - Pointer to the attached ListboxItem to be affected. -> Bool -- ^ state - -- -- -> IO () -- ^ return value - Nothing. setItemSelectState a1 a2 a3 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> let {a3' = fromBool a3} in setItemSelectState'_ a1' a2' a3' >>= \res -> return () {-# LINE 376 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Inform the list box that one or more attached ListboxItems have been externally modified, and the list should re-sync its internal state and refresh the display as needed. handleUpdatedItemData :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ return value - Nothing. handleUpdatedItemData a1 = withHG3DClass a1 $ \a1' -> handleUpdatedItemData'_ a1' >>= \res -> return () {-# LINE 380 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set whether user manipulation of the sort column and direction are enabled. setUserSortControlEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ setting - -- -- -> IO () -- ^ return value - Nothing. setUserSortControlEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setUserSortControlEnabled'_ a1' a2' >>= \res -> return () {-# LINE 385 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set whether the user may size column segments. setUserColumnSizingEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ setting - -- -- -> IO () -- ^ return value - Nothing. setUserColumnSizingEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setUserColumnSizingEnabled'_ a1' a2' >>= \res -> return () {-# LINE 390 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set whether the user may modify the order of the columns. setUserColumnDraggingEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ setting - -- -- -> IO () -- ^ setUserColumnDraggingEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setUserColumnDraggingEnabled'_ a1' a2' >>= \res -> return () {-# LINE 395 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Automatically determines the "best fit" size for the specified column and sets the column width to the same. autoSizeColumnHeader :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ col_idx - Zero based index of the column to be sized. -> IO () -- ^ return value - Nothing. autoSizeColumnHeader a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in autoSizeColumnHeader'_ a1' a2' >>= \res -> return () {-# LINE 400 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Set the ID code assigned to a given row. setRowID :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ row_idx - Zero based index of the row who's ID code is to be set. -> Int -- ^ row_id - ID code to be assigned to the row at the requested index. -> IO () -- ^ return value - Nothing. setRowID a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromIntegral a3} in setRowID'_ a1' a2' a3' >>= \res -> return () {-# LINE 406 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Constructor for the Multi-column list base class. 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 412 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} -- | Destructor for the multi-column list base class. delete :: HG3DClass -- ^ classpointer - pointer of Class instance which is going to be deleted. -> IO () -- ^ delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 416 ".\\HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_isUserSortControlEnabled" isUserSortControlEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_isUserColumnSizingEnabled" isUserColumnSizingEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_isUserColumnDraggingEnabled" isUserColumnDraggingEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getColumnCount" getColumnCount'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getRowCount" getRowCount'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getSortColumn" getSortColumn'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getColumnWithID" getColumnWithID'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CUInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getColumnWithHeaderText" getColumnWithHeaderText'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CUInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getSortDirection" getSortDirection'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getHeaderSegmentForColumn" getHeaderSegmentForColumn'_ :: ((HG3DClassPtr) -> (CUInt -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getItemRowIndex" getItemRowIndex'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getItemColumnIndex" getItemColumnIndex'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_isListboxItemInColumn" isListboxItemInColumn'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CUInt -> ((Ptr CInt) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_isListboxItemInRow" isListboxItemInRow'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CUInt -> ((Ptr CInt) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_isListboxItemInList" isListboxItemInList'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_findColumnItemWithText" findColumnItemWithText'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CUInt -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_findRowItemWithText" findRowItemWithText'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CUInt -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_findListItemWithText" findListItemWithText'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getFirstSelectedItem" getFirstSelectedItem'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getNextSelected" getNextSelected'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getSelectedCount" getSelectedCount'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getNominatedSelectionColumnID" getNominatedSelectionColumnID'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getNominatedSelectionColumn" getNominatedSelectionColumn'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getNominatedSelectionRow" getNominatedSelectionRow'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getSelectionMode" getSelectionMode'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_isVertScrollbarAlwaysShown" isVertScrollbarAlwaysShown'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_isHorzScrollbarAlwaysShown" isHorzScrollbarAlwaysShown'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getColumnID" getColumnID'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CUInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getRowID" getRowID'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CUInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getRowWithID" getRowWithID'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CUInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getVertScrollbar" getVertScrollbar'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getHorzScrollbar" getHorzScrollbar'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getListHeader" getListHeader'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getTotalRowsHeight" getTotalRowsHeight'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getWidestColumnItemWidth" getWidestColumnItemWidth'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CFloat) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_getHighestRowItemHeight" getHighestRowItemHeight'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CFloat) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_initialiseComponents" initialiseComponents'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_resetList" resetList'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_removeColumn" removeColumn'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_removeColumnWithID" removeColumnWithID'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_moveColumn" moveColumn'_ :: ((HG3DClassPtr) -> (CUInt -> (CUInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_moveColumnWithID" moveColumnWithID'_ :: ((HG3DClassPtr) -> (CUInt -> (CUInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_addRow" addRow'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CUInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_addRow2" addRow2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CUInt -> (CUInt -> ((Ptr CUInt) -> (IO ())))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_insertRow" insertRow'_ :: ((HG3DClassPtr) -> (CUInt -> (CUInt -> ((Ptr CUInt) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_insertRow2" insertRow2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CUInt -> (CUInt -> (CUInt -> ((Ptr CUInt) -> (IO ()))))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_removeRow" removeRow'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setItem2" setItem2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CUInt -> (CUInt -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setSelectionMode" setSelectionMode'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setNominatedSelectionColumnID" setNominatedSelectionColumnID'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setNominatedSelectionColumn" setNominatedSelectionColumn'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setNominatedSelectionRow" setNominatedSelectionRow'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setSortDirection" setSortDirection'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setSortColumn" setSortColumn'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setSortColumnByID" setSortColumnByID'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setShowVertScrollbar" setShowVertScrollbar'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setShowHorzScrollbar" setShowHorzScrollbar'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_clearAllSelections" clearAllSelections'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setItemSelectState" setItemSelectState'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_handleUpdatedItemData" handleUpdatedItemData'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setUserSortControlEnabled" setUserSortControlEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setUserColumnSizingEnabled" setUserColumnSizingEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setUserColumnDraggingEnabled" setUserColumnDraggingEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_autoSizeColumnHeader" autoSizeColumnHeader'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_setRowID" setRowID'_ :: ((HG3DClassPtr) -> (CUInt -> (CUInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_construct" new'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassMultiColumnList.chs.h cegui_mltclmlst_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ()))