Safe Haskell | None |
---|---|
Language | GHC2021 |
Development.IDE.Types.Location
Description
Types and functions for working with source code locations.
Synopsis
- data Location = Location {}
- noFilePath :: FilePath
- noRange :: Range
- data Position = Position {
- _line :: UInt
- _character :: UInt
- showPosition :: Position -> String
- data Range = Range {}
- newtype Uri = Uri {}
- data NormalizedUri
- toNormalizedUri :: Uri -> NormalizedUri
- fromNormalizedUri :: NormalizedUri -> Uri
- data NormalizedFilePath
- fromUri :: NormalizedUri -> NormalizedFilePath
- emptyFilePath :: NormalizedFilePath
- emptyPathUri :: NormalizedUri
- toNormalizedFilePath' :: FilePath -> NormalizedFilePath
- fromNormalizedFilePath :: NormalizedFilePath -> FilePath
- filePathToUri' :: NormalizedFilePath -> NormalizedUri
- uriToFilePath' :: Uri -> Maybe FilePath
- readSrcSpan :: ReadS RealSrcSpan
Documentation
Instances
Constructors
Position | |
Fields
|
Instances
FromJSON Position | |||||
ToJSON Position | |||||
Generic Position | |||||
Defined in Language.LSP.Protocol.Internal.Types.Position Associated Types
| |||||
Show Position | |||||
NFData Position | |||||
Eq Position | |||||
Ord Position | |||||
Hashable Position | |||||
Pretty Position | |||||
HasCharacter Position UInt | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasEnd Range Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasLine Position UInt | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition CallHierarchyPrepareParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition CompletionParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition DeclarationParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition DefinitionParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition DocumentHighlightParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition DocumentOnTypeFormattingParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition HoverParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition ImplementationParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition InlayHint Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition LinkedEditingRangeParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition MonikerParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition PrepareRenameParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition ReferenceParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition RenameParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition SignatureHelpParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition TextDocumentPositionParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition TypeDefinitionParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPosition TypeHierarchyPrepareParams Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasStart Range Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasPositions SelectionRangeParams [Position] | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
type Rep Position | |||||
Defined in Language.LSP.Protocol.Internal.Types.Position type Rep Position = D1 ('MetaData "Position" "Language.LSP.Protocol.Internal.Types.Position" "lsp-types-2.3.0.1-FBxKf7HSq8k8Km3kag4dAL" 'False) (C1 ('MetaCons "Position" 'PrefixI 'True) (S1 ('MetaSel ('Just "_line") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UInt) :*: S1 ('MetaSel ('Just "_character") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UInt))) |
showPosition :: Position -> String Source #
Instances
FromJSON Range | |||||
Defined in Language.LSP.Protocol.Internal.Types.Range | |||||
ToJSON Range | |||||
Generic Range | |||||
Defined in Language.LSP.Protocol.Internal.Types.Range Associated Types
| |||||
Show Range | |||||
NFData Range | |||||
Defined in Language.LSP.Protocol.Internal.Types.Range | |||||
Eq Range | |||||
Ord Range | |||||
MapAge Range Source # | |||||
Hashable Range | |||||
Defined in Language.LSP.Protocol.Internal.Types.Range | |||||
Pretty Range | |||||
Defined in Language.LSP.Protocol.Internal.Types.Range | |||||
HasEnd Range Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasInsert EditRangeWithInsertReplace Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasInsert InsertReplaceEdit Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange AnnotatedTextEdit Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange CallHierarchyItem Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange CodeActionParams Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange CodeLens Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange ColorInformation Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange ColorPresentationParams Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange Diagnostic Range | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods | |||||
HasRange DocumentHighlight Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange DocumentLink Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange DocumentRangeFormattingParams Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange DocumentSymbol Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange InlayHintParams Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange InlineValueEvaluatableExpression Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange InlineValueParams Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange InlineValueText Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange InlineValueVariableLookup Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange Location Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange PrepareRenamePlaceholder Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange SelectionRange Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange SemanticTokensRangeParams Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange TextDocumentContentChangePartial Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange TextEdit Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRange TypeHierarchyItem Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasReplace EditRangeWithInsertReplace Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasReplace InsertReplaceEdit Range | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasSelectionRange CallHierarchyItem Range | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods selectionRange :: Lens' CallHierarchyItem Range | |||||
HasSelectionRange DocumentSymbol Range | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods selectionRange :: Lens' DocumentSymbol Range | |||||
HasSelectionRange TypeHierarchyItem Range | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods selectionRange :: Lens' TypeHierarchyItem Range | |||||
HasStart Range Position | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasStoppedLocation InlineValueContext Range | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods stoppedLocation :: Lens' InlineValueContext Range | |||||
HasTargetRange LocationLink Range | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods targetRange :: Lens' LocationLink Range | |||||
HasTargetSelectionRange LocationLink Range | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods targetSelectionRange :: Lens' LocationLink Range | |||||
HasEditRange CompletionItemDefaults (Maybe (Range |? EditRangeWithInsertReplace)) | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasFromRanges CallHierarchyIncomingCall [Range] | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods fromRanges :: Lens' CallHierarchyIncomingCall [Range] | |||||
HasFromRanges CallHierarchyOutgoingCall [Range] | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods fromRanges :: Lens' CallHierarchyOutgoingCall [Range] | |||||
HasOriginSelectionRange LocationLink (Maybe Range) | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods originSelectionRange :: Lens' LocationLink (Maybe Range) | |||||
HasRange Hover (Maybe Range) | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRanges LinkedEditingRanges [Range] | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasSelection ShowDocumentParams (Maybe Range) | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
type Rep Range | |||||
Defined in Language.LSP.Protocol.Internal.Types.Range type Rep Range = D1 ('MetaData "Range" "Language.LSP.Protocol.Internal.Types.Range" "lsp-types-2.3.0.1-FBxKf7HSq8k8Km3kag4dAL" 'False) (C1 ('MetaCons "Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "_start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Position) :*: S1 ('MetaSel ('Just "_end") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Position))) |
Instances
FromJSON Uri | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
FromJSONKey Uri | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
ToJSON Uri | |||||
ToJSONKey Uri | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
Generic Uri | |||||
Defined in Language.LSP.Protocol.Types.Uri Associated Types
| |||||
Read Uri | |||||
Show Uri | |||||
NFData Uri | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
Eq Uri | |||||
Ord Uri | |||||
Hashable Uri | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
Pretty Uri | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
HasDocument NotebookCell Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasHref CodeDescription Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasNewUri RenameFile Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasOldUri RenameFile Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasTargetUri LocationLink Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri CallHierarchyItem Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri CreateFile Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri DeleteFile Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri FileEvent Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri Location Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri LocationUriOnly Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri NotebookDocument Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri NotebookDocumentIdentifier Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri OptionalVersionedTextDocumentIdentifier Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri PreviousResultId Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri PublishDiagnosticsParams Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri ShowDocumentParams Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri TextDocumentIdentifier Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri TextDocumentItem Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri TypeHierarchyItem Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri VersionedNotebookDocumentIdentifier Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri VersionedTextDocumentIdentifier Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri WorkspaceFolder Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri WorkspaceFullDocumentDiagnosticReport Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasUri WorkspaceUnchangedDocumentDiagnosticReport Uri | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasChanges WorkspaceEdit (Maybe (Map Uri [TextEdit])) | |||||
HasRelatedDocuments RelatedFullDocumentDiagnosticReport (Maybe (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport))) | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods relatedDocuments :: Lens' RelatedFullDocumentDiagnosticReport (Maybe (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport))) | |||||
HasRelatedDocuments RelatedUnchangedDocumentDiagnosticReport (Maybe (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport))) | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods relatedDocuments :: Lens' RelatedUnchangedDocumentDiagnosticReport (Maybe (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport))) | |||||
HasScopeUri ConfigurationItem (Maybe Uri) | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasTarget DocumentLink (Maybe Uri) | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasBaseUri RelativePattern (WorkspaceFolder |? Uri) | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRelatedDocuments DocumentDiagnosticReportPartialResult (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport)) | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods relatedDocuments :: Lens' DocumentDiagnosticReportPartialResult (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport)) | |||||
HasRootUri InitializeParams (Uri |? Null) | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
HasRootUri UInitializeParams (Uri |? Null) | |||||
Defined in Language.LSP.Protocol.Types.Lens | |||||
type Rep Uri | |||||
Defined in Language.LSP.Protocol.Types.Uri |
data NormalizedUri #
Instances
Generic NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri Associated Types
| |||||
Read NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods readsPrec :: Int -> ReadS NormalizedUri # readList :: ReadS [NormalizedUri] # | |||||
Show NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods showsPrec :: Int -> NormalizedUri -> ShowS # show :: NormalizedUri -> String # showList :: [NormalizedUri] -> ShowS # | |||||
NFData NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods rnf :: NormalizedUri -> () # | |||||
Eq NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods (==) :: NormalizedUri -> NormalizedUri -> Bool # (/=) :: NormalizedUri -> NormalizedUri -> Bool # | |||||
Ord NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods compare :: NormalizedUri -> NormalizedUri -> Ordering # (<) :: NormalizedUri -> NormalizedUri -> Bool # (<=) :: NormalizedUri -> NormalizedUri -> Bool # (>) :: NormalizedUri -> NormalizedUri -> Bool # (>=) :: NormalizedUri -> NormalizedUri -> Bool # max :: NormalizedUri -> NormalizedUri -> NormalizedUri # min :: NormalizedUri -> NormalizedUri -> NormalizedUri # | |||||
Hashable NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
Pretty NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
HasVfsMap VFS (Map NormalizedUri VirtualFile) | |||||
Defined in Language.LSP.VFS Methods vfsMap :: Lens' VFS (Map NormalizedUri VirtualFile) # | |||||
type Rep NormalizedUri | |||||
Defined in Language.LSP.Protocol.Types.Uri type Rep NormalizedUri = D1 ('MetaData "NormalizedUri" "Language.LSP.Protocol.Types.Uri" "lsp-types-2.3.0.1-FBxKf7HSq8k8Km3kag4dAL" 'False) (C1 ('MetaCons "NormalizedUri" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
toNormalizedUri :: Uri -> NormalizedUri #
fromNormalizedUri :: NormalizedUri -> Uri #
data NormalizedFilePath #
Instances
IsString NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods fromString :: String -> NormalizedFilePath # | |||||
Generic NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri Associated Types
Methods from :: NormalizedFilePath -> Rep NormalizedFilePath x # to :: Rep NormalizedFilePath x -> NormalizedFilePath # | |||||
Show NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods showsPrec :: Int -> NormalizedFilePath -> ShowS # show :: NormalizedFilePath -> String # showList :: [NormalizedFilePath] -> ShowS # | |||||
Binary NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods put :: NormalizedFilePath -> Put # get :: Get NormalizedFilePath # putList :: [NormalizedFilePath] -> Put # | |||||
NFData NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods rnf :: NormalizedFilePath -> () # | |||||
Eq NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods (==) :: NormalizedFilePath -> NormalizedFilePath -> Bool # (/=) :: NormalizedFilePath -> NormalizedFilePath -> Bool # | |||||
Ord NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri Methods compare :: NormalizedFilePath -> NormalizedFilePath -> Ordering # (<) :: NormalizedFilePath -> NormalizedFilePath -> Bool # (<=) :: NormalizedFilePath -> NormalizedFilePath -> Bool # (>) :: NormalizedFilePath -> NormalizedFilePath -> Bool # (>=) :: NormalizedFilePath -> NormalizedFilePath -> Bool # max :: NormalizedFilePath -> NormalizedFilePath -> NormalizedFilePath # min :: NormalizedFilePath -> NormalizedFilePath -> NormalizedFilePath # | |||||
Hashable NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri | |||||
type Rep NormalizedFilePath | |||||
Defined in Language.LSP.Protocol.Types.Uri type Rep NormalizedFilePath = D1 ('MetaData "NormalizedFilePath" "Language.LSP.Protocol.Types.Uri" "lsp-types-2.3.0.1-FBxKf7HSq8k8Km3kag4dAL" 'False) (C1 ('MetaCons "NormalizedFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NormalizedUri) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
uriToFilePath' :: Uri -> Maybe FilePath Source #
We use an empty string as a filepath when we don’t have a file. However, haskell-lsp doesn’t support that in uriToFilePath and given that it is not a valid filepath it does not make sense to upstream a fix. So we have our own wrapper here that supports empty filepaths.
readSrcSpan :: ReadS RealSrcSpan Source #
Parser for the GHC output format