module Graphics.UI.Gtk.Layout.Grid (
Grid,
GridClass,
castToGrid,
gTypeGrid,
toGrid,
gridNew,
gridAttach,
gridAttachNextTo,
gridSetRowHomogeneous,
gridGetRowHomogeneous,
gridSetRowSpacing,
gridGetRowSpacing,
gridSetColumnHomogeneous,
gridGetColumnHomogeneous,
gridSetColumnSpacing,
gridGetColumnSpacing,
gridGetChildAt,
gridInsertRow,
gridInsertColumn,
gridInsertNextTo,
gridRemoveRow,
gridRemoveColumn,
gridGetBaselineRow,
gridSetBaselineRow,
gridGetRowBaselinePosition,
gridSetRowBaselinePosition
) where
import Control.Monad (liftM)
import System.Glib.FFI
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.General.Enums (PositionType)
import Graphics.UI.Gtk.General.Enums (BaselinePosition)
gridNew :: IO Grid
gridNew =
makeNewObject mkGrid $
liftM (castPtr :: Ptr Widget -> Ptr Grid) $
gtk_grid_new
gridAttach :: (GridClass self, WidgetClass child)
=> self
-> child
-> Int
-> Int
-> Int
-> Int
-> IO ()
gridAttach self child left top width height =
(\(Grid arg1) (Widget arg2) arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_grid_attach argPtr1 argPtr2 arg3 arg4 arg5 arg6)
(toGrid self)
(toWidget child)
(fromIntegral left)
(fromIntegral top)
(fromIntegral width)
(fromIntegral height)
gridAttachNextTo :: (GridClass self, WidgetClass child, WidgetClass sibling)
=> self
-> child
-> Maybe sibling
-> PositionType
-> Int
-> Int
-> IO()
gridAttachNextTo self child sib pos width height =
(\(Grid arg1) (Widget arg2) (Widget arg3) arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->gtk_grid_attach_next_to argPtr1 argPtr2 argPtr3 arg4 arg5 arg6)
(toGrid self)
(toWidget child)
(maybe (Widget nullForeignPtr) toWidget sib)
(fromIntegral $ fromEnum pos)
(fromIntegral width)
(fromIntegral height)
gridSetRowHomogeneous :: GridClass self
=> self
-> Bool
-> IO ()
gridSetRowHomogeneous self homogeneous =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_set_row_homogeneous argPtr1 arg2)
(toGrid self)
(fromBool homogeneous)
gridGetRowHomogeneous :: GridClass self
=> self
-> IO Bool
gridGetRowHomogeneous self =
liftM toBool $
(\(Grid arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_get_row_homogeneous argPtr1)
(toGrid self)
gridSetRowSpacing :: GridClass self
=> self
-> Int
-> IO ()
gridSetRowSpacing self spacing =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_set_row_spacing argPtr1 arg2)
(toGrid self)
(fromIntegral spacing)
gridGetRowSpacing :: GridClass self
=> self
-> IO Int
gridGetRowSpacing self =
liftM fromIntegral $
(\(Grid arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_get_row_spacing argPtr1)
(toGrid self)
gridSetColumnHomogeneous :: GridClass self
=> self
-> Bool
-> IO ()
gridSetColumnHomogeneous self homogeneous =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_set_row_homogeneous argPtr1 arg2)
(toGrid self)
(fromBool homogeneous)
gridGetColumnHomogeneous :: GridClass self
=> self
-> IO Bool
gridGetColumnHomogeneous self =
liftM toBool $
(\(Grid arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_get_column_homogeneous argPtr1)
(toGrid self)
gridSetColumnSpacing :: GridClass self
=> self
-> Int
-> IO ()
gridSetColumnSpacing self spacing =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_set_column_spacing argPtr1 arg2)
(toGrid self)
(fromIntegral spacing)
gridGetColumnSpacing :: GridClass self
=> self
-> IO Int
gridGetColumnSpacing self =
liftM fromIntegral $
(\(Grid arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_get_column_spacing argPtr1)
(toGrid self)
gridGetChildAt :: GridClass self
=> self
-> Int
-> Int
-> IO (Maybe Widget)
gridGetChildAt self left top = do
ptr <- (\(Grid arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_get_child_at argPtr1 arg2 arg3)
(toGrid self)
(fromIntegral left)
(fromIntegral top)
if ptr == nullPtr
then return Nothing
else liftM Just $ makeNewObject mkWidget (return ptr)
gridInsertRow :: GridClass self
=> self
-> Int
-> IO ()
gridInsertRow self pos =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_insert_row argPtr1 arg2)
(toGrid self)
(fromIntegral pos)
gridInsertColumn :: GridClass self
=> self
-> Int
-> IO ()
gridInsertColumn self pos =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_insert_column argPtr1 arg2)
(toGrid self)
(fromIntegral pos)
gridInsertNextTo :: (GridClass self, WidgetClass sibling)
=> self
-> sibling
-> PositionType
-> IO ()
gridInsertNextTo self sib pos =
(\(Grid arg1) (Widget arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_grid_insert_next_to argPtr1 argPtr2 arg3)
(toGrid self)
(toWidget sib)
(fromIntegral $ fromEnum pos)
gridRemoveRow :: GridClass self
=> self
-> Int
-> IO ()
gridRemoveRow self pos =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_remove_row argPtr1 arg2)
(toGrid self)
(fromIntegral pos)
gridRemoveColumn :: GridClass self
=> self
-> Int
-> IO ()
gridRemoveColumn self pos =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_remove_column argPtr1 arg2)
(toGrid self)
(fromIntegral pos)
gridGetBaselineRow :: GridClass self
=> self
-> IO Int
gridGetBaselineRow self =
liftM fromIntegral $
(\(Grid arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_get_baseline_row argPtr1)
(toGrid self)
gridSetBaselineRow :: GridClass self
=> self
-> Int
-> IO ()
gridSetBaselineRow self row =
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_set_baseline_row argPtr1 arg2)
(toGrid self)
(fromIntegral row)
gridGetRowBaselinePosition :: GridClass self
=> self
-> Int
-> IO BaselinePosition
gridGetRowBaselinePosition self row =
liftM (toEnum . fromIntegral) $
(\(Grid arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_get_row_baseline_position argPtr1 arg2)
(toGrid self)
(fromIntegral row)
gridSetRowBaselinePosition :: GridClass self
=> self
-> Int
-> BaselinePosition
-> IO ()
gridSetRowBaselinePosition self row pos =
(\(Grid arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_grid_set_row_baseline_position argPtr1 arg2 arg3)
(toGrid self)
(fromIntegral row)
(fromIntegral $ fromEnum pos)
foreign import ccall unsafe "gtk_grid_new"
gtk_grid_new :: (IO (Ptr Widget))
foreign import ccall safe "gtk_grid_attach"
gtk_grid_attach :: ((Ptr Grid) -> ((Ptr Widget) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))
foreign import ccall safe "gtk_grid_attach_next_to"
gtk_grid_attach_next_to :: ((Ptr Grid) -> ((Ptr Widget) -> ((Ptr Widget) -> (CInt -> (CInt -> (CInt -> (IO ())))))))
foreign import ccall safe "gtk_grid_set_row_homogeneous"
gtk_grid_set_row_homogeneous :: ((Ptr Grid) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_grid_get_row_homogeneous"
gtk_grid_get_row_homogeneous :: ((Ptr Grid) -> (IO CInt))
foreign import ccall safe "gtk_grid_set_row_spacing"
gtk_grid_set_row_spacing :: ((Ptr Grid) -> (CUInt -> (IO ())))
foreign import ccall safe "gtk_grid_get_row_spacing"
gtk_grid_get_row_spacing :: ((Ptr Grid) -> (IO CUInt))
foreign import ccall safe "gtk_grid_get_column_homogeneous"
gtk_grid_get_column_homogeneous :: ((Ptr Grid) -> (IO CInt))
foreign import ccall safe "gtk_grid_set_column_spacing"
gtk_grid_set_column_spacing :: ((Ptr Grid) -> (CUInt -> (IO ())))
foreign import ccall safe "gtk_grid_get_column_spacing"
gtk_grid_get_column_spacing :: ((Ptr Grid) -> (IO CUInt))
foreign import ccall safe "gtk_grid_get_child_at"
gtk_grid_get_child_at :: ((Ptr Grid) -> (CInt -> (CInt -> (IO (Ptr Widget)))))
foreign import ccall safe "gtk_grid_insert_row"
gtk_grid_insert_row :: ((Ptr Grid) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_grid_insert_column"
gtk_grid_insert_column :: ((Ptr Grid) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_grid_insert_next_to"
gtk_grid_insert_next_to :: ((Ptr Grid) -> ((Ptr Widget) -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_grid_remove_row"
gtk_grid_remove_row :: ((Ptr Grid) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_grid_remove_column"
gtk_grid_remove_column :: ((Ptr Grid) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_grid_get_baseline_row"
gtk_grid_get_baseline_row :: ((Ptr Grid) -> (IO CInt))
foreign import ccall safe "gtk_grid_set_baseline_row"
gtk_grid_set_baseline_row :: ((Ptr Grid) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_grid_get_row_baseline_position"
gtk_grid_get_row_baseline_position :: ((Ptr Grid) -> (CInt -> (IO CInt)))
foreign import ccall safe "gtk_grid_set_row_baseline_position"
gtk_grid_set_row_baseline_position :: ((Ptr Grid) -> (CInt -> (CInt -> (IO ()))))