1- module Ide.Plugin.Cabal.Completion.CabalFields (findStanzaForColumn , findFieldSection , getOptionalSectionName , getAnnotation , getFieldName , onelineSectionArgs ) where
1+ module Ide.Plugin.Cabal.Completion.CabalFields
2+ ( findStanzaForColumn ,
3+ findFieldSection ,
4+ findTextWord ,
5+ findFieldLine ,
6+ getOptionalSectionName ,
7+ getAnnotation ,
8+ getFieldName ,
9+ onelineSectionArgs ,
10+ getFieldEndPosition ,
11+ getSectionArgEndPosition ,
12+ getNameEndPosition ,
13+ getFieldLineEndPosition ,
14+ getFieldLSPRange
15+ ) where
216
17+ import qualified Data.ByteString as BS
18+ import Data.List (find )
319import Data.List.NonEmpty (NonEmpty )
420import qualified Data.List.NonEmpty as NE
521import qualified Data.Text as T
622import qualified Data.Text.Encoding as T
723import qualified Distribution.Fields as Syntax
824import qualified Distribution.Parsec.Position as Syntax
925import Ide.Plugin.Cabal.Completion.Types
26+ import qualified Language.LSP.Protocol.Types as LSP
1027
1128-- ----------------------------------------------------------------
1229-- Cabal-syntax utilities I don't really want to write myself
@@ -28,7 +45,7 @@ findStanzaForColumn col ctx = case NE.uncons ctx of
2845--
2946-- The result is said field and its starting position
3047-- or Nothing if the passed list of fields is empty.
31-
48+ --
3249-- This only looks at the row of the cursor and not at the cursor's
3350-- position within the row.
3451--
@@ -46,6 +63,71 @@ findFieldSection cursor (x:y:ys)
4663 where
4764 cursorLine = Syntax. positionRow cursor
4865
66+ -- | Determine the field line the cursor is currently a part of.
67+ --
68+ -- The result is said field line and its starting position
69+ -- or Nothing if the passed list of fields is empty.
70+ --
71+ -- This function assumes that elements in a field's @FieldLine@ list
72+ -- do not share the same row.
73+ findFieldLine :: Syntax. Position -> [Syntax. Field Syntax. Position ] -> Maybe (Syntax. FieldLine Syntax. Position )
74+ findFieldLine _cursor [] = Nothing
75+ findFieldLine cursor fields =
76+ case findFieldSection cursor fields of
77+ Nothing -> Nothing
78+ Just (Syntax. Field _ fieldLines) -> find filterLineFields fieldLines
79+ Just (Syntax. Section _ _ fields) -> findFieldLine cursor fields
80+ where
81+ cursorLine = Syntax. positionRow cursor
82+ -- In contrast to `Field` or `Section`, `FieldLine` must have the exact
83+ -- same line position as the cursor.
84+ filterLineFields (Syntax. FieldLine pos _) = Syntax. positionRow pos == cursorLine
85+
86+ -- | Determine the exact word at the current cursor position.
87+ --
88+ -- The result is said word or Nothing if the passed list is empty
89+ -- or the cursor position is not next to, or on a word.
90+ -- For this function, a word is a sequence of consecutive characters
91+ -- that are not a space or column.
92+ --
93+ -- This function currently only considers words inside of a @FieldLine@.
94+ findTextWord :: Syntax. Position -> [Syntax. Field Syntax. Position ] -> Maybe T. Text
95+ findTextWord _cursor [] = Nothing
96+ findTextWord cursor fields =
97+ case findFieldLine cursor fields of
98+ Nothing -> Nothing
99+ Just (Syntax. FieldLine pos byteString) ->
100+ let decodedText = T. decodeUtf8 byteString
101+ lineFieldCol = Syntax. positionCol pos
102+ lineFieldLen = T. length decodedText
103+ offset = cursorCol - lineFieldCol in
104+ -- Range check if cursor is inside or or next to found line.
105+ -- The latter comparison includes the length of the line as offset,
106+ -- which is done to also include cursors that are at the end of a line.
107+ -- e.g. "foo,bar|"
108+ -- ^
109+ -- cursor
110+ --
111+ -- Having an offset which is outside of the line is possible because of `splitAt`.
112+ if offset >= 0 && lineFieldLen >= offset
113+ then
114+ let (lhs, rhs) = T. splitAt offset decodedText
115+ strippedLhs = T. takeWhileEnd isAllowedChar lhs
116+ strippedRhs = T. takeWhile isAllowedChar rhs
117+ resultText = T. concat [strippedLhs, strippedRhs] in
118+ -- It could be possible that the cursor was in-between separators, in this
119+ -- case the resulting text would be empty, which should result in `Nothing`.
120+ -- e.g. " foo ,| bar"
121+ -- ^
122+ -- cursor
123+ if not $ T. null resultText then Just resultText else Nothing
124+ else
125+ Nothing
126+ where
127+ cursorCol = Syntax. positionCol cursor
128+ separators = [' ,' , ' ' ]
129+ isAllowedChar = (`notElem` separators)
130+
49131type FieldName = T. Text
50132
51133getAnnotation :: Syntax. Field ann -> ann
@@ -73,12 +155,42 @@ getOptionalSectionName (x:xs) = case x of
73155--
74156-- For example, @flag@ @(@ @pedantic@ @)@ will be joined in
75157-- one line, instead of four @SectionArg@s separately.
76- onelineSectionArgs :: [Syntax. SectionArg Syntax. Position ] -> T. Text
158+ onelineSectionArgs :: [Syntax. SectionArg ann ] -> T. Text
77159onelineSectionArgs sectionArgs = joinedName
78160 where
79161 joinedName = T. unwords $ map getName sectionArgs
80162
81- getName :: Syntax. SectionArg Syntax. Position -> T. Text
163+ getName :: Syntax. SectionArg ann -> T. Text
82164 getName (Syntax. SecArgName _ identifier) = T. decodeUtf8 identifier
83165 getName (Syntax. SecArgStr _ quotedString) = T. decodeUtf8 quotedString
84166 getName (Syntax. SecArgOther _ string) = T. decodeUtf8 string
167+
168+
169+ -- | Returns the end position of a provided field
170+ getFieldEndPosition :: Syntax. Field Syntax. Position -> Syntax. Position
171+ getFieldEndPosition (Syntax. Field name [] ) = getNameEndPosition name
172+ getFieldEndPosition (Syntax. Field _ (x: xs)) = getFieldLineEndPosition $ NE. last (x NE. :| xs)
173+ getFieldEndPosition (Syntax. Section name [] [] ) = getNameEndPosition name
174+ getFieldEndPosition (Syntax. Section _ (x: xs) [] ) = getSectionArgEndPosition $ NE. last (x NE. :| xs)
175+ getFieldEndPosition (Syntax. Section _ _ (x: xs)) = getFieldEndPosition $ NE. last (x NE. :| xs)
176+
177+ -- | Returns the end position of a provided section arg
178+ getSectionArgEndPosition :: Syntax. SectionArg Syntax. Position -> Syntax. Position
179+ getSectionArgEndPosition (Syntax. SecArgName (Syntax. Position row col) byteString) = Syntax. Position row (col + BS. length byteString)
180+ getSectionArgEndPosition (Syntax. SecArgStr (Syntax. Position row col) byteString) = Syntax. Position row (col + BS. length byteString)
181+ getSectionArgEndPosition (Syntax. SecArgOther (Syntax. Position row col) byteString) = Syntax. Position row (col + BS. length byteString)
182+
183+ -- | Returns the end position of a provided name
184+ getNameEndPosition :: Syntax. Name Syntax. Position -> Syntax. Position
185+ getNameEndPosition (Syntax. Name (Syntax. Position row col) byteString) = Syntax. Position row (col + BS. length byteString)
186+
187+ -- | Returns the end position of a provided field line
188+ getFieldLineEndPosition :: Syntax. FieldLine Syntax. Position -> Syntax. Position
189+ getFieldLineEndPosition (Syntax. FieldLine (Syntax. Position row col) byteString) = Syntax. Position row (col + BS. length byteString)
190+
191+ -- | Returns an LSP compatible range for a provided field
192+ getFieldLSPRange :: Syntax. Field Syntax. Position -> LSP. Range
193+ getFieldLSPRange field = LSP. Range startLSPPos endLSPPos
194+ where
195+ startLSPPos = cabalPositionToLSPPosition $ getAnnotation field
196+ endLSPPos = cabalPositionToLSPPosition $ getFieldEndPosition field
0 commit comments