Skip to content

Commit

Permalink
Fix unqual modules find and duplicate imports rename.
Browse files Browse the repository at this point in the history
  • Loading branch information
wclr committed May 22, 2023
1 parent e2158a1 commit 783bd18
Show file tree
Hide file tree
Showing 4 changed files with 46 additions and 41 deletions.
7 changes: 4 additions & 3 deletions src/IdePurescript/Modules.purs
Original file line number Diff line number Diff line change
Expand Up @@ -124,9 +124,10 @@ getUnqualActiveModules state ident = getModules include state
where
include (Module { qualifier: Just _ }) = false
include (Module { importType: Explicit idents }) =
-- idents array doesn't contain imports of constructors, something like:
-- (A), (A,B) or (..)
maybe false (_ `elem` idents) ident
-- idents array contains operators inside parentheses: `(/\)`. Note: it
-- doesn't contain imports of constructors, something like: (A), (A,B) or
-- (..)
maybe false (\x -> x `elem` idents || ("(" <> x <> ")") `elem` idents) ident
include (Module { importType: Implicit }) = true
include (Module { importType: Hiding idents }) =
maybe true (_ `notElem` idents) ident
Expand Down
29 changes: 11 additions & 18 deletions src/LanguageServer/IdePurescript/Rename.purs
Original file line number Diff line number Diff line change
Expand Up @@ -226,19 +226,14 @@ getTextEdits typeInfo usages docsToEdit newText oldName =
-- that should be fixed.
# maybeParseResult identity
( \m ->
( case Array.head $ getExportedRanges m isType oldName of
Just range -> do
fixRange range
Nothing ->
identity
)
-- Apply all found ranges in the exports with
-- duplicates possible.
flip (Array.foldl (#))
(fixRange <$> getExportedRanges m isType oldName)
-- Add declaration signature.
# (<<<)
case getDeclSignatureName m isType oldName of
Just range ->
addEdit' range
Nothing ->
identity
(maybe identity addEdit' (getDeclSignatureName m isType oldName))

)
parsed

Expand Down Expand Up @@ -269,13 +264,10 @@ getTextEdits typeInfo usages docsToEdit newText oldName =
editsMap #
( maybeParseResult identity
( \m ->
case
Array.head $ getImportedRanges m isType oldName moduleDefinedIn
of
Just range ->
fixRange range
Nothing ->
identity
-- Apply all found ranges in one import with
-- duplicates possible.
flip (Array.foldl (#))
(fixRange <$> getImportedRanges m isType oldName moduleDefinedIn)
)
parsed
)
Expand Down Expand Up @@ -319,6 +311,7 @@ getTextEdits typeInfo usages docsToEdit newText oldName =
}
)


--| Uses purs ide to find information about definition and usages of rename target given its
-- symbolic name and its type position.
--
Expand Down
2 changes: 1 addition & 1 deletion test/Fixture/RenameB.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Test.Fixture.RenameB where

import Test.Fixture.RenameA (class ClsA, DataType(ACons), Newt(Newt), TypeSyn, func1, toInt, Tup(..), (/\), type (/\))
import Test.Fixture.RenameA (class ClsA, DataType(ACons), Newt(Newt), TypeSyn, func1, func1, toInt, Tup(..), (/\), type (/\))
import Test.Fixture.RenameA as A

dt :: A.DataType
Expand Down
49 changes: 30 additions & 19 deletions test/Rename.purs
Original file line number Diff line number Diff line change
Expand Up @@ -180,7 +180,6 @@ editsToCompare edits =
Map.toUnfoldable edits <#>
\((uri /\ _) /\ ranges) ->
(fileToModuleName $ show uri)
--/\ (Array.sort $ ranges <#> renderRange <<< _.range)
/\ (Array.sort $ ranges <#> map renderRange <<< lift2 (/\) _.newText _.range)

-- | Coverts found type position to ["Module.Name" /\ ["1:10-1:15"]]
Expand Down Expand Up @@ -275,13 +274,10 @@ prepare = do
rebuild moduleN = do
buildRes <-
PscIde.rebuild port mPath (Just mPath) Nothing
--(Just targets)
case buildRes of
Left err ->
--log $ "Rebuild error: " <> err
A.fail $ "Module rebuild error: " <> err
Right _ ->
--log "Rebuild ok"
pure unit
where
(ModulePath mPath) = toPath moduleN
Expand All @@ -301,7 +297,6 @@ prepare = do
notify = emptyNotify

-- | Test Rename.getTextEdits function.
--mySpec :: SpecT Aff Unit Effect Unit
renameSpec :: PrepareResult -> S.Spec Unit
renameSpec prep = do
S.before (pure prep) $
Expand All @@ -314,7 +309,8 @@ renameSpec prep = do
, moduleA /\ "func1 int" /\ "func1"
, moduleA /\ "( func1" /\ "func1" -- export
, moduleA /\ "= func1 10" /\ "func1"
, moduleB /\ "import" /\ "func1"
, moduleB /\ "import" /\ "func1" -- import
, moduleB /\ "nc1, func1" /\ "func1" -- duplicate import
, moduleB /\ "= A.func1 0" /\ "func1"
, moduleB /\ "func1 v" /\ "func1" -- inside instance
]
Expand Down Expand Up @@ -455,23 +451,37 @@ renameSpec prep = do

-- TODO: tests for value fixity, type fixity (value/ctor), value op, type op, kind

let
expectedValueOp =
[ moduleA /\ "5 Tup as" /\ "/\\" --def
, moduleA /\ ", (/\\)" /\ "/\\" -- export
, moduleB /\ "import" /\ "/\\" -- import
, moduleB /\ "tup =" /\ "/\\" -- usage
]

testRename it "value operator"
(moduleA /\ "5 Tup as" /\ "/\\")
[ moduleA /\ "5 Tup as" /\ "/\\" --def
, moduleA /\ ", (/\\)" /\ "/\\" -- export
, moduleB /\ "import" /\ "/\\" -- import
, moduleB /\ "tup =" /\ "/\\" -- usage
]
expectedValueOp

testRename it "value operator (in other module)"
(moduleB /\ "tup = 1" /\ "/\\")
expectedValueOp

let
expectedTypeOp =
[ moduleA /\ "5 type Tup as" /\ "/\\" --def
, moduleA /\ ", type (/\\)" /\ "/\\" -- export
, moduleB /\ "type (/\\)" /\ "/\\" -- import
, moduleB /\ "tup ::" /\ "/\\" -- usage
]

testRename it "type operator"
(moduleA /\ "5 type Tup as" /\ "/\\")
[ moduleA /\ "5 type Tup as" /\ "/\\" --def
, moduleA /\ ", type (/\\)" /\ "/\\" -- export
, moduleB /\ "type (/\\)" /\ "/\\" -- import
, moduleB /\ "tup ::" /\ "/\\" -- usage
]
expectedTypeOp

-- TODO: multiple times export/imports
testRename it "type operator"
(moduleA /\ "5 type Tup as" /\ "/\\")
expectedTypeOp

-- TODO: support renaming names in imports/exports

Expand All @@ -498,8 +508,9 @@ renameSpec prep = do
case mbUsage of
-- Returns usages: array of type positions.
Just (typeInfo /\ usages) -> do
let edits =
R.getTextEdits typeInfo usages docsToEdit (newName ident) identPtn
let
edits =
R.getTextEdits typeInfo usages docsToEdit (newName ident) identPtn

case makeTps modules ident of
Right tps ->
Expand Down

0 comments on commit 783bd18

Please sign in to comment.