module Graphics.UI.Gtk.Layout.Table (
Table,
TableClass,
castToTable, gTypeTable,
toTable,
tableNew,
tableResize,
AttachOptions(..),
tableAttach,
tableAttachDefaults,
tableSetRowSpacing,
tableGetRowSpacing,
tableSetColSpacing,
tableGetColSpacing,
tableSetRowSpacings,
tableGetDefaultRowSpacing,
tableSetColSpacings,
tableGetDefaultColSpacing,
tableSetHomogeneous,
tableGetHomogeneous,
tableGetSize,
tableNRows,
tableNColumns,
tableRowSpacing,
tableColumnSpacing,
tableHomogeneous,
tableChildLeftAttach,
tableChildRightAttach,
tableChildTopAttach,
tableChildBottomAttach,
tableChildXOptions,
tableChildYOptions,
tableChildXPadding,
tableChildYPadding,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.Flags (fromFlags)
import System.Glib.Attributes
import System.Glib.Properties
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.General.Enums (AttachOptions(..))
import Graphics.UI.Gtk.Abstract.ContainerChildProperties
tableNew ::
Int
-> Int
-> Bool
-> IO Table
tableNew rows columns homogeneous =
makeNewObject mkTable $
liftM (castPtr :: Ptr Widget -> Ptr Table) $
gtk_table_new
(fromIntegral rows)
(fromIntegral columns)
(fromBool homogeneous)
tableResize :: TableClass self => self
-> Int
-> Int
-> IO ()
tableResize self rows columns =
(\(Table arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_resize argPtr1 arg2 arg3)
(toTable self)
(fromIntegral rows)
(fromIntegral columns)
tableAttach :: (TableClass self, WidgetClass child) => self
-> child
-> Int
-> Int
-> Int
-> Int
-> [AttachOptions]
-> [AttachOptions]
-> Int
-> Int
-> IO ()
tableAttach self child leftAttach rightAttach topAttach bottomAttach xoptions
yoptions xpadding ypadding =
(\(Table arg1) (Widget arg2) arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_table_attach argPtr1 argPtr2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10)
(toTable self)
(toWidget child)
(fromIntegral leftAttach)
(fromIntegral rightAttach)
(fromIntegral topAttach)
(fromIntegral bottomAttach)
((fromIntegral . fromFlags) xoptions)
((fromIntegral . fromFlags) yoptions)
(fromIntegral xpadding)
(fromIntegral ypadding)
tableAttachDefaults :: (TableClass self, WidgetClass widget) => self
-> widget
-> Int
-> Int
-> Int
-> Int
-> IO ()
tableAttachDefaults self widget leftAttach rightAttach topAttach bottomAttach =
(\(Table arg1) (Widget arg2) arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_table_attach_defaults argPtr1 argPtr2 arg3 arg4 arg5 arg6)
(toTable self)
(toWidget widget)
(fromIntegral leftAttach)
(fromIntegral rightAttach)
(fromIntegral topAttach)
(fromIntegral bottomAttach)
tableSetRowSpacing :: TableClass self => self
-> Int
-> Int
-> IO ()
tableSetRowSpacing self row spacing =
(\(Table arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_set_row_spacing argPtr1 arg2 arg3)
(toTable self)
(fromIntegral row)
(fromIntegral spacing)
tableGetRowSpacing :: TableClass self => self
-> Int
-> IO Int
tableGetRowSpacing self row =
liftM fromIntegral $
(\(Table arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_get_row_spacing argPtr1 arg2)
(toTable self)
(fromIntegral row)
tableSetColSpacing :: TableClass self => self
-> Int
-> Int
-> IO ()
tableSetColSpacing self column spacing =
(\(Table arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_set_col_spacing argPtr1 arg2 arg3)
(toTable self)
(fromIntegral column)
(fromIntegral spacing)
tableGetColSpacing :: TableClass self => self
-> Int
-> IO Int
tableGetColSpacing self column =
liftM fromIntegral $
(\(Table arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_get_col_spacing argPtr1 arg2)
(toTable self)
(fromIntegral column)
tableSetRowSpacings :: TableClass self => self
-> Int
-> IO ()
tableSetRowSpacings self spacing =
(\(Table arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_set_row_spacings argPtr1 arg2)
(toTable self)
(fromIntegral spacing)
tableGetDefaultRowSpacing :: TableClass self => self
-> IO Int
tableGetDefaultRowSpacing self =
liftM fromIntegral $
(\(Table arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_get_default_row_spacing argPtr1)
(toTable self)
tableSetColSpacings :: TableClass self => self
-> Int
-> IO ()
tableSetColSpacings self spacing =
(\(Table arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_set_col_spacings argPtr1 arg2)
(toTable self)
(fromIntegral spacing)
tableGetDefaultColSpacing :: TableClass self => self
-> IO Int
tableGetDefaultColSpacing self =
liftM fromIntegral $
(\(Table arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_get_default_col_spacing argPtr1)
(toTable self)
tableSetHomogeneous :: TableClass self => self
-> Bool
-> IO ()
tableSetHomogeneous self homogeneous =
(\(Table arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_set_homogeneous argPtr1 arg2)
(toTable self)
(fromBool homogeneous)
tableGetHomogeneous :: TableClass self => self
-> IO Bool
tableGetHomogeneous self =
liftM toBool $
(\(Table arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_get_homogeneous argPtr1)
(toTable self)
tableGetSize :: TableClass self => self
-> IO (Int, Int)
tableGetSize self =
alloca $ \ rowsPtr ->
alloca $ \ columnsPtr -> do
(\(Table arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_table_get_size argPtr1 arg2 arg3)
(toTable self)
rowsPtr
columnsPtr
rows <- peek rowsPtr
columns <- peek columnsPtr
return (fromIntegral rows, fromIntegral columns)
tableNRows :: TableClass self => Attr self Int
tableNRows = newAttrFromUIntProperty "n-rows"
tableNColumns :: TableClass self => Attr self Int
tableNColumns = newAttrFromUIntProperty "n-columns"
tableRowSpacing :: TableClass self => Attr self Int
tableRowSpacing = newAttrFromUIntProperty "row-spacing"
tableColumnSpacing :: TableClass self => Attr self Int
tableColumnSpacing = newAttrFromUIntProperty "column-spacing"
tableHomogeneous :: TableClass self => Attr self Bool
tableHomogeneous = newAttr
tableGetHomogeneous
tableSetHomogeneous
tableChildLeftAttach :: (TableClass self, WidgetClass child) => child -> Attr self Int
tableChildLeftAttach = newAttrFromContainerChildUIntProperty "left-attach"
tableChildRightAttach :: (TableClass self, WidgetClass child) => child -> Attr self Int
tableChildRightAttach = newAttrFromContainerChildUIntProperty "right-attach"
tableChildTopAttach :: (TableClass self, WidgetClass child) => child -> Attr self Int
tableChildTopAttach = newAttrFromContainerChildUIntProperty "top-attach"
tableChildBottomAttach :: (TableClass self, WidgetClass child) => child -> Attr self Int
tableChildBottomAttach = newAttrFromContainerChildUIntProperty "bottom-attach"
tableChildXOptions :: (TableClass self, WidgetClass child) => child -> Attr self [AttachOptions]
tableChildXOptions = newAttrFromContainerChildFlagsProperty "x-options"
gtk_attach_options_get_type
tableChildYOptions :: (TableClass self, WidgetClass child) => child -> Attr self [AttachOptions]
tableChildYOptions = newAttrFromContainerChildFlagsProperty "y-options"
gtk_attach_options_get_type
tableChildXPadding :: (TableClass self, WidgetClass child) => child -> Attr self Int
tableChildXPadding = newAttrFromContainerChildUIntProperty "x-padding"
tableChildYPadding :: (TableClass self, WidgetClass child) => child -> Attr self Int
tableChildYPadding = newAttrFromContainerChildUIntProperty "y-padding"
foreign import ccall unsafe "gtk_table_new"
gtk_table_new :: (CUInt -> (CUInt -> (CInt -> (IO (Ptr Widget)))))
foreign import ccall safe "gtk_table_resize"
gtk_table_resize :: ((Ptr Table) -> (CUInt -> (CUInt -> (IO ()))))
foreign import ccall safe "gtk_table_attach"
gtk_table_attach :: ((Ptr Table) -> ((Ptr Widget) -> (CUInt -> (CUInt -> (CUInt -> (CUInt -> (CInt -> (CInt -> (CUInt -> (CUInt -> (IO ())))))))))))
foreign import ccall safe "gtk_table_attach_defaults"
gtk_table_attach_defaults :: ((Ptr Table) -> ((Ptr Widget) -> (CUInt -> (CUInt -> (CUInt -> (CUInt -> (IO ())))))))
foreign import ccall safe "gtk_table_set_row_spacing"
gtk_table_set_row_spacing :: ((Ptr Table) -> (CUInt -> (CUInt -> (IO ()))))
foreign import ccall unsafe "gtk_table_get_row_spacing"
gtk_table_get_row_spacing :: ((Ptr Table) -> (CUInt -> (IO CUInt)))
foreign import ccall safe "gtk_table_set_col_spacing"
gtk_table_set_col_spacing :: ((Ptr Table) -> (CUInt -> (CUInt -> (IO ()))))
foreign import ccall unsafe "gtk_table_get_col_spacing"
gtk_table_get_col_spacing :: ((Ptr Table) -> (CUInt -> (IO CUInt)))
foreign import ccall safe "gtk_table_set_row_spacings"
gtk_table_set_row_spacings :: ((Ptr Table) -> (CUInt -> (IO ())))
foreign import ccall unsafe "gtk_table_get_default_row_spacing"
gtk_table_get_default_row_spacing :: ((Ptr Table) -> (IO CUInt))
foreign import ccall safe "gtk_table_set_col_spacings"
gtk_table_set_col_spacings :: ((Ptr Table) -> (CUInt -> (IO ())))
foreign import ccall unsafe "gtk_table_get_default_col_spacing"
gtk_table_get_default_col_spacing :: ((Ptr Table) -> (IO CUInt))
foreign import ccall safe "gtk_table_set_homogeneous"
gtk_table_set_homogeneous :: ((Ptr Table) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_table_get_homogeneous"
gtk_table_get_homogeneous :: ((Ptr Table) -> (IO CInt))
foreign import ccall unsafe "gtk_table_get_size"
gtk_table_get_size :: ((Ptr Table) -> ((Ptr CUInt) -> ((Ptr CUInt) -> (IO ()))))
foreign import ccall unsafe "gtk_attach_options_get_type"
gtk_attach_options_get_type :: CULong