fltkhs-0.8.0.0: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.TextBuffer

Contents

Synopsis

Documentation

Hierarchy

Functions

addModifyCallback :: Ref TextBuffer -> TextModifyCb -> IO (FunPtr ())

addPredeleteCallback :: Ref TextBuffer -> TextPredeleteCb -> IO (FunPtr ())

appendToBuffer :: Ref TextBuffer -> Text -> IO ()

appendfile :: Ref TextBuffer -> Text -> IO (Either DataProcessingError ())

appendfileWithBuflen :: Ref TextBuffer -> Text -> Int -> IO (Either DataProcessingError ())

byteAt :: Ref TextBuffer -> AtIndex -> IO Char

callModifyCallbacks :: Ref TextBuffer -> IO ()

callPredeleteCallbacks :: Ref TextBuffer -> IO ()

canUndo :: Ref TextBuffer -> Bool -> IO ()

charAt :: Ref TextBuffer -> AtIndex -> IO (Char)

copy:: (Parent a TextBuffer) => Ref TextBuffer -> Ref a -> IndexRange -> AtIndex -> IO ()

countDisplayedCharacters :: Ref TextBuffer -> IndexRange -> IO (Int)

countLines :: Ref TextBuffer -> IndexRange -> IO (Lines)

destroy :: Ref TextBuffer -> IO ()

fileEncodingWarningMessage :: Ref TextBuffer -> IO Text

findcharBackward :: Ref TextBuffer -> AtIndex -> Char -> IO (Either NotFound AtIndex)

findcharForward :: Ref TextBuffer -> AtIndex -> Char -> IO (Either NotFound AtIndex)

getHighlight :: Ref TextBuffer -> IO (Bool)

getLength :: Ref TextBuffer -> IO (Int)

getTabDistance :: Ref TextBuffer -> IO (Int)

getText :: Ref TextBuffer -> IO Text

highlightPosition :: Ref TextBuffer -> IO (Maybe IndexRange)

highlightSelection :: Ref TextBuffer -> IO (Maybe (Ref TextSelection))

highlightText :: Ref TextBuffer -> IO Text

inputFileWasTranscoded :: Ref TextBuffer -> IO (Bool)

insert :: Ref TextBuffer -> AtIndex -> Text -> IO ()

insertfile :: Ref TextBuffer -> Text -> AtIndex -> IO (Either DataProcessingError ())

insertfileWithBuflen :: Ref TextBuffer -> Text -> AtIndex -> Int -> IO (Either DataProcessingError ())

lineEnd :: Ref TextBuffer -> LineNumber -> IO (Either OutOfRange AtIndex)

lineStart :: Ref TextBuffer -> LineNumber -> IO (Either OutOfRange AtIndex)

lineText :: Ref TextBuffer -> LineNumber -> IO (Either OutOfRange String)

loadfile :: Ref TextBuffer -> Text -> IO (Either DataProcessingError ())

loadfileWithBuflen :: Ref TextBuffer -> Text -> Int -> IO (Either DataProcessingError ())

nextChar :: Ref TextBuffer -> AtIndex -> IO AtIndex

nextCharClipped :: Ref TextBuffer -> AtIndex -> IO (AtIndex)

outputfile :: Ref TextBuffer -> Text -> IndexRange -> IO (Either DataProcessingError ())

outputfileWithBuflen :: Ref TextBuffer -> Text -> IndexRange -> Int -> IO (Either DataProcessingError ())

prevChar :: Ref TextBuffer -> AtIndex -> IO (Either OutOfRange AtIndex)

prevCharClipped :: Ref TextBuffer -> AtIndex -> IO (Either OutOfRange AtIndex)

primarySelection :: Ref TextBuffer -> IO (Maybe (Ref TextSelection))

remove :: Ref TextBuffer -> IndexRange -> IO ()

removeModifyCallback :: Ref TextBuffer -> FunPtr () -> IO ()

removePredeleteCallback :: Ref TextBuffer -> FunPtr () -> IO ()

removeSecondarySelection :: Ref TextBuffer -> IO ()

removeSelection :: Ref TextBuffer -> IO ()

replace :: Ref TextBuffer -> IndexRange -> Text -> IO ()

replaceSecondarySelection :: Ref TextBuffer -> Text -> IO ()

replaceSelection :: Ref TextBuffer -> Text -> IO ()

rewindLines :: Ref TextBuffer -> AtIndex -> Lines -> IO (AtIndex)

savefile :: Ref TextBuffer -> Text -> IO (Either DataProcessingError ())

savefileWithBuflen :: Ref TextBuffer -> Text -> Int -> IO (Either DataProcessingError ())

searchBackwardWithMatchcase :: Ref TextBuffer -> AtIndex -> Text -> Bool -> IO (Either NotFound AtIndex)

searchForwardWithMatchcase :: Ref TextBuffer -> AtIndex -> Text -> Bool -> IO (Either NotFound AtIndex)

secondarySelect :: Ref TextBuffer -> IndexRange -> IO ()

secondarySelected :: Ref TextBuffer -> IO (Bool)

secondarySelection :: Ref TextBuffer -> IO (Maybe (Ref TextSelection))

secondarySelectionPosition :: Ref TextBuffer -> IO IndexRange

secondarySelectionText :: Ref TextBuffer -> IO Text

secondaryUnselect :: Ref TextBuffer -> IO ()

select :: Ref TextBuffer -> IndexRange -> IO ()

selected :: Ref TextBuffer -> IO (Bool)

selectionPosition :: Ref TextBuffer -> IO (IndexRange)

selectionText :: Ref TextBuffer -> IO Text

setHighlight :: Ref TextBuffer -> IndexRange -> IO ()

setTabDistance :: Ref TextBuffer -> Int -> IO ()

setText :: Ref TextBuffer -> Text -> IO ()

skipDisplayedCharacters :: Ref TextBuffer -> AtIndex>- Int -> IO (AtIndex)

skipLines :: Ref TextBuffer -> AtIndex -> Lines -> IO (AtIndex)

textRange :: Ref TextBuffer -> IndexRange -> IO Text

undo :: Ref TextBuffer -> IO (Either NoChange AtIndex)

unhighlight :: Ref TextBuffer -> IO ()

unselect :: Ref TextBuffer -> IO ()

utf8Align :: Ref TextBuffer -> AtIndex -> IO (Either OutOfRange AtIndex)

wordEnd :: Ref TextBuffer -> AtIndex -> IO (Either OutOfRange AtIndex)

wordStart :: Ref TextBuffer -> AtIndex -> IO (Either OutOfRange AtIndex)

Orphan instances

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (Utf8Align ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Utf8Align () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO AtIndex) => Op (NextCharClipped ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: NextCharClipped () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO AtIndex) => Op (NextChar ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: NextChar () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (PrevCharClipped ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: PrevCharClipped () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (PrevChar ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: PrevChar () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Maybe (Ref TextSelection)) => Op (HighlightSelection ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: HighlightSelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Maybe (Ref TextSelection)) => Op (SecondarySelection ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SecondarySelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Maybe (Ref TextSelection)) => Op (PrimarySelection ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: PrimarySelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Text -> Bool -> IO (Either NotFound AtIndex)) => Op (SearchBackwardWithMatchcase ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SearchBackwardWithMatchcase () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Text -> Bool -> IO (Either NotFound AtIndex)) => Op (SearchForwardWithMatchcase ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SearchForwardWithMatchcase () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Char -> IO (Either NotFound AtIndex)) => Op (FindcharBackward ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: FindcharBackward () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Char -> IO (Either NotFound AtIndex)) => Op (FindcharForward ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: FindcharForward () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Lines -> IO AtIndex) => Op (RewindLines ()) TextBuffer orig impl Source # 
Instance details

Methods

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

impl ~ (AtIndex -> Lines -> IO AtIndex) => Op (SkipLines ()) TextBuffer orig impl Source # 
Instance details

Methods

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

impl ~ (IndexRange -> IO Lines) => Op (CountLines ()) TextBuffer orig impl Source # 
Instance details

Methods

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

impl ~ (AtIndex -> Int -> IO AtIndex) => Op (SkipDisplayedCharacters ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SkipDisplayedCharacters () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO Int) => Op (CountDisplayedCharacters ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: CountDisplayedCharacters () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (WordEnd ()) TextBuffer orig impl Source # 
Instance details

Methods

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

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (WordStart ()) TextBuffer orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO (Either OutOfRange AtIndex)) => Op (LineEnd ()) TextBuffer orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO (Either OutOfRange AtIndex)) => Op (LineStart ()) TextBuffer orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO (Either OutOfRange String)) => Op (LineText ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: LineText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (CallPredeleteCallbacks ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: CallPredeleteCallbacks () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (FunPtr () -> IO ()) => Op (RemovePredeleteCallback ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: RemovePredeleteCallback () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (TextPredeleteCb -> IO (FunPtr ())) => Op (AddPredeleteCallback ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: AddPredeleteCallback () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (CallModifyCallbacks ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: CallModifyCallbacks () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (FunPtr () -> IO ()) => Op (RemoveModifyCallback ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: RemoveModifyCallback () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (TextModifyCb -> IO (FunPtr ())) => Op (AddModifyCallback ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: AddModifyCallback () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (HighlightText ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: HighlightText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Maybe IndexRange) => Op (HighlightPosition ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: HighlightPosition () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (Unhighlight ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Unhighlight () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (SetHighlight ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SetHighlight () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Bool => Op (GetHighlight ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: GetHighlight () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO ()) => Op (ReplaceSecondarySelection ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: ReplaceSecondarySelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (RemoveSecondarySelection ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: RemoveSecondarySelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (SecondarySelectionText ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SecondarySelectionText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO IndexRange => Op (SecondarySelectionPosition ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SecondarySelectionPosition () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (SecondaryUnselect ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SecondaryUnselect () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Bool => Op (SecondarySelected ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SecondarySelected () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (SecondarySelect ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SecondarySelect () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO ()) => Op (ReplaceSelection ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: ReplaceSelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (RemoveSelection ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: RemoveSelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (SelectionText ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SelectionText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO IndexRange => Op (SelectionPosition ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SelectionPosition () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (Unselect ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Unselect () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Int -> IO ()) => Op (SetTabDistance ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SetTabDistance () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Int => Op (GetTabDistance ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: GetTabDistance () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> Int -> IO (Either DataProcessingError ())) => Op (SavefileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SavefileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO (Either DataProcessingError ())) => Op (Savefile ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Savefile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IndexRange -> Int -> IO (Either DataProcessingError ())) => Op (OutputfileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: OutputfileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IndexRange -> IO (Either DataProcessingError ())) => Op (Outputfile ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Outputfile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> Int -> IO (Either DataProcessingError ())) => Op (LoadfileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: LoadfileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO (Either DataProcessingError ())) => Op (Loadfile ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Loadfile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> Int -> IO (Either DataProcessingError ())) => Op (AppendfileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: AppendfileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO (Either DataProcessingError ())) => Op (Appendfile ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Appendfile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> AtIndex -> Int -> IO (Either DataProcessingError ())) => Op (InsertfileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: InsertfileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> AtIndex -> IO (Either DataProcessingError ())) => Op (Insertfile ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Insertfile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Bool -> IO ()) => Op (CanUndo ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: CanUndo () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO ()) => Op (AppendToBuffer ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: AppendToBuffer () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO Char) => Op (ByteAt ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: ByteAt () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO Char) => Op (CharAt ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: CharAt () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO Text) => Op (TextRange ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: TextRange () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Int => Op (GetLength ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: GetLength () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (FileEncodingWarningMessage ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: FileEncodingWarningMessage () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Bool => Op (InputFileWasTranscoded ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: InputFileWasTranscoded () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO ()) => Op (SetText ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: SetText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Bool => Op (Selected ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Selected () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (Select ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Select () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Either NoChange AtIndex) => Op (Undo ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Undo () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (GetText ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: GetText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (Remove ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Remove () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> Text -> IO ()) => Op (Replace ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Replace () -> orig -> Ref TextBuffer -> impl Source #

(Parent a TextBuffer, impl ~ (Ref a -> IndexRange -> AtIndex -> IO ())) => Op (Copy ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Copy () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Text -> IO ()) => Op (Insert ()) TextBuffer orig impl Source # 
Instance details

Methods

runOp :: Insert () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (Destroy ()) TextBuffer orig impl Source # 
Instance details

Methods

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