fltkhs-0.5.4.4: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Widget

Contents

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

:: Parent a Widget 
=> 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 -> Text -> 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

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

An empty set of functions to pass to widgetCustom.

fillCustomWidgetFunctionStruct :: forall a. Parent a Widget => 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

Hierarchy

Widget Functions

activate :: Ref Widget -> IO ()

active :: Ref Widget -> IO (Bool)

activeR :: Ref Widget -> IO (Bool)

changed :: Ref Widget -> IO (Bool)

clearActive :: Ref Widget -> IO ()

clearChanged :: Ref Widget -> IO ()

clearDamage :: Ref Widget -> IO ()

clearDamageExcept :: Ref Widget -> [Damage] -> IO ()

clearOutput :: Ref Widget -> IO ()

clearVisible :: Ref Widget -> IO ()

clearVisibleFocus :: Ref Widget -> IO ()

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

copyLabel :: Ref Widget -> Text -> IO ()

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

deactivate :: Ref Widget -> IO ()

destroy :: Ref Widget -> IO ()

doCallback :: Ref Widget -> IO ()

drawBackdrop :: Ref Widget -> IO ()

drawBox :: Ref Widget -> IO ()

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

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

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

getAlign :: Ref Widget -> IO Alignments

getBox :: Ref Widget -> IO (Boxtype)

getColor :: Ref Widget -> IO (Color)

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

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

getH :: Ref Widget -> IO (Int)

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

getLabel :: Ref Widget -> IO Text

getLabelcolor :: Ref Widget -> IO (Color)

getLabelfont :: Ref Widget -> IO (Font)

getLabelsize :: Ref Widget -> IO (FontSize)

getLabeltype :: Ref Widget -> IO (Labeltype)

getOutput :: Ref Widget -> IO (Int)

getParent :: Ref Widget -> IO (Maybe (Ref Group))

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 Int,) Op (GetY ()) obj orig (IO Int,) Op (GetW ()) obj orig (IO Int,) Op (GetH ()) obj orig (IO Int,)) => Ref Widget -> IO Rectangle

getSelectionColor :: Ref Widget -> IO (Color)

getTooltip :: Ref Widget -> IO Text

getTopWindow :: Ref Widget -> IO (Maybe (Ref Window))

getTopWindowOffset :: Ref Widget -> IO (Position)

getType_ :: Ref Widget -> IO (Word8)

getVisible :: Ref Widget -> IO Bool

getVisibleFocus :: Ref Widget -> IO (Bool)

getVisibleR :: Ref Widget -> IO Bool

getW :: Ref Widget -> IO (Int)

getWhen :: Ref Widget -> IO [When]

getWindow :: Ref Widget -> IO (Maybe (Ref Window))

getX :: Ref Widget -> IO (Int)

getY :: Ref Widget -> IO (Int)

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

hasCallback :: Ref Widget -> IO (Bool)

hide :: Ref Widget -> IO ()

hideSuper :: Ref Widget -> IO ()

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

measureLabel :: Ref Widget -> IO (Size)

modifyVisibleFocus :: Ref Widget -> Int -> IO ()

redraw :: Ref Widget -> IO ()

redrawLabel :: Ref Widget -> IO ()

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

resizeSuper :: Ref Widget -> Rectangle -> IO ()

setActive :: Ref Widget -> IO ()

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

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

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

setChanged :: Ref Widget -> IO ()

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

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

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

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

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

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

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

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

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

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

setLabeltype :: Ref Widget -> Labeltype -> IO ()

setOutput :: Ref Widget -> IO ()

setParent:: (Parent a Group) => Ref Widget -> Maybe (Ref a) -> IO ()

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

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

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

setVisible :: Ref Widget -> IO ()

setVisibleFocus :: Ref Widget -> IO ()

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

showWidget :: Ref Widget -> IO ()

showWidgetSuper :: Ref Widget -> IO ()

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

takesevents :: Ref Widget -> IO (Bool)

Orphan instances

(~) * impl (IO ()) => Op (DoCallback ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (Changed ()) Widget orig impl Source # 

Methods

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

(~) * impl (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (DrawBackdrop ()) Widget orig impl Source # 

Methods

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

(~) * impl (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (DrawBox ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (HasCallback ()) Widget orig impl Source # 

Methods

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

(~) * impl ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) Widget orig impl Source # 

Methods

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

(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Widget orig impl Source # 

Methods

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

(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) Widget orig impl Source # 

Methods

runOp :: ResizeSuper () -> orig -> Ref Widget -> impl Source #

(~) * impl (IO Position) => Op (GetTopWindowOffset ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO (Maybe (Ref Window))) => Op (GetTopWindow ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO (Maybe (Ref Window))) => Op (GetWindow ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Size) => Op (MeasureLabel ()) Widget orig impl Source # 

Methods

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

(~) * impl ([Damage] -> Rectangle -> IO ()) => Op (SetDamageInside ()) Widget orig impl Source # 

Methods

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

(~) * impl ([Damage] -> IO ()) => Op (SetDamage ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ClearDamage ()) Widget orig impl Source # 

Methods

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

(~) * impl ([Damage] -> IO ()) => Op (ClearDamageExcept ()) Widget orig impl Source # 

Methods

runOp :: ClearDamageExcept () -> orig -> Ref Widget -> impl Source #

(~) * impl (IO [Damage]) => Op (GetDamage ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (RedrawLabel ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Redraw ()) Widget orig impl Source # 

Methods

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

(Parent a Widget, (~) * impl (Ref a -> IO Bool)) => Op (Inside ()) Widget orig impl Source # 

Methods

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

(Parent a Widget, (~) * impl (Ref a -> IO Bool)) => Op (Contains ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (GetVisibleFocus ()) Widget orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (ModifyVisibleFocus ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ClearVisibleFocus ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (SetVisibleFocus ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO (Either NoChange ())) => Op (TakeFocus ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ClearActive ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (SetActive ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ClearChanged ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (SetChanged ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (Takesevents ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ClearOutput ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (SetOutput ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetOutput ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Deactivate ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Activate ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (ActiveR ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (Active ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ClearVisible ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (SetVisible ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Hide ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (HideSuper ()) Widget orig impl Source # 

Methods

runOp :: HideSuper () -> orig -> Ref Widget -> impl Source #

(~) * impl (IO ()) => Op (ShowWidget ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ShowWidgetSuper ()) Widget orig impl Source # 

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Widget -> impl Source #

(~) * impl (IO Bool) => Op (GetVisibleR ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (GetVisible ()) Widget orig impl Source # 

Methods

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

(~) * impl ([When] -> IO ()) => Op (SetWhen ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO [When]) => Op (GetWhen ()) Widget orig impl Source # 

Methods

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

(~) * impl (Text -> IO ()) => Op (SetTooltip ()) Widget orig impl Source # 

Methods

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

(~) * impl (Text -> IO ()) => Op (CopyTooltip ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Text) => Op (GetTooltip ()) Widget orig impl Source # 

Methods

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

(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetDeimage ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO (Maybe (Ref Image))) => Op (GetDeimage ()) Widget orig impl Source # 

Methods

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

(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetImage ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO (Maybe (Ref Image))) => Op (GetImage ()) Widget orig impl Source # 

Methods

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

(~) * impl (FontSize -> IO ()) => Op (SetLabelsize ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO FontSize) => Op (GetLabelsize ()) Widget orig impl Source # 

Methods

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

(~) * impl (Font -> IO ()) => Op (SetLabelfont ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Font) => Op (GetLabelfont ()) Widget orig impl Source # 

Methods

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

(~) * impl (Color -> IO ()) => Op (SetLabelcolor ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Color) => Op (GetLabelcolor ()) Widget orig impl Source # 

Methods

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

(~) * impl (Labeltype -> IO ()) => Op (SetLabeltype ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Labeltype) => Op (GetLabeltype ()) Widget orig impl Source # 

Methods

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

(~) * impl (Text -> IO ()) => Op (SetLabel ()) Widget orig impl Source # 

Methods

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

(~) * impl (Text -> IO ()) => Op (CopyLabel ()) Widget orig impl Source # 

Methods

runOp :: CopyLabel () -> orig -> Ref Widget -> impl Source #

(~) * impl (IO Text) => Op (GetLabel ()) Widget orig impl Source # 

Methods

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

(~) * impl (Color -> IO ()) => Op (SetSelectionColor ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Color) => Op (GetSelectionColor ()) Widget orig impl Source # 

Methods

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

(~) * impl (Color -> Color -> IO ()) => Op (SetColorWithBgSel ()) Widget orig impl Source # 

Methods

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

(~) * impl (Color -> IO ()) => Op (SetColor ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Color) => Op (GetColor ()) Widget orig impl Source # 

Methods

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

(~) * impl (Boxtype -> IO ()) => Op (SetBox ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Boxtype) => Op (GetBox ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Alignments) => Op (GetAlign ()) Widget orig impl Source # 

Methods

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

(~) * impl (Alignments -> IO ()) => Op (SetAlign ()) Widget orig impl Source # 

Methods

runOp :: SetAlign () -> orig -> Ref Widget -> 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 Int), Op (GetY ()) obj orig (IO Int), Op (GetW ()) obj orig (IO Int), Op (GetH ()) obj orig (IO Int), (~) * impl (IO Rectangle)) => Op (GetRectangle ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetH ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetW ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetY ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetX ()) Widget orig impl Source # 

Methods

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

(~) * impl (Maybe (Rectangle, Alignments) -> IO ()) => Op (DrawLabel ()) Widget orig impl Source # 

Methods

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

(~) * impl (Word8 -> IO ()) => Op (SetType ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO Word8) => Op (GetType_ ()) Widget orig impl Source # 

Methods

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

(Parent a Group, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetParent ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO (Maybe (Ref Group))) => Op (GetParent ()) Widget orig impl Source # 

Methods

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

(~) * impl (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Widget orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Destroy ()) Widget orig impl Source # 

Methods

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