Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data CustomWindowFuncs a = CustomWindowFuncs {
- flushCustom :: Maybe (Ref a -> IO ())
- data OptionalSizeRangeArgs = OptionalSizeRangeArgs {}
- data PositionSpec
- data WindowType
- defaultCustomWindowFuncs :: forall a. Parent a Window => CustomWindowFuncs a
- fillCustomWidgetFunctionStruct :: forall a. Parent a Widget => Ptr () -> Maybe (Ref a -> IO ()) -> CustomWidgetFuncs a -> IO ()
- defaultOptionalSizeRangeArgs :: OptionalSizeRangeArgs
- windowCustom :: Size -> Maybe Position -> Maybe Text -> Maybe (Ref Window -> IO ()) -> CustomWidgetFuncs Window -> CustomWindowFuncs Window -> IO (Ref Window)
- windowNew :: Size -> Maybe Position -> Maybe Text -> IO (Ref Window)
- windowMaker :: forall a b. (Parent a Window, Parent b Widget) => Size -> Maybe Position -> Maybe Text -> Maybe (Ref b -> IO ()) -> CustomWidgetFuncs b -> CustomWindowFuncs a -> (Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Text -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> Text -> Ptr () -> IO (Ptr ())) -> IO (Ref a)
- currentWindow :: Parent a Window => IO (Ref a)
Documentation
data CustomWindowFuncs a Source #
CustomWindowFuncs | |
|
data OptionalSizeRangeArgs Source #
data PositionSpec Source #
data WindowType Source #
defaultCustomWindowFuncs :: forall a. Parent a Window => CustomWindowFuncs a Source #
fillCustomWidgetFunctionStruct :: forall a. Parent a Widget => Ptr () -> Maybe (Ref a -> IO ()) -> CustomWidgetFuncs a -> IO () Source #
windowMaker :: forall a b. (Parent a Window, Parent b Widget) => Size -> Maybe Position -> Maybe Text -> Maybe (Ref b -> IO ()) -> CustomWidgetFuncs b -> CustomWindowFuncs a -> (Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Text -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> Text -> Ptr () -> IO (Ptr ())) -> IO (Ref a) Source #
Hierarchy
Graphics.UI.FLTK.LowLevel.Widget | v Graphics.UI.FLTK.LowLevel.Group | v Graphics.UI.FLTK.LowLevel.Window
Functions
changed ::Ref
Window
->IO
(Bool
) clearBorder ::Ref
Window
->IO
() copyLabel ::Ref
Window
->Text
->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
Text
getLabel ::Ref
Window
->IO
Text
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
Text
getYRoot ::Ref
Window
->IO
(Int
) handle ::Ref
Window
-> (Event
->IO
(Either
UnknownEvent
())) handleSuper ::Ref
Window
->Event
->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
aImage
) =>Ref
Window
->Maybe
(Ref
a ) ->IO
() setIconlabel ::Ref
Window
->Text
->IO
() setLabel ::Ref
Window
->Text
->IO
() setLabelWithIconlabel ::Ref
Window
->Text
->Text
->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
->Text
->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
()
Orphan instances
(~) * impl (IO ()) => Op (WaitForExpose ()) Window orig impl Source # | |
(~) * impl (IO Int) => Op (GetDecoratedH ()) Window orig impl Source # | |
(~) * impl (IO Int) => Op (GetDecoratedW ()) Window orig impl Source # | |
(~) * impl (CursorType -> (Maybe Color, Maybe Color) -> IO ()) => Op (SetDefaultCursorWithFgBg ()) Window orig impl Source # | |
(~) * impl (CursorType -> IO ()) => Op (SetDefaultCursor ()) Window orig impl Source # | |
(~) * impl (Cursor -> (Maybe Color, Maybe Color) -> IO ()) => Op (SetCursorWithFgBg ()) Window orig impl Source # | |
(~) * impl (Cursor -> IO ()) => Op (SetCursor ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (MakeCurrent ()) Window orig impl Source # | |
(~) * impl (IO Int) => Op (GetYRoot ()) Window orig impl Source # | |
(~) * impl (IO Int) => Op (GetXRoot ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (Iconize ()) Window orig impl Source # | |
(~) * impl (IO Bool) => Op (Shown ()) Window orig impl Source # | |
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetIcon ()) Window orig impl Source # | |
(~) * impl (IO (Maybe (Ref Image))) => Op (GetIcon ()) Window orig impl Source # | |
(~) * impl (Text -> IO ()) => Op (SetXclass ()) Window orig impl Source # | |
(~) * impl (IO Text) => Op (GetXclass ()) Window orig impl Source # | |
(~) * impl (Text -> Text -> IO ()) => Op (SetLabelWithIconlabel ()) Window orig impl Source # | |
(~) * impl (Text -> IO ()) => Op (SetIconlabel ()) Window orig impl Source # | |
(~) * impl (IO Text) => Op (GetIconlabel ()) Window orig impl Source # | |
(~) * impl (Int -> Int -> OptionalSizeRangeArgs -> IO ()) => Op (SizeRangeWithArgs ()) Window orig impl Source # | |
(~) * impl (Int -> Int -> IO ()) => Op (SizeRange ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (FreePosition ()) Window orig impl Source # | |
(~) * impl (PositionSpec -> Maybe Bool -> IO ()) => Op (HotSpot ()) Window orig impl Source # | |
(~) * impl (IO Bool) => Op (GetTooltipWindow ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (SetTooltipWindow ()) Window orig impl Source # | |
(~) * impl (IO Bool) => Op (GetMenuWindow ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (SetMenuWindow ()) Window orig impl Source # | |
(~) * impl (IO Bool) => Op (NonModal ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (SetNonModal ()) Window orig impl Source # | |
(~) * impl (IO Bool) => Op (GetModal ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (SetModal ()) Window orig impl Source # | |
(~) * impl (IO Bool) => Op (GetOverride ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (SetOverride ()) Window orig impl Source # | |
(~) * impl (IO Bool) => Op (GetBorder ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (ClearBorder ()) Window orig impl Source # | |
(~) * impl (Bool -> IO ()) => Op (SetBorder ()) Window orig impl Source # | |
(~) * impl (Maybe Rectangle -> IO ()) => Op (FullscreenOff ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (MakeFullscreen ()) Window orig impl Source # | |
(~) * impl (IO Bool) => Op (Changed ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (FlushSuper ()) Window orig impl Source # | |
(~) * impl (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (DrawSuper ()) Window orig impl Source # | |
(~) * impl (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (DrawBackdrop ()) Window orig impl Source # | |
(~) * impl (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (DrawBox ()) Window orig impl Source # | |
(~) * impl ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) Window orig impl Source # | |
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Window orig impl Source # | |
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (Hide ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (HideSuper ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (ShowWidget ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) Window orig impl Source # | |
(~) * impl (Text -> IO ()) => Op (SetLabel ()) Window orig impl Source # | |
(~) * impl (Text -> IO ()) => Op (CopyLabel ()) Window orig impl Source # | |
(~) * impl (IO Text) => Op (GetLabel ()) Window orig impl Source # | |
(~) * impl (WindowType -> IO ()) => Op (SetType ()) Window orig impl Source # | |
(~) * impl (IO WindowType) => Op (GetType_ ()) Window orig impl Source # | |
(~) * impl (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Window orig impl Source # | |
(~) * impl (IO ()) => Op (Destroy ()) Window orig impl Source # | |