In VS Code how to make symbol renaming work in simple modules?

When I have a simple module and i try to rename a symbol in VS Code I get from the editor the error

Screen Shot 2023-03-27 at 6.39.42 am

With “simple module” I mean jere something like this code:

-- File Cnt.hs
module Cnt where

mostFrequentChar' :: String -> Char -> Int -> (Char, Int)
mostFrequentChar' [] maxChar maxFreq = (maxChar, maxFreq)
mostFrequentChar' (c:cs) maxChar maxFreq =
    let freq = count c (c:cs)
    in if freq > maxFreq
        then mostFrequentChar' cs c freq
        else mostFrequentChar' cs maxChar maxFreq
    where count x xs = length $ filter (== x) xs

No exports (what ever this is). I just want to rename mostFrequentChar' to mostFrequentChar

But I can’t. Why’s that? Can I tweak VS Code’s HLS settings, so that the renaming works?

Many thanks in advance for any help.

2 Likes

Here’s an example of an explicit export list for your module:

module Cnt (mostFrequentChar') where

It makes explicit that the function mostFrequentChar' is exported from the module Cnt.

I don’t know why HLS requires an explicit export list, but it seems like the renaming will succeed if you add it.

1 Like

Well, if your module doesn’t have an explicit export list – as @jaror shows – then in effect it exports every top-level name declared in the module. (You haven’t named your module Main, so Haskell expects this isn’t ‘the’ ‘commanding’ module.)

Yeah, I don’t know either. Seems VS Code is being over-bureaucratic. If your module is being imported somewhere else, you’ll need to change all the usage sites to the new name – although the imports might or might not name your id explicitly.

Perhaps for VS Code in general/not specific to Haskell, you can rename across a whole application/multiple modules as one operation? And VS Code will go off cross-referencing by export/import names(?)

1 Like

Thanks @AntC2 and @jaror.

In my case I have no big project, just this module as a stand-alone file which load into ghci. – It feels a bit over the top just in order to satisfy the editor to add some export clauses… Would be nice if VS Code could deal with that. (For the moment I use plain find/replace to get around this limitation.)

1 Like

I have also found myself frustrated with this.

4 Likes

It is really annoying when you want to rename a variable (not even a top level function) and you need to add an explicit export list

2 Likes

Hm yeah. Is this just a bug?

Also, what happens if you just use an empty export list?

module Foo () where
1 Like

It works :confused: . But if you do so, you are exporting nothing from the module isn’t it?

1 Like

Yeah, this is probably the easiest workaround for the original problem, but it seems likely that this is just a bug…

1 Like

What happens if you use a module re-export?

module Foo (module Foo) where
1 Like

When I last checked, HLS explicitly disallows renaming exported bindings. Maybe the error is due to this problem, which means there would be no satisfactory workaround…

3 Likes

Ah, that makes sense!

1 Like

In which case the error message should probably say something like “Cannot rename an exported binding”.

2 Likes

This situation is really inconvenient!

For now I use just VS Code’s language-independent search-and-replace commands, but they are pretty cumbersome and fragile in comparison with a proper Replace Symbol command…

1 Like

Coming back here again: I went off to the HLS issues on GitHub and received there fantastic help from @July541:

When you enable (experimental) crossModule renaming, than you can rename symbols local to a module perfectly without any export list! For how to do it in VS Code, see this comment in the issue.