fltkhs-0.2.0.0: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Widget

Contents

Synopsis

Constructor

widgetMaker Source

Arguments

:: Parent a Widget 
=> Rectangle

Position and size

-> Maybe String

Title

-> Maybe (CustomWidgetFuncs a)

Custom functions

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

Foreign constructor to call if neither title nor custom functions are given

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

Foreign constructor to call if only title is given

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

Foreign constructor to call if only custom functions are given

-> (Int -> Int -> Int -> Int -> String -> 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

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 () -> 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 Widget => 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 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 ()

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

clearOutput :: Ref Widget -> IO ()

clearVisible :: Ref Widget -> IO ()

clearVisibleFocus :: Ref Widget -> IO ()

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

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

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

deactivate :: Ref Widget -> IO ()

destroy :: 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 (Word8)

getDamageInsideWidget :: Ref Widget -> Word8 -> Rectangle -> IO ()

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

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

getH :: Ref Widget -> IO (Int)

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

getLabel :: Ref Widget -> IO (String)

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:: (FindOp orig (GetX ()) (Match obj), FindOp orig (GetY ()) (Match obj), FindOp orig (GetW ()) (Match obj), FindOp orig (GetH ()) (Match obj), 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 (String)

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 Int

hasCallback :: Ref Widget -> IO (Bool)

hide :: Ref Widget -> IO ()

hideSuper :: Ref Widget -> IO ()

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

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 ()

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

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

setLabel :: Ref Widget -> String -> 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 -> String -> 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)