| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Graphics.UI.FLTK.LowLevel.Fl_Types
Contents
- 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 ()
- newtype WindowHandle = WindowHandle (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 OutOfRangeOrNotSubmenu = OutOfRangeOrNotSubmenu
- successOrOutOfRangeOrNotSubmenu :: Int -> Either OutOfRangeOrNotSubmenu ()
- data AwakeRingFull = AwakeRingFull
- successOrAwakeRingFull :: Int -> Either AwakeRingFull ()
- 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 #
Constructors
| VertSliderType | |
| HorSliderType | |
| VertFillSliderType | |
| HorFillSliderType | |
| VertNiceSliderType | |
| HorNiceSliderType | 
Instances
data BrowserType Source #
Instances
Constructors
| SortAscending | |
| SortDescending | 
data FileIconType Source #
Instances
data FileIconProps Source #
Constructors
| FileIconEnd | |
| FileIconColor | |
| FileIconLine | |
| FileIconClosedline | |
| FileIconPolygon | |
| FileIconOutlinepolygon | |
| FileIconVertex | 
Instances
data FileChooserType Source #
Instances
data ButtonType Source #
Instances
data TreeReasonType Source #
Constructors
| TreeReasonNone | |
| TreeReasonSelected | |
| TreeReasonDeselected | |
| TreeReasonOpened | |
| TreeReasonClosed | |
| TreeReasonDragged | 
Instances
data MenuItemFlag Source #
Constructors
| MenuItemNormal | |
| MenuItemInactive | |
| MenuItemToggle | |
| MenuItemValue | |
| MenuItemRadio | |
| MenuItemInvisible | |
| SubmenuPointer | |
| Submenu | |
| MenuItemDivider | |
| MenuItemHorizontal | 
Instances
data ColorChooserMode Source #
data CursorType Source #
Constructors
| NormalCursor | |
| CaretCursor | |
| DimCursor | |
| BlockCursor | |
| HeavyCursor | |
| SimpleCursor | 
Instances
Constructors
| DragNone | |
| DragStartDnd | |
| DragChar | |
| DragWord | |
| DragLine | 
data WrapTypeFl Source #
Constructors
| WrapNoneFl | |
| WrapAtColumnFl | |
| WrapAtPixelFl | |
| WrapAtBoundsFl | 
Instances
Constructors
| WrapNone | |
| WrapAtColumn ColumnNumber | |
| WrapAtPixel PixelPosition | |
| WrapAtBounds | 
data PageFormat Source #
Constructors
| A0 | |
| A1 | |
| A2 | |
| A3 | |
| A4 | |
| A5 | |
| A6 | |
| A7 | |
| A8 | |
| A9 | |
| B0 | |
| B1 | |
| B2 | |
| B3 | |
| B4 | |
| B5 | |
| B6 | |
| B7 | |
| B8 | |
| B9 | |
| B10 | |
| C5E | |
| DLE | |
| Executive | |
| Folio | |
| Ledger | |
| Legal | |
| Letter | |
| Tabloid | |
| Envelope | |
| Media | 
Instances
data TableRowSelectMode Source #
Constructors
| SelectNone | |
| SelectSingle | |
| SelectMulti | 
data TableContext Source #
Constructors
| ContextNone | |
| ContextStartPage | |
| ContextEndPage | |
| ContextRowHeader | |
| ContextColHeader | |
| ContextCell | |
| ContextTable | |
| ContextRCResize | 
Instances
data LinePosition Source #
Constructors
| LinePositionTop | |
| LinePositionBottom | |
| LinePositionMiddle | 
Instances
data ScrollbarMode Source #
Constructors
| HorizontalScrollBar | |
| VerticalScrollBar | |
| BothScrollBar | |
| AlwaysOnScrollBar | |
| HorizontalAlwaysScrollBar | |
| VerticalAlwaysScrollBar | |
| BothAlwaysScrollBar | 
Instances
data StyleTableEntry Source #
Instances
Constructors
| PackVertical | |
| PackHorizontal | 
type FlShortcut = CUInt Source #
newtype WindowHandle Source #
Constructors
| WindowHandle (Ptr ()) | 
Constructors
| Ref !(ForeignPtr (Ptr ())) | 
The FLTK widget hierarchy
Instances
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 #
Constructors
| Decimals (Between0And1, Between0And1, Between0And1) | |
| Words RGB | 
Instances
Constructors
| SpecialKeyType SpecialKey | |
| NormalKeyType Char | 
Constructors
| KeySequence ShortcutKeySequence | |
| KeyFormat Text | 
data KeyBindingKeySequence Source #
Constructors
| KeyBindingKeySequence (Maybe [EventState]) KeyType | 
Instances
data ScreenLocation Source #
Constructors
| Intersect Rectangle | |
| ScreenNumber Int | |
| ScreenPosition Position | 
Instances
Constructors
| InternalClipboard | |
| SharedClipboard | 
successOrAwakeRingFull :: Int -> Either AwakeRingFull () 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 #