| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Graphics.UI.FLTK.LowLevel.FL
- data Option
 - scrollbarSize :: IO Int
 - setScrollbarSize :: Int -> IO ()
 - selectionOwner :: IO (Maybe (Ref Widget))
 - setSelectionOwner :: Parent a Widget => Ref a -> IO ()
 - run :: IO Int
 - check :: IO Int
 - ready :: IO Int
 - option :: Option -> IO Bool
 - setOption :: Option -> Bool -> IO ()
 - addAwakeHandler :: GlobalCallback -> IO Int
 - getAwakeHandler_ :: IO GlobalCallback
 - display :: Text -> IO ()
 - ownColormap :: IO ()
 - getSystemColors :: IO ()
 - foreground :: RGB -> IO ()
 - background :: RGB -> IO ()
 - background2 :: RGB -> IO ()
 - setScheme :: Text -> IO Int
 - isScheme :: Text -> IO Bool
 - setFirstWindow :: Parent a Window => Ref a -> IO ()
 - nextWindow :: Parent a Window => Ref a -> IO (Maybe (Ref Window))
 - setGrab :: Parent a Window => Ref a -> IO ()
 - getMouse :: IO Position
 - eventStates :: [EventState]
 - extract :: Enum a => [a] -> CInt -> [a]
 - extractEventStates :: CInt -> [EventState]
 - handle :: Parent a Window => Event -> Ref a -> IO Int
 - handle_ :: Parent a Window => Event -> Ref a -> IO Int
 - belowmouse :: IO (Maybe (Ref Widget))
 - setBelowmouse :: Parent a Widget => Ref a -> IO ()
 - setPushed :: Parent a Widget => Ref a -> IO ()
 - setFocus :: Parent a Widget => Ref a -> IO ()
 - setHandler :: GlobalEventHandlerF -> IO ()
 - paste :: Parent a Widget => Ref a -> Maybe Int -> 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 :: Int -> IO ()
 - visibleFocus :: IO Int
 - setDndTextOps :: Bool -> IO ()
 - dndTextOps :: IO Option
 - deleteWidget :: Parent a Widget => Ref a -> IO ()
 - doWidgetDeletion :: IO ()
 - watchWidgetPointer :: Parent a Widget => Ref a -> IO ()
 - releaseWidgetPointer :: Parent a Widget => Ref a -> IO ()
 - clearWidgetPointer :: Parent a Widget => Ref a -> IO ()
 - version :: IO Double
 - help :: IO Text
 - visual :: Mode -> IO Bool
 - glVisual :: Mode -> IO Bool
 - glVisualWithAlist :: Mode -> Ptr CInt -> IO Bool
 - scheme :: Text
 - wait :: IO Int
 - setWait :: Double -> IO Double
 - readqueue :: IO (Ref Widget)
 - addTimeout :: Double -> GlobalCallback -> IO ()
 - repeatTimeout :: Double -> GlobalCallback -> IO ()
 - hasTimeout :: GlobalCallback -> IO Int
 - removeTimeout :: GlobalCallback -> IO ()
 - addCheck :: GlobalCallback -> IO ()
 - hasCheck :: GlobalCallback -> IO Int
 - removeCheck :: GlobalCallback -> IO ()
 - addIdle :: GlobalCallback -> IO ()
 - hasIdle :: GlobalCallback -> IO Int
 - removeIdle :: GlobalCallback -> IO ()
 - damage :: IO Int
 - redraw :: IO ()
 - flush :: IO ()
 - firstWindow :: IO (Maybe (Ref Window))
 - modal :: IO (Maybe (Ref Window))
 - grab :: IO (Maybe (Ref Window))
 - getKey :: KeyType -> IO Bool
 - compose :: IO (Bool, Int)
 - composeReset :: IO ()
 - testShortcut :: FlShortcut -> IO Bool
 - enableIm :: IO ()
 - disableIm :: IO ()
 - pushed :: IO (Maybe (Ref Widget))
 - focus :: IO (Maybe (Ref Widget))
 - copy :: Text -> Int -> IO ()
 - copyWithDestination :: Text -> Int -> Int -> IO ()
 - pasteWithSource :: Ptr () -> Int -> IO ()
 - dnd :: IO Int
 - x :: IO Int
 - y :: IO Int
 - w :: IO Int
 - h :: IO Int
 - screenCount :: IO Int
 - setColor :: Color -> Int -> IO ()
 - getColor :: Color -> IO Int
 - getColorRgb :: Color -> IO RGB
 - removeFromColormap :: Maybe Int -> Color -> IO ()
 - data BoxtypeSpec
 - getBoxtype :: Boxtype -> IO BoxDrawF
 - setBoxtype :: Boxtype -> BoxtypeSpec -> IO ()
 - boxDx :: Boxtype -> IO Int
 - boxDy :: Boxtype -> IO Int
 - boxDw :: Boxtype -> IO Int
 - boxDh :: Boxtype -> IO Int
 - drawBoxActive :: IO Bool
 - getFontName :: Font -> IO (Text, Maybe FontAttribute)
 - getFont :: Font -> IO Text
 - getFontSizes :: Font -> IO (Int, Int)
 - setFontByString :: Font -> Text -> IO ()
 - setFontByFont :: Font -> Font -> IO ()
 - setFonts :: IO Font
 - setFontsWithString :: Text -> IO Font
 - 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 Int
 - eventY :: IO Int
 - eventXRoot :: IO Int
 - eventYRoot :: IO Int
 - eventDx :: IO Int
 - eventDy :: IO Int
 - eventClicks :: IO Int
 - setEventClicks :: Int -> IO ()
 - eventIsClick :: IO Bool
 - setEventIsClick :: Int -> IO ()
 - eventButton :: IO 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 Widget => Ref a -> IO Event
 - eventDispatch :: Parent a Widget => IO (Event -> Ref a -> IO Int)
 - setEventDispatch :: Parent a Widget => (Event -> Ref a -> IO Int) -> IO ()
 - eventText :: IO Text
 - eventLength :: IO Int
 
Documentation
scrollbarSize :: IO Int Source #
setScrollbarSize :: Int -> IO () Source #
addAwakeHandler :: GlobalCallback -> IO Int Source #
ownColormap :: IO () Source #
getSystemColors :: IO () Source #
foreground :: RGB -> IO () Source #
background :: RGB -> IO () Source #
background2 :: RGB -> IO () Source #
eventStates :: [EventState] Source #
extractEventStates :: CInt -> [EventState] Source #
setHandler :: GlobalEventHandlerF -> IO () Source #
toAttribute :: Ptr CInt -> IO (Maybe FontAttribute) Source #
setVisibleFocus :: Int -> IO () Source #
visibleFocus :: IO Int Source #
setDndTextOps :: Bool -> IO () Source #
dndTextOps :: IO Option Source #
doWidgetDeletion :: IO () Source #
addTimeout :: Double -> GlobalCallback -> IO () Source #
repeatTimeout :: Double -> GlobalCallback -> IO () Source #
hasTimeout :: GlobalCallback -> IO Int Source #
removeTimeout :: GlobalCallback -> IO () Source #
addCheck :: GlobalCallback -> IO () Source #
removeCheck :: GlobalCallback -> IO () Source #
addIdle :: GlobalCallback -> IO () Source #
removeIdle :: GlobalCallback -> IO () Source #
composeReset :: IO () Source #
testShortcut :: FlShortcut -> IO Bool Source #
screenCount :: IO Int Source #
Box
data BoxtypeSpec 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 Int Source #
eventYRoot :: IO Int Source #
eventClicks :: IO Int Source #
setEventClicks :: Int -> IO () Source #
eventIsClick :: IO Bool Source #
setEventIsClick :: Int -> IO () Source #
eventState :: IO [EventState] Source #
containsEventState :: EventState -> IO Bool Source #
eventLength :: IO Int Source #