fltkhs-0.8.0.3: FLTK bindings
Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Base.Widget

Synopsis

Constructor

widgetCustom Source #

Arguments

:: Rectangle

The bounds of this widget

-> Maybe Text

The widget label

-> (Ref Widget -> IO ())

Custom drawing function

-> CustomWidgetFuncs Widget

Other custom functions

-> IO (Ref Widget) 

widgetMaker Source #

Arguments

:: forall a. Parent a WidgetBase 
=> Rectangle

Position and size

-> Maybe Text

Title

-> Maybe (Ref a -> IO ())

Custom drawing function

-> Maybe (CustomWidgetFuncs a)

Custom functions

-> (Int -> Int -> Int -> Int -> Ptr () -> IO (Ptr ()))

Foreign constructor to call if only custom functions are given

-> (Int -> Int -> Int -> Int -> CString -> Ptr () -> IO (Ptr ()))

Foreign constructor to call if both title and custom functions are given

-> IO (Ref a)

Reference to the widget

Lots of Widget subclasses have the same constructor parameters. This function consolidates them.

Only of interest to Widget contributors.

Custom

data CustomWidgetFuncs a Source #

Overrideable Widget functions | Do not create this directly. Instead use defaultWidgetCustomFuncs

Constructors

CustomWidgetFuncs 

Fields

defaultCustomWidgetFuncs :: forall a. Parent a WidgetBase => CustomWidgetFuncs a Source #

An empty set of functions to pass to widgetCustom.

fillCustomWidgetFunctionStruct :: forall a. Parent a WidgetBase => Ptr () -> Maybe (Ref a -> IO ()) -> CustomWidgetFuncs a -> IO () Source #

Fill up a struct with pointers to functions on the Haskell side that will get called instead of the default ones.

Fill up the Widget part the function pointer struct.

Only of interest to Widget contributors

customWidgetFunctionStruct :: forall a. Parent a WidgetBase => Maybe (Ref a -> IO ()) -> CustomWidgetFuncs a -> IO (Ptr ()) Source #

Given a record of functions, return a pointer to a struct with function pointers back to those functions.

Only of interest to Widget contributors.

Hierarchy

Widget Functions

activate :: Ref WidgetBase -> IO ()

active :: Ref WidgetBase -> IO (Bool)

activeR :: Ref WidgetBase -> IO (Bool)

changed :: Ref WidgetBase -> IO (Bool)

clearActive :: Ref WidgetBase -> IO ()

clearChanged :: Ref WidgetBase -> IO ()

clearDamage :: Ref WidgetBase -> IO ()

clearDamageThenSet :: Ref WidgetBase -> [Damage] -> IO ()

clearFlag :: Ref WidgetBase -> WidgetFlag -> IO ()

clearOutput :: Ref WidgetBase -> IO ()

clearVisible :: Ref WidgetBase -> IO ()

clearVisibleFocus :: Ref WidgetBase -> IO ()

contains:: (Parent a WidgetBase) => Ref WidgetBase -> Ref a -> IO Bool

copyTooltip :: Ref WidgetBase -> Text -> IO ()

deactivate :: Ref WidgetBase -> IO ()

destroy :: Ref WidgetBase -> IO ()

doCallback :: Ref WidgetBase -> IO ()

draw :: Ref WidgetBase -> IO ()

drawBackdrop :: Ref WidgetBase -> IO ()

drawBox :: Ref WidgetBase -> IO ()

drawBoxWithBoxtype :: Ref WidgetBase -> Boxtype -> Color -> Maybe Rectangle -> IO ()

drawFocus :: Ref WidgetBase -> Maybe (Boxtype, Rectangle) -> IO ()

drawLabel :: Ref WidgetBase -> Maybe (Rectangle, Alignments) -> IO ()

flags :: Ref WidgetBase -> IO [WidgetFlag]

getAlign :: Ref WidgetBase -> IO Alignments

getBox :: Ref WidgetBase -> IO (Boxtype)

getCallback :: Ref WidgetBase -> IO (FunPtr CallbackWithUserDataPrim)

getColor :: Ref WidgetBase -> IO (Color)

getDamage :: Ref WidgetBase -> IO ([Damage])

getDeimage :: Ref WidgetBase -> IO (Maybe (Ref Image))

getH :: Ref WidgetBase -> IO (Height)

getImage :: Ref WidgetBase -> IO (Maybe (Ref Image))

getLabel :: Ref WidgetBase -> IO Text

getLabelcolor :: Ref WidgetBase -> IO (Color)

getLabelfont :: Ref WidgetBase -> IO (Font)

getLabelsize :: Ref WidgetBase -> IO (FontSize)

getLabeltype :: Ref WidgetBase -> IO (Labeltype)

getOutput :: Ref WidgetBase -> IO (Int)

getParent :: Ref WidgetBase -> IO (Maybe (Ref GroupBase))

getRectangle:: (Match obj ~ FindOp orig orig (GetX ()), Match obj ~ FindOp orig orig (GetY ()), Match obj ~ FindOp orig orig (GetW ()), Match obj ~ FindOp orig orig (GetH ()), Op (GetX ()) obj orig (IO X,) Op (GetY ()) obj orig (IO Y,) Op (GetW ()) obj orig (IO Width,) Op (GetH ()) obj orig (IO Height,)) => Ref WidgetBase -> IO Rectangle

getSelectionColor :: Ref WidgetBase -> IO (Color)

getTooltip :: Ref WidgetBase -> IO Text

getTopWindow :: Ref WidgetBase -> IO (Maybe (Ref WindowBase))

getTopWindowOffset :: Ref WidgetBase -> IO (Position)

getType_ :: Ref WidgetBase -> IO (Word8)

getVisible :: Ref WidgetBase -> IO Bool

getVisibleFocus :: Ref WidgetBase -> IO (Bool)

getVisibleR :: Ref WidgetBase -> IO Bool

getW :: Ref WidgetBase -> IO (Width)

getWhen :: Ref WidgetBase -> IO [When]

getWindow :: Ref WidgetBase -> IO (Maybe (Ref WindowBase))

getX :: Ref WidgetBase -> IO (X)

getY :: Ref WidgetBase -> IO (Y)

handle :: Ref WidgetBase -> Event -> IO (Either UnknownEvent ())

hasCallback :: Ref WidgetBase -> IO (Bool)

hide :: Ref WidgetBase -> IO ()

inside:: (Parent a WidgetBase) => Ref WidgetBase -> Ref a -> IO (Bool)

measureLabel :: Ref WidgetBase -> Maybe Width -> IO (Size)

modifyVisibleFocus :: Ref WidgetBase -> Bool -> IO ()

redraw :: Ref WidgetBase -> IO ()

redrawLabel :: Ref WidgetBase -> IO ()

resize :: Ref WidgetBase -> Rectangle -> IO ()

setActive :: Ref WidgetBase -> IO ()

setAlign :: Ref WidgetBase -> Alignments -> IO ()

setBox :: Ref WidgetBase -> Boxtype -> IO ()

setCallback :: Ref WidgetBase -> (Ref orig -> IO ()) -> IO ()

setChanged :: Ref WidgetBase -> IO ()

setColor :: Ref WidgetBase -> Color -> IO ()

setColorWithBgSel :: Ref WidgetBase -> Color -> Color -> IO ()

setDamage :: Ref WidgetBase -> [Damage] -> IO ()

setDamageInside :: Ref WidgetBase -> [Damage] -> Rectangle -> IO ()

setDeimage:: (Parent a Image) => Ref WidgetBase -> Maybe( Ref a ) -> IO ()

setFlag :: Ref WidgetBase -> WidgetFlag -> IO ()

setImage:: (Parent a Image) => Ref WidgetBase -> Maybe( Ref a ) -> IO ()

setLabel :: Ref WidgetBase -> Text -> IO ()

setLabelcolor :: Ref WidgetBase -> Color -> IO ()

setLabelfont :: Ref WidgetBase -> Font -> IO ()

setLabelsize :: Ref WidgetBase -> FontSize -> IO ()

setLabeltype :: Ref WidgetBase -> Labeltype -> ResolveImageLabelConflict -> IO ()

setOutput :: Ref WidgetBase -> IO ()

setParent:: (Parent a GroupBase) => Ref WidgetBase -> Maybe (Ref a) -> IO ()

setSelectionColor :: Ref WidgetBase -> Color -> IO ()

setTooltip :: Ref WidgetBase -> Text -> IO ()

setType :: Ref WidgetBase -> Word8 -> IO ()

setVisible :: Ref WidgetBase -> IO ()

setVisibleFocus :: Ref WidgetBase -> IO ()

setWhen :: Ref WidgetBase -> [When] -> IO ()

showWidget :: Ref WidgetBase -> IO ()

takeFocus :: Ref WidgetBase -> IO (Either NoChange ())

takesevents :: Ref WidgetBase -> IO (Bool)

Orphan instances

impl ~ IO () => Op (DoCallback ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: DoCallback () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (Draw ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Draw () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (Changed ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Changed () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (WidgetFlag -> IO ()) => Op (ClearFlag ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ClearFlag () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (WidgetFlag -> IO ()) => Op (SetFlag ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetFlag () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO [WidgetFlag] => Op (Flags ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Flags () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: DrawFocus () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (DrawBackdrop ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: DrawBackdrop () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: DrawBoxWithBoxtype () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (DrawBox ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: DrawBox () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (HasCallback ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: HasCallback () -> orig -> Ref WidgetBase -> impl Source #

impl ~ ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetCallback () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO (FunPtr CallbackWithUserDataPrim) => Op (GetCallback ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetCallback () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Resize () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Position => Op (GetTopWindowOffset ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetTopWindowOffset () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO (Maybe (Ref WindowBase)) => Op (GetTopWindow ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetTopWindow () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO (Maybe (Ref WindowBase)) => Op (GetWindow ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetWindow () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Maybe Width -> IO Size) => Op (MeasureLabel ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: MeasureLabel () -> orig -> Ref WidgetBase -> impl Source #

impl ~ ([Damage] -> Rectangle -> IO ()) => Op (SetDamageInside ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetDamageInside () -> orig -> Ref WidgetBase -> impl Source #

impl ~ ([Damage] -> IO ()) => Op (SetDamage ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetDamage () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (ClearDamage ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ClearDamage () -> orig -> Ref WidgetBase -> impl Source #

impl ~ ([Damage] -> IO ()) => Op (ClearDamageThenSet ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ClearDamageThenSet () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO [Damage] => Op (GetDamage ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetDamage () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (RedrawLabel ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: RedrawLabel () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (Redraw ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Redraw () -> orig -> Ref WidgetBase -> impl Source #

(Parent a WidgetBase, impl ~ (Ref a -> IO Bool)) => Op (Inside ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Inside () -> orig -> Ref WidgetBase -> impl Source #

(Parent a WidgetBase, impl ~ (Ref a -> IO Bool)) => Op (Contains ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Contains () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (GetVisibleFocus ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetVisibleFocus () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Bool -> IO ()) => Op (ModifyVisibleFocus ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ModifyVisibleFocus () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (ClearVisibleFocus ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ClearVisibleFocus () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (SetVisibleFocus ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetVisibleFocus () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO (Either NoChange ()) => Op (TakeFocus ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: TakeFocus () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (ClearActive ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ClearActive () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (SetActive ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetActive () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (ClearChanged ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ClearChanged () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (SetChanged ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetChanged () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (Takesevents ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Takesevents () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (ClearOutput ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ClearOutput () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (SetOutput ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetOutput () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (GetOutput ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetOutput () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (Deactivate ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Deactivate () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (Activate ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Activate () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (ActiveR ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ActiveR () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (Active ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Active () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (ClearVisible ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ClearVisible () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (SetVisible ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetVisible () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (Hide ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Hide () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (ShowWidget ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: ShowWidget () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (GetVisibleR ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetVisibleR () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Bool => Op (GetVisible ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetVisible () -> orig -> Ref WidgetBase -> impl Source #

impl ~ ([When] -> IO ()) => Op (SetWhen ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetWhen () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO [When] => Op (GetWhen ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetWhen () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Text -> IO ()) => Op (SetTooltip ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetTooltip () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Text -> IO ()) => Op (CopyTooltip ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: CopyTooltip () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Text => Op (GetTooltip ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetTooltip () -> orig -> Ref WidgetBase -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetDeimage ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetDeimage () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetDeimage ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetDeimage () -> orig -> Ref WidgetBase -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetImage ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetImage () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetImage ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetImage () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetLabelsize ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetLabelsize () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO FontSize => Op (GetLabelsize ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetLabelsize () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Font -> IO ()) => Op (SetLabelfont ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetLabelfont () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Font => Op (GetLabelfont ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetLabelfont () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelcolor ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetLabelcolor () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Color => Op (GetLabelcolor ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetLabelcolor () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Labeltype -> ResolveImageLabelConflict -> IO ()) => Op (SetLabeltype ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetLabeltype () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Labeltype => Op (GetLabeltype ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetLabeltype () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Text -> IO ()) => Op (SetLabel ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetLabel () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Text => Op (GetLabel ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetLabel () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Color -> IO ()) => Op (SetSelectionColor ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetSelectionColor () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Color => Op (GetSelectionColor ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetSelectionColor () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Color -> Color -> IO ()) => Op (SetColorWithBgSel ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetColorWithBgSel () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Color -> IO ()) => Op (SetColor ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetColor () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Color => Op (GetColor ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetColor () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetBox ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetBox () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Boxtype => Op (GetBox ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetBox () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Alignments => Op (GetAlign ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetAlign () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Alignments -> IO ()) => Op (SetAlign ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetAlign () -> orig -> Ref WidgetBase -> impl Source #

(Match obj ~ FindOp orig orig (GetX ()), Match obj ~ FindOp orig orig (GetY ()), Match obj ~ FindOp orig orig (GetW ()), Match obj ~ FindOp orig orig (GetH ()), Op (GetX ()) obj orig (IO X), Op (GetY ()) obj orig (IO Y), Op (GetW ()) obj orig (IO Width), Op (GetH ()) obj orig (IO Height), impl ~ IO Rectangle) => Op (GetRectangle ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetRectangle () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Height => Op (GetH ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetH () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Width => Op (GetW ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetW () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Y => Op (GetY ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetY () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO X => Op (GetX ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetX () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Maybe (Rectangle, Alignments) -> IO ()) => Op (DrawLabel ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: DrawLabel () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Word8 -> IO ()) => Op (SetType ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetType () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO Word8 => Op (GetType_ ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetType_ () -> orig -> Ref WidgetBase -> impl Source #

(Parent a GroupBase, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetParent ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: SetParent () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO (Maybe (Ref GroupBase)) => Op (GetParent ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: GetParent () -> orig -> Ref WidgetBase -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Handle () -> orig -> Ref WidgetBase -> impl Source #

impl ~ IO () => Op (Destroy ()) WidgetBase orig impl Source # 
Instance details

Methods

runOp :: Destroy () -> orig -> Ref WidgetBase -> impl Source #