module Development.IDE.Plugin.CodeAction.PositionIndexed
( PositionIndexed
, PositionIndexedString
, indexedByPosition
, indexedByPositionStartingFrom
, extendAllToIncludeCommaIfPossible
, mergeRanges
)
where
import Data.Char
import Data.List
import Language.Haskell.LSP.Types
type PositionIndexed a = [(Position, a)]
type PositionIndexedString = PositionIndexed Char
indexedByPositionStartingFrom :: Position -> String -> PositionIndexedString
indexedByPositionStartingFrom initialPos = unfoldr f . (initialPos, ) where
f (_, []) = Nothing
f (p@(Position l _), '\n' : rest) =
Just ((p, '\n'), (Position (l + 1) 0, rest))
f (p@(Position l c), x : rest) = Just ((p, x), (Position l (c + 1), rest))
indexedByPosition :: String -> PositionIndexedString
indexedByPosition = indexedByPositionStartingFrom (Position 0 0)
unconsRange
:: Range
-> PositionIndexed a
-> Maybe (PositionIndexed a, PositionIndexed a, PositionIndexed a)
unconsRange Range {..} indexedString
| (before, rest@(_ : _)) <- span ((/= _start) . fst) indexedString
, (mid, after@(_ : _)) <- span ((/= _end) . fst) rest
= Just (before, mid, after)
| otherwise
= Nothing
stripRange :: Range -> PositionIndexed a -> Maybe (PositionIndexed a)
stripRange r s = case unconsRange r s of
Just (b, _, a) -> Just (b ++ a)
Nothing -> Nothing
mergeRanges :: [Range] -> [Range]
mergeRanges (r : r' : rest)
|
_end r > _end r' = mergeRanges (r : rest)
|
_end r > _start r' = mergeRanges (r { _end = _end r' } : rest)
| otherwise = r : mergeRanges (r' : rest)
mergeRanges other = other
extendAllToIncludeCommaIfPossible :: PositionIndexedString -> [Range] -> [Range]
extendAllToIncludeCommaIfPossible indexedString =
mergeRanges . go indexedString . sortOn _start
where
go _ [] = []
go input (r : rr)
| r' : _ <- extendToIncludeCommaIfPossible input r
, Just input' <- stripRange r' input
= r' : go input' rr
| otherwise
= go input rr
extendToIncludeCommaIfPossible :: PositionIndexedString -> Range -> [Range]
extendToIncludeCommaIfPossible indexedString range
| Just (before, _, after) <- unconsRange range indexedString
, after' <- dropWhile (isSpace . snd) after
, before' <- dropWhile (isSpace . snd) (reverse before)
=
[ range { _start = start' } | (start', ',') : _ <- [before'] ]
++
[ range { _end = end' }
| (_, ',') : rest <- [after']
, let (end', _) : _ = dropWhile (isSpace . snd) rest
]
| otherwise
= [range]