@@ -50,8 +50,6 @@ module Language.LSP.VFS (
5050
5151 -- * manipulating the file contents
5252 rangeLinesFromVfs ,
53- PosPrefixInfo (.. ),
54- getCompletionPrefix ,
5553
5654 -- * for tests
5755 applyChanges ,
@@ -63,19 +61,16 @@ import Colog.Core (LogAction (..), Severity (..), WithSeverity (..), (<&))
6361import Control.Lens hiding (parts , (<.>) )
6462import Control.Monad
6563import Control.Monad.State
66- import Data.Char (isAlphaNum , isUpper )
6764import Data.Foldable (traverse_ )
6865import Data.Hashable
6966import Data.Int (Int32 )
7067import Data.List
7168import Data.Map.Strict qualified as Map
72- import Data.Maybe
7369import Data.Ord
7470import Data.Row
7571import Data.Text (Text )
7672import Data.Text qualified as T
7773import Data.Text.IO qualified as T
78- import Data.Text.Lines as Char (Position (.. ))
7974import Data.Text.Prettyprint.Doc hiding (line )
8075import Data.Text.Utf16.Lines as Utf16 (Position (.. ))
8176import Data.Text.Utf16.Rope.Mixed (Rope )
@@ -471,64 +466,9 @@ rangeToCodePointRange :: VirtualFile -> J.Range -> Maybe CodePointRange
471466rangeToCodePointRange vFile (J. Range b e) =
472467 CodePointRange <$> positionToCodePointPosition vFile b <*> positionToCodePointPosition vFile e
473468
474- -- ---------------------------------------------------------------------
475-
476- -- TODO:AZ:move this to somewhere sane
477-
478- -- | Describes the line at the current cursor position
479- data PosPrefixInfo = PosPrefixInfo
480- { fullLine :: ! T. Text
481- -- ^ The full contents of the line the cursor is at
482- , prefixModule :: ! T. Text
483- -- ^ If any, the module name that was typed right before the cursor position.
484- -- For example, if the user has typed "Data.Maybe.from", then this property
485- -- will be "Data.Maybe"
486- , prefixText :: ! T. Text
487- -- ^ The word right before the cursor position, after removing the module part.
488- -- For example if the user has typed "Data.Maybe.from",
489- -- then this property will be "from"
490- , cursorPos :: ! J. Position
491- -- ^ The cursor position
492- }
493- deriving (Show , Eq )
494-
495- getCompletionPrefix :: (Monad m ) => J. Position -> VirtualFile -> m (Maybe PosPrefixInfo )
496- getCompletionPrefix pos@ (J. Position l c) (VirtualFile _ _ ropetext) =
497- return $ Just $ fromMaybe (PosPrefixInfo " " " " " " pos) $ do
498- -- Maybe monad
499- let lastMaybe [] = Nothing
500- lastMaybe xs = Just $ last xs
501-
502- let curRope = fst $ Rope. splitAtLine 1 $ snd $ Rope. splitAtLine (fromIntegral l) ropetext
503- beforePos <- Rope. toText . fst <$> Rope. utf16SplitAt (fromIntegral c) curRope
504- curWord <-
505- if
506- | T. null beforePos -> Just " "
507- | T. last beforePos == ' ' -> Just " " -- don't count abc as the curword in 'abc '
508- | otherwise -> lastMaybe (T. words beforePos)
509-
510- let parts =
511- T. split (== ' .' ) $
512- T. takeWhileEnd (\ x -> isAlphaNum x || x `elem` (" ._'" :: String )) curWord
513- case reverse parts of
514- [] -> Nothing
515- (x : xs) -> do
516- let modParts =
517- dropWhile (not . isUpper . T. head ) $
518- reverse $
519- filter (not . T. null ) xs
520- modName = T. intercalate " ." modParts
521- -- curRope is already a single line, but it may include an enclosing '\n'
522- let curLine = T. dropWhileEnd (== ' \n ' ) $ Rope. toText curRope
523- return $ PosPrefixInfo curLine modName x pos
524-
525- -- ---------------------------------------------------------------------
526-
527469rangeLinesFromVfs :: VirtualFile -> J. Range -> T. Text
528470rangeLinesFromVfs (VirtualFile _ _ ropetext) (J. Range (J. Position lf _cf) (J. Position lt _ct)) = r
529471 where
530472 (_, s1) = Rope. splitAtLine (fromIntegral lf) ropetext
531473 (s2, _) = Rope. splitAtLine (fromIntegral (lt - lf)) s1
532474 r = Rope. toText s2
533-
534- -- ---------------------------------------------------------------------
0 commit comments