| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Graphics.UI.FLTK.LowLevel.Window
- 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
Constructors
| CustomWindowFuncs | |
Fields
| |
data PositionSpec 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)
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 -> 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 ()