diff --git a/.hlint.yaml b/.hlint.yaml index ec26e34ed6a..ed54788a0a2 100644 --- a/.hlint.yaml +++ b/.hlint.yaml @@ -75,7 +75,7 @@ - {name: ViewPatterns, within: []} # Shady extensions - - {name: CPP, within: [DA.Sdk.Cli.System, DA.Sdk.Cli.Version, DAML.Assistant.Install.Path]} + - {name: CPP, within: [DA.Sdk.Cli.System, DA.Sdk.Cli.Version, DAML.Assistant.Install.Path, Development.IDE.Functions.Compile]} - {name: ImplicitParams, within: []} - flags: diff --git a/compiler/haskell-ide-core/src/Development/IDE/Functions/Compile.hs b/compiler/haskell-ide-core/src/Development/IDE/Functions/Compile.hs index f12452b57de..a6b036b4077 100644 --- a/compiler/haskell-ide-core/src/Development/IDE/Functions/Compile.hs +++ b/compiler/haskell-ide-core/src/Development/IDE/Functions/Compile.hs @@ -3,6 +3,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} +{-# LANGUAGE CPP #-} -- | Based on https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/API. -- Given a list of paths to find libraries, and a file to compile, produce a list of 'CoreModule' values. @@ -414,7 +415,9 @@ getModSummaryFromBuffer fp (contents, fileDate) dflags parsed = do { ml_hs_file = Just fp , ml_hi_file = replaceExtension fp "hi" , ml_obj_file = replaceExtension fp "o" +#ifndef USE_GHC , ml_hie_file = replaceExtension fp "hie" +#endif -- This does not consider the dflags configuration -- (-osuf and -hisuf, object and hi dir.s). -- However, we anyway don't want to generate them. @@ -433,7 +436,9 @@ getModSummaryFromBuffer fp (contents, fileDate) dflags parsed = do , ms_hsc_src = HsSrcFile , ms_obj_date = Nothing , ms_iface_date = Nothing +#ifndef USE_GHC , ms_hie_date = Nothing +#endif , ms_srcimps = [] -- source imports are not allowed , ms_parsed_mod = Nothing } @@ -450,8 +455,13 @@ parseFileContents preprocessor filename (time, contents) = do let loc = mkRealSrcLoc (mkFastString filename) 1 1 dflags <- parsePragmasIntoDynFlags filename contents case unP Parser.parseModule (mkPState dflags contents loc) of +#ifdef USE_GHC + PFailed getMessages _ _ -> + Ex.throwE $ toDiagnostics dflags $ snd $ getMessages dflags +#else PFailed s -> Ex.throwE $ toDiagnostics dflags $ snd $ getMessages s dflags +#endif POk pst rdr_module -> let hpm_annotations = (Map.fromListWith (++) $ annotations pst, diff --git a/compiler/haskell-ide-core/src/Development/IDE/Functions/Documentation.hs b/compiler/haskell-ide-core/src/Development/IDE/Functions/Documentation.hs index ce1c89a6850..020575bad47 100644 --- a/compiler/haskell-ide-core/src/Development/IDE/Functions/Documentation.hs +++ b/compiler/haskell-ide-core/src/Development/IDE/Functions/Documentation.hs @@ -80,7 +80,7 @@ getDocumentation targetName tcs = fromMaybe [] $ do -- | Shows this part of the documentation docHeaders :: [RealLocated AnnotationComment] -> [T.Text] -docHeaders = mapMaybe (wrk . unRealSrcSpan) +docHeaders = mapMaybe (\(L _ x) -> wrk x) where wrk = \case AnnDocCommentNext s -> Just $ T.pack s diff --git a/compiler/haskell-ide-core/src/Development/IDE/Functions/SpanInfo.hs b/compiler/haskell-ide-core/src/Development/IDE/Functions/SpanInfo.hs index f426720eb7c..aede813ae83 100644 --- a/compiler/haskell-ide-core/src/Development/IDE/Functions/SpanInfo.hs +++ b/compiler/haskell-ide-core/src/Development/IDE/Functions/SpanInfo.hs @@ -36,7 +36,7 @@ getSpanInfo mods tcm = do let tcs = tm_typechecked_source tcm bs = listifyAllSpans tcs :: [LHsBind GhcTc] es = listifyAllSpans tcs :: [LHsExpr GhcTc] - ps = listifyAllSpans' tcs :: [LPat GhcTc] + ps = listifyAllSpans' tcs :: [Pat GhcTc] bts <- mapM (getTypeLHsBind tcm) bs -- binds ets <- mapM (getTypeLHsExpr tcm) es -- expressions pts <- mapM (getTypeLPat tcm) ps -- patterns