6
6
{-# LANGUAGE DataKinds #-}
7
7
{-# LANGUAGE ViewPatterns #-}
8
8
{-# LANGUAGE OverloadedStrings #-}
9
+ {-# LANGUAGE RecordWildCards #-}
9
10
10
11
11
12
module Ide.Plugin.Cabal.Outline
@@ -14,37 +15,63 @@ module Ide.Plugin.Cabal.Outline
14
15
where
15
16
16
17
import Control.Monad.IO.Class
17
- import Data.Foldable (toList )
18
- import Data.Functor
19
- import Data.List.NonEmpty (nonEmpty )
20
18
import Data.Maybe
21
19
import Development.IDE.Core.Rules
22
- import Development.IDE.Core.Shake
23
- import Development.IDE.GHC.Compat
24
- import Development.IDE.GHC.Error (rangeToRealSrcSpan ,
25
- realSrcSpanToRange )
26
- import Development.IDE.Types.Location
27
- import Development.IDE.GHC.Util (printOutputable )
20
+ import Development.IDE.Core.Shake ( IdeState (shakeExtras ), runIdeAction , useWithStaleFast )
21
+ import Development.IDE.Types.Location ( toNormalizedFilePath' )
28
22
import Ide.Types
29
- import Language.LSP.Protocol.Types (DocumentSymbol (.. ),
30
- DocumentSymbolParams (DocumentSymbolParams , _textDocument ),
31
- SymbolKind (.. ),
32
- TextDocumentIdentifier (TextDocumentIdentifier ),
33
- type (|? ) (InL , InR ), uriToFilePath , mkRange , SymbolInformation (_deprecated ))
34
- import Language.LSP.Protocol.Message
35
- ( Method (Method_TextDocumentDocumentSymbol ) )
23
+ import qualified Language.LSP.Protocol.Types as LSP
24
+ import qualified Language.LSP.Protocol.Message as LSP
25
+
26
+ import Data.Text.Encoding (decodeASCII )
27
+
28
+ import Ide.Plugin.Cabal.Completion.Types (ParseCabalFields (.. ))
29
+ import Ide.Plugin.Cabal.Orphans ()
30
+
31
+ import Distribution.Fields.Field (Field (Field ), Name (Name ))
32
+ import Distribution.Parsec.Position (Position (Position ))
36
33
37
34
import qualified Data.Text as T
35
+ import Debug.Trace as Debug
36
+
37
+ moduleOutline :: PluginMethodHandler IdeState LSP. Method_TextDocumentDocumentSymbol
38
+ moduleOutline ideState _ LSP. DocumentSymbolParams { _textDocument = LSP. TextDocumentIdentifier uri }
39
+ = case LSP. uriToFilePath uri of
40
+ Just (toNormalizedFilePath' -> fp) -> do
41
+ mFields <- liftIO $ runIdeAction " cabal-plugin.fields" (shakeExtras ideState) (useWithStaleFast ParseCabalFields fp)
42
+ let debug = fmap fst mFields
43
+ -- Debug.traceShowM debug
44
+ case fmap fst mFields of
45
+ Just fieldPositions -> pure $ LSP. InR (LSP. InL allSymbols)
46
+ where
47
+ allSymbols = mapMaybe documentSymbolForField fieldPositions
48
+ -- pure $ InR (InL [DocumentSymbol {_name="hello!"
49
+ -- ,_detail=Nothing
50
+ -- ,_kind=SymbolKind_Module
51
+ -- ,_tags=Nothing
52
+ -- ,_range=mkRange 1 0 1 11
53
+ -- ,_deprecated=Nothing
54
+ -- ,_selectionRange=mkRange 1 0 1 11
55
+ -- ,_children=Nothing}])
56
+ Nothing -> pure $ LSP. InL []
57
+ Nothing -> pure $ LSP. InL []
58
+
59
+ documentSymbolForField :: Field Position -> Maybe LSP. DocumentSymbol
60
+ documentSymbolForField (Field (Name pos@ (Position line char) fieldName) _ )= Just $ LSP. DocumentSymbol { .. } where
61
+ _detail = Nothing
62
+ _deprecated = Nothing
63
+ _name = decodeASCII fieldName
64
+
65
+ _kind = LSP. SymbolKind_Field
66
+ _range = LSP. Range (parserToLSPPosition pos) (parserToLSPPosition (Position line char))
67
+ _selectionRange = LSP. Range (parserToLSPPosition pos) (parserToLSPPosition (Position line char))
68
+ _children = Nothing
69
+ _tags = Nothing
70
+
71
+ -- addNameLength :: UInt -> FieldName -> UInt
72
+ -- addNameLength char name = toEnum (fromEnum char + length name)
73
+ documentSymbolForField _ = Nothing
74
+
38
75
39
- moduleOutline :: PluginMethodHandler IdeState Method_TextDocumentDocumentSymbol
40
- moduleOutline ideState _ DocumentSymbolParams { _textDocument = TextDocumentIdentifier uri }
41
- = liftIO $ case uriToFilePath uri of
42
- Just (toNormalizedFilePath' -> fp) -> pure $ InR (InL [DocumentSymbol {_name= " hello!"
43
- ,_detail= Nothing
44
- ,_kind= SymbolKind_Module
45
- ,_tags= Nothing
46
- ,_range= mkRange 1 0 1 11
47
- ,_deprecated= Nothing
48
- ,_selectionRange= mkRange 1 0 1 11
49
- ,_children= Nothing }])
50
- Nothing -> pure $ InL []
76
+ parserToLSPPosition :: Position -> LSP. Position
77
+ parserToLSPPosition (Position start end) = LSP. Position (toEnum start) (toEnum end)
0 commit comments