| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
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
- data VFS = VFS {- _vfsMap :: !(Map NormalizedUri VirtualFile)
 
- vfsMap :: HasVfsMap s a => Lens' s a
- data VirtualFile = VirtualFile {- _lsp_version :: !Int32
- _file_version :: !Int
- _file_text :: !Rope
 
- lsp_version :: HasLsp_version s a => Lens' s a
- file_version :: HasFile_version s a => Lens' s a
- file_text :: HasFile_text s a => Lens' s a
- virtualFileText :: VirtualFile -> Text
- virtualFileVersion :: VirtualFile -> Int32
- data VfsLog- = SplitInsideCodePoint Position Rope
- | URINotFound NormalizedUri
- | Opening NormalizedUri
- | Closing NormalizedUri
- | PersistingFile NormalizedUri FilePath
- | CantRecursiveDelete NormalizedUri
- | DeleteNonExistent NormalizedUri
 
- emptyVFS :: VFS
- openVFS :: MonadState VFS m => LogAction m (WithSeverity VfsLog) -> TMessage 'Method_TextDocumentDidOpen -> m ()
- changeFromClientVFS :: MonadState VFS m => LogAction m (WithSeverity VfsLog) -> TMessage 'Method_TextDocumentDidChange -> m ()
- changeFromServerVFS :: forall m. MonadState VFS m => LogAction m (WithSeverity VfsLog) -> TMessage 'Method_WorkspaceApplyEdit -> m ()
- persistFileVFS :: MonadIO m => LogAction m (WithSeverity VfsLog) -> FilePath -> VFS -> NormalizedUri -> Maybe (FilePath, m ())
- closeVFS :: MonadState VFS m => LogAction m (WithSeverity VfsLog) -> TMessage 'Method_TextDocumentDidClose -> m ()
- data CodePointPosition = CodePointPosition {- _line :: UInt
- _character :: UInt
 
- line :: HasLine s a => Lens' s a
- character :: HasCharacter s a => Lens' s a
- codePointPositionToPosition :: VirtualFile -> CodePointPosition -> Maybe Position
- positionToCodePointPosition :: VirtualFile -> Position -> Maybe CodePointPosition
- data CodePointRange = CodePointRange {}
- start :: HasStart s a => Lens' s a
- end :: HasEnd s a => Lens' s a
- codePointRangeToRange :: VirtualFile -> CodePointRange -> Maybe Range
- rangeToCodePointRange :: VirtualFile -> Range -> Maybe CodePointRange
- rangeLinesFromVfs :: VirtualFile -> Range -> Text
- applyChanges :: Monad m => LogAction m (WithSeverity VfsLog) -> Rope -> [TextDocumentContentChangeEvent] -> m Rope
- applyChange :: Monad m => LogAction m (WithSeverity VfsLog) -> Rope -> TextDocumentContentChangeEvent -> m Rope
- changeChars :: Monad m => LogAction m (WithSeverity VfsLog) -> Rope -> Position -> Position -> Text -> m Rope
Documentation
Constructors
| VFS | |
| Fields 
 | |
data VirtualFile Source #
Constructors
| VirtualFile | |
| Fields 
 | |
Instances
| Show VirtualFile Source # | |
| Defined in Language.LSP.VFS Methods showsPrec :: Int -> VirtualFile -> ShowS # show :: VirtualFile -> String # showList :: [VirtualFile] -> ShowS # | |
lsp_version :: HasLsp_version s a => Lens' s a Source #
file_version :: HasFile_version s a => Lens' s a Source #
virtualFileText :: VirtualFile -> Text Source #
Constructors
| SplitInsideCodePoint Position Rope | |
| URINotFound NormalizedUri | |
| Opening NormalizedUri | |
| Closing NormalizedUri | |
| PersistingFile NormalizedUri FilePath | |
| CantRecursiveDelete NormalizedUri | |
| DeleteNonExistent NormalizedUri | 
Managing the VFS
openVFS :: MonadState VFS m => LogAction m (WithSeverity VfsLog) -> TMessage 'Method_TextDocumentDidOpen -> m () Source #
Applies the changes from a DidOpenTextDocument to the VFS
changeFromClientVFS :: MonadState VFS m => LogAction m (WithSeverity VfsLog) -> TMessage 'Method_TextDocumentDidChange -> m () Source #
Applies a DidChangeTextDocumentNotification to the VFS
changeFromServerVFS :: forall m. MonadState VFS m => LogAction m (WithSeverity VfsLog) -> TMessage 'Method_WorkspaceApplyEdit -> m () Source #
Applies the changes from a ApplyWorkspaceEditRequest to the VFS
persistFileVFS :: MonadIO m => LogAction m (WithSeverity VfsLog) -> FilePath -> VFS -> NormalizedUri -> Maybe (FilePath, m ()) Source #
Write a virtual file to a file in the given directory if it exists in the VFS.
closeVFS :: MonadState VFS m => LogAction m (WithSeverity VfsLog) -> TMessage 'Method_TextDocumentDidClose -> m () Source #
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 
 | |
Instances
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 
 | |
Instances
| Read CodePointRange Source # | |
| Defined in Language.LSP.VFS Methods readsPrec :: Int -> ReadS CodePointRange # readList :: ReadS [CodePointRange] # | |
| Show CodePointRange Source # | |
| Defined in Language.LSP.VFS Methods showsPrec :: Int -> CodePointRange -> ShowS # show :: CodePointRange -> String # showList :: [CodePointRange] -> ShowS # | |
| Eq CodePointRange Source # | |
| Defined in Language.LSP.VFS Methods (==) :: CodePointRange -> CodePointRange -> Bool # (/=) :: CodePointRange -> CodePointRange -> Bool # | |
| Ord CodePointRange Source # | |
| Defined in Language.LSP.VFS Methods compare :: CodePointRange -> CodePointRange -> Ordering # (<) :: CodePointRange -> CodePointRange -> Bool # (<=) :: CodePointRange -> CodePointRange -> Bool # (>) :: CodePointRange -> CodePointRange -> Bool # (>=) :: CodePointRange -> CodePointRange -> Bool # max :: CodePointRange -> CodePointRange -> CodePointRange # min :: CodePointRange -> CodePointRange -> CodePointRange # | |
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
rangeLinesFromVfs :: VirtualFile -> Range -> Text Source #
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.
applyChange :: Monad m => LogAction m (WithSeverity VfsLog) -> Rope -> TextDocumentContentChangeEvent -> m Rope Source #