@@ -21,7 +21,7 @@ import Control.Monad.Trans.Maybe
21
21
import Data.Aeson (Value (Null ), toJSON )
22
22
import Data.Char (isLower )
23
23
import qualified Data.HashMap.Strict as HashMap
24
- import Data.List (find , intercalate , isPrefixOf )
24
+ import Data.List (intercalate , isPrefixOf , minimumBy )
25
25
import Data.Maybe (maybeToList )
26
26
import Data.String (IsString )
27
27
import qualified Data.Text as T
@@ -44,6 +44,7 @@ import Language.LSP.VFS (virtualFileText)
44
44
import System.Directory (canonicalizePath )
45
45
import System.FilePath (dropExtension , splitDirectories ,
46
46
takeFileName )
47
+ import Data.Ord (comparing )
47
48
48
49
-- | Plugin descriptor
49
50
descriptor :: PluginId -> PluginDescriptor IdeState
@@ -97,36 +98,40 @@ action state uri =
97
98
contents <- lift . getVirtualFile $ toNormalizedUri uri
98
99
let emptyModule = maybe True (T. null . T. strip . virtualFileText) contents
99
100
100
- correctName <- MaybeT . liftIO $ traceAs " correctName" <$> pathModuleName state nfp fp
101
+ correctNames <- liftIO $ traceAs " correctNames" <$> pathModuleNames state nfp fp
102
+ let bestName = minimumBy (comparing T. length ) correctNames
101
103
102
104
statedNameMaybe <- liftIO $ traceAs " statedName" <$> codeModuleName state nfp
103
105
case statedNameMaybe of
104
106
Just (nameRange, statedName)
105
- | correctName /= statedName ->
106
- pure $ Replace uri nameRange (" Set module name to " <> correctName) correctName
107
+ | statedName `notElem` correctNames ->
108
+ pure $ Replace uri nameRange (" Set module name to " <> bestName) bestName
107
109
Nothing
108
110
| emptyModule ->
109
- let code = " module " <> correctName <> " where\n "
111
+ let code = " module " <> bestName <> " where\n "
110
112
in pure $ Replace uri (Range (Position 0 0 ) (Position 0 0 )) code code
111
113
_ -> MaybeT $ pure Nothing
112
114
113
- -- | The module name, as derived by the position of the module in its source directory
114
- pathModuleName :: IdeState -> NormalizedFilePath -> String -> IO (Maybe T. Text )
115
- pathModuleName state normFilePath filePath
116
- | isLower . head $ takeFileName filePath = return $ Just " Main"
115
+ -- | Possible module names, as derived by the position of the module in the
116
+ -- source directories. There may be more than one possible name, if the source
117
+ -- directories are nested inside each other.
118
+ pathModuleNames :: IdeState -> NormalizedFilePath -> String -> IO [T. Text ]
119
+ pathModuleNames state normFilePath filePath
120
+ | isLower . head $ takeFileName filePath = return [" Main" ]
117
121
| otherwise = do
118
122
session <- runAction " ModuleName.ghcSession" state $ use_ GhcSession normFilePath
119
123
srcPaths <- evalGhcEnv (hscEnvWithImportPaths session) $ importPaths <$> getSessionDynFlags
120
124
paths <- mapM canonicalizePath srcPaths
121
125
mdlPath <- canonicalizePath filePath
122
- pure $ do
123
- prefix <- find (`isPrefixOf` mdlPath) paths
124
- pure
125
- . T. pack
126
- . intercalate " ."
127
- . splitDirectories
128
- . drop (length prefix + 1 )
129
- $ dropExtension mdlPath
126
+ let prefixes = filter (`isPrefixOf` mdlPath) paths
127
+ pure (map (moduleNameFrom mdlPath) prefixes)
128
+ where
129
+ moduleNameFrom mdlPath prefix =
130
+ T. pack
131
+ . intercalate " ."
132
+ . splitDirectories
133
+ . drop (length prefix + 1 )
134
+ $ dropExtension mdlPath
130
135
131
136
-- | The module name, as stated in the module
132
137
codeModuleName :: IdeState -> NormalizedFilePath -> IO (Maybe (Range , T. Text ))
0 commit comments