lsp-1.6.0.0: Haskell library for the Microsoft Language Server Protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.LSP.VFS

Description

Handles the Language.LSP.Types.TextDocumentDidChange / Language.LSP.Types.TextDocumentDidOpen / Language.LSP.Types.TextDocumentDidClose messages to keep an in-memory filesystem of the current client workspace. The server can access and edit files in the client workspace by operating on the VFS in LspFuncs.

Synopsis

Documentation

data VFS Source #

Constructors

VFS 

Fields

Instances

Instances details
Show VFS Source # 
Instance details

Defined in Language.LSP.VFS

Methods

showsPrec :: Int -> VFS -> ShowS #

show :: VFS -> String #

showList :: [VFS] -> ShowS #

vfsMap :: HasVfsMap s a => Lens' s a Source #

vfsTempDir :: HasVfsTempDir s a => Lens' s a Source #

data VirtualFile Source #

Constructors

VirtualFile 

Fields

Instances

Instances details
Show VirtualFile Source # 
Instance details

Defined in Language.LSP.VFS

lsp_version :: HasLsp_version s a => Lens' s a Source #

file_version :: HasFile_version s a => Lens' s a Source #

file_text :: HasFile_text s a => Lens' s a Source #

Managing the VFS

initVFS :: (VFS -> IO r) -> IO r Source #

openVFS :: MonadState VFS m => LogAction m (WithSeverity VfsLog) -> Message 'TextDocumentDidOpen -> m () Source #

Applies the changes from a DidOpenTextDocument to the VFS

changeFromClientVFS :: MonadState VFS m => LogAction m (WithSeverity VfsLog) -> Message 'TextDocumentDidChange -> m () Source #

Applies a DidChangeTextDocumentNotification to the VFS

changeFromServerVFS :: forall m. MonadState VFS m => LogAction m (WithSeverity VfsLog) -> Message 'WorkspaceApplyEdit -> m () Source #

Applies the changes from a ApplyWorkspaceEditRequest to the VFS

persistFileVFS :: MonadIO m => LogAction m (WithSeverity VfsLog) -> VFS -> NormalizedUri -> Maybe (FilePath, m ()) Source #

Write a virtual file to a temporary file if it exists in the VFS.

Positions and transformations

data CodePointPosition Source #

A position, like a Position, but where the offsets in the line are measured in Unicode code points instead of UTF-16 code units.

Constructors

CodePointPosition 

Fields

  • _line :: UInt

    Line position in a document (zero-based).

  • _character :: UInt

    Character offset on a line in a document in *code points* (zero-based).

line :: HasLine s a => Lens' s a Source #

character :: HasCharacter s a => Lens' s a Source #

codePointPositionToPosition :: VirtualFile -> CodePointPosition -> Maybe Position Source #

Given a virtual file, translate a CodePointPosition in that file into a Position in that file.

Will return Nothing if the requested position is out of bounds of the document.

Logarithmic in the number of lines in the document, and linear in the length of the line containing the position.

positionToCodePointPosition :: VirtualFile -> Position -> Maybe CodePointPosition Source #

Given a virtual file, translate a Position in that file into a CodePointPosition in that file.

Will return Nothing if the requested position lies inside a code point, or if it is out of bounds of the document.

Logarithmic in the number of lines in the document, and linear in the length of the line containing the position.

data CodePointRange Source #

A range, like a Range, but where the offsets in the line are measured in Unicode code points instead of UTF-16 code units.

Constructors

CodePointRange 

Fields

start :: HasStart s a => Lens' s a Source #

end :: HasEnd s a => Lens' s a Source #

codePointRangeToRange :: VirtualFile -> CodePointRange -> Maybe Range Source #

Given a virtual file, translate a CodePointRange in that file into a Range in that file.

Will return Nothing if any of the positions are out of bounds of the document.

Logarithmic in the number of lines in the document, and linear in the length of the lines containing the positions.

rangeToCodePointRange :: VirtualFile -> Range -> Maybe CodePointRange Source #

Given a virtual file, translate a Range in that file into a CodePointRange in that file.

Will return Nothing if any of the positions are out of bounds of the document.

Logarithmic in the number of lines in the document, and linear in the length of the lines containing the positions.

manipulating the file contents

data PosPrefixInfo Source #

Describes the line at the current cursor position

Constructors

PosPrefixInfo 

Fields

  • fullLine :: !Text

    The full contents of the line the cursor is at

  • prefixModule :: !Text

    If any, the module name that was typed right before the cursor position. For example, if the user has typed "Data.Maybe.from", then this property will be Data.Maybe

  • prefixText :: !Text

    The word right before the cursor position, after removing the module part. For example if the user has typed "Data.Maybe.from", then this property will be "from"

  • cursorPos :: !Position

    The cursor position

Instances

Instances details
Show PosPrefixInfo Source # 
Instance details

Defined in Language.LSP.VFS

Eq PosPrefixInfo Source # 
Instance details

Defined in Language.LSP.VFS

for tests

applyChanges :: Monad m => LogAction m (WithSeverity VfsLog) -> Rope -> [TextDocumentContentChangeEvent] -> m Rope Source #

Apply the list of changes. Changes should be applied in the order that they are received from the client.

changeChars :: Monad m => LogAction m (WithSeverity VfsLog) -> Rope -> Position -> Position -> Text -> m Rope Source #

Given a Rope, start and end positions, and some new text, replace the given range with the new text. If the given positions lie within a code point then this does nothing (returns the original Rope) and logs.