Skip to content

Commit

Permalink
Remove a couple of CPP statements from Wingman
Browse files Browse the repository at this point in the history
  • Loading branch information
fendor committed Sep 15, 2021
1 parent 26b444b commit 02a7bd1
Show file tree
Hide file tree
Showing 5 changed files with 38 additions and 14 deletions.
23 changes: 23 additions & 0 deletions ghcide/src/Development/IDE/GHC/Compat/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -272,6 +272,7 @@ module Development.IDE.GHC.Compat.Core (
-- * Role
Role(..),
-- * Panic
PlainGhcException,
panic,
-- * Util Module re-exports
#if MIN_VERSION_ghc(9,0,0)
Expand All @@ -293,6 +294,7 @@ module Development.IDE.GHC.Compat.Core (
module GHC.Core.TyCon,
module GHC.Core.TyCo.Ppr,
module GHC.Core.Type,
module GHC.Core.Unify,
module GHC.Core.Utils,

module GHC.HsToCore.Docs,
Expand All @@ -301,6 +303,11 @@ module Development.IDE.GHC.Compat.Core (

module GHC.Iface.Tidy,
module GHC.Iface.Syntax,

#if MIN_VERSION_ghc(9,2,0)
module Language.Haskell.Syntax.Expr,
#endif

module GHC.Rename.Names,
module GHC.Rename.Splice,

Expand Down Expand Up @@ -371,6 +378,7 @@ module Development.IDE.GHC.Compat.Core (
module TysPrim,
module TysWiredIn,
module Type,
module Unify,
module UniqSupply,
module Var,
#endif
Expand Down Expand Up @@ -429,6 +437,7 @@ import GHC.Core.TyCo.Ppr
import qualified GHC.Core.TyCo.Rep as TyCoRep
import GHC.Core.TyCon
import GHC.Core.Type hiding (mkInfForAllTys, mkVisFunTys)
import GHC.Core.Unify
import GHC.Core.Utils

#if MIN_VERSION_ghc(9,2,0)
Expand Down Expand Up @@ -525,6 +534,7 @@ import GHC.Unit.Module.ModIface (IfaceExport)
import GHC.Unit.State (ModuleOrigin (..))
import GHC.Utils.Error (Severity (..))
import GHC.Utils.Panic hiding (try)
import qualified GHC.Utils.Panic.Plain as Plain
#else
import qualified Avail
import BasicTypes hiding (Version)
Expand Down Expand Up @@ -583,7 +593,13 @@ import NameCache
import NameEnv
import NameSet
import Packages
#if MIN_VERSION_ghc(8,8,0)
import Panic hiding (try)
import qualified PlainPanic as Plain
#else
import Panic hiding (GhcException, try)
import qualified Panic as Plain
#endif
import Parser
import PatSyn
#if MIN_VERSION_ghc(8,8,0)
Expand Down Expand Up @@ -614,6 +630,7 @@ import TyCon
import Type hiding (mkVisFunTys)
import TysPrim
import TysWiredIn
import Unify
import UniqSupply
import Var (Var (varName), setTyVarUnique,
setVarUnique, varType)
Expand Down Expand Up @@ -822,3 +839,9 @@ pattern NotBoot, IsBoot :: IsBootInterface
pattern NotBoot = False
pattern IsBoot = True
#endif

#if MIN_VERSION_ghc(8,8,0)
type PlainGhcException = Plain.PlainGhcException
#else
type PlainGhcException = Plain.GhcException
#endif
12 changes: 2 additions & 10 deletions plugins/hls-tactics-plugin/src/Wingman/Debug.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,17 +18,9 @@ import Control.DeepSeq
import Control.Exception
import Debug.Trace
import Development.IDE.GHC.Compat.Outputable
import Development.IDE.GHC.Compat (PlainGhcException)
import System.IO.Unsafe (unsafePerformIO)

#if __GLASGOW_HASKELL__ >= 808
import PlainPanic (PlainGhcException)
type GHC_EXCEPTION = PlainGhcException
#else
import Panic (GhcException)
type GHC_EXCEPTION = GhcException
#endif


------------------------------------------------------------------------------
-- | Print something
unsafeRender :: Outputable a => a -> String
Expand All @@ -40,7 +32,7 @@ unsafeRender' sdoc = unsafePerformIO $ do
let z = showSDocUnsafe sdoc
-- We might not have unsafeGlobalDynFlags (like during testing), in which
-- case GHC panics. Instead of crashing, let's just fail to print.
!res <- try @GHC_EXCEPTION $ evaluate $ deepseq z z
!res <- try @PlainGhcException $ evaluate $ deepseq z z
pure $ either (const "<unsafeRender'>") id res
{-# NOINLINE unsafeRender' #-}

Expand Down
1 change: 0 additions & 1 deletion plugins/hls-tactics-plugin/src/Wingman/GHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@ import Development.IDE.GHC.Compat
import Development.IDE.GHC.Compat.Util
import GHC.SourceGen (lambda)
import Generics.SYB (Data, everything, everywhere, listify, mkQ, mkT)
import Unify
import Wingman.StaticPlugin (pattern MetaprogramSyntax)
import Wingman.Types

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Data.String (IsString)
import Data.Text (Text)
import Data.Text.Prettyprint.Doc hiding (parens)
import Data.Text.Prettyprint.Doc.Render.String (renderString)
import GhcPlugins (OccName)
import Development.IDE.GHC.Compat (OccName)
import qualified Text.Megaparsec as P
import Wingman.Metaprogramming.Lexer (Parser, identifier, variable, parens)
import Wingman.Types (TacticsM)
Expand Down
14 changes: 12 additions & 2 deletions plugins/hls-tactics-plugin/src/Wingman/StaticPlugin.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,9 +40,15 @@ pattern MetaprogramSourceText = SourceText "wingman-meta-program"


pattern WingmanMetaprogram :: FastString -> HsExpr p
pattern WingmanMetaprogram mp
<- HsSCC _ MetaprogramSourceText (StringLiteral NoSourceText mp)
pattern WingmanMetaprogram mp <-
#if __GLASGOW_HASKELL__ >= 900
HsPragE _ (HsPragSCC _ MetaprogramSourceText (StringLiteral NoSourceText mp))
(L _ ( HsVar _ _))
#else
HsSCC _ MetaprogramSourceText (StringLiteral NoSourceText mp)
(L _ ( HsVar _ _))
#endif



enableQuasiQuotes :: DynFlags -> DynFlags
Expand Down Expand Up @@ -72,7 +78,11 @@ metaprogramHoleName = mkVarOcc "_$metaprogram"

mkMetaprogram :: SrcSpan -> FastString -> HsExpr GhcPs
mkMetaprogram ss mp =
#if __GLASGOW_HASKELL__ >= 900
HsPragE noExtField (HsPragSCC noExtField MetaprogramSourceText (StringLiteral NoSourceText mp))
#else
HsSCC noExtField MetaprogramSourceText (StringLiteral NoSourceText mp)
#endif
$ L ss
$ HsVar noExtField
$ L ss
Expand Down

0 comments on commit 02a7bd1

Please sign in to comment.