Skip to content

Commit

Permalink
Bump ghcide (digital-asset#5128)
Browse files Browse the repository at this point in the history
This PR bumps ghcide, haskell-lsp and haskell-lsp-types. There aren’t
really any important changes in ghcide itself but the haskell-lsp
update includes my fix for crashing completions.

One change in ghcide itself is that NormalizedFilePath got moved to
haskell-lsp. ghcide needs special treatment for empty file paths so we
use `toNormalizedFilePath'` from ghcide instead of
`toNormalizedFilePath` from `haskell-lsp`. I’ve added an hlint rule to
enforce this.

changelog_begin
changelog_end
  • Loading branch information
cocreature authored Mar 23, 2020
1 parent ceeb7c3 commit aa48f30
Show file tree
Hide file tree
Showing 20 changed files with 60 additions and 47 deletions.
1 change: 1 addition & 0 deletions .hlint.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,7 @@
- warn: {lhs: Data.Text.Lazy.readFile, rhs: Data.Text.Extended.readFileUtf8}
- warn: {lhs: Data.Text.Lazy.writeFile, rhs: Data.Text.Extended.writeFileUtf8}
- warn: {lhs: System.Environment.setEnv, rhs: System.Environment.Blank.setEnv}
- warn: {lhs: toNormalizedFilePath, rhs: toNormalizedFilePath'}

# Hints that do not always make sense
- ignore: {name: "Use if", within: [DA.Daml.LF.Proto3.EncodeV1, DA.Daml.LF.Ast.Pretty]}
Expand Down
4 changes: 2 additions & 2 deletions bazel-haskell-deps.bzl
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,8 @@ load("@os_info//:os_info.bzl", "is_windows")
load("@dadew//:dadew.bzl", "dadew_tool_home")
load("@rules_haskell//haskell:cabal.bzl", "stack_snapshot")

GHCIDE_REV = "45f97424619d6f78b1397f98f75f40e2c9462e65"
GHCIDE_SHA256 = "9e203c4393d462eb24af981c2df5be6c75204208db66b5078782b540af68f7af"
GHCIDE_REV = "9b6e7122516f9de9b0ba20cd37d59c58a4d634ec"
GHCIDE_SHA256 = "e125fc97f35b418918cd29d4d70b36e46bde506d1669426d6802d8531fe3e9ac"
GHCIDE_VERSION = "0.1.0"
JS_JQUERY_VERSION = "3.3.1"
JS_DGTABLE_VERSION = "0.5.2"
Expand Down
20 changes: 10 additions & 10 deletions compiler/damlc/daml-compiler/src/DA/Daml/Compiler/Dar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -123,7 +123,7 @@ buildDar service pkgConf@PackageConfigFields {..} ifDir dalfInput = do
bytes <- BSL.readFile pSrc
-- in the dalfInput case we interpret pSrc as the filepath pointing to the dalf.
-- Note that the package id is obviously wrong but this feature is not something we expose to users.
pure $ Just $ createArchive pkgConf (LF.PackageId "") bytes [] (toNormalizedFilePath ".") [] [] []
pure $ Just $ createArchive pkgConf (LF.PackageId "") bytes [] (toNormalizedFilePath' ".") [] [] []
-- We need runActionSync here to ensure that diagnostics are printed to the terminal.
-- Otherwise runAction can return before the diagnostics have been printed and we might die
-- without ever seeing diagnostics.
Expand All @@ -136,7 +136,7 @@ buildDar service pkgConf@PackageConfigFields {..} ifDir dalfInput = do
Nothing -> mergePkgs pName pVersion lfVersion <$> usesE GeneratePackage files
Just _ -> generateSerializedPackage pName pVersion files

MaybeT $ finalPackageCheck (toNormalizedFilePath pSrc) pkg
MaybeT $ finalPackageCheck (toNormalizedFilePath' pSrc) pkg

let pkgModuleNames = map T.unpack $ LF.packageModuleNames pkg
let missingExposed =
Expand Down Expand Up @@ -207,20 +207,20 @@ writeIfacesAndHie ifDir files =
(fst $ tm_internals_ $ tmrModule tcm)
(fromJust $ tm_renamed_source $ tmrModule tcm)
writeHieFile hieFp hieFile
pure [toNormalizedFilePath ifaceFp, toNormalizedFilePath hieFp]
pure [toNormalizedFilePath' ifaceFp, toNormalizedFilePath' hieFp]

-- For backwards compatibility we allow both a file or a directory in "source".
-- For a file we use the import path as the src root.
getSrcRoot :: FilePath -> MaybeT Action NormalizedFilePath
getSrcRoot fileOrDir = do
let fileOrDir' = toNormalizedFilePath fileOrDir
let fileOrDir' = toNormalizedFilePath' fileOrDir
isDir <- liftIO $ doesDirectoryExist fileOrDir
if isDir
then pure fileOrDir'
else do
pm <- useE GetParsedModule fileOrDir'
Just root <- pure $ moduleImportPath fileOrDir' pm
pure $ toNormalizedFilePath root
pure $ toNormalizedFilePath' root

-- | Merge several packages into one.
mergePkgs :: LF.PackageName -> Maybe LF.PackageVersion -> LF.Version -> [WhnfPackage] -> LF.Package
Expand All @@ -243,7 +243,7 @@ getDamlFiles srcRoot = do
if isDir
then liftIO $ damlFilesInDir srcRoot
else do
let normalizedSrcRoot = toNormalizedFilePath srcRoot
let normalizedSrcRoot = toNormalizedFilePath' srcRoot
deps <- MaybeT $ getDependencies normalizedSrcRoot
pure (normalizedSrcRoot : deps)

Expand All @@ -256,7 +256,7 @@ damlFilesInDir srcRoot = do
(\fp ->
return $ fp == "." || (not $ isPrefixOf "." $ takeFileName fp))
srcRoot
pure $ map toNormalizedFilePath $ filter (".daml" `isExtensionOf`) fs
pure $ map toNormalizedFilePath' $ filter (".daml" `isExtensionOf`) fs

-- | Find all DAML files below a given source root. If the source root is a file we interpret it as
-- main and return only that file. This is different from getDamlFiles which also returns
Expand All @@ -266,7 +266,7 @@ getDamlRootFiles srcRoot = do
isDir <- liftIO $ doesDirectoryExist srcRoot
if isDir
then liftIO $ damlFilesInDir srcRoot
else pure [toNormalizedFilePath srcRoot]
else pure [toNormalizedFilePath' srcRoot]

mkConfFile ::
PackageConfigFields -> [String] -> LF.PackageId -> IO (String, BS.ByteString)
Expand Down Expand Up @@ -338,7 +338,7 @@ createArchive PackageConfigFields {..} pkgId dalf dalfDependencies srcRoot fileD
sinkEntryDeterministic Zip.Deflate (sourceFile $ fromNormalizedFilePath mPath) entry
forM_ ifaces $ \mPath -> do
let ifaceRoot =
toNormalizedFilePath
toNormalizedFilePath'
(ifaceDir </> fromNormalizedFilePath srcRoot)
entry <- Zip.mkEntrySelector $ pkgName </> fromNormalizedFilePath (makeRelative' ifaceRoot mPath)
sinkEntryDeterministic Zip.Deflate (sourceFile $ fromNormalizedFilePath mPath) entry
Expand Down Expand Up @@ -399,7 +399,7 @@ breakAt72Bytes s =
-- > makeRelative "./a" "a/b" == "a/b"
makeRelative' :: NormalizedFilePath -> NormalizedFilePath -> NormalizedFilePath
makeRelative' a b =
toNormalizedFilePath $
toNormalizedFilePath' $
-- Note that NormalizedFilePath only takes care of normalizing slashes.
-- Here we also want to normalise things like ./a to a
makeRelative (normalise $ fromNormalizedFilePath a) (normalise $ fromNormalizedFilePath b)
Original file line number Diff line number Diff line change
Expand Up @@ -787,7 +787,7 @@ generateSrcPkgFromLf :: Config -> LF.Package -> [(NormalizedFilePath, String)]
generateSrcPkgFromLf envConfig pkg = do
mod <- NM.toList $ LF.packageModules pkg
let fp =
toNormalizedFilePath $
toNormalizedFilePath' $
(joinPath $ map T.unpack $ LF.unModuleName $ LF.moduleName mod) <.>
".daml"
pure
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ import System.FilePath
docTest :: IdeState -> [NormalizedFilePath] -> IO ()
docTest ideState files = do
ms <- runActionSync ideState (uses_ GenerateDocTestModule files)
let docTestFile m = toNormalizedFilePath $
let docTestFile m = toNormalizedFilePath' $
genDir </>
T.unpack (T.replace "." "/" (docTestModuleName $ genModuleName m)) -<.>
"daml"
Expand Down
2 changes: 1 addition & 1 deletion compiler/damlc/daml-compiler/src/DA/Daml/Compiler/Repl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -216,7 +216,7 @@ expand (unLoc -> AbsBinds{..}) = toList abs_binds
expand bind = [bind]

lineFilePath :: Int -> NormalizedFilePath
lineFilePath i = toNormalizedFilePath $ "Line" <> show i <> ".daml"
lineFilePath i = toNormalizedFilePath' $ "Line" <> show i <> ".daml"

lineModuleName :: Int -> String
lineModuleName i = "Line" <> show i
Expand Down
4 changes: 2 additions & 2 deletions compiler/damlc/daml-doc/test/DA/Daml/Doc/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -259,15 +259,15 @@ runDamldoc testfile importPathM = do
}

let diagLogger = \case
EventFileDiagnostics fp diags -> T.hPutStrLn stderr $ showDiagnostics $ map (toNormalizedFilePath fp,ShowDiag,) diags
EventFileDiagnostics fp diags -> T.hPutStrLn stderr $ showDiagnostics $ map (toNormalizedFilePath' fp,ShowDiag,) diags
_ -> pure ()

-- run the doc generator on that file
mbResult <- runMaybeT $ extractDocs
defaultExtractOptions
diagLogger
(toCompileOpts opts (IdeReportProgress False))
[toNormalizedFilePath testfile]
[toNormalizedFilePath' testfile]

case mbResult of
Nothing ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,7 @@ uriToVirtualResource uri = do
let decoded = queryString uri
file <- Map.lookup "file" decoded
topLevelDecl <- Map.lookup "top-level-decl" decoded
pure $ VRScenario (toNormalizedFilePath file) (T.pack topLevelDecl)
pure $ VRScenario (toNormalizedFilePath' file) (T.pack topLevelDecl)
_ -> Nothing

where
Expand All @@ -162,7 +162,7 @@ sendFileDiagnostics diags =
-- TODO: Move this to ghcide, perhaps.
sendDiagnostics :: NormalizedFilePath -> [Diagnostic] -> Action ()
sendDiagnostics fp diags = do
let uri = filePathToUri (fromNormalizedFilePath fp)
let uri = fromNormalizedUri (filePathToUri' fp)
event = LSP.NotPublishDiagnostics $
LSP.NotificationMessage "2.0" LSP.TextDocumentPublishDiagnostics $
LSP.PublishDiagnosticsParams uri (List diags)
Expand Down Expand Up @@ -496,7 +496,7 @@ readDalfPackage dalf = do
bs <- BS.readFile dalf
pure $ do
(pkgId, package) <-
mapLeft (ideErrorPretty $ toNormalizedFilePath dalf) $ Archive.decodeArchive Archive.DecodeAsDependency bs
mapLeft (ideErrorPretty $ toNormalizedFilePath' dalf) $ Archive.decodeArchive Archive.DecodeAsDependency bs
Right (LF.DalfPackage pkgId (LF.ExternalPackage pkgId package) bs)

generatePackageMapRule :: Options -> Rules ()
Expand Down Expand Up @@ -616,12 +616,12 @@ buildDir = ".daml/build"
-- | Path to the dalf file used in incremental builds.
dalfFileName :: NormalizedFilePath -> NormalizedFilePath
dalfFileName file =
toNormalizedFilePath $ buildDir </> fromNormalizedFilePath file -<.> "dalf"
toNormalizedFilePath' $ buildDir </> fromNormalizedFilePath file -<.> "dalf"

-- | Path to the interface file used in incremental builds.
hiFileName :: NormalizedFilePath -> NormalizedFilePath
hiFileName file =
toNormalizedFilePath $ buildDir </> fromNormalizedFilePath file -<.> "hi"
toNormalizedFilePath' $ buildDir </> fromNormalizedFilePath file -<.> "hi"

readDalfFromFile :: NormalizedFilePath -> Action LF.Module
readDalfFromFile dalfFile = do
Expand Down Expand Up @@ -737,6 +737,7 @@ runScenariosRule =
, _source = Just "Scenario"
, _message = Pretty.renderPlain $ formatScenarioError world err
, _code = Nothing
, _tags = Nothing
, _relatedInformation = Nothing
}
where scenarioName = LF.qualObject scenario
Expand All @@ -756,7 +757,7 @@ encodeModule :: LF.Version -> LF.Module -> Action (SS.Hash, BS.ByteString)
encodeModule lfVersion m =
case LF.moduleSource m of
Just file
| isAbsolute file -> use_ EncodeModule $ toNormalizedFilePath file
| isAbsolute file -> use_ EncodeModule $ toNormalizedFilePath' file
_ -> pure $ SS.encodeModule lfVersion m

getScenarioRootsRule :: Rules ()
Expand Down Expand Up @@ -910,7 +911,7 @@ ofInterestRule opts = do
-- To guard against buggy dependency info, we add
-- the roots even though they should be included.
roots `HashSet.union`
(HashSet.insert "" $ HashSet.fromList $ concatMap reachableModules depInfos)
(HashSet.insert emptyFilePath $ HashSet.fromList $ concatMap reachableModules depInfos)
garbageCollect (`HashSet.member` reachableFiles)
DamlEnv{..} <- getDamlServiceEnv
liftIO $ whenJust envScenarioService $ \scenarioService -> do
Expand Down Expand Up @@ -1031,6 +1032,7 @@ getDlintDiagnosticsRule =
, _source = Just "linter"
, _message = T.pack $ show i
, _relatedInformation = Nothing
, _tags = Nothing
})

--
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -205,7 +205,7 @@ checkRelativePath (D.fromNormalizedFilePath -> relPath) = do
unless (FilePath.isRelative relPath) $
throwError (ExpectedRelativePath relPath)
testDirPath <- ShakeTest $ Reader.asks steTestDirPath
let path = D.toNormalizedFilePath $ testDirPath </> relPath
let path = D.toNormalizedFilePath' $ testDirPath </> relPath
checkPath path
return path

Expand All @@ -230,7 +230,7 @@ makeFile relPath contents = do

-- | (internal) Turn a module name into a relative file path.
moduleNameToFilePath :: String -> D.NormalizedFilePath
moduleNameToFilePath modName = D.toNormalizedFilePath $ FilePath.addExtension (replace "." [FilePath.pathSeparator] modName) "daml"
moduleNameToFilePath modName = D.toNormalizedFilePath' $ FilePath.addExtension (replace "." [FilePath.pathSeparator] modName) "daml"

-- | Similar to makeFile but including a header derived from the module name.
makeModule :: String -> [T.Text] -> ShakeTest D.NormalizedFilePath
Expand Down Expand Up @@ -350,7 +350,7 @@ cursorPosition (_absPath, line, col) = D.Position line col

locationStartCursor :: D.Location -> Cursor
locationStartCursor (D.Location path (D.Range (D.Position line col) _)) =
(D.toNormalizedFilePath $ fromMaybe D.noFilePath $ D.uriToFilePath' path, line, col)
(D.toNormalizedFilePath' $ fromMaybe D.noFilePath $ D.uriToFilePath' path, line, col)

-- | Same as Cursor, but passing a list of columns, so you can specify a range
-- such as (foo,1,[10..20]).
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ handle
-> IO (Either e (List CodeLens))
handle ide (CodeLensParams (TextDocumentIdentifier uri) _) = Right <$> do
mbResult <- case uriToFilePath' uri of
Just (toNormalizedFilePath -> filePath) -> do
Just (toNormalizedFilePath' -> filePath) -> do
logInfo (ideLogger ide) $ "CodeLens request for file: " <> T.pack (fromNormalizedFilePath filePath)
mbModMapping <- runAction ide (useWithStale GenerateRawDalf filePath)
case mbModMapping of
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import qualified DA.Daml.LF.Ast as LF
import qualified DA.Daml.Visual as Visual

collectTexts :: List Aeson.Value -> Maybe NormalizedFilePath
collectTexts (List [Aeson.String file]) = Just (toNormalizedFilePath (T.unpack file))
collectTexts (List [Aeson.String file]) = Just (toNormalizedFilePath' (T.unpack file))
collectTexts _= Nothing

onCommand
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,7 @@ conversionError msg = do
, _message = T.pack msg
, _code = Nothing
, _relatedInformation = Nothing
, _tags = Nothing
}

unsupported :: (HasCallStack, Outputable a) => String -> a -> ConvertM e
Expand Down
16 changes: 8 additions & 8 deletions compiler/damlc/lib/DA/Cli/Damlc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -202,7 +202,7 @@ runTestsInProjectOrFiles projectOpts Nothing color mbJUnitOutput cliOptions init
runTestsInProjectOrFiles projectOpts (Just inFiles) color mbJUnitOutput cliOptions initPkgDb = Command Test (Just projectOpts) effect
where effect = withProjectRoot' projectOpts $ \relativize -> do
initPackageDb cliOptions initPkgDb
inFiles' <- mapM (fmap toNormalizedFilePath . relativize) inFiles
inFiles' <- mapM (fmap toNormalizedFilePath' . relativize) inFiles
execTest inFiles' color mbJUnitOutput cliOptions

cmdInspect :: Mod CommandFields Command
Expand Down Expand Up @@ -445,7 +445,7 @@ execCompile inputFile outputFile opts (WriteInterface writeInterface) mbIfaceDir
projectOpts = ProjectOpts Nothing (ProjectCheck "" False)
effect = withProjectRoot' projectOpts $ \relativize -> do
loggerH <- getLogger opts "compile"
inputFile <- toNormalizedFilePath <$> relativize inputFile
inputFile <- toNormalizedFilePath' <$> relativize inputFile
opts <- pure opts { optIfaceDir = mbIfaceDir }
withDamlIdeState opts loggerH diagnosticsLogger $ \ide -> do
setFilesOfInterest ide (HashSet.singleton inputFile)
Expand All @@ -460,7 +460,7 @@ execCompile inputFile outputFile opts (WriteInterface writeInterface) mbIfaceDir

when writeInterface $ do
files <- nubSort . concatMap transitiveModuleDeps <$> use GetDependencies inputFile
mbIfaces <- writeIfacesAndHie (toNormalizedFilePath $ fromMaybe ifaceDir $ optIfaceDir opts) files
mbIfaces <- writeIfacesAndHie (toNormalizedFilePath' $ fromMaybe ifaceDir $ optIfaceDir opts) files
void $ liftIO $ mbErr "ERROR: Compilation failed." mbIfaces

mbDalf <- getDalf inputFile
Expand All @@ -481,7 +481,7 @@ execLint inputFile opts =
withProjectRoot' projectOpts $ \relativize ->
do
loggerH <- getLogger opts "lint"
inputFile <- toNormalizedFilePath <$> relativize inputFile
inputFile <- toNormalizedFilePath' <$> relativize inputFile
opts <- setDlintDataDir opts
withDamlIdeState opts loggerH diagnosticsLogger $ \ide -> do
setFilesOfInterest ide (HashSet.singleton inputFile)
Expand Down Expand Up @@ -572,7 +572,7 @@ initPackageDb opts (InitPkgDb shouldInit) =
when isProject $ do
projRoot <- getCurrentDirectory
withPackageConfig defaultProjectPath $ \PackageConfigFields {..} ->
createProjectPackageDb (toNormalizedFilePath projRoot) opts pSdkVersion pDependencies pDataDependencies
createProjectPackageDb (toNormalizedFilePath' projRoot) opts pSdkVersion pDependencies pDataDependencies

createDarFile :: FilePath -> Zip.ZipArchive () -> IO ()
createDarFile fp dar = do
Expand Down Expand Up @@ -600,7 +600,7 @@ execBuild projectOpts opts mbOutFile incrementalBuild initPkgDb =
buildDar
compilerH
pkgConfig
(toNormalizedFilePath $ fromMaybe ifaceDir $ optIfaceDir opts)
(toNormalizedFilePath' $ fromMaybe ifaceDir $ optIfaceDir opts)
(FromDalf False)
dar <- mbErr "ERROR: Creation of DAR file failed." mbDar
let fp = targetFilePath $ unitIdString (pkgNameVersion pName pVersion)
Expand Down Expand Up @@ -691,7 +691,7 @@ execPackage projectOpts filePath opts mbOutFile dalfInput =
, pDataDependencies = []
, pSdkVersion = PackageSdkVersion SdkVersion.sdkVersion
}
(toNormalizedFilePath $ fromMaybe ifaceDir $ optIfaceDir opts)
(toNormalizedFilePath' $ fromMaybe ifaceDir $ optIfaceDir opts)
dalfInput
case mbDar of
Nothing -> do
Expand Down Expand Up @@ -820,7 +820,7 @@ execDocTest opts files =
Command DocTest Nothing effect
where
effect = do
let files' = map toNormalizedFilePath files
let files' = map toNormalizedFilePath' files
logger <- getLogger opts "doctest"
-- We don’t add a logger here since we will otherwise emit logging messages twice.
importPaths <-
Expand Down
2 changes: 1 addition & 1 deletion compiler/damlc/lib/DA/Cli/Damlc/Command/Damldoc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -213,7 +213,7 @@ exec Damldoc{..} = do
, do_outputPath = cOutputPath
, do_outputFormat = cOutputFormat
, do_inputFormat = cInputFormat
, do_inputFiles = map toNormalizedFilePath cMainFiles
, do_inputFiles = map toNormalizedFilePath' cMainFiles
, do_docTemplate = cTemplate
, do_transformOptions = transformOptions
, do_docTitle = T.pack . unitIdString <$> optUnitId cOptions
Expand Down
4 changes: 2 additions & 2 deletions compiler/damlc/lib/DA/Cli/Damlc/Packaging.hs
Original file line number Diff line number Diff line change
Expand Up @@ -257,7 +257,7 @@ generateAndInstallIfaceFiles ::
-> IO ()
generateAndInstallIfaceFiles dalf src opts workDir dbPath projectPackageDatabase pkgIdStr pkgName mbPkgVersion deps dependencies = do
loggerH <- getLogger opts "generate interface files"
let src' = [ (toNormalizedFilePath $ workDir </> fromNormalizedFilePath nfp, str) | (nfp, str) <- src]
let src' = [ (toNormalizedFilePath' $ workDir </> fromNormalizedFilePath nfp, str) | (nfp, str) <- src]
mapM_ writeSrc src'
-- We expose dependencies under a Pkg_$pkgId prefix so we can unambiguously refer to them
-- while avoiding name collisions in package imports.
Expand Down Expand Up @@ -294,7 +294,7 @@ generateAndInstallIfaceFiles dalf src opts workDir dbPath projectPackageDatabase
-- Setting ifDir to . means that the interface files will end up directly next to
-- the source files which is what we want here.
writeIfacesAndHie
(toNormalizedFilePath ".")
(toNormalizedFilePath' ".")
[fp | (fp, _content) <- src']
when (isNothing res) $
errorIO
Expand Down
2 changes: 1 addition & 1 deletion compiler/damlc/lib/DA/Cli/Output.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,5 +60,5 @@ diagnosticsLogger = hDiagnosticsLogger stderr

hDiagnosticsLogger :: Handle -> FromServerMessage -> IO ()
hDiagnosticsLogger handle = \case
EventFileDiagnostics fp diags -> printDiagnostics handle $ map (toNormalizedFilePath fp,ShowDiag,) diags
EventFileDiagnostics fp diags -> printDiagnostics handle $ map (toNormalizedFilePath' fp,ShowDiag,) diags
_ -> pure ()
Loading

0 comments on commit aa48f30

Please sign in to comment.