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 WrapType
- data PageFormat
- data PageLayout
- data TableRowSelectMode
- data TableContext
- data LinePosition
- data ScrollbarMode
- data StyleTableEntry = StyleTableEntry (Maybe Color) (Maybe Font) (Maybe FontSize)
- data PackType
- data GLUTproc = GLUTproc (C2HSImp.FunPtr (IO ()))
- newtype GLUTIdleFunction = GLUTIdleFunction (C2HSImp.FunPtr (IO ()))
- newtype GLUTMenuStateFunction = GLUTMenuStateFunction (C2HSImp.FunPtr (C2HSImp.CInt -> IO ()))
- newtype GLUTMenuStatusFunction = GLUTMenuStatusFunction (C2HSImp.FunPtr (C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> IO ()))
- newtype GlutBitmapFontPtr = GlutBitmapFontPtr (C2HSImp.Ptr GlutBitmapFontPtr)
- newtype GlutStrokeVertexPtr = GlutStrokeVertexPtr (C2HSImp.Ptr GlutStrokeVertexPtr)
- newtype GlutStrokeStripPtr = GlutStrokeStripPtr (C2HSImp.Ptr GlutStrokeStripPtr)
- newtype GlutStrokeFontPtr = GlutStrokeFontPtr (C2HSImp.Ptr GlutStrokeFontPtr)
- type FlShortcut = C2HSImp.CUInt
- type FlColor = C2HSImp.CUInt
- type FlFont = C2HSImp.CInt
- type FlAlign = C2HSImp.CUInt
- type LineDelta = Maybe Int
- type Delta = Maybe Int
- type FlIntPtr = C2HSImp.CLong
- type FlUIntPtr = C2HSImp.CULong
- type ID = C2HSImp.Ptr ()
- data Ref a = Ref !(ForeignPtr (C2HSImp.Ptr ()))
- data FunRef = FunRef !(C2HSImp.FunPtr ())
- data CBase parent
- type Base = CBase ()
- type GlobalCallback = IO ()
- type CallbackWithUserDataPrim = C2HSImp.Ptr () -> C2HSImp.Ptr () -> IO ()
- type CallbackPrim = C2HSImp.Ptr () -> IO ()
- type ColorAverageCallbackPrim = C2HSImp.Ptr () -> C2HSImp.CUInt -> C2HSImp.CFloat -> IO ()
- type ImageDrawCallbackPrim = C2HSImp.Ptr () -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> IO ()
- type ImageCopyCallbackPrim = C2HSImp.Ptr () -> C2HSImp.CInt -> C2HSImp.CInt -> IO (C2HSImp.Ptr ())
- type GlobalEventHandlerPrim = C2HSImp.CInt -> IO C2HSImp.CInt
- type GlobalEventHandlerF = Event -> IO Int
- type DrawCallback = String -> Position -> IO ()
- type DrawCallbackPrim = CString -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> IO ()
- type TextBufferCallback = C2HSImp.FunPtr (C2HSImp.Ptr () -> IO ())
- type FileChooserCallback = C2HSImp.FunPtr (C2HSImp.Ptr () -> C2HSImp.Ptr () -> IO ())
- type SharedImageHandler = C2HSImp.FunPtr (CString -> C2HSImp.CUChar -> C2HSImp.CInt -> C2HSImp.Ptr ())
- type BoxDrawF = Rectangle -> Color -> IO ()
- type BoxDrawFPrim = C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> FlColor -> IO ()
- type FDHandlerPrim = C2HSImp.CInt -> C2HSImp.Ptr () -> IO ()
- type FDHandler = C2HSImp.CInt -> IO ()
- type TextModifyCb = Int -> Int -> Int -> Int -> String -> IO ()
- type TextModifyCbPrim = C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.Ptr C2HSImp.CChar -> C2HSImp.Ptr () -> IO ()
- type TextPredeleteCb = BufferOffset -> Int -> IO ()
- type TextPredeleteCbPrim = C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.Ptr () -> IO ()
- type UnfinishedStyleCb = BufferOffset -> IO ()
- type UnfinishedStyleCbPrim = C2HSImp.CInt -> C2HSImp.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 C2HSImp.CShort
- data Position = Position X Y
- data CountDirection
- data DPI = DPI Float Float
- newtype TextDisplayStyle = TextDisplayStyle C2HSImp.CInt
- newtype BufferOffset = BufferOffset Int
- data BufferRange = BufferRange BufferOffset BufferOffset
- statusToBufferRange :: (C2HSImp.Ptr C2HSImp.CInt -> C2HSImp.Ptr C2HSImp.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
- 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 C2HSImp.CInt
- newtype PixmapHs = PixmapHs [String]
- data BitmapHs = BitmapHs B.ByteString Size
- data Clipboard
- data UnknownError = UnknownError
- 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
- throwStackOnError :: IO a -> IO a
- withForeignPtrs :: [ForeignPtr a] -> ([C2HSImp.Ptr a] -> IO c) -> IO c
- toRefPtr :: HasCallStack => C2HSImp.Ptr (C2HSImp.Ptr a) -> IO (C2HSImp.Ptr a)
- withRef :: HasCallStack => Ref a -> (C2HSImp.Ptr b -> IO c) -> IO c
- isNull :: Ref a -> IO Bool
- unsafeRefToPtr :: Ref a -> IO (C2HSImp.Ptr ())
- withRefs :: [Ref a] -> (C2HSImp.Ptr (C2HSImp.Ptr b) -> IO c) -> IO c
- withMaybeRef :: Maybe (Ref a) -> (C2HSImp.Ptr () -> IO c) -> IO c
- swapRef :: Ref a -> (C2HSImp.Ptr b -> IO (C2HSImp.Ptr ())) -> IO ()
- wrapInRef :: ForeignPtr (C2HSImp.Ptr ()) -> Ref a
- toFunRef :: C2HSImp.FunPtr a -> FunRef
- fromFunRef :: FunRef -> C2HSImp.FunPtr ()
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 |
Constructors
WrapNone | |
WrapAtColumn | |
WrapAtPixel | |
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 |
Constructors
GLUTproc (C2HSImp.FunPtr (IO ())) |
newtype GLUTIdleFunction Source #
Constructors
GLUTIdleFunction (C2HSImp.FunPtr (IO ())) |
newtype GLUTMenuStateFunction Source #
Constructors
GLUTMenuStateFunction (C2HSImp.FunPtr (C2HSImp.CInt -> IO ())) |
newtype GLUTMenuStatusFunction Source #
Constructors
GLUTMenuStatusFunction (C2HSImp.FunPtr (C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> IO ())) |
newtype GlutBitmapFontPtr Source #
Constructors
GlutBitmapFontPtr (C2HSImp.Ptr GlutBitmapFontPtr) |
newtype GlutStrokeVertexPtr Source #
Constructors
GlutStrokeVertexPtr (C2HSImp.Ptr GlutStrokeVertexPtr) |
newtype GlutStrokeStripPtr Source #
Constructors
GlutStrokeStripPtr (C2HSImp.Ptr GlutStrokeStripPtr) |
newtype GlutStrokeFontPtr Source #
Constructors
GlutStrokeFontPtr (C2HSImp.Ptr GlutStrokeFontPtr) |
type FlShortcut = C2HSImp.CUInt Source #
type FlColor = C2HSImp.CUInt Source #
type FlFont = C2HSImp.CInt Source #
type FlAlign = C2HSImp.CUInt Source #
type FlIntPtr = C2HSImp.CLong Source #
type FlUIntPtr = C2HSImp.CULong Source #
type ID = C2HSImp.Ptr () Source #
Constructors
Ref !(ForeignPtr (C2HSImp.Ptr ())) |
Constructors
FunRef !(C2HSImp.FunPtr ()) |
The FLTK widget hierarchy
Instances
type GlobalCallback = IO () Source #
type CallbackWithUserDataPrim = C2HSImp.Ptr () -> C2HSImp.Ptr () -> IO () Source #
type CallbackPrim = C2HSImp.Ptr () -> IO () Source #
type ColorAverageCallbackPrim = C2HSImp.Ptr () -> C2HSImp.CUInt -> C2HSImp.CFloat -> IO () Source #
type ImageDrawCallbackPrim = C2HSImp.Ptr () -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> IO () Source #
type ImageCopyCallbackPrim = C2HSImp.Ptr () -> C2HSImp.CInt -> C2HSImp.CInt -> IO (C2HSImp.Ptr ()) Source #
type GlobalEventHandlerPrim = C2HSImp.CInt -> IO C2HSImp.CInt Source #
type DrawCallbackPrim = CString -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> IO () Source #
type TextBufferCallback = C2HSImp.FunPtr (C2HSImp.Ptr () -> IO ()) Source #
type FileChooserCallback = C2HSImp.FunPtr (C2HSImp.Ptr () -> C2HSImp.Ptr () -> IO ()) Source #
type SharedImageHandler = C2HSImp.FunPtr (CString -> C2HSImp.CUChar -> C2HSImp.CInt -> C2HSImp.Ptr ()) Source #
type BoxDrawFPrim = C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> FlColor -> IO () Source #
type FDHandlerPrim = C2HSImp.CInt -> C2HSImp.Ptr () -> IO () Source #
type FDHandler = C2HSImp.CInt -> IO () Source #
type TextModifyCbPrim = C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.Ptr C2HSImp.CChar -> C2HSImp.Ptr () -> IO () Source #
type TextPredeleteCb = BufferOffset -> Int -> IO () Source #
type TextPredeleteCbPrim = C2HSImp.CInt -> C2HSImp.CInt -> C2HSImp.Ptr () -> IO () Source #
type UnfinishedStyleCb = BufferOffset -> IO () Source #
type UnfinishedStyleCbPrim = C2HSImp.CInt -> C2HSImp.Ptr () -> IO () Source #
statusToBufferRange :: (C2HSImp.Ptr C2HSImp.CInt -> C2HSImp.Ptr C2HSImp.CInt -> IO Int) -> IO (Maybe BufferRange) Source #
data ColorChooserRGB Source #
Constructors
Decimals (Between0And1, Between0And1, Between0And1) | |
Words RGB |
Instances
Constructors
SpecialKeyType SpecialKey | |
NormalKeyType Char |
Constructors
KeySequence ShortcutKeySequence | |
KeyFormat String |
data KeyBindingKeySequence Source #
Constructors
KeyBindingKeySequence (Maybe [EventState]) KeyType |
Instances
data ScreenLocation Source #
Constructors
Intersect Rectangle | |
ScreenNumber Int | |
ScreenPosition Position |
Instances
Constructors
InternalClipboard | |
SharedClipboard |
successOrOutOfRange :: a -> Bool -> (a -> IO b) -> IO (Either OutOfRange b) Source #
data DataProcessingError Source #
throwStackOnError :: IO a -> IO a Source #
withForeignPtrs :: [ForeignPtr a] -> ([C2HSImp.Ptr a] -> IO c) -> IO c Source #
toRefPtr :: HasCallStack => C2HSImp.Ptr (C2HSImp.Ptr a) -> IO (C2HSImp.Ptr a) Source #
withRef :: HasCallStack => Ref a -> (C2HSImp.Ptr b -> IO c) -> IO c Source #
unsafeRefToPtr :: Ref a -> IO (C2HSImp.Ptr ()) Source #
withRefs :: [Ref a] -> (C2HSImp.Ptr (C2HSImp.Ptr b) -> IO c) -> IO c Source #
withMaybeRef :: Maybe (Ref a) -> (C2HSImp.Ptr () -> IO c) -> IO c Source #
swapRef :: Ref a -> (C2HSImp.Ptr b -> IO (C2HSImp.Ptr ())) -> IO () Source #
wrapInRef :: ForeignPtr (C2HSImp.Ptr ()) -> Ref a Source #
toFunRef :: C2HSImp.FunPtr a -> FunRef Source #
fromFunRef :: FunRef -> C2HSImp.FunPtr () Source #