Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data SliderType
- data ScrollbarType
- data BrowserType
- data SortType
- data FileBrowserType
- data FileIconType
- data FileIconProps
- data FileChooserType
- data ButtonType
- data TreeReasonType
- data MenuItemFlag
- data ColorChooserMode
- newtype MenuItemFlags = MenuItemFlags [MenuItemFlag]
- allMenuItemFlags :: [MenuItemFlag]
- data CursorType
- data PositionType
- data DragType
- data WrapTypeFl
- data WrapType
- data PageFormat
- data PageLayout
- data TableRowSelectMode
- data TableContext
- data LinePosition
- data ScrollbarMode
- data StyleTableEntry = StyleTableEntry (Maybe Color) (Maybe Font) (Maybe FontSize)
- data PackType
- type FlShortcut = CUInt
- type FlColor = CUInt
- type FlFont = CInt
- type FlAlign = CUInt
- type LineDelta = Maybe Int
- type Delta = Maybe Int
- type FlIntPtr = CLong
- type FlUIntPtr = CULong
- type ID = Ptr ()
- data Ref a = Ref !(ForeignPtr (Ptr ()))
- data FunRef = FunRef !(FunPtr ())
- data CBase parent
- type Base = CBase ()
- type GlobalCallback = IO ()
- type CallbackWithUserDataPrim = Ptr () -> Ptr () -> IO ()
- type CallbackPrim = Ptr () -> IO ()
- type ColorAverageCallbackPrim = Ptr () -> CUInt -> CFloat -> IO ()
- type ImageDrawCallbackPrim = Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ()
- type ImageCopyCallbackPrim = Ptr () -> CInt -> CInt -> IO (Ptr ())
- type GlobalEventHandlerPrim = CInt -> IO CInt
- type GlobalEventHandlerF = Event -> IO Int
- type DrawCallback = Text -> Position -> IO ()
- type DrawCallbackPrim = CString -> CInt -> CInt -> CInt -> IO ()
- type TextBufferCallback = FunPtr (Ptr () -> IO ())
- type FileChooserCallback = FunPtr (Ptr () -> Ptr () -> IO ())
- type SharedImageHandler = FunPtr (CString -> CUChar -> CInt -> Ptr ())
- type BoxDrawF = Rectangle -> Color -> IO ()
- type BoxDrawFPrim = CInt -> CInt -> CInt -> CInt -> FlColor -> IO ()
- type FDHandlerPrim = CInt -> Ptr () -> IO ()
- type FDHandler = CInt -> IO ()
- type TextModifyCb = Int -> Int -> Int -> Int -> Text -> IO ()
- type TextModifyCbPrim = CInt -> CInt -> CInt -> CInt -> Ptr CChar -> Ptr () -> IO ()
- type TextPredeleteCb = BufferOffset -> Int -> IO ()
- type TextPredeleteCbPrim = CInt -> CInt -> Ptr () -> IO ()
- type UnfinishedStyleCb = BufferOffset -> IO ()
- type UnfinishedStyleCbPrim = CInt -> Ptr () -> IO ()
- newtype Width = Width Int
- newtype Height = Height Int
- newtype Depth = Depth Int
- newtype LineSize = LineSize Int
- newtype X = X Int
- newtype Y = Y Int
- newtype ByX = ByX Double
- newtype ByY = ByY Double
- newtype Angle = Angle CShort
- data Position = Position X Y
- data CountDirection
- data DPI = DPI Float Float
- newtype TextDisplayStyle = TextDisplayStyle CInt
- newtype BufferOffset = BufferOffset Int
- data BufferRange = BufferRange BufferOffset BufferOffset
- statusToBufferRange :: (Ptr CInt -> Ptr CInt -> IO Int) -> IO (Maybe BufferRange)
- data ColorChooserRGB
- data Rectangle = Rectangle Position Size
- data ByXY = ByXY ByX ByY
- data Intersection
- data Size = Size Width Height
- newtype LineNumber = LineNumber Int
- newtype ColumnNumber = ColumnNumber Int
- newtype PixelPosition = PixelPosition Int
- data KeyType
- data ShortcutKeySequence = ShortcutKeySequence [EventState] KeyType
- data Shortcut
- data KeyBindingKeySequence = KeyBindingKeySequence (Maybe [EventState]) KeyType
- newtype Between0And1 = Between0And1 Double
- newtype Between0And6 = Between0And6 Double
- data ScreenLocation
- newtype FontSize = FontSize CInt
- newtype PixmapHs = PixmapHs [Text]
- data BitmapHs = BitmapHs ByteString Size
- data Clipboard
- data UnknownEvent = UnknownEvent
- successOrUnknownEvent :: Int -> Either UnknownEvent ()
- data UnknownError = UnknownError
- successOrUnknownError :: a -> Bool -> (a -> IO b) -> IO (Either UnknownError b)
- data NotFound = NotFound
- data OutOfRange = OutOfRange
- successOrOutOfRange :: a -> Bool -> (a -> IO b) -> IO (Either OutOfRange b)
- data NoChange = NoChange
- successOrNoChange :: Int -> Either NoChange ()
- data DataProcessingError
- successOrDataProcessingError :: Int -> Either DataProcessingError ()
- toRectangle :: (Int, Int, Int, Int) -> Rectangle
- fromRectangle :: Rectangle -> (Int, Int, Int, Int)
- toSize :: (Int, Int) -> Size
- toPosition :: (Int, Int) -> Position
- throwStackOnError :: IO a -> IO a
- withForeignPtrs :: [ForeignPtr a] -> ([Ptr a] -> IO c) -> IO c
- toRefPtr :: HasCallStack => Ptr (Ptr a) -> IO (Ptr a)
- withRef :: HasCallStack => Ref a -> (Ptr b -> IO c) -> IO c
- isNull :: Ref a -> IO Bool
- unsafeRefToPtr :: HasCallStack => Ref a -> IO (Ptr ())
- withRefs :: HasCallStack => [Ref a] -> (Ptr (Ptr b) -> IO c) -> IO c
- withMaybeRef :: Maybe (Ref a) -> (Ptr () -> IO c) -> IO c
- swapRef :: Ref a -> (Ptr b -> IO (Ptr ())) -> IO ()
- wrapInRef :: ForeignPtr (Ptr ()) -> Ref a
- toFunRef :: FunPtr a -> FunRef
- fromFunRef :: FunRef -> FunPtr ()
- refPtrEquals :: Ref a -> Ref b -> IO Bool
Documentation
data SliderType Source #
data ScrollbarType Source #
data BrowserType Source #
data FileBrowserType Source #
data FileIconType Source #
data FileIconProps Source #
data FileChooserType Source #
data ButtonType Source #
data TreeReasonType Source #
data MenuItemFlag Source #
data ColorChooserMode Source #
data CursorType Source #
data PositionType Source #
data WrapTypeFl Source #
data PageFormat Source #
data PageLayout Source #
data TableRowSelectMode Source #
data TableContext Source #
data LinePosition Source #
data ScrollbarMode Source #
data StyleTableEntry Source #
type FlShortcut = CUInt Source #
The FLTK widget hierarchy
type GlobalCallback = IO () Source #
type CallbackPrim = Ptr () -> IO () Source #
type ImageDrawCallbackPrim = Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () Source #
type TextPredeleteCb = BufferOffset -> Int -> IO () Source #
type UnfinishedStyleCb = BufferOffset -> IO () Source #
data ColorChooserRGB Source #
newtype LineNumber Source #
newtype ColumnNumber Source #
newtype PixelPosition Source #
data ShortcutKeySequence Source #
data KeyBindingKeySequence Source #
data ScreenLocation Source #
successOrUnknownEvent :: Int -> Either UnknownEvent () Source #
successOrUnknownError :: a -> Bool -> (a -> IO b) -> IO (Either UnknownError b) Source #
successOrOutOfRange :: a -> Bool -> (a -> IO b) -> IO (Either OutOfRange b) Source #
data DataProcessingError Source #
throwStackOnError :: IO a -> IO a Source #
withForeignPtrs :: [ForeignPtr a] -> ([Ptr a] -> IO c) -> IO c Source #
unsafeRefToPtr :: HasCallStack => Ref a -> IO (Ptr ()) Source #
fromFunRef :: FunRef -> FunPtr () Source #