{-# LINE 2 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
module Graphics.UI.Gtk.Abstract.Widget (
Widget,
WidgetClass,
castToWidget, gTypeWidget,
toWidget,
EventMask(..),
GType,
KeyVal,
Requisition(..),
Rectangle(..),
Color,
IconSize(..),
StateType(..),
TextDirection(..),
AccelFlags(..),
DirectionType(..),
StockId,
WidgetHelpType(..),
Allocation,
widgetShow,
widgetShowNow,
widgetHide,
widgetShowAll,
widgetDestroy,
widgetDraw,
widgetQueueDraw,
widgetQueueResize,
widgetQueueResizeNoRedraw,
widgetGetFrameClock,
widgetGetScaleFactor,
widgetSizeRequest,
widgetGetChildRequisition,
widgetSizeAllocate,
widgetSizeAllocateWithBaseline,
widgetAddAccelerator,
widgetRemoveAccelerator,
widgetSetAccelPath,
widgetCanActivateAccel,
widgetActivate,
widgetIntersect,
widgetHasIntersection,
widgetGetIsFocus,
widgetGrabFocus,
widgetGrabDefault,
widgetSetName,
widgetGetName,
widgetSetSensitive,
widgetSetSensitivity,
widgetGetParentWindow,
widgetDelEvents,
widgetAddEvents,
widgetGetEvents,
widgetSetEvents,
widgetGetToplevel,
widgetGetAncestor,
widgetGetPointer,
widgetIsAncestor,
widgetTranslateCoordinates,
widgetSetStyle,
widgetGetStyle,
widgetGetDefaultStyle,
widgetSetDirection,
widgetGetDirection,
widgetSetDefaultDirection,
widgetGetDefaultDirection,
widgetShapeCombineRegion,
widgetInputShapeCombineRegion,
widgetPath,
widgetClassPath,
widgetGetCompositeName,
widgetOverrideBackgroundColor,
widgetOverrideColor,
widgetOverrideFont,
widgetOverrideSymbolicColor,
widgetOverrideCursor,
widgetModifyStyle,
widgetGetModifierStyle,
widgetModifyFg,
widgetModifyBg,
widgetModifyText,
widgetModifyBase,
widgetModifyFont,
widgetRestoreFg,
widgetRestoreBg,
widgetRestoreText,
widgetRestoreBase,
widgetCreatePangoContext,
widgetGetPangoContext,
widgetCreateLayout,
widgetRenderIcon,
widgetQueueDrawArea,
widgetQueueDrawRegion,
widgetSetAppPaintable,
widgetSetDoubleBuffered,
widgetSetRedrawOnAllocate,
widgetSetCompositeName,
widgetMnemonicActivate,
widgetGetAccessible,
widgetChildFocus,
widgetGetChildVisible,
widgetGetParent,
widgetGetSettings,
widgetGetClipboard,
widgetGetDisplay,
widgetGetRootWindow,
widgetGetScreen,
widgetHasScreen,
widgetGetSizeRequest,
widgetSetChildVisible,
widgetSetSizeRequest,
widgetSetNoShowAll,
widgetGetNoShowAll,
widgetListMnemonicLabels,
widgetAddMnemonicLabel,
widgetRemoveMnemonicLabel,
widgetIsComposited,
widgetErrorBell,
widgetKeynavFailed,
widgetGetTooltipMarkup,
widgetSetTooltipMarkup,
widgetGetTooltipText,
widgetSetTooltipText,
widgetGetTooltipWindow,
widgetSetTooltipWindow,
widgetGetHasTooltip,
widgetSetHasTooltip,
widgetTriggerTooltipQuery,
widgetGetWindow,
widgetRegisterWindow,
widgetUnregisterWindow,
cairoShouldDrawWindow,
cairoTransformToWindow,
widgetReparent,
widgetGetCanFocus,
widgetSetCanFocus,
widgetGetAllocation,
widgetGetAllocatedWidth,
widgetGetAllocatedHeight,
widgetGetAllocatedBaseline,
widgetGetAppPaintable,
widgetGetCanDefault,
widgetSetCanDefault,
widgetGetHasWindow,
widgetSetHasWindow,
widgetGetSensitive,
widgetIsSensitive,
widgetGetState,
widgetGetVisible,
widgetIsVisible,
widgetSetStateFlags,
widgetUnsetStateFlags,
widgetGetStateFlags,
widgetGetHasDefault,
widgetGetHasFocus,
widgetHasVisibleFocus,
widgetHasGrab,
widgetIsDrawable,
widgetIsToplevel,
widgetSetWindow,
widgetSetReceivesDefault,
widgetGetReceivesDefault,
widgetDeviceIsShadowed,
widgetGetModifierMask,
widgetSetSupportMultidevice,
widgetGetSupportMultidevice,
widgetSetState,
widgetEvent,
widgetGetHAlign,
widgetSetHAlign,
widgetGetVAlign,
widgetGetVAlignWithBaseline,
widgetSetVAlign,
widgetName,
widgetParent,
widgetWidthRequest,
widgetHeightRequest,
widgetMarginLeft,
widgetMarginRight,
widgetMarginTop,
widgetMarginBottom,
widgetVisible,
widgetOpacity,
widgetSensitive,
widgetAppPaintable,
widgetCanFocus,
widgetHasFocus,
widgetIsFocus,
widgetCanDefault,
widgetHasDefault,
widgetReceivesDefault,
widgetCompositeChild,
widgetStyle,
widgetState,
widgetEvents,
widgetExpand,
widgetHExpand,
widgetHExpandSet,
widgetVExpand,
widgetVExpandSet,
widgetNoShowAll,
widgetChildVisible,
widgetCompositeName,
widgetDirection,
widgetTooltipMarkup,
widgetTooltipText,
widgetHasTooltip,
widgetHasRcStyle,
widgetGetRealized,
widgetGetMapped,
widgetSetRealized,
widgetSetMapped,
widgetGetStyleContext,
realize,
unrealize,
mapSignal,
unmapSignal,
sizeRequest,
sizeAllocate,
showSignal,
hideSignal,
focus,
stateChanged,
stateFlagsChanged,
parentSet,
hierarchyChanged,
styleSet,
directionChanged,
grabNotify,
popupMenuSignal,
showHelp,
accelClosuresChanged,
screenChanged,
queryTooltip,
draw,
buttonPressEvent,
buttonReleaseEvent,
configureEvent,
deleteEvent,
destroyEvent,
enterNotifyEvent,
exposeEvent,
focusInEvent,
focusOutEvent,
grabBrokenEvent,
keyPressEvent,
keyReleaseEvent,
leaveNotifyEvent,
mapEvent,
motionNotifyEvent,
noExposeEvent,
proximityInEvent,
proximityOutEvent,
scrollEvent,
unmapEvent,
visibilityNotifyEvent,
windowStateEvent,
{-# LINE 536 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
) where
import Control.Monad (liftM, unless)
import Data.Maybe (fromMaybe)
import Control.Monad.Reader (ask)
import Control.Monad.Trans (liftIO)
import System.Glib.FFI
import System.Glib.Flags (fromFlags, toFlags)
import System.Glib.GError (failOnGError)
import System.Glib.Flags (Flags)
import System.Glib.UTFString
import System.Glib.Attributes
import System.Glib.Properties
import System.Glib.GType (GType)
import System.Glib.GList (fromGList)
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.General.DNDTypes (Atom (Atom), SelectionTag)
import Graphics.UI.Gtk.Types
{-# LINE 556 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
import Graphics.UI.Gtk.Signals
{-# LINE 557 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
import Graphics.UI.Gtk.Gdk.Enums (EventMask(..)
)
import Graphics.UI.Gtk.Gdk.Keys (KeyVal)
import Graphics.UI.Gtk.General.Structs (Allocation, Rectangle(..)
,Requisition(..), Color, IconSize(..)
,Point
)
import Graphics.UI.Gtk.Gdk.EventM (EventM,
EventM,
EAny,
EKey,
EButton,
EScroll,
EMotion,
EExpose,
EVisibility,
ECrossing,
EFocus,
EConfigure,
EProperty,
EProximity,
EWindowState,
EGrabBroken,
)
import Graphics.UI.Gtk.General.Enums (StateType(..), TextDirection(..),
AccelFlags(..), DirectionType(..), Modifier
,StateFlags(..), Align(..)
,ModifierIntent(..)
)
import Graphics.Rendering.Pango.Types
{-# LINE 610 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
import Graphics.Rendering.Pango.BasicTypes (FontDescription(FontDescription),
PangoLayout(PangoLayout), makeNewPangoString )
import Graphics.UI.Gtk.General.StockItems (StockId)
import Data.IORef ( newIORef )
import Control.Monad.Reader ( runReaderT )
import Graphics.Rendering.Cairo.Types (Cairo(..), unCairo, Region(..), withRegion)
import Graphics.Rendering.Cairo.Internal (Render(..))
{-# LINE 621 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetShow :: WidgetClass self => self -> IO ()
widgetShow self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_show argPtr1)
{-# LINE 640 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetShowNow :: WidgetClass self => self -> IO ()
widgetShowNow self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_show_now argPtr1)
{-# LINE 650 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetHide :: WidgetClass self => self -> IO ()
widgetHide self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_hide argPtr1)
{-# LINE 658 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetShowAll :: WidgetClass self => self -> IO ()
widgetShowAll self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_show_all argPtr1)
{-# LINE 666 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
{-# LINE 678 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetDestroy :: WidgetClass self => self -> IO ()
widgetDestroy self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_destroy argPtr1)
{-# LINE 694 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetDraw :: WidgetClass self
=> self
-> Cairo
-> IO ()
widgetDraw self cr =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_draw argPtr1 arg2)
{-# LINE 722 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(castPtr $ unCairo cr)
widgetQueueDraw :: WidgetClass self => self -> IO ()
widgetQueueDraw self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_queue_draw argPtr1)
{-# LINE 735 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetQueueResize :: WidgetClass self => self -> IO ()
widgetQueueResize self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_queue_resize argPtr1)
{-# LINE 747 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetQueueResizeNoRedraw :: WidgetClass self => self -> IO ()
widgetQueueResizeNoRedraw self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_queue_resize_no_redraw argPtr1)
{-# LINE 758 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetFrameClock :: WidgetClass self => self -> IO FrameClock
widgetGetFrameClock self =
makeNewGObject mkFrameClock $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_frame_clock argPtr1)
{-# LINE 786 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetScaleFactor :: WidgetClass self => self -> IO Int
widgetGetScaleFactor self =
liftM fromIntegral $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_scale_factor argPtr1)
{-# LINE 800 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetSizeRequest :: WidgetClass self => self -> IO Requisition
widgetSizeRequest self = alloca $ \reqPtr -> do
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_size_request argPtr1 arg2) (toWidget self) (castPtr reqPtr)
peek reqPtr
widgetGetChildRequisition :: WidgetClass self => self -> IO Requisition
widgetGetChildRequisition self = alloca $ \reqPtr -> do
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_child_requisition argPtr1 arg2) (toWidget self) (castPtr reqPtr)
peek reqPtr
widgetSizeAllocate :: WidgetClass self => self
-> Allocation
-> IO ()
widgetSizeAllocate self rect = with rect $ \rectPtr ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_size_allocate argPtr1 arg2) (toWidget self) (castPtr rectPtr)
widgetSizeAllocateWithBaseline :: WidgetClass self => self
-> Allocation
-> Int
-> IO ()
widgetSizeAllocateWithBaseline self rect baseline = with rect $ \rectPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_size_allocate_with_baseline argPtr1 arg2 arg3) (toWidget self) (castPtr rectPtr) (fromIntegral baseline)
widgetAddAccelerator :: (WidgetClass self, GlibString string) => self
-> string
-> AccelGroup
-> KeyVal
-> [Modifier]
-> [AccelFlags]
-> IO ()
widgetAddAccelerator self accelSignal accelGroup accelKey accelMods accelFlags =
withUTFString accelSignal $ \accelSignalPtr ->
(\(Widget arg1) arg2 (AccelGroup arg3) arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg3 $ \argPtr3 ->gtk_widget_add_accelerator argPtr1 arg2 argPtr3 arg4 arg5 arg6)
{-# LINE 903 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
accelSignalPtr
accelGroup
(fromIntegral accelKey)
((fromIntegral . fromFlags) accelMods)
((fromIntegral . fromFlags) accelFlags)
widgetRemoveAccelerator :: WidgetClass self => self
-> AccelGroup
-> KeyVal
-> [Modifier]
-> IO Bool
widgetRemoveAccelerator self accelGroup accelKey accelMods =
liftM toBool $
(\(Widget arg1) (AccelGroup arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_remove_accelerator argPtr1 argPtr2 arg3 arg4)
{-# LINE 924 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
accelGroup
(fromIntegral accelKey)
((fromIntegral . fromFlags) accelMods)
widgetSetAccelPath :: (WidgetClass self, GlibString string) => self
-> string
-> AccelGroup
-> IO ()
widgetSetAccelPath self accelPath accelGroup =
withUTFString accelPath $ \accelPathPtr ->
(\(Widget arg1) arg2 (AccelGroup arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg3 $ \argPtr3 ->gtk_widget_set_accel_path argPtr1 arg2 argPtr3)
{-# LINE 953 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
accelPathPtr
accelGroup
widgetCanActivateAccel :: WidgetClass self =>
(ConnectId self)
-> IO Bool
widgetCanActivateAccel (ConnectId signalId self) =
liftM toBool $
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_can_activate_accel argPtr1 arg2)
{-# LINE 974 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromIntegral signalId)
widgetActivate :: WidgetClass self => self
-> IO Bool
widgetActivate self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_activate argPtr1)
{-# LINE 988 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetIntersect :: WidgetClass self => self
-> Rectangle
-> IO (Maybe Rectangle)
widgetIntersect self area =
with area $ \areaPtr ->
alloca $ \intersectionPtr -> do
hasIntersection <- (\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_intersect argPtr1 arg2 arg3)
{-# LINE 1000 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(castPtr areaPtr)
(castPtr intersectionPtr)
if (toBool hasIntersection)
then liftM Just $ peek intersectionPtr
else return Nothing
widgetHasIntersection :: WidgetClass self => self
-> Rectangle
-> IO Bool
widgetHasIntersection self area =
liftM toBool $
with area $ \areaPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_intersect argPtr1 arg2 arg3)
{-# LINE 1016 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(castPtr areaPtr)
(castPtr nullPtr)
widgetGetIsFocus :: WidgetClass self => self
-> IO Bool
widgetGetIsFocus self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_is_focus argPtr1)
{-# LINE 1031 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGrabFocus :: WidgetClass self => self -> IO ()
widgetGrabFocus self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_grab_focus argPtr1)
{-# LINE 1043 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGrabDefault :: WidgetClass self => self -> IO ()
widgetGrabDefault self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_grab_default argPtr1)
{-# LINE 1054 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetSetName :: (WidgetClass self, GlibString string) => self
-> string
-> IO ()
widgetSetName self name =
withUTFString name $ \namePtr ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_name argPtr1 arg2)
{-# LINE 1070 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
namePtr
widgetGetName :: (WidgetClass self, GlibString string) => self -> IO string
widgetGetName self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_name argPtr1)
{-# LINE 1079 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
>>= peekUTFString
widgetSetSensitive :: WidgetClass self => self
-> Bool
-> IO ()
widgetSetSensitive self sensitive =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_sensitive argPtr1 arg2)
{-# LINE 1093 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromBool sensitive)
widgetSetSensitivity :: WidgetClass self => self -> Bool -> IO ()
widgetSetSensitivity = widgetSetSensitive
widgetGetParentWindow :: WidgetClass self => self -> IO DrawWindow
widgetGetParentWindow self =
makeNewGObject mkDrawWindow $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_parent_window argPtr1)
{-# LINE 1106 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetDelEvents :: WidgetClass self => self -> [EventMask] -> IO ()
widgetDelEvents self events = do
mask <- (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_events argPtr1) (toWidget self)
let mask' = mask .&. (complement (fromIntegral $ fromFlags events))
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_events argPtr1 arg2) (toWidget self) mask'
widgetAddEvents :: WidgetClass self => self -> [EventMask] -> IO ()
widgetAddEvents self [] = return ()
widgetAddEvents self events =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_add_events argPtr1 arg2)
{-# LINE 1134 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromIntegral $ fromFlags events)
widgetGetEvents :: WidgetClass self => self -> IO [EventMask]
widgetGetEvents self =
liftM (toFlags . fromIntegral) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_events argPtr1)
{-# LINE 1145 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetSetEvents :: WidgetClass self => self
-> [EventMask]
-> IO ()
widgetSetEvents self events =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_events argPtr1 arg2)
{-# LINE 1163 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromIntegral $ fromFlags events)
{-# LINE 1191 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetGetToplevel :: WidgetClass self =>
self
-> IO Widget
widgetGetToplevel self =
makeNewObject mkWidget $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_toplevel argPtr1)
{-# LINE 1203 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetAncestor :: WidgetClass self => self
-> GType
-> IO (Maybe Widget)
widgetGetAncestor self widgetType = do
ptr <- (\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_ancestor argPtr1 arg2)
{-# LINE 1219 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetType
if ptr==nullPtr then return Nothing else
liftM Just $ makeNewObject mkWidget (return ptr)
{-# LINE 1249 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetGetPointer :: WidgetClass self => self
-> IO (Int, Int)
widgetGetPointer self =
alloca $ \xPtr ->
alloca $ \yPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_pointer argPtr1 arg2 arg3)
{-# LINE 1262 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
xPtr
yPtr
>>
peek xPtr >>= \x ->
peek yPtr >>= \y ->
return (fromIntegral x, fromIntegral y)
widgetIsAncestor :: (WidgetClass self, WidgetClass ancestor) =>
self
-> ancestor
-> IO Bool
widgetIsAncestor self ancestor =
liftM toBool $
(\(Widget arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_is_ancestor argPtr1 argPtr2)
{-# LINE 1282 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(toWidget ancestor)
widgetTranslateCoordinates :: (WidgetClass self, WidgetClass destWidget) =>
self
-> destWidget
-> Int
-> Int
-> IO (Maybe (Int, Int))
widgetTranslateCoordinates self destWidget srcX srcY =
alloca $ \destXPtr ->
alloca $ \destYPtr -> do
worked <- (\(Widget arg1) (Widget arg2) arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_translate_coordinates argPtr1 argPtr2 arg3 arg4 arg5 arg6)
{-# LINE 1303 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(toWidget destWidget)
(fromIntegral srcX)
(fromIntegral srcY)
destXPtr
destYPtr
if (toBool worked)
then do destX <- peek destXPtr
destY <- peek destYPtr
return (Just (fromIntegral destX, fromIntegral destY))
else return Nothing
widgetSetStyle :: WidgetClass self => self
-> Maybe Style
-> IO ()
widgetSetStyle self style =
(\(Widget arg1) (Style arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_set_style argPtr1 argPtr2)
{-# LINE 1326 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromMaybe (Style nullForeignPtr) style)
widgetGetStyle :: WidgetClass widget => widget -> IO Style
widgetGetStyle widget = do
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_ensure_style argPtr1) (toWidget widget)
makeNewGObject mkStyle $ (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_style argPtr1) (toWidget widget)
{-# LINE 1369 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetGetDefaultStyle ::
IO Style
widgetGetDefaultStyle =
makeNewGObject mkStyle $
gtk_widget_get_default_style
{-# LINE 1390 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetSetDirection :: WidgetClass self => self -> TextDirection -> IO ()
widgetSetDirection self dir =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_direction argPtr1 arg2)
{-# LINE 1405 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) dir)
widgetGetDirection :: WidgetClass self => self -> IO TextDirection
widgetGetDirection self =
liftM (toEnum . fromIntegral) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_direction argPtr1)
{-# LINE 1415 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetSetDefaultDirection ::
TextDirection
-> IO ()
widgetSetDefaultDirection dir =
gtk_widget_set_default_direction
{-# LINE 1427 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
((fromIntegral . fromEnum) dir)
widgetGetDefaultDirection :: IO TextDirection
widgetGetDefaultDirection =
liftM (toEnum . fromIntegral) $
gtk_widget_get_default_direction
{-# LINE 1485 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetShapeCombineRegion :: WidgetClass self => self
-> Maybe Region
-> IO ()
widgetShapeCombineRegion self region =
withRegion (fromMaybe (Region nullForeignPtr) region) $ \ptrRegion ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_shape_combine_region argPtr1 arg2)
{-# LINE 1493 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(castPtr ptrRegion)
widgetInputShapeCombineRegion :: WidgetClass self => self
-> Maybe Region
-> IO ()
widgetInputShapeCombineRegion self region =
withRegion (fromMaybe (Region nullForeignPtr) region) $ \ptrRegion ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_input_shape_combine_region argPtr1 arg2)
{-# LINE 1505 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(castPtr ptrRegion)
{-# LINE 1543 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetPath :: (WidgetClass self, GlibString string) => self
-> IO (Int, string, string)
widgetPath self =
alloca $ \pathLengthPtr ->
alloca $ \pathPtr ->
alloca $ \pathReversedPtr ->
(\(Widget arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_path argPtr1 arg2 arg3 arg4)
{-# LINE 1564 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
pathLengthPtr
pathPtr
pathReversedPtr
>>
peek pathLengthPtr >>= \pathLength ->
peek pathPtr >>= readUTFString >>= \path ->
peek pathReversedPtr >>= readUTFString >>= \pathReversed ->
return (fromIntegral pathLength, path, pathReversed)
widgetClassPath :: (WidgetClass self, GlibString string) => self
-> IO (Int, string, string)
widgetClassPath self =
alloca $ \pathLengthPtr ->
alloca $ \pathPtr ->
alloca $ \pathReversedPtr ->
(\(Widget arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_class_path argPtr1 arg2 arg3 arg4)
{-# LINE 1587 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
pathLengthPtr
pathPtr
pathReversedPtr
>>
peek pathLengthPtr >>= \pathLength ->
peek pathPtr >>= readUTFString >>= \path ->
peek pathReversedPtr >>= readUTFString >>= \pathReversed ->
return (fromIntegral pathLength, path, pathReversed)
widgetGetCompositeName :: (WidgetClass self, GlibString string) => self
-> IO (Maybe string)
widgetGetCompositeName self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_composite_name argPtr1)
{-# LINE 1605 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
>>= maybePeek peekUTFString
widgetOverrideBackgroundColor :: WidgetClass self => self
-> StateType
-> Maybe Color
-> IO ()
widgetOverrideBackgroundColor self state color =
maybeWith with color $ \colorPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_override_background_color argPtr1 arg2 arg3)
{-# LINE 1620 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
(castPtr colorPtr)
widgetOverrideColor :: WidgetClass self => self
-> StateType
-> Maybe Color
-> IO ()
widgetOverrideColor self state color =
maybeWith with color $ \colorPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_override_color argPtr1 arg2 arg3)
{-# LINE 1655 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
(castPtr colorPtr)
widgetOverrideFont :: WidgetClass self => self
-> Maybe FontDescription
-> IO ()
widgetOverrideFont self fontDesc =
(\(Widget arg1) (FontDescription arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_override_font argPtr1 argPtr2)
{-# LINE 1668 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromMaybe (FontDescription nullForeignPtr) fontDesc)
widgetOverrideSymbolicColor :: (WidgetClass self, GlibString string) => self
-> string
-> Maybe Color
-> IO ()
widgetOverrideSymbolicColor self name color =
withUTFString name $ \namePtr ->
maybeWith with color $ \colorPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_override_symbolic_color argPtr1 arg2 arg3)
{-# LINE 1683 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
namePtr
(castPtr colorPtr)
widgetOverrideCursor :: WidgetClass self => self
-> Maybe Color
-> Maybe Color
-> IO ()
widgetOverrideCursor self cursor secondaryCursor =
maybeWith with cursor $ \cursorPtr ->
maybeWith with secondaryCursor $ \secondaryCursorPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_override_cursor argPtr1 arg2 arg3)
{-# LINE 1702 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(castPtr cursorPtr)
(castPtr secondaryCursorPtr)
widgetModifyStyle :: (WidgetClass self, RcStyleClass style) => self
-> style
-> IO ()
widgetModifyStyle self style =
(\(Widget arg1) (RcStyle arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_modify_style argPtr1 argPtr2)
{-# LINE 1728 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(toRcStyle style)
widgetGetModifierStyle :: WidgetClass self => self -> IO RcStyle
widgetGetModifierStyle self =
makeNewGObject mkRcStyle $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_modifier_style argPtr1)
{-# LINE 1748 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetModifyFg :: WidgetClass self => self
-> StateType
-> Color
-> IO ()
widgetModifyFg self state color =
with color $ \colorPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_modify_fg argPtr1 arg2 arg3)
{-# LINE 1762 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
(castPtr colorPtr)
widgetRestoreFg :: WidgetClass self => self
-> StateType
-> IO ()
widgetRestoreFg self state =
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_modify_fg argPtr1 arg2 arg3)
{-# LINE 1774 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
nullPtr
widgetModifyBg :: WidgetClass self => self
-> StateType
-> Color
-> IO ()
widgetModifyBg self state color =
with color $ \colorPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_modify_bg argPtr1 arg2 arg3)
{-# LINE 1797 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
(castPtr colorPtr)
widgetRestoreBg :: WidgetClass self => self
-> StateType
-> IO ()
widgetRestoreBg self state =
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_modify_bg argPtr1 arg2 arg3)
{-# LINE 1809 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
nullPtr
widgetModifyText :: WidgetClass self => self
-> StateType
-> Color
-> IO ()
widgetModifyText self state color =
with color $ \colorPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_modify_text argPtr1 arg2 arg3)
{-# LINE 1827 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
(castPtr colorPtr)
widgetRestoreText :: WidgetClass self => self
-> StateType
-> IO ()
widgetRestoreText self state =
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_modify_text argPtr1 arg2 arg3)
{-# LINE 1839 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
nullPtr
widgetModifyBase :: WidgetClass self => self
-> StateType
-> Color
-> IO ()
widgetModifyBase self state color =
with color $ \colorPtr ->
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_modify_base argPtr1 arg2 arg3)
{-# LINE 1864 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
(castPtr colorPtr)
widgetRestoreBase :: WidgetClass self => self
-> StateType
-> IO ()
widgetRestoreBase self state =
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_modify_base argPtr1 arg2 arg3)
{-# LINE 1876 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) state)
nullPtr
widgetModifyFont :: WidgetClass self => self
-> Maybe FontDescription
-> IO ()
widgetModifyFont self fontDesc =
(\(Widget arg1) (FontDescription arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_modify_font argPtr1 argPtr2)
{-# LINE 1892 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromMaybe (FontDescription nullForeignPtr) fontDesc)
widgetCreatePangoContext :: WidgetClass self => self
-> IO PangoContext
widgetCreatePangoContext self =
wrapNewGObject mkPangoContext $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_create_pango_context argPtr1)
{-# LINE 1904 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetPangoContext :: WidgetClass self => self
-> IO PangoContext
widgetGetPangoContext self =
makeNewGObject mkPangoContext $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_pango_context argPtr1)
{-# LINE 1924 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetCreateLayout :: (WidgetClass self, GlibString string) => self
-> string
-> IO PangoLayout
widgetCreateLayout self text = do
pl <- wrapNewGObject mkPangoLayoutRaw $
withUTFString text $ \textPtr ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_create_pango_layout argPtr1 arg2)
{-# LINE 1950 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
textPtr
ps <- makeNewPangoString text
psRef <- newIORef ps
return (PangoLayout psRef pl)
widgetRenderIcon :: (WidgetClass self, GlibString string) => self
-> string
-> IconSize
-> string
-> IO (Maybe Pixbuf)
widgetRenderIcon self stockId size detail =
maybeNull (wrapNewGObject mkPixbuf) $
withUTFString detail $ \detailPtr ->
withUTFString stockId $ \stockIdPtr ->
(\(Widget arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_render_icon argPtr1 arg2 arg3 arg4)
{-# LINE 1982 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
stockIdPtr
((fromIntegral . fromEnum) size)
detailPtr
widgetQueueDrawArea :: WidgetClass self => self
-> Int
-> Int
-> Int
-> Int
-> IO ()
widgetQueueDrawArea self x y width height =
(\(Widget arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_queue_draw_area argPtr1 arg2 arg3 arg4 arg5)
{-# LINE 2020 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromIntegral x)
(fromIntegral y)
(fromIntegral width)
(fromIntegral height)
widgetQueueDrawRegion :: WidgetClass self => self
-> Region
-> IO ()
widgetQueueDrawRegion self region =
withRegion region $ \regionPtr ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_queue_draw_region argPtr1 arg2)
{-# LINE 2042 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(castPtr regionPtr)
{-# LINE 2056 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetSetAppPaintable :: WidgetClass self => self
-> Bool
-> IO ()
widgetSetAppPaintable self appPaintable =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_app_paintable argPtr1 arg2)
{-# LINE 2072 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromBool appPaintable)
widgetSetDoubleBuffered :: WidgetClass self => self
-> Bool
-> IO ()
widgetSetDoubleBuffered self doubleBuffered =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_double_buffered argPtr1 arg2)
{-# LINE 2102 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromBool doubleBuffered)
widgetSetRedrawOnAllocate :: WidgetClass self => self
-> Bool
-> IO ()
widgetSetRedrawOnAllocate self redrawOnAllocate =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_redraw_on_allocate argPtr1 arg2)
{-# LINE 2127 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromBool redrawOnAllocate)
widgetSetCompositeName :: (WidgetClass self, GlibString string) => self
-> string
-> IO ()
widgetSetCompositeName self name =
withUTFString name $ \namePtr ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_composite_name argPtr1 arg2)
{-# LINE 2140 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
namePtr
widgetMnemonicActivate :: WidgetClass self => self
-> Bool
-> IO Bool
widgetMnemonicActivate self groupCycling =
liftM toBool $
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_mnemonic_activate argPtr1 arg2)
{-# LINE 2153 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromBool groupCycling)
{-# LINE 2201 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetGetAccessible :: WidgetClass self => self
-> IO GObject
widgetGetAccessible self =
makeNewGObject mkGObject $
liftM castPtr $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_accessible argPtr1)
{-# LINE 2230 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetChildFocus :: WidgetClass self => self
-> DirectionType
-> IO Bool
widgetChildFocus self direction =
liftM toBool $
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_child_focus argPtr1 arg2)
{-# LINE 2251 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) direction)
widgetGetChildVisible :: WidgetClass self => self
-> IO Bool
widgetGetChildVisible self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_child_visible argPtr1)
{-# LINE 2266 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetParent :: WidgetClass self => self
-> IO (Maybe Widget)
widgetGetParent self = do
parentPtr <- (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_parent argPtr1) (toWidget self)
if parentPtr==nullPtr then return Nothing else
liftM Just $ makeNewObject mkWidget (return parentPtr)
widgetGetSettings :: WidgetClass self => self
-> IO Settings
widgetGetSettings self =
makeNewGObject mkSettings $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_settings argPtr1)
{-# LINE 2293 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetClipboard :: WidgetClass self => self
-> SelectionTag
-> IO Clipboard
widgetGetClipboard self (Atom tagPtr) =
makeNewGObject mkClipboard $
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_clipboard argPtr1 arg2)
{-# LINE 2313 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
tagPtr
widgetGetDisplay :: WidgetClass self => self
-> IO Display
widgetGetDisplay self =
makeNewGObject mkDisplay $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_display argPtr1)
{-# LINE 2332 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetRootWindow :: WidgetClass self => self
-> IO DrawWindow
widgetGetRootWindow self =
makeNewGObject mkDrawWindow $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_root_window argPtr1)
{-# LINE 2352 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetScreen :: WidgetClass self => self
-> IO Screen
widgetGetScreen self =
makeNewGObject mkScreen $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_screen argPtr1)
{-# LINE 2370 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetHasScreen :: WidgetClass self => self
-> IO Bool
widgetHasScreen self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_has_screen argPtr1)
{-# LINE 2385 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetSizeRequest :: WidgetClass self => self
-> IO (Int, Int)
widgetGetSizeRequest self =
alloca $ \widthPtr ->
alloca $ \heightPtr -> do
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_size_request argPtr1 arg2 arg3)
{-# LINE 2402 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widthPtr
heightPtr
width <- peek widthPtr
height <- peek heightPtr
return (fromIntegral width, fromIntegral height)
widgetSetChildVisible :: WidgetClass self => self
-> Bool
-> IO ()
widgetSetChildVisible self isVisible =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_child_visible argPtr1 arg2)
{-# LINE 2432 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromBool isVisible)
widgetSetSizeRequest :: WidgetClass self => self
-> Int
-> Int
-> IO ()
widgetSetSizeRequest self width height =
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_size_request argPtr1 arg2 arg3)
{-# LINE 2469 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromIntegral width)
(fromIntegral height)
widgetSetNoShowAll :: WidgetClass self => self
-> Bool
-> IO ()
widgetSetNoShowAll self noShowAll =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_no_show_all argPtr1 arg2)
{-# LINE 2488 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromBool noShowAll)
widgetGetNoShowAll :: WidgetClass self => self
-> IO Bool
widgetGetNoShowAll self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_no_show_all argPtr1)
{-# LINE 2503 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetListMnemonicLabels :: WidgetClass self => self
-> IO [Widget]
widgetListMnemonicLabels self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_list_mnemonic_labels argPtr1)
{-# LINE 2516 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
>>= fromGList
>>= mapM (makeNewGObject mkWidget . return)
widgetAddMnemonicLabel :: (WidgetClass self, WidgetClass label) => self
-> label
-> IO ()
widgetAddMnemonicLabel self label =
(\(Widget arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_add_mnemonic_label argPtr1 argPtr2)
{-# LINE 2535 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(toWidget label)
widgetRemoveMnemonicLabel :: (WidgetClass self, WidgetClass label) => self
-> label
-> IO ()
widgetRemoveMnemonicLabel self label =
(\(Widget arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_remove_mnemonic_label argPtr1 argPtr2)
{-# LINE 2551 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(toWidget label)
{-# LINE 2573 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetIsComposited :: WidgetClass self => self
-> IO Bool
widgetIsComposited self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_is_composited argPtr1)
{-# LINE 2586 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetErrorBell :: WidgetClass self => self
-> IO ()
widgetErrorBell self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_error_bell argPtr1)
{-# LINE 2602 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetKeynavFailed :: WidgetClass self => self
-> DirectionType
-> IO Bool
widgetKeynavFailed self direction =
liftM toBool $
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_keynav_failed argPtr1 arg2)
{-# LINE 2638 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
((fromIntegral . fromEnum) direction)
widgetGetTooltipMarkup :: (WidgetClass self, GlibString markup) => self
-> IO (Maybe markup)
widgetGetTooltipMarkup self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_tooltip_markup argPtr1)
{-# LINE 2646 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
>>= maybePeek peekUTFString
widgetSetTooltipMarkup :: (WidgetClass self, GlibString markup) => self
-> Maybe markup
-> IO ()
widgetSetTooltipMarkup self markup =
maybeWith withUTFString markup $ \ markupPtr ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_tooltip_markup argPtr1 arg2)
{-# LINE 2662 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
markupPtr
widgetGetTooltipText :: (WidgetClass self, GlibString text) => self
-> IO (Maybe text)
widgetGetTooltipText self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_tooltip_text argPtr1)
{-# LINE 2670 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
>>= maybePeek peekUTFString
widgetSetTooltipText :: (WidgetClass widget, GlibString text) => widget
-> Maybe text
-> IO ()
widgetSetTooltipText widget text =
maybeWith withUTFString text $ \ textPtr ->
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_tooltip_text argPtr1 arg2)
{-# LINE 2684 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
textPtr
widgetGetTooltipWindow :: WidgetClass self => self
-> IO Window
widgetGetTooltipWindow self =
makeNewObject mkWindow $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_tooltip_window argPtr1)
{-# LINE 2697 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetSetTooltipWindow :: (WidgetClass self, WindowClass customWindow) => self
-> Maybe customWindow
-> IO ()
widgetSetTooltipWindow self customWindow =
(\(Widget arg1) (Window arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_set_tooltip_window argPtr1 argPtr2)
{-# LINE 2713 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(maybe (Window nullForeignPtr) toWindow customWindow)
widgetGetHasTooltip :: WidgetClass widget => widget
-> IO Bool
widgetGetHasTooltip widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_has_tooltip argPtr1)
{-# LINE 2723 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetSetHasTooltip :: WidgetClass widget => widget
-> Bool
-> IO ()
widgetSetHasTooltip widget hasTooltip =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_has_tooltip argPtr1 arg2)
{-# LINE 2732 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromBool hasTooltip)
widgetTriggerTooltipQuery :: WidgetClass self => self -> IO ()
widgetTriggerTooltipQuery self =
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_trigger_tooltip_query argPtr1)
{-# LINE 2743 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetWindow :: WidgetClass self => self -> IO (Maybe DrawWindow)
widgetGetWindow self =
maybeNull (makeNewGObject mkDrawWindow) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_window argPtr1)
{-# LINE 2755 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetRegisterWindow :: (WidgetClass widget, DrawWindowClass window) => widget
-> window
-> IO ()
widgetRegisterWindow widget window =
(\(Widget arg1) (DrawWindow arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_register_window argPtr1 argPtr2)
{-# LINE 2767 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(toDrawWindow window)
widgetUnregisterWindow :: (WidgetClass widget, DrawWindowClass window) => widget
-> window
-> IO ()
widgetUnregisterWindow widget window =
(\(Widget arg1) (DrawWindow arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_unregister_window argPtr1 argPtr2)
{-# LINE 2778 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(toDrawWindow window)
cairoShouldDrawWindow :: DrawWindowClass window
=> Cairo
-> window
-> IO Bool
cairoShouldDrawWindow cr window =
liftM toBool $
(\arg1 (DrawWindow arg2) -> withForeignPtr arg2 $ \argPtr2 ->gtk_cairo_should_draw_window arg1 argPtr2)
{-# LINE 2798 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(castPtr $ unCairo cr)
(toDrawWindow window)
cairoTransformToWindow :: (WidgetClass widget, DrawWindowClass window)
=> Cairo
-> widget
-> window
-> IO ()
cairoTransformToWindow cr widget window =
(\arg1 (Widget arg2) (DrawWindow arg3) -> withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->gtk_cairo_transform_to_window arg1 argPtr2 argPtr3)
{-# LINE 2816 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(castPtr $ unCairo cr)
(toWidget widget)
(toDrawWindow window)
widgetReparent :: (WidgetClass self, WidgetClass newParent) => self
-> newParent
-> IO ()
widgetReparent self newParent =
(\(Widget arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_reparent argPtr1 argPtr2)
{-# LINE 2828 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(toWidget newParent)
widgetSetCanFocus :: WidgetClass self => self -> Bool -> IO ()
widgetSetCanFocus = objectSetPropertyBool "can_focus"
widgetGetCanFocus :: WidgetClass self => self -> IO Bool
widgetGetCanFocus = objectGetPropertyBool "can_focus"
widgetGetAllocation :: WidgetClass self => self -> IO Allocation
widgetGetAllocation widget =
alloca $ \ allocationPtr -> do
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_allocation argPtr1 arg2) (toWidget widget) (castPtr allocationPtr)
peek allocationPtr
widgetGetAllocatedWidth :: WidgetClass self => self -> IO Int
widgetGetAllocatedWidth widget =
liftM fromIntegral $ (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_allocated_width argPtr1) (toWidget widget)
widgetGetAllocatedHeight :: WidgetClass self => self -> IO Int
widgetGetAllocatedHeight widget =
liftM fromIntegral $ (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_allocated_height argPtr1) (toWidget widget)
widgetGetAllocatedBaseline :: WidgetClass self => self -> IO Int
widgetGetAllocatedBaseline widget =
liftM fromIntegral $ (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_allocated_baseline argPtr1) (toWidget widget)
{-# LINE 2916 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetGetAppPaintable :: WidgetClass widget => widget
-> IO Bool
widgetGetAppPaintable widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_app_paintable argPtr1)
{-# LINE 2924 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetGetCanDefault :: WidgetClass widget => widget
-> IO Bool
widgetGetCanDefault widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_can_default argPtr1)
{-# LINE 2933 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetSetCanDefault :: WidgetClass widget => widget
-> Bool
-> IO ()
widgetSetCanDefault widget canDefault =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_can_default argPtr1 arg2)
{-# LINE 2942 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromBool canDefault)
widgetGetHasWindow :: WidgetClass widget => widget
-> IO Bool
widgetGetHasWindow widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_has_window argPtr1)
{-# LINE 2951 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetSetHasWindow :: WidgetClass widget => widget
-> Bool
-> IO ()
widgetSetHasWindow widget hasWindow =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_has_window argPtr1 arg2)
{-# LINE 2967 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromBool hasWindow)
widgetGetSensitive :: WidgetClass widget => widget
-> IO Bool
widgetGetSensitive widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_sensitive argPtr1)
{-# LINE 2980 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetIsSensitive :: WidgetClass widget => widget
-> IO Bool
widgetIsSensitive widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_is_sensitive argPtr1)
{-# LINE 2989 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetGetState :: WidgetClass self => self -> IO StateType
widgetGetState widget =
liftM (toEnum . fromIntegral) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_state argPtr1)
{-# LINE 3000 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetGetVisible :: WidgetClass widget => widget
-> IO Bool
widgetGetVisible widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_visible argPtr1)
{-# LINE 3013 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetIsVisible :: WidgetClass widget => widget
-> IO Bool
widgetIsVisible widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_is_visible argPtr1)
{-# LINE 3027 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetSetStateFlags :: WidgetClass widget => widget
-> [StateFlags]
-> Bool
-> IO ()
widgetSetStateFlags widget flags clear =
(\(Widget arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_state_flags argPtr1 arg2 arg3)
{-# LINE 3050 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromIntegral $ fromFlags flags)
(fromBool clear)
widgetUnsetStateFlags :: WidgetClass widget => widget
-> [StateFlags]
-> IO ()
widgetUnsetStateFlags widget flags =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_unset_state_flags argPtr1 arg2)
{-# LINE 3062 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromIntegral $ fromFlags flags)
widgetGetStateFlags :: WidgetClass widget => widget
-> IO [StateFlags]
widgetGetStateFlags widget =
liftM (toFlags . fromIntegral) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_state_flags argPtr1)
{-# LINE 3073 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetGetHasDefault :: WidgetClass widget => widget
-> IO Bool
widgetGetHasDefault widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_has_default argPtr1)
{-# LINE 3084 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetGetHasFocus :: WidgetClass widget => widget
-> IO Bool
widgetGetHasFocus widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_has_focus argPtr1)
{-# LINE 3094 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetHasVisibleFocus :: WidgetClass widget => widget
-> IO Bool
widgetHasVisibleFocus widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_has_visible_focus argPtr1)
{-# LINE 3110 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetHasGrab :: WidgetClass widget => widget
-> IO Bool
widgetHasGrab widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_has_grab argPtr1)
{-# LINE 3123 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetIsDrawable :: WidgetClass widget => widget
-> IO Bool
widgetIsDrawable widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_is_drawable argPtr1)
{-# LINE 3132 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetIsToplevel :: WidgetClass widget => widget
-> IO Bool
widgetIsToplevel widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_is_toplevel argPtr1)
{-# LINE 3143 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetSetWindow :: (WidgetClass widget, DrawWindowClass window) => widget
-> window
-> IO ()
widgetSetWindow widget window =
(\(Widget arg1) (DrawWindow arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_set_window argPtr1 argPtr2)
{-# LINE 3160 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(toDrawWindow window)
widgetSetReceivesDefault :: WidgetClass widget => widget
-> Bool
-> IO ()
widgetSetReceivesDefault widget receivesDefault =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_receives_default argPtr1 arg2)
{-# LINE 3172 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromBool receivesDefault)
widgetGetReceivesDefault :: WidgetClass widget => widget
-> IO Bool
widgetGetReceivesDefault widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_receives_default argPtr1)
{-# LINE 3185 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetDeviceIsShadowed :: (WidgetClass widget, DeviceClass device) => widget
-> device
-> IO Bool
widgetDeviceIsShadowed widget device =
liftM toBool $
(\(Widget arg1) (Device arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_widget_device_is_shadowed argPtr1 argPtr2)
{-# LINE 3199 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(toDevice device)
widgetGetModifierMask :: WidgetClass widget => widget
-> ModifierIntent
-> IO [Modifier]
widgetGetModifierMask widget intent =
liftM (toFlags . fromIntegral) $
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_modifier_mask argPtr1 arg2)
{-# LINE 3214 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
((fromIntegral . fromEnum) intent)
widgetSetSupportMultidevice :: WidgetClass widget => widget
-> Bool
-> IO ()
widgetSetSupportMultidevice widget supportMultidevice =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_support_multidevice argPtr1 arg2)
{-# LINE 3228 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromBool supportMultidevice)
widgetGetSupportMultidevice :: WidgetClass widget => widget
-> IO Bool
widgetGetSupportMultidevice widget =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_support_multidevice argPtr1)
{-# LINE 3238 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetSetState :: WidgetClass self => self -> StateType -> IO ()
widgetSetState widget state =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_state argPtr1 arg2)
{-# LINE 3248 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
((fromIntegral . fromEnum) state)
widgetEvent :: WidgetClass self => self -> EventM t Bool
widgetEvent widget = do
ptr <- ask
liftIO $ liftM toBool $ (\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_event argPtr1 arg2) (toWidget widget) (castPtr ptr)
widgetName :: (WidgetClass self, GlibString string) => Attr self (Maybe string)
widgetName = newAttrFromMaybeStringProperty "name"
widgetMarginLeft :: WidgetClass self => Attr self Int
widgetMarginLeft = newAttrFromIntProperty "margin-left"
widgetMarginRight :: WidgetClass self => Attr self Int
widgetMarginRight = newAttrFromIntProperty "margin-right"
{-# LINE 3286 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetMarginTop :: WidgetClass self => Attr self Int
widgetMarginTop = newAttrFromIntProperty "margin-top"
widgetMarginBottom :: WidgetClass self => Attr self Int
widgetMarginBottom = newAttrFromIntProperty "margin-bottom"
widgetParent :: (WidgetClass self, ContainerClass container) => ReadWriteAttr self (Maybe Container) (Maybe container)
widgetParent = newAttrFromMaybeObjectProperty "parent" gTypeContainer
widgetWidthRequest :: WidgetClass self => Attr self Int
widgetWidthRequest = newAttrFromIntProperty "width-request"
widgetHeightRequest :: WidgetClass self => Attr self Int
widgetHeightRequest = newAttrFromIntProperty "height-request"
widgetVisible :: WidgetClass self => Attr self Bool
widgetVisible = newAttrFromBoolProperty "visible"
widgetOpacity :: WidgetClass self => Attr self Double
widgetOpacity = newAttrFromDoubleProperty "opacity"
widgetSensitive :: WidgetClass self => Attr self Bool
widgetSensitive = newAttrFromBoolProperty "sensitive"
widgetAppPaintable :: WidgetClass self => Attr self Bool
widgetAppPaintable = newAttrFromBoolProperty "app-paintable"
widgetCanFocus :: WidgetClass self => Attr self Bool
widgetCanFocus = newAttrFromBoolProperty "can-focus"
widgetHasFocus :: WidgetClass self => Attr self Bool
widgetHasFocus = newAttrFromBoolProperty "has-focus"
widgetIsFocus :: WidgetClass self => Attr self Bool
widgetIsFocus = newAttrFromBoolProperty "is-focus"
widgetCanDefault :: WidgetClass self => Attr self Bool
widgetCanDefault = newAttrFromBoolProperty "can-default"
widgetHasDefault :: WidgetClass self => Attr self Bool
widgetHasDefault = newAttrFromBoolProperty "has-default"
widgetReceivesDefault :: WidgetClass self => Attr self Bool
widgetReceivesDefault = newAttrFromBoolProperty "receives-default"
widgetCompositeChild :: WidgetClass self => ReadAttr self Bool
widgetCompositeChild = readAttrFromBoolProperty "composite-child"
widgetStyle :: WidgetClass self => Attr self Style
widgetStyle = newAttrFromObjectProperty "style" gTypeStyle
widgetState :: WidgetClass self => Attr self StateType
widgetState = newAttr
widgetGetState
widgetSetState
widgetEvents :: WidgetClass self => Attr self [EventMask]
widgetEvents = newAttrFromFlagsProperty "events"
gdk_event_mask_get_type
{-# LINE 3444 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetExpand :: WidgetClass self => Attr self Bool
widgetExpand = newAttrFromBoolProperty "expand"
widgetHExpand :: WidgetClass self => Attr self Bool
widgetHExpand = newAttrFromBoolProperty "hexpand"
widgetHExpandSet :: WidgetClass self => Attr self Bool
widgetHExpandSet = newAttrFromBoolProperty "hexpand-set"
widgetVExpand :: WidgetClass self => Attr self Bool
widgetVExpand = newAttrFromBoolProperty "vexpand"
widgetVExpandSet :: WidgetClass self => Attr self Bool
widgetVExpandSet = newAttrFromBoolProperty "vexpand-set"
widgetNoShowAll :: WidgetClass self => Attr self Bool
widgetNoShowAll = newAttrFromBoolProperty "no-show-all"
widgetChildVisible :: WidgetClass self => Attr self Bool
widgetChildVisible = newAttr
widgetGetChildVisible
widgetSetChildVisible
{-# LINE 3507 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
widgetCompositeName :: (WidgetClass self, GlibString string) => ReadWriteAttr self (Maybe string) string
widgetCompositeName = newAttr
widgetGetCompositeName
widgetSetCompositeName
widgetDirection :: WidgetClass self => Attr self TextDirection
widgetDirection = newAttr
widgetGetDirection
widgetSetDirection
widgetTooltipMarkup :: (WidgetClass self, GlibString markup) => Attr self (Maybe markup)
widgetTooltipMarkup = newAttrFromMaybeStringProperty "tooltip-markup"
widgetTooltipText :: (WidgetClass self, GlibString string) => Attr self (Maybe string)
widgetTooltipText = newAttrFromMaybeStringProperty "tooltip-text"
widgetHasTooltip :: WidgetClass self => Attr self Bool
widgetHasTooltip = newAttrFromBoolProperty "has-tooltip"
widgetHasRcStyle :: WidgetClass self => self
-> IO Bool
widgetHasRcStyle self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_has_rc_style argPtr1)
{-# LINE 3575 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetRealized :: WidgetClass self => self
-> IO Bool
widgetGetRealized self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_realized argPtr1)
{-# LINE 3583 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetMapped :: WidgetClass self => self
-> IO Bool
widgetGetMapped self =
liftM toBool $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_mapped argPtr1)
{-# LINE 3591 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetSetRealized :: WidgetClass widget => widget
-> Bool
-> IO ()
widgetSetRealized widget realized =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_realized argPtr1 arg2)
{-# LINE 3603 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromBool realized)
widgetSetMapped :: WidgetClass widget => widget
-> Bool
-> IO ()
widgetSetMapped widget mapped =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_mapped argPtr1 arg2)
{-# LINE 3615 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
(fromBool mapped)
widgetGetStyleContext :: WidgetClass widget
=> widget
-> IO StyleContext
widgetGetStyleContext widget =
makeNewGObject mkStyleContext $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_style_context argPtr1)
{-# LINE 3627 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget widget)
widgetGetHAlign :: WidgetClass self => self -> IO Align
widgetGetHAlign self =
liftM (toEnum . fromIntegral) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_halign argPtr1)
{-# LINE 3639 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetSetHAlign :: WidgetClass self => self -> Align -> IO ()
widgetSetHAlign self align =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_halign argPtr1 arg2)
{-# LINE 3646 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromIntegral $ fromEnum align)
widgetGetVAlign :: WidgetClass self => self -> IO Align
widgetGetVAlign self =
liftM (toEnum . fromIntegral) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_valign argPtr1)
{-# LINE 3659 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetGetVAlignWithBaseline :: WidgetClass self => self -> IO Align
widgetGetVAlignWithBaseline self =
liftM (toEnum . fromIntegral) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_get_valign_with_baseline argPtr1)
{-# LINE 3667 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
widgetSetVAlign :: WidgetClass self => self -> Align -> IO ()
widgetSetVAlign self align =
(\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_widget_set_valign argPtr1 arg2)
{-# LINE 3674 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
(toWidget self)
(fromIntegral $ fromEnum align)
mapSignal :: WidgetClass self => Signal self (IO ())
mapSignal = Signal (connect_NONE__NONE "map")
unmapSignal :: WidgetClass self => Signal self (IO ())
unmapSignal = Signal (connect_NONE__NONE "unmap")
realize :: WidgetClass self => Signal self (IO ())
realize = Signal (connect_NONE__NONE "realize")
unrealize :: WidgetClass self => Signal self (IO ())
unrealize = Signal (connect_NONE__NONE "unrealize")
sizeRequest :: WidgetClass self => Signal self (IO Requisition)
sizeRequest = Signal (\after w fun ->
connect_PTR__NONE "size-request" after w
(\rqPtr -> fun >>= \req -> unless (rqPtr==nullPtr) $ poke rqPtr req))
sizeAllocate :: WidgetClass self => Signal self (Allocation -> IO ())
sizeAllocate = Signal (connect_BOXED__NONE "size-allocate" peek)
showSignal :: WidgetClass self => Signal self (IO ())
showSignal = Signal (connect_NONE__NONE "show")
hideSignal :: WidgetClass self => Signal self (IO ())
hideSignal = Signal (connect_NONE__NONE "hide")
focus :: WidgetClass self => Signal self (DirectionType -> IO Bool)
focus = Signal (connect_ENUM__BOOL "focus")
stateChanged :: WidgetClass self => Signal self (StateType -> IO ())
stateChanged = Signal (connect_ENUM__NONE "state-changed")
connect_FLAGS__NONE ::
(Flags a, GObjectClass obj) => SignalName ->
ConnectAfter -> obj ->
([a] -> IO ()) ->
IO (ConnectId obj)
connect_FLAGS__NONE signal after obj user =
connectGeneric signal after obj action
where action :: Ptr GObject -> Int -> IO ()
action _ flags1 =
failOnGError $
user (toFlags flags1)
stateFlagsChanged :: WidgetClass self => Signal self ([StateFlags] -> IO ())
stateFlagsChanged = Signal (connect_FLAGS__NONE "state-flags-changed")
parentSet :: WidgetClass self => Signal self (Maybe Widget -> IO ())
parentSet = Signal (connect_MOBJECT__NONE "parent-set")
hierarchyChanged :: WidgetClass self => Signal self (Maybe Widget -> IO ())
hierarchyChanged = Signal (connect_MOBJECT__NONE "hierarchy-changed")
styleSet :: WidgetClass self => Signal self (Style -> IO ())
styleSet = Signal (connect_OBJECT__NONE "style-set")
directionChanged :: WidgetClass self => Signal self (TextDirection -> IO ())
directionChanged = Signal (connect_ENUM__NONE "direction-changed")
grabNotify :: WidgetClass self => Signal self (Bool -> IO ())
grabNotify = Signal (connect_BOOL__NONE "grab-notify")
popupMenuSignal :: WidgetClass self => Signal self (IO Bool)
popupMenuSignal = Signal (connect_NONE__BOOL "popup-menu")
data WidgetHelpType = WidgetHelpTooltip
| WidgetHelpWhatsThis
deriving (Enum,Eq,Show)
{-# LINE 3829 "./Graphics/UI/Gtk/Abstract/Widget.chs" #-}
showHelp :: WidgetClass self => Signal self (WidgetHelpType -> IO Bool)
showHelp = Signal (connect_ENUM__BOOL "show-help")
accelClosuresChanged :: WidgetClass self => Signal self (IO ())
accelClosuresChanged = Signal (connect_NONE__NONE "accel-closures-changed")
screenChanged :: WidgetClass self => Signal self (Screen -> IO ())
screenChanged = Signal (connect_OBJECT__NONE "screen-changed")
queryTooltip :: WidgetClass self => Signal self (Widget -> Maybe Point -> Tooltip -> IO Bool)
queryTooltip =
Signal (\after model user ->
connect_OBJECT_INT_INT_BOOL_OBJECT__BOOL "query-tooltip"
after model (\widget x y keyb tooltip ->
user widget (if keyb then Nothing else Just (x, y)) tooltip))
draw :: WidgetClass self => Signal self (Render ())
draw =
Signal (\after model (Render user) ->
connect_PTR__NONE "draw" after model (\ptr -> runReaderT user (Cairo ptr)))
eventM :: WidgetClass w => SignalName -> [EventMask] ->
ConnectAfter -> w -> (EventM t Bool) -> IO (ConnectId w)
eventM name eMask after obj fun = do
id <- connect_PTR__BOOL name after obj (runReaderT fun)
widgetAddEvents obj eMask
return id
buttonPressEvent :: WidgetClass self => Signal self (EventM EButton Bool)
buttonPressEvent = Signal (eventM "button_press_event" [ButtonPressMask])
buttonReleaseEvent :: WidgetClass self => Signal self (EventM EButton Bool)
buttonReleaseEvent = Signal (eventM "button_release_event" [ButtonReleaseMask])
scrollEvent :: WidgetClass self => Signal self (EventM EScroll Bool)
scrollEvent = Signal (eventM "scroll_event" [ScrollMask])
motionNotifyEvent :: WidgetClass self => Signal self (EventM EMotion Bool)
motionNotifyEvent = Signal (eventM "motion_notify_event" [])
deleteEvent :: WidgetClass self => Signal self (EventM EAny Bool)
deleteEvent = Signal (eventM "delete_event" [])
destroyEvent :: WidgetClass self => Signal self (EventM EAny Bool)
destroyEvent = Signal (eventM "destroy_event" [])
exposeEvent :: WidgetClass self => Signal self (EventM EExpose Bool)
exposeEvent = Signal (eventM "expose_event" [])
keyPressEvent :: WidgetClass self => Signal self (EventM EKey Bool)
keyPressEvent = Signal (eventM "key_press_event" [KeyPressMask])
keyReleaseEvent :: WidgetClass self => Signal self (EventM EKey Bool)
keyReleaseEvent = Signal (eventM "key_release_event" [KeyReleaseMask])
enterNotifyEvent :: WidgetClass self => Signal self (EventM ECrossing Bool)
enterNotifyEvent = Signal (eventM "enter_notify_event" [EnterNotifyMask])
leaveNotifyEvent :: WidgetClass self => Signal self (EventM ECrossing Bool)
leaveNotifyEvent = Signal (eventM "leave_notify_event" [LeaveNotifyMask])
configureEvent :: WidgetClass self => Signal self (EventM EConfigure Bool)
configureEvent = Signal (eventM "configure_event" [])
focusInEvent :: WidgetClass self => Signal self (EventM EFocus Bool)
focusInEvent = Signal (eventM "focus_in_event" [FocusChangeMask])
focusOutEvent :: WidgetClass self => Signal self (EventM EFocus Bool)
focusOutEvent = Signal (eventM "focus_out_event" [FocusChangeMask])
mapEvent :: WidgetClass self => Signal self (EventM EAny Bool)
mapEvent = Signal (eventM "map_event" [])
unmapEvent :: WidgetClass self => Signal self (EventM EAny Bool)
unmapEvent = Signal (eventM "unmap_event" [])
_propertyNotifyEvent :: WidgetClass self => Signal self (EventM EProperty Bool)
_propertyNotifyEvent = Signal (eventM "property_notify_event" [PropertyChangeMask])
proximityInEvent :: WidgetClass self => Signal self (EventM EProximity Bool)
proximityInEvent = Signal (eventM "proximity_in_event" [ProximityInMask])
proximityOutEvent :: WidgetClass self => Signal self (EventM EProximity Bool)
proximityOutEvent = Signal (eventM "proximity_out_event" [ProximityOutMask])
visibilityNotifyEvent :: WidgetClass self => Signal self (EventM EVisibility Bool)
visibilityNotifyEvent = Signal (eventM "visibility_notify_event" [VisibilityNotifyMask])
noExposeEvent :: WidgetClass self => Signal self (EventM EAny Bool)
noExposeEvent = Signal (eventM "no_expose_event" [])
windowStateEvent :: WidgetClass self => Signal self (EventM EWindowState Bool)
windowStateEvent = Signal (eventM "window_state_event" [])
grabBrokenEvent :: WidgetClass self => Signal self (EventM EGrabBroken Bool)
grabBrokenEvent = Signal (eventM "grab_broken_event" [])
foreign import ccall safe "gtk_widget_show"
gtk_widget_show :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_show_now"
gtk_widget_show_now :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_hide"
gtk_widget_hide :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_show_all"
gtk_widget_show_all :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_destroy"
gtk_widget_destroy :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_draw"
gtk_widget_draw :: ((Ptr Widget) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_widget_queue_draw"
gtk_widget_queue_draw :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_queue_resize"
gtk_widget_queue_resize :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_queue_resize_no_redraw"
gtk_widget_queue_resize_no_redraw :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_get_frame_clock"
gtk_widget_get_frame_clock :: ((Ptr Widget) -> (IO (Ptr FrameClock)))
foreign import ccall safe "gtk_widget_get_scale_factor"
gtk_widget_get_scale_factor :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_size_request"
gtk_widget_size_request :: ((Ptr Widget) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_widget_get_child_requisition"
gtk_widget_get_child_requisition :: ((Ptr Widget) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_widget_size_allocate"
gtk_widget_size_allocate :: ((Ptr Widget) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_widget_size_allocate_with_baseline"
gtk_widget_size_allocate_with_baseline :: ((Ptr Widget) -> ((Ptr ()) -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_widget_add_accelerator"
gtk_widget_add_accelerator :: ((Ptr Widget) -> ((Ptr CChar) -> ((Ptr AccelGroup) -> (CUInt -> (CInt -> (CInt -> (IO ())))))))
foreign import ccall safe "gtk_widget_remove_accelerator"
gtk_widget_remove_accelerator :: ((Ptr Widget) -> ((Ptr AccelGroup) -> (CUInt -> (CInt -> (IO CInt)))))
foreign import ccall safe "gtk_widget_set_accel_path"
gtk_widget_set_accel_path :: ((Ptr Widget) -> ((Ptr CChar) -> ((Ptr AccelGroup) -> (IO ()))))
foreign import ccall safe "gtk_widget_can_activate_accel"
gtk_widget_can_activate_accel :: ((Ptr Widget) -> (CUInt -> (IO CInt)))
foreign import ccall safe "gtk_widget_activate"
gtk_widget_activate :: ((Ptr Widget) -> (IO CInt))
foreign import ccall unsafe "gtk_widget_intersect"
gtk_widget_intersect :: ((Ptr Widget) -> ((Ptr ()) -> ((Ptr ()) -> (IO CInt))))
foreign import ccall unsafe "gtk_widget_is_focus"
gtk_widget_is_focus :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_grab_focus"
gtk_widget_grab_focus :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_grab_default"
gtk_widget_grab_default :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_set_name"
gtk_widget_set_name :: ((Ptr Widget) -> ((Ptr CChar) -> (IO ())))
foreign import ccall unsafe "gtk_widget_get_name"
gtk_widget_get_name :: ((Ptr Widget) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_widget_set_sensitive"
gtk_widget_set_sensitive :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_parent_window"
gtk_widget_get_parent_window :: ((Ptr Widget) -> (IO (Ptr DrawWindow)))
foreign import ccall unsafe "gtk_widget_get_events"
gtk_widget_get_events :: ((Ptr Widget) -> (IO CInt))
foreign import ccall unsafe "gtk_widget_set_events"
gtk_widget_set_events :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_widget_add_events"
gtk_widget_add_events :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_widget_get_toplevel"
gtk_widget_get_toplevel :: ((Ptr Widget) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_widget_get_ancestor"
gtk_widget_get_ancestor :: ((Ptr Widget) -> (CULong -> (IO (Ptr Widget))))
foreign import ccall safe "gtk_widget_get_pointer"
gtk_widget_get_pointer :: ((Ptr Widget) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall unsafe "gtk_widget_is_ancestor"
gtk_widget_is_ancestor :: ((Ptr Widget) -> ((Ptr Widget) -> (IO CInt)))
foreign import ccall safe "gtk_widget_translate_coordinates"
gtk_widget_translate_coordinates :: ((Ptr Widget) -> ((Ptr Widget) -> (CInt -> (CInt -> ((Ptr CInt) -> ((Ptr CInt) -> (IO CInt)))))))
foreign import ccall safe "gtk_widget_set_style"
gtk_widget_set_style :: ((Ptr Widget) -> ((Ptr Style) -> (IO ())))
foreign import ccall safe "gtk_widget_ensure_style"
gtk_widget_ensure_style :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_get_style"
gtk_widget_get_style :: ((Ptr Widget) -> (IO (Ptr Style)))
foreign import ccall safe "gtk_widget_get_default_style"
gtk_widget_get_default_style :: (IO (Ptr Style))
foreign import ccall safe "gtk_widget_set_direction"
gtk_widget_set_direction :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_direction"
gtk_widget_get_direction :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_default_direction"
gtk_widget_set_default_direction :: (CInt -> (IO ()))
foreign import ccall safe "gtk_widget_get_default_direction"
gtk_widget_get_default_direction :: (IO CInt)
foreign import ccall safe "gtk_widget_shape_combine_region"
gtk_widget_shape_combine_region :: ((Ptr Widget) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_widget_input_shape_combine_region"
gtk_widget_input_shape_combine_region :: ((Ptr Widget) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_widget_path"
gtk_widget_path :: ((Ptr Widget) -> ((Ptr CUInt) -> ((Ptr (Ptr CChar)) -> ((Ptr (Ptr CChar)) -> (IO ())))))
foreign import ccall safe "gtk_widget_class_path"
gtk_widget_class_path :: ((Ptr Widget) -> ((Ptr CUInt) -> ((Ptr (Ptr CChar)) -> ((Ptr (Ptr CChar)) -> (IO ())))))
foreign import ccall safe "gtk_widget_get_composite_name"
gtk_widget_get_composite_name :: ((Ptr Widget) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_widget_override_background_color"
gtk_widget_override_background_color :: ((Ptr Widget) -> (CInt -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_widget_override_color"
gtk_widget_override_color :: ((Ptr Widget) -> (CInt -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_widget_override_font"
gtk_widget_override_font :: ((Ptr Widget) -> ((Ptr FontDescription) -> (IO ())))
foreign import ccall safe "gtk_widget_override_symbolic_color"
gtk_widget_override_symbolic_color :: ((Ptr Widget) -> ((Ptr CChar) -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_widget_override_cursor"
gtk_widget_override_cursor :: ((Ptr Widget) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_widget_modify_style"
gtk_widget_modify_style :: ((Ptr Widget) -> ((Ptr RcStyle) -> (IO ())))
foreign import ccall safe "gtk_widget_get_modifier_style"
gtk_widget_get_modifier_style :: ((Ptr Widget) -> (IO (Ptr RcStyle)))
foreign import ccall safe "gtk_widget_modify_fg"
gtk_widget_modify_fg :: ((Ptr Widget) -> (CInt -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_widget_modify_bg"
gtk_widget_modify_bg :: ((Ptr Widget) -> (CInt -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_widget_modify_text"
gtk_widget_modify_text :: ((Ptr Widget) -> (CInt -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_widget_modify_base"
gtk_widget_modify_base :: ((Ptr Widget) -> (CInt -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_widget_modify_font"
gtk_widget_modify_font :: ((Ptr Widget) -> ((Ptr FontDescription) -> (IO ())))
foreign import ccall safe "gtk_widget_create_pango_context"
gtk_widget_create_pango_context :: ((Ptr Widget) -> (IO (Ptr PangoContext)))
foreign import ccall safe "gtk_widget_get_pango_context"
gtk_widget_get_pango_context :: ((Ptr Widget) -> (IO (Ptr PangoContext)))
foreign import ccall unsafe "gtk_widget_create_pango_layout"
gtk_widget_create_pango_layout :: ((Ptr Widget) -> ((Ptr CChar) -> (IO (Ptr PangoLayoutRaw))))
foreign import ccall safe "gtk_widget_render_icon"
gtk_widget_render_icon :: ((Ptr Widget) -> ((Ptr CChar) -> (CInt -> ((Ptr CChar) -> (IO (Ptr Pixbuf))))))
foreign import ccall safe "gtk_widget_queue_draw_area"
gtk_widget_queue_draw_area :: ((Ptr Widget) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))
foreign import ccall safe "gtk_widget_queue_draw_region"
gtk_widget_queue_draw_region :: ((Ptr Widget) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_widget_set_app_paintable"
gtk_widget_set_app_paintable :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_set_double_buffered"
gtk_widget_set_double_buffered :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_set_redraw_on_allocate"
gtk_widget_set_redraw_on_allocate :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_set_composite_name"
gtk_widget_set_composite_name :: ((Ptr Widget) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_widget_mnemonic_activate"
gtk_widget_mnemonic_activate :: ((Ptr Widget) -> (CInt -> (IO CInt)))
foreign import ccall safe "gtk_widget_get_accessible"
gtk_widget_get_accessible :: ((Ptr Widget) -> (IO (Ptr AtkObject)))
foreign import ccall safe "gtk_widget_child_focus"
gtk_widget_child_focus :: ((Ptr Widget) -> (CInt -> (IO CInt)))
foreign import ccall safe "gtk_widget_get_child_visible"
gtk_widget_get_child_visible :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_parent"
gtk_widget_get_parent :: ((Ptr Widget) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_widget_get_settings"
gtk_widget_get_settings :: ((Ptr Widget) -> (IO (Ptr Settings)))
foreign import ccall safe "gtk_widget_get_clipboard"
gtk_widget_get_clipboard :: ((Ptr Widget) -> ((Ptr ()) -> (IO (Ptr Clipboard))))
foreign import ccall safe "gtk_widget_get_display"
gtk_widget_get_display :: ((Ptr Widget) -> (IO (Ptr Display)))
foreign import ccall safe "gtk_widget_get_root_window"
gtk_widget_get_root_window :: ((Ptr Widget) -> (IO (Ptr DrawWindow)))
foreign import ccall safe "gtk_widget_get_screen"
gtk_widget_get_screen :: ((Ptr Widget) -> (IO (Ptr Screen)))
foreign import ccall safe "gtk_widget_has_screen"
gtk_widget_has_screen :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_size_request"
gtk_widget_get_size_request :: ((Ptr Widget) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "gtk_widget_set_child_visible"
gtk_widget_set_child_visible :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_set_size_request"
gtk_widget_set_size_request :: ((Ptr Widget) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_widget_set_no_show_all"
gtk_widget_set_no_show_all :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_no_show_all"
gtk_widget_get_no_show_all :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_list_mnemonic_labels"
gtk_widget_list_mnemonic_labels :: ((Ptr Widget) -> (IO (Ptr ())))
foreign import ccall safe "gtk_widget_add_mnemonic_label"
gtk_widget_add_mnemonic_label :: ((Ptr Widget) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_widget_remove_mnemonic_label"
gtk_widget_remove_mnemonic_label :: ((Ptr Widget) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_widget_is_composited"
gtk_widget_is_composited :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_error_bell"
gtk_widget_error_bell :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_keynav_failed"
gtk_widget_keynav_failed :: ((Ptr Widget) -> (CInt -> (IO CInt)))
foreign import ccall safe "gtk_widget_get_tooltip_markup"
gtk_widget_get_tooltip_markup :: ((Ptr Widget) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_widget_set_tooltip_markup"
gtk_widget_set_tooltip_markup :: ((Ptr Widget) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_widget_get_tooltip_text"
gtk_widget_get_tooltip_text :: ((Ptr Widget) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_widget_set_tooltip_text"
gtk_widget_set_tooltip_text :: ((Ptr Widget) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_widget_get_tooltip_window"
gtk_widget_get_tooltip_window :: ((Ptr Widget) -> (IO (Ptr Window)))
foreign import ccall safe "gtk_widget_set_tooltip_window"
gtk_widget_set_tooltip_window :: ((Ptr Widget) -> ((Ptr Window) -> (IO ())))
foreign import ccall safe "gtk_widget_get_has_tooltip"
gtk_widget_get_has_tooltip :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_has_tooltip"
gtk_widget_set_has_tooltip :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_trigger_tooltip_query"
gtk_widget_trigger_tooltip_query :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_widget_get_window"
gtk_widget_get_window :: ((Ptr Widget) -> (IO (Ptr DrawWindow)))
foreign import ccall safe "gtk_widget_register_window"
gtk_widget_register_window :: ((Ptr Widget) -> ((Ptr DrawWindow) -> (IO ())))
foreign import ccall safe "gtk_widget_unregister_window"
gtk_widget_unregister_window :: ((Ptr Widget) -> ((Ptr DrawWindow) -> (IO ())))
foreign import ccall safe "gtk_cairo_should_draw_window"
gtk_cairo_should_draw_window :: ((Ptr ()) -> ((Ptr DrawWindow) -> (IO CInt)))
foreign import ccall safe "gtk_cairo_transform_to_window"
gtk_cairo_transform_to_window :: ((Ptr ()) -> ((Ptr Widget) -> ((Ptr DrawWindow) -> (IO ()))))
foreign import ccall safe "gtk_widget_reparent"
gtk_widget_reparent :: ((Ptr Widget) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_widget_get_allocation"
gtk_widget_get_allocation :: ((Ptr Widget) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_widget_get_allocated_width"
gtk_widget_get_allocated_width :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_allocated_height"
gtk_widget_get_allocated_height :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_allocated_baseline"
gtk_widget_get_allocated_baseline :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_app_paintable"
gtk_widget_get_app_paintable :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_can_default"
gtk_widget_get_can_default :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_can_default"
gtk_widget_set_can_default :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_has_window"
gtk_widget_get_has_window :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_has_window"
gtk_widget_set_has_window :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_sensitive"
gtk_widget_get_sensitive :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_is_sensitive"
gtk_widget_is_sensitive :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_state"
gtk_widget_get_state :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_visible"
gtk_widget_get_visible :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_is_visible"
gtk_widget_is_visible :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_state_flags"
gtk_widget_set_state_flags :: ((Ptr Widget) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_widget_unset_state_flags"
gtk_widget_unset_state_flags :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_state_flags"
gtk_widget_get_state_flags :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_has_default"
gtk_widget_has_default :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_has_focus"
gtk_widget_has_focus :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_has_visible_focus"
gtk_widget_has_visible_focus :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_has_grab"
gtk_widget_has_grab :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_is_drawable"
gtk_widget_is_drawable :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_is_toplevel"
gtk_widget_is_toplevel :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_window"
gtk_widget_set_window :: ((Ptr Widget) -> ((Ptr DrawWindow) -> (IO ())))
foreign import ccall safe "gtk_widget_set_receives_default"
gtk_widget_set_receives_default :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_receives_default"
gtk_widget_get_receives_default :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_device_is_shadowed"
gtk_widget_device_is_shadowed :: ((Ptr Widget) -> ((Ptr Device) -> (IO CInt)))
foreign import ccall safe "gtk_widget_get_modifier_mask"
gtk_widget_get_modifier_mask :: ((Ptr Widget) -> (CInt -> (IO CInt)))
foreign import ccall safe "gtk_widget_set_support_multidevice"
gtk_widget_set_support_multidevice :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_support_multidevice"
gtk_widget_get_support_multidevice :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_state"
gtk_widget_set_state :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_event"
gtk_widget_event :: ((Ptr Widget) -> ((Ptr ()) -> (IO CInt)))
foreign import ccall unsafe "gdk_event_mask_get_type"
gdk_event_mask_get_type :: CULong
foreign import ccall safe "gtk_widget_has_rc_style"
gtk_widget_has_rc_style :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_realized"
gtk_widget_get_realized :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_mapped"
gtk_widget_get_mapped :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_realized"
gtk_widget_set_realized :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_set_mapped"
gtk_widget_set_mapped :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_style_context"
gtk_widget_get_style_context :: ((Ptr Widget) -> (IO (Ptr StyleContext)))
foreign import ccall safe "gtk_widget_get_halign"
gtk_widget_get_halign :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_halign"
gtk_widget_set_halign :: ((Ptr Widget) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_widget_get_valign"
gtk_widget_get_valign :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_get_valign_with_baseline"
gtk_widget_get_valign_with_baseline :: ((Ptr Widget) -> (IO CInt))
foreign import ccall safe "gtk_widget_set_valign"
gtk_widget_set_valign :: ((Ptr Widget) -> (CInt -> (IO ())))