fltkhs-0.4.0.7: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Window

Contents

Synopsis

Documentation

data CustomWindowFuncs a Source

Constructors

CustomWindowFuncs 

Fields

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

data PositionSpec Source

Constructors

ByPosition Position 
forall a . Parent a Widget => ByWidget (Ref a) 

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

windowCustom Source

Arguments

:: Size

Size of this window

-> Maybe Position

Optional position of this window

-> Maybe String

Optional label

-> Maybe (Ref Window -> IO ())

Optional table drawing routine

-> CustomWidgetFuncs Window

Custom widget overrides

-> CustomWindowFuncs Window

Custom window overrides

-> IO (Ref Window) 

windowMaker :: forall a b. (Parent a Window, Parent b Widget) => Size -> Maybe Position -> Maybe String -> Maybe (Ref b -> IO ()) -> CustomWidgetFuncs b -> CustomWindowFuncs a -> (Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> String -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> String -> Ptr () -> IO (Ptr ())) -> IO (Ref a) Source

Hierarchy

Functions

changed :: Ref Window -> IO (Bool)

clearBorder :: Ref Window -> IO ()

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

destroy :: Ref Window -> IO ()

drawBackdrop :: Ref Window -> IO ()

drawBox :: Ref Window -> IO ()

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

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

drawSuper :: Ref Window -> IO ()

flushSuper :: Ref Window -> IO ()

freePosition :: Ref Window -> IO ()

fullscreenOff :: Ref Window -> Maybe Rectangle -> IO ()

getBorder :: Ref Window -> IO (Bool)

getDecoratedH :: Ref Window -> IO (Int)

getDecoratedW :: Ref Window -> IO (Int)

getIcon :: Ref Window -> IO (Maybe (Ref Image))

getIconlabel :: Ref Window -> IO (String)

getLabel :: Ref Window -> IO (String)

getMenuWindow :: Ref Window -> IO (Bool)

getModal :: Ref Window -> IO (Bool)

getOverride :: Ref Window -> IO (Bool)

getTooltipWindow :: Ref Window -> IO (Bool)

getType_ :: Ref Window -> IO (WindowType)

getXRoot :: Ref Window -> IO (Int)

getXclass :: Ref Window -> IO (String)

getYRoot :: Ref Window -> IO (Int)

handle :: Ref Window -> Event -> IO Int

handleSuper :: Ref Window -> Int -> IO (Int)

hide :: Ref Window -> IO ()

hideSuper :: Ref Window -> IO ()

hotSpot :: Ref Window -> PositionSpec -> Maybe Bool -> IO ()

iconize :: Ref Window -> IO ()

makeCurrent :: Ref Window -> IO ()

makeFullscreen :: Ref Window -> IO ()

nonModal :: Ref Window -> IO (Bool)

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

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

setBorder :: Ref Window -> Bool -> IO ()

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

setCursor :: Ref Window -> Cursor -> IO ()

setCursorWithFgBg :: Ref Window -> Cursor -> (Maybe Color, Maybe Color) -> IO ()

setDefaultCursor :: Ref Window -> CursorType -> IO ()

setDefaultCursorWithFgBg :: Ref Window -> CursorType -> (Maybe Color, Maybe Color) -> IO ()

setIcon:: (Parent a Image) => Ref Window -> Maybe( Ref a ) -> IO ()

setIconlabel :: Ref Window -> String -> IO ()

setLabel :: Ref Window -> String -> IO ()

setLabelWithIconlabel :: Ref Window -> String -> String -> IO ()

setMenuWindow :: Ref Window -> IO ()

setModal :: Ref Window -> IO ()

setNonModal :: Ref Window -> IO ()

setOverride :: Ref Window -> IO ()

setTooltipWindow :: Ref Window -> IO ()

setType :: Ref Window -> WindowType -> IO ()

setXclass :: Ref Window -> String -> IO ()

showWidget :: Ref Window -> IO ()

showWidgetSuper :: Ref Window -> IO ()

shown :: Ref Window -> IO (Bool)

sizeRange :: Ref Window -> Int -> Int -> IO ()

sizeRangeWithArgs :: Ref Window -> Int -> Int -> OptionalSizeRangeArgs -> IO ()

waitForExpose :: Ref Window -> IO ()