fltkhs-0.8.0.3: FLTK bindings
Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Base.Window

Synopsis

Documentation

data CustomWindowFuncs a Source #

Constructors

CustomWindowFuncs 

Fields

data PositionSpec Source #

Constructors

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

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

windowCustom Source #

Arguments

:: Size

Size of this window

-> Maybe Position

Optional position of this window

-> Maybe Text

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 WindowBase, Parent b WidgetBase) => Size -> Maybe Position -> Maybe Text -> Maybe (Ref b -> IO ()) -> CustomWidgetFuncs b -> CustomWindowFuncs a -> (Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> CString -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> CString -> Ptr () -> IO (Ptr ())) -> IO (Ref a) Source #

Hierarchy

Functions

changed :: Ref WindowBase -> IO (Bool)

clearBorder :: Ref WindowBase -> IO ()

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

destroy :: Ref WindowBase -> IO ()

drawBackdrop :: Ref WindowBase -> IO ()

drawBox :: Ref WindowBase -> IO ()

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

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

flush :: Ref WindowBase -> IO ()

freePosition :: Ref WindowBase -> IO ()

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

getBorder :: Ref WindowBase -> IO (Bool)

getDecoratedH :: Ref WindowBase -> IO (Int)

getDecoratedW :: Ref WindowBase -> IO (Int)

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

getIconlabel :: Ref WindowBase -> IO Text

getLabel :: Ref WindowBase -> IO Text

getMenuWindow :: Ref WindowBase -> IO (Bool)

getModal :: Ref WindowBase -> IO (Bool)

getOverride :: Ref WindowBase -> IO (Bool)

getTooltipWindow :: Ref WindowBase -> IO (Bool)

getType_ :: Ref WindowBase -> IO (WindowType)

getXRoot :: Ref WindowBase -> IO (X)

getXclass :: Ref WindowBase -> IO Text

getYRoot :: Ref WindowBase -> IO (Y)

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

hide :: Ref WindowBase -> IO ()

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

iconize :: Ref WindowBase -> IO ()

makeCurrent :: Ref WindowBase -> IO ()

makeFullscreen :: Ref WindowBase -> IO ()

nonModal :: Ref WindowBase -> IO (Bool)

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

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

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

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

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

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

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

setIcon:: (Parent a RGBImage) => Ref WindowBase -> Maybe( Ref a ) -> IO ()

setIconlabel :: Ref WindowBase -> Text -> IO ()

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

setLabelWithIconlabel :: Ref WindowBase -> Text -> Text -> IO ()

setMenuWindow :: Ref WindowBase -> IO ()

setModal :: Ref WindowBase -> IO ()

setNonModal :: Ref WindowBase -> IO ()

setOverride :: Ref WindowBase -> IO ()

setTooltipWindow :: Ref WindowBase -> IO ()

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

setXclass :: Ref WindowBase -> Text -> IO ()

showWidget :: Ref WindowBase -> IO ()

shown :: Ref WindowBase -> IO (Bool)

sizeRange :: Ref WindowBase -> Size -> IO ()

sizeRangeWithArgs :: Ref WindowBase -> Size -> OptionalSizeRangeArgs -> IO ()

waitForExpose :: Ref WindowBase -> IO ()

Orphan instances

impl ~ IO () => Op (Flush ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: Flush () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (WaitForExpose ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: WaitForExpose () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Int => Op (GetDecoratedH ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetDecoratedH () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Int => Op (GetDecoratedW ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetDecoratedW () -> orig -> Ref WindowBase -> impl Source #

impl ~ (CursorType -> (Maybe Color, Maybe Color) -> IO ()) => Op (SetDefaultCursorWithFgBg ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetDefaultCursorWithFgBg () -> orig -> Ref WindowBase -> impl Source #

impl ~ (CursorType -> IO ()) => Op (SetDefaultCursor ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetDefaultCursor () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Cursor -> (Maybe Color, Maybe Color) -> IO ()) => Op (SetCursorWithFgBg ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetCursorWithFgBg () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Cursor -> IO ()) => Op (SetCursor ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetCursor () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (MakeCurrent ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: MakeCurrent () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Y => Op (GetYRoot ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetYRoot () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO X => Op (GetXRoot ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetXRoot () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (Iconize ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: Iconize () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Bool => Op (Shown ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: Shown () -> orig -> Ref WindowBase -> impl Source #

(Parent a RGBImage, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetIcon ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetIcon () -> orig -> Ref WindowBase -> impl Source #

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

Methods

runOp :: GetIcon () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Text -> IO ()) => Op (SetXclass ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetXclass () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Text => Op (GetXclass ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetXclass () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Text -> Text -> IO ()) => Op (SetLabelWithIconlabel ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetLabelWithIconlabel () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Text -> IO ()) => Op (SetIconlabel ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetIconlabel () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Text => Op (GetIconlabel ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetIconlabel () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Size -> OptionalSizeRangeArgs -> IO ()) => Op (SizeRangeWithArgs ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SizeRangeWithArgs () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Size -> IO ()) => Op (SizeRange ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SizeRange () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (FreePosition ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: FreePosition () -> orig -> Ref WindowBase -> impl Source #

impl ~ (PositionSpec -> Maybe Bool -> IO ()) => Op (HotSpot ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: HotSpot () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Bool => Op (GetTooltipWindow ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetTooltipWindow () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (SetTooltipWindow ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetTooltipWindow () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Bool => Op (GetMenuWindow ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetMenuWindow () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (SetMenuWindow ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetMenuWindow () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Bool => Op (NonModal ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: NonModal () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (SetNonModal ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetNonModal () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Bool => Op (GetModal ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetModal () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (SetModal ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetModal () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Bool => Op (GetOverride ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetOverride () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (SetOverride ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetOverride () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO Bool => Op (GetBorder ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: GetBorder () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (ClearBorder ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: ClearBorder () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetBorder ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: SetBorder () -> orig -> Ref WindowBase -> impl Source #

impl ~ (Maybe Rectangle -> IO ()) => Op (FullscreenOff ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: FullscreenOff () -> orig -> Ref WindowBase -> impl Source #

impl ~ IO () => Op (MakeFullscreen ()) WindowBase orig impl Source # 
Instance details

Methods

runOp :: MakeFullscreen () -> orig -> Ref WindowBase -> impl Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

impl ~ (Text -> IO ()) => Op (CopyLabel ()) WindowBase orig impl Source # 
Instance details

Methods

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

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

Methods

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

impl ~ (WindowType -> IO ()) => Op (SetType ()) WindowBase orig impl Source # 
Instance details

Methods

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

impl ~ IO WindowType => Op (GetType_ ()) WindowBase orig impl Source # 
Instance details

Methods

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

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

Methods

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

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

Methods

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