Skip to content

Commit

Permalink
9.6 support (#392)
Browse files Browse the repository at this point in the history
  • Loading branch information
wz1000 authored Mar 13, 2023
1 parent 62d9fa7 commit 16669d1
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 4 deletions.
14 changes: 13 additions & 1 deletion src/HIE/Bios/Ghc/Doc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,14 @@
module HIE.Bios.Ghc.Doc where


import GHC (DynFlags, getPrintUnqual, pprCols, GhcMonad)
import GHC (DynFlags
#if __GLASGOW_HASKELL__ < 905
, getPrintUnqual
#endif
, pprCols, GhcMonad)
#if __GLASGOW_HASKELL__ >= 905
import GHC.Utils.Outputable
#endif

#if __GLASGOW_HASKELL__ >= 900
import GHC.Driver.Session (initSDocContext)
Expand All @@ -16,6 +23,11 @@ import Pretty (Mode(..), Doc, Style(..), renderStyle, style)

import HIE.Bios.Ghc.Gap (makeUserStyle, pageMode, oneLineMode)

#if __GLASGOW_HASKELL__ >= 905
getPrintUnqual :: Monad m => m NamePprCtx
getPrintUnqual = pure neverQualify
#endif

showPage :: DynFlags -> PprStyle -> SDoc -> String
showPage dflag stl sdoc = showDocWith dflag pageMode $ runSDoc sdoc scontext
where
Expand Down
8 changes: 7 additions & 1 deletion src/HIE/Bios/Ghc/Gap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -217,7 +217,9 @@ pattern RealSrcSpan t <- G.RealSrcSpan t
----------------------------------------------------------------

setNoCode :: DynFlags -> DynFlags
#if __GLASGOW_HASKELL__ >= 901
#if __GLASGOW_HASKELL__ >= 905
setNoCode d = d { G.backend = G.noBackend }
#elif __GLASGOW_HASKELL__ >= 901
setNoCode d = d { G.backend = G.NoBackend }
#else
setNoCode d = d { G.hscTarget = G.HscNothing }
Expand Down Expand Up @@ -251,7 +253,11 @@ guessTarget a _ b = G.guessTarget a b

----------------------------------------------------------------

#if __GLASGOW_HASKELL__ >= 905
makeUserStyle :: DynFlags -> NamePprCtx -> PprStyle
#else
makeUserStyle :: DynFlags -> PrintUnqualified -> PprStyle
#endif
#if __GLASGOW_HASKELL__ >= 900
makeUserStyle _dflags style = mkUserStyle style AllTheWay
#elif __GLASGOW_HASKELL__ >= 804
Expand Down
10 changes: 8 additions & 2 deletions src/HIE/Bios/Ghc/Logger.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE BangPatterns, CPP #-}
{-# LANGUAGE BangPatterns, CPP, TypeApplications #-}

module HIE.Bios.Ghc.Logger (
withLogger
Expand Down Expand Up @@ -64,8 +64,10 @@ appendLogRef :: DynFlags -> Gap.PprStyle -> LogRef -> LogAction
appendLogRef df style (LogRef ref)
#if __GLASGOW_HASKELL__ < 903
_ _ sev src
#else
#elif __GLASGOW_HASKELL__ < 905
_ (MCDiagnostic sev _) src
#else
_ (MCDiagnostic sev _ _) src
#endif
#if __GLASGOW_HASKELL__ < 900
_style
Expand Down Expand Up @@ -127,7 +129,11 @@ ppErrMsg :: DynFlags -> Gap.PprStyle -> MsgEnvelope GhcMessage -> String
ppErrMsg dflag style err = ppMsg spn SevError dflag style msg -- ++ ext
where
spn = errMsgSpan err
#if __GLASGOW_HASKELL__ >= 905
msg = pprLocMsgEnvelope (defaultDiagnosticOpts @GhcMessage) err
#else
msg = pprLocMsgEnvelope err
#endif
-- fixme
#elif __GLASGOW_HASKELL__ >= 902
errBagToStrList :: DynFlags -> Gap.PprStyle -> Bag (MsgEnvelope DecoratedSDoc) -> [String]
Expand Down

0 comments on commit 16669d1

Please sign in to comment.