mirror of
https://github.com/IHaskell/IHaskell.git
synced 2025-04-20 21:36:07 +00:00
Drop support for GHC < 8.4 (#1531)
* Drop support for GHC < 8.4 * src/IHaskell/Eval/Util.hs: update * src/IHaskell/Eval/Evaluate.hs: update * ghc-parser/generic-src/Language/Haskell/GHC/Parser.hs: update * src/IHaskell/Eval/Info.hs: update * src/IHaskell/Eval/Parser.hs: update * src/IHaskell/Eval/Completion.hs: update * src/tests/IHaskell/Test/Eval.hs: update * ghc-parser: remove unused files * README.md: update
This commit is contained in:
parent
00736a25ef
commit
b62ca93c0f
@ -6,7 +6,7 @@
|
||||
>
|
||||
> Alternatively, watch a [talk and demo](http://begriffs.com/posts/2016-01-20-ihaskell-notebook.html) showing off IHaskell features.
|
||||
|
||||
IHaskell is a kernel for the [Jupyter project](https://jupyter.org), which allows you to use Haskell inside Jupyter frontends (including the console and notebook). It currently supports GHC 8.0 through 9.0. For GHC 7.10 support please use the [`GHC7`](https://github.com/gibiansky/IHaskell/releases/tag/GHC7) tag.
|
||||
IHaskell is a kernel for the [Jupyter project](https://jupyter.org), which allows you to use Haskell inside Jupyter frontends (including the console and notebook). It currently supports GHC 8.4 through 9.10.
|
||||
|
||||
For a tour of some IHaskell features, check out the [demo Notebook](http://nbviewer.org/github/gibiansky/IHaskell/blob/master/notebooks/IHaskell.ipynb). More example notebooks are available on the [wiki](https://github.com/gibiansky/IHaskell/wiki).
|
||||
The [wiki](https://github.com/gibiansky/IHaskell/wiki) also has more extensive documentation of IHaskell features.
|
||||
|
@ -76,12 +76,8 @@ import StringBuffer hiding (len)
|
||||
#else
|
||||
import ErrUtils hiding (ErrMsg)
|
||||
#endif
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
import GHC hiding (Located, Parsed, parser)
|
||||
#else
|
||||
import GHC hiding (Located, parser)
|
||||
#endif
|
||||
|
||||
import GHC hiding (Located, Parsed, parser)
|
||||
import qualified Language.Haskell.GHC.HappyParser as Parse
|
||||
|
||||
-- | A line number in an input string.
|
||||
@ -115,49 +111,27 @@ data Located a = Located {
|
||||
data Parser a = Parser (P a)
|
||||
|
||||
-- Our parsers.
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
parserStatement :: Parser (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
|
||||
#else
|
||||
parserStatement :: Parser (Maybe (LStmt RdrName (LHsExpr RdrName)))
|
||||
#endif
|
||||
parserStatement = Parser Parse.fullStatement
|
||||
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
parserImport :: Parser (LImportDecl GhcPs)
|
||||
#else
|
||||
parserImport :: Parser (LImportDecl RdrName)
|
||||
#endif
|
||||
parserImport = Parser Parse.fullImport
|
||||
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
parserDeclaration :: Parser (OrdList (LHsDecl GhcPs))
|
||||
#else
|
||||
parserDeclaration :: Parser (OrdList (LHsDecl RdrName))
|
||||
#endif
|
||||
parserDeclaration = Parser Parse.fullDeclaration
|
||||
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
parserExpression :: Parser (LHsExpr GhcPs)
|
||||
#else
|
||||
parserExpression :: Parser (LHsExpr RdrName)
|
||||
#endif
|
||||
parserExpression = Parser Parse.fullExpression
|
||||
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
parserTypeSignature :: Parser (SrcLoc.Located (OrdList (LHsDecl GhcPs)))
|
||||
#else
|
||||
parserTypeSignature :: Parser (SrcLoc.Located (OrdList (LHsDecl RdrName)))
|
||||
#endif
|
||||
parserTypeSignature = Parser Parse.fullTypeSignature
|
||||
|
||||
#if MIN_VERSION_ghc(9,6,0)
|
||||
parserModule :: Parser (SrcLoc.Located (HsModule GhcPs))
|
||||
#elif MIN_VERSION_ghc(9,0,0)
|
||||
parserModule :: Parser (SrcLoc.Located HsModule)
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
parserModule :: Parser (SrcLoc.Located (HsModule GhcPs))
|
||||
#else
|
||||
parserModule :: Parser (SrcLoc.Located (HsModule RdrName))
|
||||
parserModule :: Parser (SrcLoc.Located (HsModule GhcPs))
|
||||
#endif
|
||||
parserModule = Parser Parse.fullModule
|
||||
|
||||
@ -206,14 +180,8 @@ runParser flags (Parser parser) str =
|
||||
ln = srcLocLine $ SrcLoc.realSrcSpanStart realSpan
|
||||
col = srcLocCol $ SrcLoc.realSrcSpanStart realSpan
|
||||
in Failure errMsg $ Loc ln col
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
toParseOut (PFailed _ spn@(RealSrcSpan realSpan) err) =
|
||||
let errMsg = printErrorBag $ unitBag $ mkPlainErrMsg flags spn err
|
||||
ln = srcLocLine $ SrcLoc.realSrcSpanStart realSpan
|
||||
col = srcLocCol $ SrcLoc.realSrcSpanStart realSpan
|
||||
in Failure errMsg $ Loc ln col
|
||||
#else
|
||||
toParseOut (PFailed spn@(RealSrcSpan realSpan) err) =
|
||||
toParseOut (PFailed _ spn@(RealSrcSpan realSpan) err) =
|
||||
let errMsg = printErrorBag $ unitBag $ mkPlainErrMsg flags spn err
|
||||
ln = srcLocLine $ SrcLoc.realSrcSpanStart realSpan
|
||||
col = srcLocCol $ SrcLoc.realSrcSpanStart realSpan
|
||||
@ -221,12 +189,8 @@ runParser flags (Parser parser) str =
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_ghc(8,10,0)
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
toParseOut (PFailed _ spn err) =
|
||||
let errMsg = printErrorBag $ unitBag $ mkPlainErrMsg flags spn err
|
||||
in Failure errMsg $ Loc 0 0
|
||||
#else
|
||||
toParseOut (PFailed spn err) =
|
||||
toParseOut (PFailed _ spn err) =
|
||||
let errMsg = printErrorBag $ unitBag $ mkPlainErrMsg flags spn err
|
||||
in Failure errMsg $ Loc 0 0
|
||||
#endif
|
||||
|
@ -23,10 +23,8 @@ library
|
||||
-- other-modules:
|
||||
-- other-extensions:
|
||||
build-depends: base >=4.9 && < 5,
|
||||
ghc >=8.0 && <9.11
|
||||
ghc >=8.4 && <9.11
|
||||
|
||||
if impl(ghc >= 8.0) && impl(ghc < 8.4)
|
||||
hs-source-dirs: generic-src src-8.0
|
||||
if impl(ghc >= 8.4) && impl(ghc < 8.10)
|
||||
hs-source-dirs: generic-src src-8.4
|
||||
if impl(ghc >= 8.10) && impl(ghc < 9.0)
|
||||
|
@ -1,41 +0,0 @@
|
||||
module Language.Haskell.GHC.HappyParser
|
||||
( fullStatement
|
||||
, fullImport
|
||||
, fullDeclaration
|
||||
, fullExpression
|
||||
, fullTypeSignature
|
||||
, fullModule
|
||||
) where
|
||||
|
||||
import Parser
|
||||
import SrcLoc
|
||||
|
||||
-- compiler/hsSyn
|
||||
import HsSyn
|
||||
|
||||
-- compiler/utils
|
||||
import OrdList
|
||||
|
||||
-- compiler/parser
|
||||
import Lexer
|
||||
|
||||
-- compiler/basicTypes
|
||||
import RdrName
|
||||
|
||||
fullStatement :: P (Maybe (LStmt RdrName (LHsExpr RdrName)))
|
||||
fullStatement = parseStmt
|
||||
|
||||
fullImport :: P (LImportDecl RdrName)
|
||||
fullImport = parseImport
|
||||
|
||||
fullDeclaration :: P (OrdList (LHsDecl RdrName))
|
||||
fullDeclaration = fmap unitOL parseDeclaration
|
||||
|
||||
fullExpression :: P (LHsExpr RdrName)
|
||||
fullExpression = parseExpression
|
||||
|
||||
fullTypeSignature :: P (Located (OrdList (LHsDecl RdrName)))
|
||||
fullTypeSignature = fmap (noLoc . unitOL) parseTypeSignature
|
||||
|
||||
fullModule :: P (Located (HsModule RdrName))
|
||||
fullModule = parseModule
|
@ -71,7 +71,7 @@ library
|
||||
bytestring ,
|
||||
exceptions ,
|
||||
filepath ,
|
||||
ghc >=8.0 && <9.11,
|
||||
ghc >=8.4 && <9.11,
|
||||
ghc-boot ,
|
||||
haskeline ,
|
||||
parsec ,
|
||||
|
@ -68,10 +68,8 @@ data CompletionType = Empty
|
||||
| Extension String
|
||||
deriving (Show, Eq)
|
||||
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
exposedName :: (a, b) -> a
|
||||
exposedName = fst
|
||||
#endif
|
||||
|
||||
extName :: FlagSpec flag -> String
|
||||
extName (FlagSpec { flagSpecName = name }) = name
|
||||
|
@ -107,18 +107,13 @@ import StringUtils (replace, split, strip, rstrip)
|
||||
import IHaskell.Eval.Lint
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
import qualified Data.Text as Text
|
||||
import IHaskell.Eval.Evaluate.HTML (htmlify)
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_ghc(9,0,0)
|
||||
import GHC.Data.FastString
|
||||
#elif MIN_VERSION_ghc(8,2,0)
|
||||
import FastString (unpackFS)
|
||||
#else
|
||||
import Paths_ihaskell (version)
|
||||
import Data.Version (versionBranch)
|
||||
import FastString (unpackFS)
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_ghc(9,2,0)
|
||||
@ -257,7 +252,7 @@ packageIdString' dflags pkg_cfg =
|
||||
Just cfg -> let
|
||||
PackageName name = unitPackageName cfg
|
||||
in unpackFS name
|
||||
#elif MIN_VERSION_ghc(8,2,0)
|
||||
#else
|
||||
packageIdString' :: DynFlags -> PackageConfig -> String
|
||||
packageIdString' dflags pkg_cfg =
|
||||
case (lookupPackage dflags $ packageConfigId pkg_cfg) of
|
||||
@ -265,10 +260,6 @@ packageIdString' dflags pkg_cfg =
|
||||
Just cfg -> let
|
||||
PackageName name = packageName cfg
|
||||
in unpackFS name
|
||||
#else
|
||||
packageIdString' :: DynFlags -> PackageConfig -> String
|
||||
packageIdString' dflags pkg_cfg =
|
||||
fromMaybe "(unknown)" (unitIdPackageIdString dflags $ packageConfigId pkg_cfg)
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_ghc(9,4,0)
|
||||
@ -334,14 +325,8 @@ initializeImports importSupportLibraries = do
|
||||
initStr = "ihaskell-"
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
-- Name of the ihaskell package, i.e. "ihaskell"
|
||||
iHaskellPkgName = "ihaskell"
|
||||
#else
|
||||
-- Name of the ihaskell package, e.g. "ihaskell-1.2.3.4"
|
||||
iHaskellPkgName = initStr ++ intercalate "." (map show (versionBranch version))
|
||||
#endif
|
||||
|
||||
displayPkgs = [ pkgName
|
||||
| pkgName <- packageNames
|
||||
, Just (x:_) <- [stripPrefix initStr pkgName]
|
||||
@ -357,17 +342,8 @@ initializeImports importSupportLibraries = do
|
||||
|
||||
importFmt = "import IHaskell.Display.%s"
|
||||
|
||||
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
toImportStmt :: String -> String
|
||||
toImportStmt = printf importFmt . concatMap capitalize . drop 1 . split "-"
|
||||
#else
|
||||
dropFirstAndLast :: [a] -> [a]
|
||||
dropFirstAndLast = reverse . drop 1 . reverse . drop 1
|
||||
|
||||
toImportStmt :: String -> String
|
||||
toImportStmt = printf importFmt . concatMap capitalize . dropFirstAndLast . split "-"
|
||||
#endif
|
||||
|
||||
displayImports = map toImportStmt displayPkgs
|
||||
|
||||
@ -954,11 +930,9 @@ evalCommand _ (Directive GetInfo str) state = safely state $ do
|
||||
{ evalStatus = Success
|
||||
, evalResult = Display [
|
||||
plain strings
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
, htmlify (Text.pack <$> htmlCodeWrapperClass state)
|
||||
(Text.pack $ htmlCodeTokenPrefix state)
|
||||
strings
|
||||
#endif
|
||||
]
|
||||
, evalState = state
|
||||
, evalPager = []
|
||||
@ -1007,28 +981,16 @@ evalCommand output (Expression expr) state = do
|
||||
-- is no appropriate typeclass instance, this will throw an exception and thus `attempt` will return
|
||||
-- False, and we just resort to plaintext.
|
||||
let displayExpr = printf "(IHaskell.Display.display (%s))" expr :: String
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
canRunDisplay <- attempt $ exprType TM_Inst displayExpr
|
||||
#else
|
||||
canRunDisplay <- attempt $ exprType displayExpr
|
||||
#endif
|
||||
|
||||
-- Check if this is a widget.
|
||||
let widgetExpr = printf "(IHaskell.Display.Widget (%s))" expr :: String
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
isWidget <- attempt $ exprType TM_Inst widgetExpr
|
||||
#else
|
||||
isWidget <- attempt $ exprType widgetExpr
|
||||
#endif
|
||||
|
||||
-- Check if this is a template haskell declaration
|
||||
let declExpr = printf "((id :: IHaskellTH.DecsQ -> IHaskellTH.DecsQ) (%s))" expr :: String
|
||||
let anyExpr = printf "((id :: IHaskellPrelude.Int -> IHaskellPrelude.Int) (%s))" expr :: String
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
isTHDeclaration <- liftM2 (&&) (attempt $ exprType TM_Inst declExpr) (not <$> attempt (exprType TM_Inst anyExpr))
|
||||
#else
|
||||
isTHDeclaration <- liftM2 (&&) (attempt $ exprType declExpr) (not <$> attempt (exprType anyExpr))
|
||||
#endif
|
||||
|
||||
write state $ "Can Display: " ++ show canRunDisplay
|
||||
write state $ "Is Widget: " ++ show isWidget
|
||||
@ -1124,11 +1086,7 @@ evalCommand output (Expression expr) state = do
|
||||
then disp :: Display
|
||||
else removeSvg disp
|
||||
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
isIO exp = attempt $ exprType TM_Inst $ printf "((\\x -> x) :: IO a -> IO a) (%s)" exp
|
||||
#else
|
||||
isIO exp = attempt $ exprType $ printf "((\\x -> x) :: IO a -> IO a) (%s)" exp
|
||||
#endif
|
||||
|
||||
postprocessShowError :: EvalOut -> EvalOut
|
||||
postprocessShowError evalOut = evalOut { evalResult = Display $ map postprocess disps }
|
||||
@ -1174,11 +1132,7 @@ evalCommand _ (Declaration decl) state = wrapExecution state $ do
|
||||
-- Get all the type strings.
|
||||
dflags <- getSessionDynFlags
|
||||
types <- forM nonDataNames $ \name -> do
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
theType <- showSDocUnqual dflags . ppr <$> exprType TM_Inst name
|
||||
#else
|
||||
theType <- showSDocUnqual dflags . ppr <$> exprType name
|
||||
#endif
|
||||
return $ name ++ " :: " ++ theType
|
||||
|
||||
return $ Display [html' (Just ihaskellCSS) $ unlines $ map formatGetType types]
|
||||
@ -1562,11 +1516,7 @@ evalStatementOrIO publish state cmd = do
|
||||
else do
|
||||
-- Get all the type strings.
|
||||
types <- forM nonItNames $ \name -> do
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
theType <- showSDocUnqual dflags . ppr <$> exprType TM_Inst name
|
||||
#else
|
||||
theType <- showSDocUnqual dflags . ppr <$> exprType name
|
||||
#endif
|
||||
return $ name ++ " :: " ++ theType
|
||||
|
||||
let joined = unlines types
|
||||
|
@ -26,11 +26,7 @@ info name = handle handler $ do
|
||||
info name = ghandle handler $ do
|
||||
#endif
|
||||
dflags <- getSessionDynFlags
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
result <- exprType TM_Inst name
|
||||
#else
|
||||
result <- exprType name
|
||||
#endif
|
||||
return $ typeCleaner $ showPpr dflags result
|
||||
where
|
||||
handler :: SomeException -> Interpreter String
|
||||
|
@ -22,11 +22,7 @@ import Data.Char (toLower)
|
||||
import Data.List (maximumBy, inits)
|
||||
import Prelude (head, tail)
|
||||
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
import GHC hiding (Located, Parsed)
|
||||
#else
|
||||
import GHC hiding (Located)
|
||||
#endif
|
||||
|
||||
import Language.Haskell.GHC.Parser
|
||||
import IHaskell.Eval.Util
|
||||
|
@ -132,7 +132,7 @@ import GHC
|
||||
import StringUtils (replace)
|
||||
|
||||
#if MIN_VERSION_ghc(9,0,0)
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
#else
|
||||
import CmdLineParser (warnMsg)
|
||||
#endif
|
||||
|
||||
@ -225,10 +225,8 @@ pprDynFlags show_all dflags =
|
||||
default_dflags = defaultDynFlags (settings dflags) (llvmConfig dflags)
|
||||
#elif MIN_VERSION_ghc(8,6,0)
|
||||
default_dflags = defaultDynFlags (settings dflags) (llvmTargets dflags, llvmPasses dflags)
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
default_dflags = defaultDynFlags (settings dflags) (llvmTargets dflags)
|
||||
#else
|
||||
default_dflags = defaultDynFlags (settings dflags)
|
||||
default_dflags = defaultDynFlags (settings dflags) (llvmTargets dflags)
|
||||
#endif
|
||||
|
||||
fstr, fnostr :: String -> O.SDoc
|
||||
@ -285,10 +283,8 @@ pprLanguages show_all dflags =
|
||||
defaultDynFlags (settings dflags) (llvmConfig dflags) `lang_set`
|
||||
#elif MIN_VERSION_ghc(8,6,0)
|
||||
defaultDynFlags (settings dflags) (llvmTargets dflags, llvmPasses dflags) `lang_set`
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
defaultDynFlags (settings dflags) (llvmTargets dflags) `lang_set`
|
||||
#else
|
||||
defaultDynFlags (settings dflags) `lang_set`
|
||||
defaultDynFlags (settings dflags) (llvmTargets dflags) `lang_set`
|
||||
#endif
|
||||
case language dflags of
|
||||
Nothing -> Just Haskell2010
|
||||
@ -340,10 +336,8 @@ setFlags ext = do
|
||||
let noParseErrs = map (("Could not parse: " ++) . unLoc) unrecognized
|
||||
#if MIN_VERSION_ghc(9,8,0)
|
||||
allWarns = map (show . flip O.runSDoc O.defaultSDocContext . E.formatBulleted . diagnosticMessage defaultOpts . errMsgDiagnostic) (bagToList $ getWarningMessages warnings) ++
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
allWarns = map (unLoc . warnMsg) warnings ++
|
||||
#else
|
||||
allWarns = map unLoc warnings ++
|
||||
allWarns = map (unLoc . warnMsg) warnings ++
|
||||
#endif
|
||||
-- Stack appears to duplicate package flags, so we use `nub` to work around this
|
||||
["-package not supported yet" | nub (packageFlags flags) /= nub (packageFlags flags0)]
|
||||
@ -364,10 +358,8 @@ doc sdoc = do
|
||||
#endif
|
||||
#if MIN_VERSION_ghc(9,0,0)
|
||||
let style = O.mkUserStyle unqual O.AllTheWay
|
||||
#elif MIN_VERSION_ghc(8,2,0)
|
||||
let style = O.mkUserStyle flags unqual O.AllTheWay
|
||||
#else
|
||||
let style = O.mkUserStyle unqual O.AllTheWay
|
||||
let style = O.mkUserStyle flags unqual O.AllTheWay
|
||||
#endif
|
||||
let cols = pprCols flags
|
||||
#if MIN_VERSION_ghc(9,2,0)
|
||||
@ -417,7 +409,6 @@ initGhci sandboxPackages = do
|
||||
let flag = flip xopt_set
|
||||
unflag = flip xopt_unset
|
||||
dflags = flag ExtendedDefaultRules . unflag MonomorphismRestriction $ setWayDynFlag originalFlags
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
pkgFlags =
|
||||
case sandboxPackages of
|
||||
Nothing -> packageDBFlags originalFlags
|
||||
@ -441,21 +432,6 @@ initGhci sandboxPackages = do
|
||||
, pprCols = 300
|
||||
, packageDBFlags = pkgFlags
|
||||
}
|
||||
#else
|
||||
pkgConfs =
|
||||
case sandboxPackages of
|
||||
Nothing -> extraPkgConfs originalFlags
|
||||
Just path ->
|
||||
let pkg = PkgConfFile path
|
||||
in (pkg :) . extraPkgConfs originalFlags
|
||||
|
||||
void $ setSessionDynFlags $ dflags
|
||||
{ hscTarget = HscInterpreted
|
||||
, ghcLink = LinkInMemory
|
||||
, pprCols = 300
|
||||
, extraPkgConfs = pkgConfs
|
||||
}
|
||||
#endif
|
||||
|
||||
-- | Evaluate a single import statement. If this import statement is importing a module which was
|
||||
-- previously imported implicitly (such as `Prelude`) or if this module has a `hiding` annotation,
|
||||
@ -478,11 +454,7 @@ evalImport imports = do
|
||||
|
||||
where
|
||||
-- Check whether an import is the same as another import (same module).
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
importOf :: ImportDecl GhcPs -> InteractiveImport -> Bool
|
||||
#else
|
||||
importOf :: ImportDecl RdrName -> InteractiveImport -> Bool
|
||||
#endif
|
||||
importOf _ (IIModule _) = False
|
||||
importOf imp (IIDecl decl) =
|
||||
#if MIN_VERSION_ghc(8,10,0)
|
||||
@ -496,12 +468,8 @@ evalImport imports = do
|
||||
implicitImportOf :: ImportDecl GhcPs -> InteractiveImport -> Bool
|
||||
implicitImportOf _ (IIModule _) = False
|
||||
implicitImportOf imp (IIDecl decl) = ideclImplicit (ideclExt decl) && imp `importOf` IIDecl decl
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
implicitImportOf :: ImportDecl GhcPs -> InteractiveImport -> Bool
|
||||
implicitImportOf _ (IIModule _) = False
|
||||
implicitImportOf imp (IIDecl decl) = ideclImplicit decl && imp `importOf` IIDecl decl
|
||||
#else
|
||||
implicitImportOf :: ImportDecl RdrName -> InteractiveImport -> Bool
|
||||
implicitImportOf :: ImportDecl GhcPs -> InteractiveImport -> Bool
|
||||
implicitImportOf _ (IIModule _) = False
|
||||
implicitImportOf imp (IIDecl decl) = ideclImplicit decl && imp `importOf` IIDecl decl
|
||||
#endif
|
||||
@ -513,14 +481,8 @@ evalImport imports = do
|
||||
case ideclImportList imp of
|
||||
Just (EverythingBut, _) -> True
|
||||
_ -> False
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
isHiddenImport :: ImportDecl GhcPs -> Bool
|
||||
isHiddenImport imp =
|
||||
case ideclHiding imp of
|
||||
Just (True, _) -> True
|
||||
_ -> False
|
||||
#else
|
||||
isHiddenImport :: ImportDecl RdrName -> Bool
|
||||
isHiddenImport :: ImportDecl GhcPs -> Bool
|
||||
isHiddenImport imp =
|
||||
case ideclHiding imp of
|
||||
Just (True, _) -> True
|
||||
@ -573,11 +535,7 @@ cleanUpDuplicateInstances = modifySession $ \hscEnv ->
|
||||
-- | Get the type of an expression and convert it to a string.
|
||||
getType :: GhcMonad m => String -> m String
|
||||
getType expr = do
|
||||
#if MIN_VERSION_ghc(8,2,0)
|
||||
result <- exprType TM_Inst expr
|
||||
#else
|
||||
result <- exprType expr
|
||||
#endif
|
||||
flags <- getSessionDynFlags
|
||||
#if MIN_VERSION_ghc(9,2,0)
|
||||
let typeStr = showSDoc flags $ O.ppr result
|
||||
@ -617,26 +575,12 @@ getDescription str = do
|
||||
where
|
||||
|
||||
getInfo' = getInfo False
|
||||
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
getInfoType (theType, _, _, _, _) = theType
|
||||
#else
|
||||
getInfoType (theType, _, _, _) = theType
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_ghc(8,4,0)
|
||||
printInfo (thing, fixity, classInstances, famInstances, _) =
|
||||
pprTyThingInContextLoc thing O.$$
|
||||
showFixity thing fixity O.$$
|
||||
O.vcat (map GHC.pprInstance classInstances) O.$$
|
||||
O.vcat (map GHC.pprFamInst famInstances)
|
||||
#else
|
||||
printInfo (thing, fixity, classInstances, famInstances) =
|
||||
pprTyThingInContextLoc thing O.$$
|
||||
showFixity thing fixity O.$$
|
||||
O.vcat (map GHC.pprInstance classInstances) O.$$
|
||||
O.vcat (map GHC.pprFamInst famInstances)
|
||||
#endif
|
||||
showFixity thing fixity =
|
||||
if fixity == GHC.defaultFixity
|
||||
then O.empty
|
||||
|
@ -151,11 +151,9 @@ testEval =
|
||||
#elif MIN_VERSION_ghc(9,0,0)
|
||||
-- brackets around the type variable
|
||||
":typ 3" `becomes` ["3 :: forall {p}. Num p => p"]
|
||||
#elif MIN_VERSION_ghc(8,2,0)
|
||||
#else
|
||||
-- It's `p` instead of `t` for some reason
|
||||
":typ 3" `becomes` ["3 :: forall p. Num p => p"]
|
||||
#else
|
||||
":typ 3" `becomes` ["3 :: forall t. Num t => t"]
|
||||
#endif
|
||||
|
||||
it "evaluates :k directive" $ do
|
||||
@ -176,23 +174,11 @@ testEval =
|
||||
, DisplayData MimeHtml "<div class=\"code CodeMirror cm-s-jupyter cm-s-ipython\"><span class=\"cm-keyword\">type</span><span class=\"cm-space\"> </span><span class=\"cm-variable-2\">String</span><span class=\"cm-space\"> </span><span class=\"cm-atom\">::</span><span class=\"cm-space\"> </span><span class=\"cm-atom\">*</span><span class=\"cm-space\"><br /></span>\n<span class=\"cm-keyword\">type</span><span class=\"cm-space\"> </span><span class=\"cm-variable-2\">String</span><span class=\"cm-space\"> </span><span class=\"cm-atom\">=</span><span class=\"cm-space\"> </span><span class=\"cm-atom\">[</span><span class=\"cm-variable-2\">Char</span><span class=\"cm-atom\">]</span><span class=\"cm-space\"><br /> \t</span><span class=\"cm-comment\">-- Defined in \8216GHC.Base\8217</span><span class=\"cm-space\"><br /></span></div>"
|
||||
]]
|
||||
]
|
||||
#elif MIN_VERSION_ghc(8,4,0)
|
||||
displayDatasBecome ":in String" [
|
||||
ManyDisplay [Display [
|
||||
DisplayData PlainText "type String = [Char] \t-- Defined in \8216GHC.Base\8217"
|
||||
, DisplayData MimeHtml "<div class=\"code CodeMirror cm-s-jupyter cm-s-ipython\"><span class=\"cm-keyword\">type</span><span class=\"cm-space\"> </span><span class=\"cm-variable-2\">String</span><span class=\"cm-space\"> </span><span class=\"cm-atom\">=</span><span class=\"cm-space\"> </span><span class=\"cm-atom\">[</span><span class=\"cm-variable-2\">Char</span><span class=\"cm-atom\">]</span><span class=\"cm-space\"> \t</span><span class=\"cm-comment\">-- Defined in \8216GHC.Base\8217</span><span class=\"cm-space\"><br /></span></div>"
|
||||
]]
|
||||
]
|
||||
#elif MIN_VERSION_ghc(8,2,0)
|
||||
displayDatasBecome ":in String" [
|
||||
ManyDisplay [Display [
|
||||
DisplayData PlainText "type String = [Char] \t-- Defined in \8216GHC.Base\8217"
|
||||
]]
|
||||
]
|
||||
#else
|
||||
displayDatasBecome ":in String" [
|
||||
ManyDisplay [Display [
|
||||
DisplayData PlainText "type String = [Char] \t-- Defined in \8216GHC.Base\8217"
|
||||
, DisplayData MimeHtml "<div class=\"code CodeMirror cm-s-jupyter cm-s-ipython\"><span class=\"cm-keyword\">type</span><span class=\"cm-space\"> </span><span class=\"cm-variable-2\">String</span><span class=\"cm-space\"> </span><span class=\"cm-atom\">=</span><span class=\"cm-space\"> </span><span class=\"cm-atom\">[</span><span class=\"cm-variable-2\">Char</span><span class=\"cm-atom\">]</span><span class=\"cm-space\"> \t</span><span class=\"cm-comment\">-- Defined in \8216GHC.Base\8217</span><span class=\"cm-space\"><br /></span></div>"
|
||||
]]
|
||||
]
|
||||
#endif
|
||||
|
Loading…
x
Reference in New Issue
Block a user