Skip to content
Snippets Groups Projects
Commit a4732584 authored by Ryan Scott's avatar Ryan Scott
Browse files

Patch doctest-0.17

parent b566be04
No related branches found
No related tags found
No related merge requests found
diff --git a/doctest.cabal b/doctest.cabal
index d66be9d..2f68e5c 100644
--- a/doctest.cabal
+++ b/doctest.cabal
@@ -142,6 +142,9 @@ library
, process
, syb >=0.3
, transformers
+ if impl(ghc >= 8.11)
+ build-depends:
+ exceptions
default-language: Haskell2010
executable doctest
diff --git a/src/Extract.hs b/src/Extract.hs
index 81ed5a9..f26f639 100644
--- a/src/Extract.hs
+++ b/src/Extract.hs
@@ -21,10 +21,19 @@ import GHC hiding (flags, Module, Located)
import MonadUtils (liftIO, MonadIO)
#else
import GHC hiding (Module, Located)
+# if __GLASGOW_HASKELL__ >= 811
+import qualified Control.Monad.Catch as MC
+import GHC.Data.Graph.Directed (flattenSCCs)
+import GHC.Driver.Session
+import GHC.Utils.Exception (ExceptionMonad)
+import GHC.Utils.Monad (liftIO)
+# else
+import Digraph (flattenSCCs)
import DynFlags
+import Exception (ExceptionMonad)
import MonadUtils (liftIO)
+# endif
#endif
-import Exception (ExceptionMonad)
import System.Directory
import System.FilePath
@@ -37,8 +46,6 @@ import Coercion (Coercion)
import FastString (unpackFS)
#endif
-import Digraph (flattenSCCs)
-
import System.Posix.Internals (c_getpid)
import GhcUtil (withGhc)
@@ -47,7 +54,9 @@ import Location hiding (unLoc)
import Util (convertDosLineEndings)
import PackageDBs (getPackageDBArgs)
-#if __GLASGOW_HASKELL__ >= 806
+#if __GLASGOW_HASKELL__ >= 811
+import GHC.Runtime.Loader (initializePlugins)
+#elif __GLASGOW_HASKELL__ >= 806
import DynamicLoading (initializePlugins)
#endif
@@ -159,7 +168,11 @@ parse args = withGhc args $ \modules_ -> withTempOutputDir $ do
-- | A variant of 'gbracket' where the return value from the first computation
-- is not required.
gbracket_ :: ExceptionMonad m => m a -> m b -> m c -> m c
+#if __GLASGOW_HASKELL__ >= 811
+ gbracket_ = MC.bracket_
+#else
gbracket_ before_ after thing = gbracket before_ (const after) (const thing)
+#endif
setOutputDir f d = d {
objectDir = Just f
diff --git a/src/GhcUtil.hs b/src/GhcUtil.hs
index 52e965e..862b033 100644
--- a/src/GhcUtil.hs
+++ b/src/GhcUtil.hs
@@ -8,11 +8,17 @@ import GHC hiding (flags)
import DynFlags (dopt_set)
#else
import GHC
+# if __GLASGOW_HASKELL__ >= 811
+import GHC.Driver.Session (gopt_set)
+import GHC.Utils.Monad (liftIO)
+import GHC.Utils.Panic (throwGhcException)
+# else
import DynFlags (gopt_set)
-#endif
+import MonadUtils (liftIO)
import Panic (throwGhcException)
+# endif
+#endif
-import MonadUtils (liftIO)
import System.Exit (exitFailure)
#if __GLASGOW_HASKELL__ < 702
diff --git a/src/Location.hs b/src/Location.hs
index e005fe5..a3f06fc 100644
--- a/src/Location.hs
+++ b/src/Location.hs
@@ -2,9 +2,15 @@
module Location where
import Control.DeepSeq (deepseq, NFData(rnf))
+#if __GLASGOW_HASKELL__ >= 811
+import GHC.Data.FastString (unpackFS)
+import GHC.Types.SrcLoc hiding (Located)
+import qualified GHC.Types.SrcLoc as GHC
+#else
+import FastString (unpackFS)
import SrcLoc hiding (Located)
import qualified SrcLoc as GHC
-import FastString (unpackFS)
+#endif
#if __GLASGOW_HASKELL__ < 702
import Outputable (showPpr)
@@ -63,5 +69,9 @@ toLocation loc
#else
toLocation loc = case loc of
UnhelpfulSpan str -> UnhelpfulLocation (unpackFS str)
- RealSrcSpan sp -> Location (unpackFS . srcSpanFile $ sp) (srcSpanStartLine sp)
+ RealSrcSpan sp
+# if __GLASGOW_HASKELL__ >= 811
+ _
+# endif
+ -> Location (unpackFS . srcSpanFile $ sp) (srcSpanStartLine sp)
#endif
diff --git a/src/Options.hs b/src/Options.hs
index a7c2758..54d3bb3 100644
--- a/src/Options.hs
+++ b/src/Options.hs
@@ -23,7 +23,11 @@ import Data.Maybe
import qualified Paths_doctest
import Data.Version (showVersion)
+#if __GLASGOW_HASKELL__ >= 811
+import GHC.Settings.Config as GHC
+#else
import Config as GHC
+#endif
import Interpreter (ghc)
usage :: String
diff --git a/src/Run.hs b/src/Run.hs
index 95c2c14..6f51252 100644
--- a/src/Run.hs
+++ b/src/Run.hs
@@ -20,7 +20,11 @@ import System.IO
import System.IO.CodePage (withCP65001)
import qualified Control.Exception as E
+#if __GLASGOW_HASKELL__ >= 811
+import GHC.Utils.Panic
+#else
import Panic
+#endif
import PackageDBs
import Parse
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment