Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Option
- data ClipboardContents
- scrollbarSize :: IO Int
- setScrollbarSize :: Int -> IO ()
- selectionOwner :: IO (Maybe (Ref WidgetBase))
- setSelectionOwner :: Parent a WidgetBase => Ref a -> IO ()
- run :: IO Int
- replRun :: IO ()
- check :: IO Int
- ready :: IO Int
- option :: Option -> IO Bool
- setOption :: Option -> Bool -> IO ()
- lock :: IO Bool
- unlock :: IO ()
- awake :: IO ()
- awakeToHandler :: IO ()
- addAwakeHandler_ :: GlobalCallback -> IO (Either AwakeRingFull ())
- getAwakeHandler_ :: IO GlobalCallback
- display :: Text -> IO ()
- ownColormap :: IO ()
- getSystemColors :: IO ()
- foreground :: RGB -> IO ()
- background :: RGB -> IO ()
- background2 :: RGB -> IO ()
- setScheme :: Text -> IO Int
- getScheme :: IO Text
- reloadScheme :: Int
- isScheme :: Text -> IO Bool
- setFirstWindow :: Parent a WindowBase => Ref a -> IO ()
- nextWindow :: Ref a -> IO (Maybe (Ref WindowBase))
- setGrab :: Parent a WindowBase => Ref a -> IO ()
- getMouse :: IO Position
- eventStates :: [EventState]
- extract :: Enum a => [a] -> CInt -> [a]
- extractEventStates :: CInt -> [EventState]
- handle :: Parent a WindowBase => Event -> Ref a -> IO (Either UnknownEvent ())
- handle_ :: Parent a WindowBase => Event -> Ref a -> IO (Either UnknownEvent ())
- belowmouse :: IO (Maybe (Ref Widget))
- setBelowmouse :: Parent a WidgetBase => Ref a -> IO ()
- setPushed :: Parent a WidgetBase => Ref a -> IO ()
- setFocus :: Parent a WidgetBase => Ref a -> IO ()
- setHandler :: GlobalEventHandlerF -> IO ()
- toRectangle :: (Int, Int, Int, Int) -> Rectangle
- fromRectangle :: Rectangle -> (Int, Int, Int, Int)
- screenBounds :: Maybe ScreenLocation -> IO Rectangle
- screenDPI :: Maybe Int -> IO DPI
- screenWorkArea :: Maybe ScreenLocation -> IO Rectangle
- setColorRgb :: Color -> Word8 -> Word8 -> Word8 -> IO ()
- toAttribute :: Ptr CInt -> IO (Maybe FontAttribute)
- release :: IO ()
- setVisibleFocus :: Bool -> IO ()
- visibleFocus :: IO Bool
- setDndTextOps :: Bool -> IO ()
- dndTextOps :: IO Option
- deleteWidget :: Parent a WidgetBase => Ref a -> IO ()
- doWidgetDeletion :: IO ()
- watchWidgetPointer :: Parent a WidgetBase => Ref a -> IO ()
- releaseWidgetPointer :: Parent a WidgetBase => Ref a -> IO ()
- clearWidgetPointer :: Parent a WidgetBase => Ref a -> IO ()
- version :: IO Double
- help :: IO Text
- visual :: Mode -> IO Bool
- glVisual :: Mode -> IO Bool
- glVisualWithAlist :: Mode -> Ptr CInt -> IO Bool
- wait :: IO Int
- setWait :: Double -> IO Double
- waitFor :: Double -> IO Double
- readqueue :: IO (Maybe (Ref WidgetBase))
- addTimeout :: Double -> GlobalCallback -> IO (FunPtr CallbackPrim)
- repeatTimeout :: Double -> GlobalCallback -> IO (FunPtr CallbackPrim)
- hasTimeout :: FunPtr CallbackPrim -> IO Bool
- removeTimeout :: FunPtr CallbackPrim -> IO ()
- addCheck :: GlobalCallback -> IO (FunPtr CallbackPrim)
- hasCheck :: FunPtr CallbackPrim -> IO Bool
- removeCheck :: FunPtr CallbackPrim -> IO ()
- addIdle :: GlobalCallback -> IO (FunPtr CallbackPrim)
- hasIdle :: FunPtr CallbackPrim -> IO Bool
- removeIdle :: FunPtr CallbackPrim -> IO ()
- damage :: IO Int
- redraw :: IO ()
- flush :: IO ()
- firstWindow :: IO (Maybe (Ref WindowBase))
- modal :: IO (Maybe (Ref WindowBase))
- grab :: IO (Maybe (Ref WindowBase))
- getKey :: KeyType -> IO Bool
- compose :: IO (Bool, Int)
- composeReset :: IO ()
- testShortcut :: FlShortcut -> IO Bool
- enableIm :: IO ()
- disableIm :: IO ()
- pushed :: IO (Maybe (Ref WidgetBase))
- focus :: IO (Maybe (Ref WidgetBase))
- copyToClipboard :: Text -> IO ()
- copyToSelectionBuffer :: Text -> IO ()
- copyLengthToClipboard :: Text -> Int -> IO ()
- copyLengthToSelectionBuffer :: Text -> Int -> IO ()
- pasteImageFromSelectionBuffer :: Parent a WidgetBase => Ref a -> IO ()
- pasteFromSelectionBuffer :: Parent a WidgetBase => Ref a -> IO ()
- pasteImageFromClipboard :: Parent a WidgetBase => Ref a -> IO ()
- pasteFromClipboard :: Parent a WidgetBase => Ref a -> IO ()
- dnd :: IO Int
- x :: IO Int
- y :: IO Int
- w :: IO Int
- h :: IO Int
- screenCount :: IO Int
- setColor :: Color -> Color -> IO ()
- getColor :: Color -> IO Color
- getColorRgb :: Color -> IO RGB
- removeFromColormap :: Maybe Color -> Color -> IO ()
- data BoxtypeSpec
- getBoxtype :: Boxtype -> IO (FunPtr BoxDrawFPrim)
- setBoxtype :: Boxtype -> BoxtypeSpec -> IO ()
- boxDx :: Boxtype -> IO Int
- boxDy :: Boxtype -> IO Int
- boxDw :: Boxtype -> IO Int
- boxDh :: Boxtype -> IO Int
- adjustBoundsByBoxtype :: Rectangle -> Boxtype -> IO Rectangle
- boxDifferences :: Rectangle -> Rectangle -> (Int, Int, Int, Int)
- drawBoxActive :: IO Bool
- getFontName :: Font -> IO (Text, Maybe FontAttribute)
- getFont :: Font -> IO Text
- getFontSizes :: Font -> IO [FontSize]
- setFontToString :: Font -> Text -> IO ()
- setFontToFont :: Font -> Font -> IO ()
- setFonts :: Maybe Text -> IO Int
- addFd :: CInt -> FDHandler -> IO ()
- addFdWhen :: CInt -> [FdWhen] -> FDHandler -> IO ()
- removeFd :: CInt -> IO ()
- removeFdWhen :: CInt -> [FdWhen] -> IO ()
- event :: IO Event
- eventShift :: IO Bool
- eventCtrl :: IO Bool
- eventCommand :: IO Bool
- eventAlt :: IO Bool
- eventButtons :: IO Bool
- eventButton1 :: IO Bool
- eventButton2 :: IO Bool
- eventButton3 :: IO Bool
- eventX :: IO X
- eventY :: IO Y
- eventPosition :: IO Position
- eventXRoot :: IO X
- eventYRoot :: IO Y
- eventRootPosition :: IO Position
- eventDx :: IO Int
- eventDy :: IO Int
- eventClicks :: IO Int
- setEventClicks :: Int -> IO ()
- eventIsClick :: IO Bool
- setEventIsClick :: Int -> IO ()
- eventButton :: IO (Maybe MouseButton)
- eventState :: IO [EventState]
- containsEventState :: EventState -> IO Bool
- eventKey :: IO KeyType
- eventOriginalKey :: IO KeyType
- eventKeyPressed :: KeyType -> IO Bool
- eventInsideRegion :: Rectangle -> IO Event
- eventInsideWidget :: Parent a WidgetBase => Ref a -> IO Event
- eventDispatch :: Parent a WidgetBase => IO (Event -> Ref a -> IO (Either UnknownEvent ()))
- setEventDispatch :: Parent a WidgetBase => (Event -> Ref a -> IO (Either UnknownEvent ())) -> IO ()
- eventText :: IO Text
- eventLength :: IO Int
- eventClipboardContents :: IO (Maybe ClipboardContents)
- setBoxColor :: Color -> IO ()
- boxColor :: Color -> IO Color
- abiVersion :: IO Int
- apiVersion :: IO Int
- abiCheck :: Int -> IO Int
- localCtrl :: IO Text
- localMeta :: IO Text
- localAlt :: IO Text
- localShift :: IO Text
- useHighResGL :: IO Bool
- setUseHighResGL :: Bool -> IO ()
- insertionPointLocation :: Position -> Height -> IO ()
- resetMarkedText :: IO ()
- runChecks :: IO ()
- screenDriver :: IO (Maybe (Ref ScreenDriver))
- systemDriver :: IO (Maybe (Ref SystemDriver))
- screenXYWH :: IO (Int, Int, Int, Int)
- setProgramShouldQuit :: Bool -> IO ()
- getProgramShouldQuit :: IO Bool
Documentation
data ClipboardContents Source #
scrollbarSize :: IO Int Source #
setScrollbarSize :: Int -> IO () Source #
selectionOwner :: IO (Maybe (Ref WidgetBase)) Source #
setSelectionOwner :: Parent a WidgetBase => Ref a -> IO () Source #
awakeToHandler :: IO () Source #
addAwakeHandler_ :: GlobalCallback -> IO (Either AwakeRingFull ()) Source #
ownColormap :: IO () Source #
getSystemColors :: IO () Source #
foreground :: RGB -> IO () Source #
background :: RGB -> IO () Source #
background2 :: RGB -> IO () Source #
reloadScheme :: Int Source #
setFirstWindow :: Parent a WindowBase => Ref a -> IO () Source #
nextWindow :: Ref a -> IO (Maybe (Ref WindowBase)) Source #
eventStates :: [EventState] Source #
extractEventStates :: CInt -> [EventState] Source #
handle :: Parent a WindowBase => Event -> Ref a -> IO (Either UnknownEvent ()) Source #
handle_ :: Parent a WindowBase => Event -> Ref a -> IO (Either UnknownEvent ()) Source #
setBelowmouse :: Parent a WidgetBase => Ref a -> IO () Source #
setHandler :: GlobalEventHandlerF -> IO () Source #
toAttribute :: Ptr CInt -> IO (Maybe FontAttribute) Source #
setVisibleFocus :: Bool -> IO () Source #
visibleFocus :: IO Bool Source #
setDndTextOps :: Bool -> IO () Source #
dndTextOps :: IO Option Source #
deleteWidget :: Parent a WidgetBase => Ref a -> IO () Source #
doWidgetDeletion :: IO () Source #
watchWidgetPointer :: Parent a WidgetBase => Ref a -> IO () Source #
releaseWidgetPointer :: Parent a WidgetBase => Ref a -> IO () Source #
clearWidgetPointer :: Parent a WidgetBase => Ref a -> IO () Source #
glVisual :: Mode -> IO Bool Source #
Only available if on a non OSX platform and if the opengl
flag is set (stack build --flag fltkhs:opengl).
glVisualWithAlist :: Mode -> Ptr CInt -> IO Bool Source #
Only available if on a non OSX platform and if the opengl
flag is set (stack build --flag fltkhs:opengl).
addTimeout :: Double -> GlobalCallback -> IO (FunPtr CallbackPrim) Source #
Returns a function pointer so it can be freed with freeHaskellFunPtr
, please don't invoke it.
repeatTimeout :: Double -> GlobalCallback -> IO (FunPtr CallbackPrim) Source #
Returns a function pointer so it can be freed with freeHaskellFunPtr
, please don't invoke it.
hasTimeout :: FunPtr CallbackPrim -> IO Bool Source #
removeTimeout :: FunPtr CallbackPrim -> IO () Source #
addCheck :: GlobalCallback -> IO (FunPtr CallbackPrim) Source #
Returns a function pointer so it can be freed with freeHaskellFunPtr
, please don't invoke it.
removeCheck :: FunPtr CallbackPrim -> IO () Source #
addIdle :: GlobalCallback -> IO (FunPtr CallbackPrim) Source #
Returns a function pointer so it can be freed with freeHaskellFunPtr
, please don't invoke it.
removeIdle :: FunPtr CallbackPrim -> IO () Source #
firstWindow :: IO (Maybe (Ref WindowBase)) Source #
composeReset :: IO () Source #
testShortcut :: FlShortcut -> IO Bool Source #
copyToClipboard :: Text -> IO () Source #
copyToSelectionBuffer :: Text -> IO () Source #
pasteImageFromSelectionBuffer :: Parent a WidgetBase => Ref a -> IO () Source #
pasteFromSelectionBuffer :: Parent a WidgetBase => Ref a -> IO () Source #
pasteImageFromClipboard :: Parent a WidgetBase => Ref a -> IO () Source #
pasteFromClipboard :: Parent a WidgetBase => Ref a -> IO () Source #
screenCount :: IO Int Source #
Box
data BoxtypeSpec Source #
getBoxtype :: Boxtype -> IO (FunPtr BoxDrawFPrim) Source #
setBoxtype :: Boxtype -> BoxtypeSpec -> IO () Source #
drawBoxActive :: IO Bool Source #
Fonts
getFontName :: Font -> IO (Text, Maybe FontAttribute) Source #
File Descriptor Callbacks
Events
eventShift :: IO Bool Source #
eventCommand :: IO Bool Source #
eventButtons :: IO Bool Source #
eventButton1 :: IO Bool Source #
eventButton2 :: IO Bool Source #
eventButton3 :: IO Bool Source #
eventXRoot :: IO X Source #
eventYRoot :: IO Y Source #
eventClicks :: IO Int Source #
setEventClicks :: Int -> IO () Source #
eventIsClick :: IO Bool Source #
setEventIsClick :: Int -> IO () Source #
eventButton :: IO (Maybe MouseButton) Source #
eventState :: IO [EventState] Source #
containsEventState :: EventState -> IO Bool Source #
eventInsideWidget :: Parent a WidgetBase => Ref a -> IO Event Source #
eventDispatch :: Parent a WidgetBase => IO (Event -> Ref a -> IO (Either UnknownEvent ())) Source #
setEventDispatch :: Parent a WidgetBase => (Event -> Ref a -> IO (Either UnknownEvent ())) -> IO () Source #
eventLength :: IO Int Source #
setBoxColor :: Color -> IO () Source #
Only available on FLTK version 1.3.4 and above.
abiVersion :: IO Int Source #
Only available on FLTK version 1.3.4 and above.
apiVersion :: IO Int Source #
Only available on FLTK version 1.3.4 and above.
localShift :: IO Text Source #
Only available on FLTK version 1.3.4 and above.
useHighResGL :: IO Bool Source #
Only available on FLTK version 1.3.4 and above if GL is enabled with 'stack build --flag fltkhs:opengl'
setUseHighResGL :: Bool -> IO () Source #
Only available on FLTK version 1.3.4 and above if GL is enabled with 'stack build --flag fltkhs:opengl'
resetMarkedText :: IO () Source #
screenDriver :: IO (Maybe (Ref ScreenDriver)) Source #
systemDriver :: IO (Maybe (Ref SystemDriver)) Source #
setProgramShouldQuit :: Bool -> IO () Source #