Skip to content

Commit

Permalink
outline tests changes
Browse files Browse the repository at this point in the history
  • Loading branch information
VenInf committed Jul 2, 2024
1 parent d201493 commit f4d57a5
Show file tree
Hide file tree
Showing 4 changed files with 56 additions and 46 deletions.
35 changes: 17 additions & 18 deletions plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Outline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}

module Ide.Plugin.Cabal.Outline where
Expand All @@ -26,8 +25,8 @@ import Ide.Plugin.Cabal.Completion.Types (ParseCabalFields (..),
import Ide.Plugin.Cabal.Orphans ()
import Ide.Types (PluginMethodHandler)
import Language.LSP.Protocol.Message (Method (..))
import qualified Language.LSP.Protocol.Types as LSP
import Language.LSP.Protocol.Types (DocumentSymbol (..))
import qualified Language.LSP.Protocol.Types as LSP


moduleOutline :: PluginMethodHandler IdeState Method_TextDocumentDocumentSymbol
Expand All @@ -49,18 +48,18 @@ documentSymbolForField :: Field Position -> Maybe DocumentSymbol
documentSymbolForField (Field (Name pos fieldName) _) =
Just
(defDocumentSymbol range)
{ LSP._name = decodeUtf8 fieldName,
LSP._kind = LSP.SymbolKind_Field,
LSP._children = Nothing
{ _name = decodeUtf8 fieldName,
_kind = LSP.SymbolKind_Field,
_children = Nothing
}
where
range = cabalPositionToLSPRange pos `addNameLengthToLSPRange` decodeUtf8 fieldName
documentSymbolForField (Section (Name pos fieldName) sectionArgs fields) =
Just
(defDocumentSymbol range)
{ LSP._name = joinedName,
LSP._kind = LSP.SymbolKind_Object,
LSP._children =
{ _name = joinedName,
_kind = LSP.SymbolKind_Object,
_children =
Just
(mapMaybe documentSymbolForField fields)
}
Expand Down Expand Up @@ -92,13 +91,13 @@ addNameLengthToLSPRange (LSP.Range pos1 (LSP.Position line char)) name =
(LSP.Position line (char + fromIntegral (T.length name)))

defDocumentSymbol :: LSP.Range -> DocumentSymbol
defDocumentSymbol range = DocumentSymbol {..}
where
_detail = Nothing
_deprecated = Nothing
_name = ""
_kind = LSP.SymbolKind_File
_range = range
_selectionRange = range
_children = Nothing
_tags = Nothing
defDocumentSymbol range = DocumentSymbol
{ _detail = Nothing
, _deprecated = Nothing
, _name = ""
, _kind = LSP.SymbolKind_File
, _range = range
, _selectionRange = range
, _children = Nothing
, _tags = Nothing
}
58 changes: 31 additions & 27 deletions plugins/hls-cabal-plugin/test/Outline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,7 @@ module Outline (
outlineTests
) where

import qualified Ide.Plugin.Cabal.Outline as Outline
import qualified Language.LSP.Protocol.Types as LSP
import Ide.Plugin.Cabal.Outline (defDocumentSymbol)
import Test.Hls
import Utils

Expand Down Expand Up @@ -39,32 +38,37 @@ outlineTests =
[sectionArgDocumentSymbol]
]
where
fieldDocumentSymbol = (Outline.defDocumentSymbol (LSP.Range {_start = LSP.Position {_line = 0, _character = 0},
_end = LSP.Position {_line = 0, _character = 8}}))
{ LSP._name = "homepage",
LSP._kind = LSP.SymbolKind_Field,
LSP._children = Nothing
fieldDocumentSymbol :: DocumentSymbol
fieldDocumentSymbol = (defDocumentSymbol (Range {_start = Position {_line = 0, _character = 0},
_end = Position {_line = 0, _character = 8}}))
{ _name = "homepage",

Check failure on line 44 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 44 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 44 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 44 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 44 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 44 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_name’
_kind = SymbolKind_Field,

Check failure on line 45 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 45 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 45 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 45 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 45 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 45 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_kind’
_children = Nothing
}
fieldLineDocumentSymbol = (Outline.defDocumentSymbol (LSP.Range {_start = LSP.Position {_line = 0, _character = 0},
_end = LSP.Position {_line = 0, _character = 13}}))
{ LSP._name = "cabal-version",
LSP._kind = LSP.SymbolKind_Field,
LSP._children = Nothing -- the values of fieldLine are removed from the outline
fieldLineDocumentSymbol :: DocumentSymbol
fieldLineDocumentSymbol = (defDocumentSymbol (Range {_start = Position {_line = 0, _character = 0},
_end = Position {_line = 0, _character = 13}}))
{ _name = "cabal-version",

Check failure on line 51 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 51 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 51 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 51 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 51 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 51 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_name’
_kind = SymbolKind_Field,

Check failure on line 52 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 52 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 52 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 52 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 52 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 52 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_kind’
_children = Nothing -- the values of fieldLine are removed from the outline
}
sectionDocumentSymbol = (Outline.defDocumentSymbol (LSP.Range {_start = LSP.Position {_line = 0, _character = 2},
_end = LSP.Position {_line = 0, _character = 15}}))
{ LSP._name = "build-depends",
LSP._kind = LSP.SymbolKind_Field,
LSP._children = Nothing -- the values of fieldLine are removed from the outline
sectionDocumentSymbol :: DocumentSymbol
sectionDocumentSymbol = (defDocumentSymbol (Range {_start = Position {_line = 0, _character = 2},
_end = Position {_line = 0, _character = 15}}))
{ _name = "build-depends",

Check failure on line 58 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 58 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 58 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 58 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 58 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 58 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_name’
_kind = SymbolKind_Field,

Check failure on line 59 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 59 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 59 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 59 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 59 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 59 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_kind’
_children = Nothing -- the values of fieldLine are removed from the outline
}
sectionArgDocumentSymbol = (Outline.defDocumentSymbol (LSP.Range {_start = LSP.Position {_line = 0, _character = 2},
_end = LSP.Position {_line = 0, _character = 19}}))
{ LSP._name = "if os ( windows )",
LSP._kind = LSP.SymbolKind_Object,
LSP._children = Just $ [sectionArgChildrenDocumentSymbol] }
sectionArgChildrenDocumentSymbol = (Outline.defDocumentSymbol (LSP.Range {_start = LSP.Position {_line = 1, _character = 4},
_end = LSP.Position {_line = 1, _character = 17}}))
{ LSP._name = "build-depends",
LSP._kind = LSP.SymbolKind_Field,
LSP._children = Nothing
sectionArgDocumentSymbol :: DocumentSymbol
sectionArgDocumentSymbol = (defDocumentSymbol (Range {_start = Position {_line = 0, _character = 2},
_end = Position {_line = 0, _character = 19}}))
{ _name = "if os ( windows )",

Check failure on line 65 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 65 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 65 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 65 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 65 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 65 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_name’
_kind = SymbolKind_Object,

Check failure on line 66 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 66 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 66 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 66 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 66 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 66 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_kind’
_children = Just $ [sectionArgChildrenDocumentSymbol] }
sectionArgChildrenDocumentSymbol :: DocumentSymbol
sectionArgChildrenDocumentSymbol = (defDocumentSymbol (Range {_start = Position {_line = 1, _character = 4},
_end = Position {_line = 1, _character = 17}}))
{ _name = "build-depends",

Check failure on line 71 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 71 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 71 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 71 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_name’

Check failure on line 71 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_name’

Check failure on line 71 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_name’
_kind = SymbolKind_Field,

Check failure on line 72 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 72 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, ubuntu-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 72 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 72 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, macOS-latest, false)

Ambiguous occurrence ‘_kind’

Check failure on line 72 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.6, windows-latest, true)

Ambiguous occurrence ‘_kind’

Check failure on line 72 in plugins/hls-cabal-plugin/test/Outline.hs

View workflow job for this annotation

GitHub Actions / test (9.4, windows-latest, true)

Ambiguous occurrence ‘_kind’
_children = Nothing
}
3 changes: 2 additions & 1 deletion test/testdata/schema/ghc98/default-config.golden.json
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,8 @@
"cabal": {
"codeActionsOn": true,
"completionOn": true,
"diagnosticsOn": true
"diagnosticsOn": true,
"symbolsOn": true
},
"cabal-fmt": {
"config": {
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,12 @@
"scope": "resource",
"type": "boolean"
},
"haskell.plugin.cabal.symbolsOn": {
"default": true,
"description": "Enables cabal symbols",
"scope": "resource",
"type": "boolean"
},
"haskell.plugin.callHierarchy.globalOn": {
"default": true,
"description": "Enables callHierarchy plugin",
Expand Down

0 comments on commit f4d57a5

Please sign in to comment.