Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data IDEBuffer = forall editor . TextEditor editor => IDEBuffer {
- fileName :: Maybe FilePath
- bufferName :: Text
- addedIndex :: Int
- sourceView :: EditorView editor
- scrolledWindow :: ScrolledWindow
- modTime :: IORef (Maybe UTCTime)
- mode :: Mode
- data BufferState
- maybeActiveBuf :: IDEM (Maybe IDEBuffer)
- lastActiveBufferPane :: IDEM (Maybe PaneName)
- recentSourceBuffers :: IDEM [PaneName]
- getStartAndEndLineOfSelection :: TextEditor editor => EditorBuffer editor -> IDEM (Int, Int)
- inBufContext :: MonadIDE m => alpha -> IDEBuffer -> (forall editor. TextEditor editor => Notebook -> EditorView editor -> EditorBuffer editor -> IDEBuffer -> Int -> m alpha) -> m alpha
- inActiveBufContext :: alpha -> (forall editor. TextEditor editor => Notebook -> EditorView editor -> EditorBuffer editor -> IDEBuffer -> Int -> IDEM alpha) -> IDEM alpha
- doForSelectedLines :: [a] -> (forall editor. TextEditor editor => EditorBuffer editor -> Int -> IDEM a) -> IDEM [a]
- data Mode = Mode {
- modeName :: Text
- modeEditComment :: IDEAction
- modeEditUncomment :: IDEAction
- modeSelectedModuleName :: IDEM (Maybe Text)
- modeEditToCandy :: (Text -> Bool) -> IDEAction
- modeTransformToCandy :: forall editor. TextEditor editor => (Text -> Bool) -> EditorBuffer editor -> IDEAction
- modeTransformFromCandy :: forall editor. TextEditor editor => EditorBuffer editor -> IDEAction
- modeEditFromCandy :: IDEAction
- modeEditKeystrokeCandy :: Maybe Char -> (Text -> Bool) -> IDEAction
- modeEditInsertCode :: forall editor. TextEditor editor => Text -> EditorIter editor -> EditorBuffer editor -> IDEAction
- modeEditInCommentOrString :: Text -> Bool
- modFromFileName :: Maybe FilePath -> Mode
- haskellMode :: Mode
- literalHaskellMode :: Mode
- cabalMode :: Mode
- otherMode :: Mode
- isHaskellMode :: Mode -> Bool
- withCurrentMode :: alpha -> (Mode -> IDEM alpha) -> IDEM alpha
- editComment :: IDEAction
- editUncomment :: IDEAction
- selectedModuleName :: IDEM (Maybe Text)
- editToCandy :: IDEAction
- editFromCandy :: IDEAction
- editKeystrokeCandy :: Maybe Char -> IDEAction
- editInsertCode :: TextEditor editor => EditorBuffer editor -> EditorIter editor -> Text -> IDEAction
Buffer Basics
A text editor pane description
forall editor . TextEditor editor => IDEBuffer | |
|
data BufferState Source
getStartAndEndLineOfSelection :: TextEditor editor => EditorBuffer editor -> IDEM (Int, Int) Source
inBufContext :: MonadIDE m => alpha -> IDEBuffer -> (forall editor. TextEditor editor => Notebook -> EditorView editor -> EditorBuffer editor -> IDEBuffer -> Int -> m alpha) -> m alpha Source
inActiveBufContext :: alpha -> (forall editor. TextEditor editor => Notebook -> EditorView editor -> EditorBuffer editor -> IDEBuffer -> Int -> IDEM alpha) -> IDEM alpha Source
doForSelectedLines :: [a] -> (forall editor. TextEditor editor => EditorBuffer editor -> Int -> IDEM a) -> IDEM [a] Source
Buffer Modes
Mode | |
|
modFromFileName :: Maybe FilePath -> Mode Source
Assumes
isHaskellMode :: Mode -> Bool Source
withCurrentMode :: alpha -> (Mode -> IDEM alpha) -> IDEM alpha Source
editInsertCode :: TextEditor editor => EditorBuffer editor -> EditorIter editor -> Text -> IDEAction Source