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


-- ClassListHeader.chs

-- 

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

-- | Return the number of columns or segments attached to the header. 
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 / segments currently in the header.     
getColumnCount a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getColumnCount'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 49 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the ListHeaderSegment
getSegmentFromColumn :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ column - zero based column index of the ListHeaderSegment to be returned.
  ->  IO (HG3DClass)
 -- ^ 
getSegmentFromColumn a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getSegmentFromColumn'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 55 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the ListHeaderSegment
getSegmentFromID :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ id - id code of the ListHeaderSegment to be returned.
  ->  IO (HG3DClass)
 -- ^ 
getSegmentFromID a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getSegmentFromID'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 61 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the ListHeaderSegment
getSortSegment :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (HG3DClass)
 -- ^ 
getSortSegment a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSortSegment'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 66 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the zero based column index of the specified segment. 
getColumnFromSegment :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ segment - ListHeaderSegment whos zero based index is to be returned.
  ->  IO (Int)
 -- ^ return value - Zero based column index of the     
getColumnFromSegment a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  alloca $ \a3' -> 
  getColumnFromSegment'_ a1' a2' a3' >>= \res ->
  peekIntConv  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 72 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the zero based column index of the segment with the specified ID. 
getColumnFromID :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ id - ID code of the segment whos column index is to be returned.
  ->  IO (Int)
 -- ^ return value - Zero based column index of the first     
getColumnFromID a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getColumnFromID'_ a1' a2' a3' >>= \res ->
  peekIntConv  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 78 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the zero based index of the current sort column. There must be at least one segment/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 83 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the zero based column index of the segment with the specified text. 
getColumnWithText :: 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 segment with the specified text.    
getColumnWithText a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getColumnWithText'_ a1' a2' a3' >>= \res ->
  peekIntConv  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 89 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the pixel offset to the given ListHeaderSegment
getPixelOffsetToSegment :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ segment - ListHeaderSegment object that the offset to is to be returned.
  ->  IO (Float)
 -- ^ return value - The number of pixels up-to the begining of the     
getPixelOffsetToSegment a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  alloca $ \a3' -> 
  getPixelOffsetToSegment'_ a1' a2' a3' >>= \res ->
  peekFloatConv  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 95 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the pixel offset to the ListHeaderSegment
getPixelOffsetToColumn :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ column - Zero based column index of the ListHeaderSegment whos pixel offset it to be returned.
  ->  IO (Float)
 -- ^ return value - The number of pixels up-to the begining of the     
getPixelOffsetToColumn a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getPixelOffsetToColumn'_ a1' a2' a3' >>= \res ->
  peekFloatConv  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 101 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the total pixel width of all attached segments. 
getTotalSegmentsPixelExtent :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ return value - Sum of the pixel widths of all attached     
getTotalSegmentsPixelExtent a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getTotalSegmentsPixelExtent'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 106 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.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 111 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return whether user manipulation of the sort column & direction are enabled. 
isSortingEnabled :: 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).     
isSortingEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isSortingEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 116 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return whether the user may size column segments. 
isColumnSizingEnabled :: 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 column segments, false if they may not.     
isColumnSizingEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isColumnSizingEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 121 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return whether the user may modify the order of the segments. 
isColumnDraggingEnabled :: 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 column segments, false if they may not.     
isColumnDraggingEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isColumnDraggingEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 126 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Return the current segment offset value. This value is used to implement scrolling of the header segments within the ListHeader
getSegmentOffset :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ return value - float value specifying the current segment offset value in whatever metrics system is active for the     
getSegmentOffset a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSegmentOffset'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 131 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Set whether user manipulation of the sort column and direction is enabled. 
setSortingEnabled :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ setting - 
--
--
  ->  IO ()
 -- ^ return value - Nothing.     
setSortingEnabled a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setSortingEnabled'_ a1' a2' >>= \res ->
  return ()
{-# LINE 136 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Set the current sort direction. 
setSortDirection :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  EnumSortDirection  -- ^ direction - One of the ListHeaderSegment::SortDirection enumerated values indicating 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 141 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Set the column segment to be used as the sort column. 
setSortSegment :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ segment - ListHeaderSegment object indicating the column to be sorted.
  ->  IO ()
 -- ^ return value - Nothing.    
setSortSegment a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setSortSegment'_ a1' a2' >>= \res ->
  return ()
{-# LINE 146 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Set the column to be used as the sort column. 
setSortColumn :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ column - Zero based column index indicating the column to be sorted.
  ->  IO ()
 -- ^ return value - Nothing.    
setSortColumn a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  setSortColumn'_ a1' a2' >>= \res ->
  return ()
{-# LINE 151 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Set the column to to be used for sorting via its ID code. 
setSortColumnFromID :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ id - ID code of the column segment that is to be used as the sort column.
  ->  IO ()
 -- ^ return value - Nothing.    
setSortColumnFromID a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  setSortColumnFromID'_ a1' a2' >>= \res ->
  return ()
{-# LINE 156 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Set whether columns may be sized by the user. 
setColumnSizingEnabled :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ setting - 
--
--
  ->  IO ()
 -- ^ return value - Nothing.     
setColumnSizingEnabled a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setColumnSizingEnabled'_ a1' a2' >>= \res ->
  return ()
{-# LINE 161 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Set whether columns may be reordered by the user via drag and drop. 
setColumnDraggingEnabled :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ setting - 
--
--
  ->  IO ()
 -- ^ return value - Nothing.     
setColumnDraggingEnabled a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setColumnDraggingEnabled'_ a1' a2' >>= \res ->
  return ()
{-# LINE 166 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Removes a column segment from the ListHeader
removeColumn :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ column - Zero based column index indicating the segment to be removed.
  ->  IO ()
 -- ^ return value - Nothing.    
removeColumn a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  removeColumn'_ a1' a2' >>= \res ->
  return ()
{-# LINE 171 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Remove the specified segment from the ListHeader
removeSegment :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ segment - ListHeaderSegment object that is to be removed from the ListHeader.
  ->  IO ()
 -- ^ return value - Nothing.    
removeSegment a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  removeSegment'_ a1' a2' >>= \res ->
  return ()
{-# LINE 176 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Moves a column segment into a new position. 
moveColumn :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ column - Zero based column index indicating the column segment to be moved.
  ->  Int  -- ^ position - Zero based column index indicating the new position for the segment. If this is greater than the current number of segments, the segment is moved to the end of the header.
  ->  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 182 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Move a column segment to a new position. 
moveColumn2 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ column - Zero based column index indicating the column segment to be moved.
  ->  HG3DClass  -- ^ position - ListHeaderSegment object indicating the new position for the segment. The segment at column will be moved behind segment position (that is, segment column will appear to the right of segment position).
  ->  IO ()
 -- ^ return value - Nothing.    
moveColumn2 a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withHG3DClass a3 $ \a3' -> 
  moveColumn2'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 188 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Moves a segment into a new position. 
moveSegment :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ segment - ListHeaderSegment object that is to be moved.
  ->  Int  -- ^ position - Zero based column index indicating the new position for the segment. If this is greater than the current number of segments, the segment is moved to the end of the header.
  ->  IO ()
 -- ^ return value - Nothing.    
moveSegment a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  moveSegment'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 194 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Move a segment to a new position. 
moveSegment2 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ segment - ListHeaderSegment object that is to be moved.
  ->  HG3DClass  -- ^ position - ListHeaderSegment object indicating the new position for the segment. The segment segment will be moved behind segment position (that is, segment segment will appear to the right of segment position).
  ->  IO ()
 -- ^ return value - Nothing.    
moveSegment2 a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  withHG3DClass a3 $ \a3' -> 
  moveSegment2'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 200 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Set the current base segment offset. (This implements scrolling of the header segments within the header area). 
setSegmentOffset :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ offset - New base offset for the first segment. The segments will of offset to the left by the amount specified. offset should be specified using the active metrics system for the ListHeader.
  ->  IO ()
 -- ^ return value - Nothing.     
setSegmentOffset a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setSegmentOffset'_ a1' a2' >>= \res ->
  return ()
{-# LINE 205 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Constructor for the list header 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 211 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}

-- | Destructor for the list header 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 215 ".\\HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs" #-}


foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getColumnCount"
  getColumnCount'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getSegmentFromColumn"
  getSegmentFromColumn'_ :: ((HG3DClassPtr) -> (CUInt -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getSegmentFromID"
  getSegmentFromID'_ :: ((HG3DClassPtr) -> (CUInt -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getSortSegment"
  getSortSegment'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getColumnFromSegment"
  getColumnFromSegment'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getColumnFromID"
  getColumnFromID'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CUInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getSortColumn"
  getSortColumn'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getColumnWithText"
  getColumnWithText'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CUInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getPixelOffsetToSegment"
  getPixelOffsetToSegment'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getPixelOffsetToColumn"
  getPixelOffsetToColumn'_ :: ((HG3DClassPtr) -> (CUInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getTotalSegmentsPixelExtent"
  getTotalSegmentsPixelExtent'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getSortDirection"
  getSortDirection'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_isSortingEnabled"
  isSortingEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_isColumnSizingEnabled"
  isColumnSizingEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_isColumnDraggingEnabled"
  isColumnDraggingEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_getSegmentOffset"
  getSegmentOffset'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_setSortingEnabled"
  setSortingEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_setSortDirection"
  setSortDirection'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_setSortSegment"
  setSortSegment'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_setSortColumn"
  setSortColumn'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_setSortColumnFromID"
  setSortColumnFromID'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_setColumnSizingEnabled"
  setColumnSizingEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_setColumnDraggingEnabled"
  setColumnDraggingEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_removeColumn"
  removeColumn'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_removeSegment"
  removeSegment'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_moveColumn"
  moveColumn'_ :: ((HG3DClassPtr) -> (CUInt -> (CUInt -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_moveColumn2"
  moveColumn2'_ :: ((HG3DClassPtr) -> (CUInt -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_moveSegment"
  moveSegment'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CUInt -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_moveSegment2"
  moveSegment2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_setSegmentOffset"
  setSegmentOffset'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_construct"
  new'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassListHeader.chs.h cegui_lsthdr_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))