fltkhs-0.5.1.6: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.TextDisplay

Contents

Synopsis

Documentation

textDisplayCustom Source #

Arguments

:: Rectangle

The bounds of this TextDisplay

-> Maybe Text

The TextDisplay label

-> Maybe (Ref TextDisplay -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs TextDisplay)

Optional custom widget functions

-> IO (Ref TextDisplay) 

Hierarchy

Functions

colToX :: Ref TextDisplay -> Double -> IO (Double)

countLines :: Ref TextDisplay -> BufferRange -> Bool -> IO (Int)

destroy :: Ref TextDisplay -> IO ()

draw :: Ref TextDisplay -> IO ()

drawSuper :: Ref TextDisplay -> IO ()

getBuffer :: Ref TextDisplay -> IO (Maybe (Ref TextBuffer))

getCursorColor :: Ref TextDisplay -> IO (Color)

getInsertPosition :: Ref TextDisplay -> IO BufferOffset

getLinenumberAlign :: Ref TextDisplay -> IO (AlignType)

getLinenumberBgcolor :: Ref TextDisplay -> IO (Color)

getLinenumberFgcolor :: Ref TextDisplay -> IO (Color)

getLinenumberFont :: Ref TextDisplay -> IO (Font)

getLinenumberFormat :: Ref TextDisplay -> IO Text

getLinenumberSize :: Ref TextDisplay -> IO (FontSize)

getLinenumberWidth :: Ref TextDisplay -> IO (Width)

getScrollbarAlign :: Ref TextDisplay -> IO (AlignType)

getScrollbarWidth :: Ref TextDisplay -> IO (Width)

getShortcut :: Ref TextDisplay -> IO (Maybe ShortcutKeySequence)

getTextcolor :: Ref TextDisplay -> IO (Color)

getTextfont :: Ref TextDisplay -> IO (Font)

getTextsize :: Ref TextDisplay -> IO (FontSize)

handle :: Ref TextDisplay -> Event -> IO (Either UnknownEvent ())

handleSuper :: Ref TextDisplay -> Event -> IO (Either UnknownEvent ())

hide :: Ref TextDisplay -> IO ()

hideSuper :: Ref TextDisplay -> IO ()

highlightData:: (Parent a TextBuffer) => Ref TextDisplay -> Ref a -> [(Char, StyleTableEntry]) -> 'Maybe(Char,UnfinishedStyleCb') -> IO ()

inSelection :: Ref TextDisplay -> Position -> IO (Bool)

lineEnd :: Ref TextDisplay -> BufferOffset -> Bool -> IO (BufferOffset)

lineStart :: Ref TextDisplay -> BufferOffset -> IO (BufferOffset)

moveDown :: Ref TextDisplay -> IO (Either OutOfRange ())

moveLeft :: Ref TextDisplay -> IO (Either OutOfRange ())

moveRight :: Ref TextDisplay -> IO (Either OutOfRange ())

moveUp :: Ref TextDisplay -> IO (Either OutOfRange ())

nextWord :: Ref TextDisplay -> IO ()

overstrike :: Ref TextDisplay -> Text -> IO ()

positionStyle :: Ref TextDisplay -> BufferOffset -> Int -> Int -> IO TextDisplayStyle

positionToXy :: Ref TextDisplay -> BufferOffset -> IO (Either OutOfRange Position)

previousWord :: Ref TextDisplay -> IO ()

redisplayRange :: Ref TextDisplay -> BufferRange -> IO ()

resize :: Ref TextDisplay -> Rectangle -> IO ()

resizeSuper :: Ref TextDisplay -> Rectangle -> IO ()

rewindLines :: Ref TextDisplay -> BufferOffset -> Int -> IO (BufferOffset)

scroll :: Ref TextDisplay -> Int -> BufferOffset -> IO ()

setBuffer:: (Parent a TextBuffer) => Ref TextDisplay -> Maybe ( Ref a ) -> IO ()

setCursorColor :: Ref TextDisplay -> Color -> IO ()

setCursorStyle :: Ref TextDisplay -> CursorType -> IO ()

setInsertPosition :: Ref TextDisplay -> BufferOffset -> IO ()

setLinenumberAlign :: Ref TextDisplay -> AlignType -> IO ()

setLinenumberBgcolor :: Ref TextDisplay -> Color -> IO ()

setLinenumberFgcolor :: Ref TextDisplay -> Color -> IO ()

setLinenumberFont :: Ref TextDisplay -> Font -> IO ()

setLinenumberFormat :: Ref TextDisplay -> Text -> IO ()

setLinenumberSize :: Ref TextDisplay -> FontSize -> IO ()

setLinenumberWidth :: Ref TextDisplay -> Width -> IO ()

setScrollbarAlign :: Ref TextDisplay -> AlignType -> IO ()

setScrollbarWidth :: Ref TextDisplay -> Width -> IO ()

setShortcut :: Ref TextDisplay -> ShortcutKeySequence -> IO ()

setTextcolor :: Ref TextDisplay -> Color -> IO ()

setTextfont :: Ref TextDisplay -> Font -> IO ()

setTextsize :: Ref TextDisplay -> FontSize -> IO ()

showCursor :: Ref TextDisplay -> Bool -> IO ()

showInsertPosition :: Ref TextDisplay -> IO ()

showWidget :: Ref TextDisplay -> IO ()

showWidgetSuper :: Ref TextDisplay -> IO ()

skipLines :: Ref TextDisplay -> BufferOffset -> Int -> Bool -> IO (BufferOffset)

wordEnd :: Ref TextDisplay -> BufferOffset -> IO (BufferOffset)

wordStart :: Ref TextDisplay -> BufferOffset -> IO (BufferOffset)

wrapMode :: Ref TextDisplay -> WrapType -> IO ()

xToCol :: Ref TextDisplay -> Double -> IO (Double)

Orphan instances

(~) * impl (WrapType -> IO ()) => Op (WrapMode ()) TextDisplay orig impl Source # 

Methods

runOp :: WrapMode () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Text) => Op (GetLinenumberFormat ()) TextDisplay orig impl Source # 

Methods

runOp :: GetLinenumberFormat () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Text -> IO ()) => Op (SetLinenumberFormat ()) TextDisplay orig impl Source # 

Methods

runOp :: SetLinenumberFormat () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO AlignType) => Op (GetLinenumberAlign ()) TextDisplay orig impl Source # 

Methods

runOp :: GetLinenumberAlign () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (AlignType -> IO ()) => Op (SetLinenumberAlign ()) TextDisplay orig impl Source # 

Methods

runOp :: SetLinenumberAlign () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Color) => Op (GetLinenumberBgcolor ()) TextDisplay orig impl Source # 

Methods

runOp :: GetLinenumberBgcolor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Color -> IO ()) => Op (SetLinenumberBgcolor ()) TextDisplay orig impl Source # 

Methods

runOp :: SetLinenumberBgcolor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Color) => Op (GetLinenumberFgcolor ()) TextDisplay orig impl Source # 

Methods

runOp :: GetLinenumberFgcolor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Color -> IO ()) => Op (SetLinenumberFgcolor ()) TextDisplay orig impl Source # 

Methods

runOp :: SetLinenumberFgcolor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO FontSize) => Op (GetLinenumberSize ()) TextDisplay orig impl Source # 

Methods

runOp :: GetLinenumberSize () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (FontSize -> IO ()) => Op (SetLinenumberSize ()) TextDisplay orig impl Source # 

Methods

runOp :: SetLinenumberSize () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Font) => Op (GetLinenumberFont ()) TextDisplay orig impl Source # 

Methods

runOp :: GetLinenumberFont () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Font -> IO ()) => Op (SetLinenumberFont ()) TextDisplay orig impl Source # 

Methods

runOp :: SetLinenumberFont () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Width) => Op (GetLinenumberWidth ()) TextDisplay orig impl Source # 

Methods

runOp :: GetLinenumberWidth () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Width -> IO ()) => Op (SetLinenumberWidth ()) TextDisplay orig impl Source # 

Methods

runOp :: SetLinenumberWidth () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Double -> IO Double) => Op (ColToX ()) TextDisplay orig impl Source # 

Methods

runOp :: ColToX () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Double -> IO Double) => Op (XToCol ()) TextDisplay orig impl Source # 

Methods

runOp :: XToCol () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> Int -> Int -> IO TextDisplayStyle) => Op (PositionStyle ()) TextDisplay orig impl Source # 

Methods

runOp :: PositionStyle () -> orig -> Ref TextDisplay -> impl Source #

(Parent a TextBuffer, (~) * impl (Ref a -> [(Char, StyleTableEntry)] -> Maybe (Char, UnfinishedStyleCb) -> IO ())) => Op (HighlightData ()) TextDisplay orig impl Source # 

Methods

runOp :: HighlightData () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (AlignType -> IO ()) => Op (SetScrollbarAlign ()) TextDisplay orig impl Source # 

Methods

runOp :: SetScrollbarAlign () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO AlignType) => Op (GetScrollbarAlign ()) TextDisplay orig impl Source # 

Methods

runOp :: GetScrollbarAlign () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (CursorType -> IO ()) => Op (SetCursorStyle ()) TextDisplay orig impl Source # 

Methods

runOp :: SetCursorStyle () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Bool -> IO ()) => Op (ShowCursor ()) TextDisplay orig impl Source # 

Methods

runOp :: ShowCursor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (PreviousWord ()) TextDisplay orig impl Source # 

Methods

runOp :: PreviousWord () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (NextWord ()) TextDisplay orig impl Source # 

Methods

runOp :: NextWord () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO (Either OutOfRange ())) => Op (MoveDown ()) TextDisplay orig impl Source # 

Methods

runOp :: MoveDown () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO (Either OutOfRange ())) => Op (MoveUp ()) TextDisplay orig impl Source # 

Methods

runOp :: MoveUp () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO (Either OutOfRange ())) => Op (MoveLeft ()) TextDisplay orig impl Source # 

Methods

runOp :: MoveLeft () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO (Either OutOfRange ())) => Op (MoveRight ()) TextDisplay orig impl Source # 

Methods

runOp :: MoveRight () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (ShowInsertPosition ()) TextDisplay orig impl Source # 

Methods

runOp :: ShowInsertPosition () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Position -> IO Bool) => Op (InSelection ()) TextDisplay orig impl Source # 

Methods

runOp :: InSelection () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> IO (Either OutOfRange Position)) => Op (PositionToXy ()) TextDisplay orig impl Source # 

Methods

runOp :: PositionToXy () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO BufferOffset) => Op (GetInsertPosition ()) TextDisplay orig impl Source # 

Methods

runOp :: GetInsertPosition () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> IO ()) => Op (SetInsertPosition ()) TextDisplay orig impl Source # 

Methods

runOp :: SetInsertPosition () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Text -> IO ()) => Op (Overstrike ()) TextDisplay orig impl Source # 

Methods

runOp :: Overstrike () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Int -> BufferOffset -> IO ()) => Op (Scroll ()) TextDisplay orig impl Source # 

Methods

runOp :: Scroll () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferRange -> IO ()) => Op (RedisplayRange ()) TextDisplay orig impl Source # 

Methods

runOp :: RedisplayRange () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO (Maybe (Ref TextBuffer))) => Op (GetBuffer ()) TextDisplay orig impl Source # 

Methods

runOp :: GetBuffer () -> orig -> Ref TextDisplay -> impl Source #

(Parent a TextBuffer, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetBuffer ()) TextDisplay orig impl Source # 

Methods

runOp :: SetBuffer () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> Int -> IO BufferOffset) => Op (RewindLines ()) TextDisplay orig impl Source # 

Methods

runOp :: RewindLines () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> Int -> Bool -> IO BufferOffset) => Op (SkipLines ()) TextDisplay orig impl Source # 

Methods

runOp :: SkipLines () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferRange -> Bool -> IO Int) => Op (CountLines ()) TextDisplay orig impl Source # 

Methods

runOp :: CountLines () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> IO BufferOffset) => Op (WordEnd ()) TextDisplay orig impl Source # 

Methods

runOp :: WordEnd () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> IO BufferOffset) => Op (WordStart ()) TextDisplay orig impl Source # 

Methods

runOp :: WordStart () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> Bool -> IO BufferOffset) => Op (LineEnd ()) TextDisplay orig impl Source # 

Methods

runOp :: LineEnd () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (BufferOffset -> IO BufferOffset) => Op (LineStart ()) TextDisplay orig impl Source # 

Methods

runOp :: LineStart () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Width -> IO ()) => Op (SetScrollbarWidth ()) TextDisplay orig impl Source # 

Methods

runOp :: SetScrollbarWidth () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Width) => Op (GetScrollbarWidth ()) TextDisplay orig impl Source # 

Methods

runOp :: GetScrollbarWidth () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Color -> IO ()) => Op (SetCursorColor ()) TextDisplay orig impl Source # 

Methods

runOp :: SetCursorColor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Color) => Op (GetCursorColor ()) TextDisplay orig impl Source # 

Methods

runOp :: GetCursorColor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) TextDisplay orig impl Source # 

Methods

runOp :: SetTextcolor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Color) => Op (GetTextcolor ()) TextDisplay orig impl Source # 

Methods

runOp :: GetTextcolor () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) TextDisplay orig impl Source # 

Methods

runOp :: SetTextsize () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO FontSize) => Op (GetTextsize ()) TextDisplay orig impl Source # 

Methods

runOp :: GetTextsize () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Font -> IO ()) => Op (SetTextfont ()) TextDisplay orig impl Source # 

Methods

runOp :: SetTextfont () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO Font) => Op (GetTextfont ()) TextDisplay orig impl Source # 

Methods

runOp :: GetTextfont () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (Draw ()) TextDisplay orig impl Source # 

Methods

runOp :: Draw () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) TextDisplay orig impl Source # 

Methods

runOp :: SetShortcut () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO (Maybe ShortcutKeySequence)) => Op (GetShortcut ()) TextDisplay orig impl Source # 

Methods

runOp :: GetShortcut () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) TextDisplay orig impl Source # 

Methods

runOp :: HandleSuper () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (DrawSuper ()) TextDisplay orig impl Source # 

Methods

runOp :: DrawSuper () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Rectangle -> IO ()) => Op (Resize ()) TextDisplay orig impl Source # 

Methods

runOp :: Resize () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) TextDisplay orig impl Source # 

Methods

runOp :: ResizeSuper () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (Hide ()) TextDisplay orig impl Source # 

Methods

runOp :: Hide () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (HideSuper ()) TextDisplay orig impl Source # 

Methods

runOp :: HideSuper () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (ShowWidget ()) TextDisplay orig impl Source # 

Methods

runOp :: ShowWidget () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (ShowWidgetSuper ()) TextDisplay orig impl Source # 

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) TextDisplay orig impl Source # 

Methods

runOp :: Handle () -> orig -> Ref TextDisplay -> impl Source #

(~) * impl (IO ()) => Op (Destroy ()) TextDisplay orig impl Source # 

Methods

runOp :: Destroy () -> orig -> Ref TextDisplay -> impl Source #