fltkhs-0.5.4.5: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Fl_Types

Contents

Synopsis

Documentation

type ID = Ptr () Source #

newtype WindowHandle Source #

Constructors

WindowHandle (Ptr ()) 

data Ref a Source #

Constructors

Ref !(ForeignPtr (Ptr ())) 

Instances

Eq (Ref a) Source # 

Methods

(==) :: Ref a -> Ref a -> Bool #

(/=) :: Ref a -> Ref a -> Bool #

Show (Ref a) Source # 

Methods

showsPrec :: Int -> Ref a -> ShowS #

show :: Ref a -> String #

showList :: [Ref a] -> ShowS #

data FunRef Source #

Constructors

FunRef !(FunPtr ()) 

The FLTK widget hierarchy

data CBase parent Source #

Instances

type Functions Base Source # 
type Functions Base = ()
type Functions FileInput Source # 
type Functions PNMImage Source # 
type Functions PNGImage Source # 
type Functions XPMImage Source # 
type Functions XBMImage Source # 
type Functions GIFImage Source # 
type Functions BMPImage Source # 
type Functions JPEGImage Source # 
type Functions RGBImage Source # 
type Functions FileBrowser Source # 
type Functions ColorChooser Source # 
type Functions Spinner Source # 
type Functions Tabs Source # 
type Functions Scrolled Source # 
type Functions Pack Source # 
type Functions Tile Source # 
type Functions NativeFileChooser Source # 
type Functions TextEditor Source # 
type Functions TextDisplay Source # 
type Functions TextBuffer Source # 
type Functions TextSelection Source # 
type Functions Tree Source # 
type Functions TreeItem Source # 
type Functions TreePrefs Source # 
type Functions Clock Source # 
type Functions IntInput Source # 
type Functions SelectBrowser Source # 
type Functions Browser Source # 
type Functions Box Source # 
type Functions Box = ()
type Functions GlWindow Source # 
type Functions TableRow Source # 
type Functions Table Source # 
type Functions Wizard Source # 
type Functions Positioner Source # 
type Functions Progress Source # 
type Functions ValueTimer Source # 
type Functions HiddenTimer Source # 
type Functions Timer Source # 
type Functions ValueOutput Source # 
type Functions ValueInput Source # 
type Functions Output Source # 
type Functions Input Source # 
type Functions HorValueSlider Source # 
type Functions ValueSlider Source # 
type Functions Scrollbar Source # 
type Functions SimpleCounter Source # 
type Functions Counter Source # 
type Functions Roller Source # 
type Functions LineDial Source # 
type Functions FillDial Source # 
type Functions Dial Source # 
type Functions Adjuster Source # 
type Functions ImageSurface Source # 
type Functions CopySurface Source # 
type Functions Pixmap Source # 
type Functions Bitmap Source # 
type Functions Image Source # 
type Functions MenuButton Source # 
type Functions Choice Source # 
type Functions SysMenuBar Source # 
type Functions MenuBar Source # 
type Functions MenuPrim Source # 
type Functions MenuItem Source # 
type Functions HorNiceSlider Source # 
type Functions NiceSlider Source # 
type Functions HorFillSlider Source # 
type Functions HorSlider Source # 
type Functions FillSlider Source # 
type Functions Slider Source # 
type Functions Valuator Source # 
type Functions ToggleButton Source # 
type Functions RepeatButton Source # 
type Functions RoundButton Source # 
type Functions ReturnButton Source # 
type Functions CheckButton Source # 
type Functions RadioLightButton Source # 
type Functions LightButton Source # 
type Functions Button Source # 
type Functions OverlayWindow Source # 
type Functions DoubleWindow Source # 
type Functions SingleWindow Source # 
type Functions Window Source # 
type Functions Group Source # 
type Functions Widget Source # 
type Functions GlContext Source # 
type Functions Region Source # 
type Functions Region = ()

type Base = CBase () Source #

type CallbackWithUserDataPrim = Ptr () -> Ptr () -> IO () Source #

type CallbackPrim = Ptr () -> IO () Source #

type ImageDrawCallbackPrim = Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () Source #

type ImageCopyCallbackPrim = Ptr () -> CInt -> CInt -> IO (Ptr ()) Source #

type FileChooserCallback = FunPtr (Ptr () -> Ptr () -> IO ()) Source #

type BoxDrawF = Rectangle -> Color -> IO () Source #

type BoxDrawFPrim = CInt -> CInt -> CInt -> CInt -> FlColor -> IO () Source #

type FDHandlerPrim = CInt -> Ptr () -> IO () Source #

type FDHandler = CInt -> IO () Source #

type TextModifyCb = Int -> Int -> Int -> Int -> Text -> IO () Source #

type TextModifyCbPrim = CInt -> CInt -> CInt -> CInt -> Ptr CChar -> Ptr () -> IO () Source #

type TextPredeleteCbPrim = CInt -> CInt -> Ptr () -> IO () Source #

newtype Width Source #

Constructors

Width Int 

Instances

Eq Width Source # 

Methods

(==) :: Width -> Width -> Bool #

(/=) :: Width -> Width -> Bool #

Show Width Source # 

Methods

showsPrec :: Int -> Width -> ShowS #

show :: Width -> String #

showList :: [Width] -> ShowS #

newtype Height Source #

Constructors

Height Int 

Instances

newtype Depth Source #

Constructors

Depth Int 

Instances

newtype LineSize Source #

Constructors

LineSize Int 

newtype X Source #

Constructors

X Int 

Instances

Eq X Source # 

Methods

(==) :: X -> X -> Bool #

(/=) :: X -> X -> Bool #

Show X Source # 

Methods

showsPrec :: Int -> X -> ShowS #

show :: X -> String #

showList :: [X] -> ShowS #

newtype Y Source #

Constructors

Y Int 

Instances

Eq Y Source # 

Methods

(==) :: Y -> Y -> Bool #

(/=) :: Y -> Y -> Bool #

Show Y Source # 

Methods

showsPrec :: Int -> Y -> ShowS #

show :: Y -> String #

showList :: [Y] -> ShowS #

newtype ByX Source #

Constructors

ByX Double 

Instances

Show ByX Source # 

Methods

showsPrec :: Int -> ByX -> ShowS #

show :: ByX -> String #

showList :: [ByX] -> ShowS #

newtype ByY Source #

Constructors

ByY Double 

Instances

Show ByY Source # 

Methods

showsPrec :: Int -> ByY -> ShowS #

show :: ByY -> String #

showList :: [ByY] -> ShowS #

newtype Angle Source #

Constructors

Angle CShort 

Instances

data DPI Source #

Constructors

DPI Float Float 

Instances

Show DPI Source # 

Methods

showsPrec :: Int -> DPI -> ShowS #

show :: DPI -> String #

showList :: [DPI] -> ShowS #

data ByXY Source #

Constructors

ByXY ByX ByY 

Instances

data Size Source #

Constructors

Size Width Height 

Instances

Eq Size Source # 

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

newtype FontSize Source #

Constructors

FontSize CInt 

newtype PixmapHs Source #

Constructors

PixmapHs [Text] 

data NotFound Source #

Constructors

NotFound 

successOrOutOfRange :: a -> Bool -> (a -> IO b) -> IO (Either OutOfRange b) Source #

data NoChange Source #

Constructors

NoChange 

withForeignPtrs :: [ForeignPtr a] -> ([Ptr a] -> IO c) -> IO c Source #

withRef :: HasCallStack => Ref a -> (Ptr b -> IO c) -> IO c Source #

withRefs :: HasCallStack => [Ref a] -> (Ptr (Ptr b) -> IO c) -> IO c Source #

withMaybeRef :: Maybe (Ref a) -> (Ptr () -> IO c) -> IO c Source #

swapRef :: Ref a -> (Ptr b -> IO (Ptr ())) -> IO () Source #