Commit e97b7019 authored by Andrei Barbu's avatar Andrei Barbu

Apply #686

parent 00478f3b
...@@ -33,8 +33,8 @@ library ...@@ -33,8 +33,8 @@ library
Language.Haskell.GHC.HappyParser Language.Haskell.GHC.HappyParser
-- other-modules: -- other-modules:
-- other-extensions: -- other-extensions:
build-depends: base >=4.6 && <4.9, build-depends: base >=4.6 && <4.10,
ghc >=7.6 && <7.11 ghc >=7.6 && <8.1
if impl(ghc >= 7.6) && impl(ghc < 7.8) if impl(ghc >= 7.6) && impl(ghc < 7.8)
hs-source-dirs: generic-src src-7.6 hs-source-dirs: generic-src src-7.6
...@@ -45,6 +45,9 @@ library ...@@ -45,6 +45,9 @@ library
if impl(ghc < 7.10) if impl(ghc < 7.10)
hs-source-dirs: generic-src src-7.8.3 hs-source-dirs: generic-src src-7.8.3
else else
hs-source-dirs: generic-src src-7.10 if impl(ghc < 8.0)
hs-source-dirs: generic-src src-7.10
else
hs-source-dirs: generic-src src-8.0
default-language: Haskell2010 default-language: Haskell2010
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 RdrHsSyn
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
...@@ -57,7 +57,7 @@ library ...@@ -57,7 +57,7 @@ library
OverloadedStrings OverloadedStrings
-- Other library packages from which modules are imported. -- Other library packages from which modules are imported.
build-depends: base >=4.6 && <4.9, build-depends: base >=4.6 && <4.10,
here, here,
text, text,
bytestring, bytestring,
......
...@@ -58,7 +58,7 @@ library ...@@ -58,7 +58,7 @@ library
OverloadedStrings OverloadedStrings
-- Other library packages from which modules are imported. -- Other library packages from which modules are imported.
build-depends: base >=4.6 && <4.9, build-depends: base >=4.6 && <4.10,
text, text,
bytestring, bytestring,
directory, directory,
......
...@@ -58,7 +58,7 @@ library ...@@ -58,7 +58,7 @@ library
OverloadedStrings OverloadedStrings
-- Other library packages from which modules are imported. -- Other library packages from which modules are imported.
build-depends: base >=4.6 && <4.9, build-depends: base >=4.6 && <4.10,
bytestring, bytestring,
gnuplot >= 0.5.4, gnuplot >= 0.5.4,
ihaskell >= 0.6.2 ihaskell >= 0.6.2
......
...@@ -14,7 +14,7 @@ cabal-version: >=1.16 ...@@ -14,7 +14,7 @@ cabal-version: >=1.16
library library
exposed-modules: IHaskell.Display.Hatex exposed-modules: IHaskell.Display.Hatex
build-depends: base >=4.6 && <4.9, build-depends: base >=4.6 && <4.10,
text, text,
HaTeX >= 3.9, HaTeX >= 3.9,
ihaskell >= 0.5 ihaskell >= 0.5
......
...@@ -61,7 +61,7 @@ library ...@@ -61,7 +61,7 @@ library
OverloadedStrings OverloadedStrings
-- Other library packages from which modules are imported. -- Other library packages from which modules are imported.
build-depends: base >=4.6 && <4.9, build-depends: base >=4.6 && <4.10,
magic >= 1.0.8, magic >= 1.0.8,
text, text,
bytestring, bytestring,
......
...@@ -55,7 +55,7 @@ library ...@@ -55,7 +55,7 @@ library
default-language: Haskell2010 default-language: Haskell2010
build-depends: build-depends:
aeson >=0.7 && < 0.12, aeson >=0.7 && < 0.12,
base >=4.6 && < 4.9, base >=4.6 && < 4.10,
base64-bytestring >=1.0, base64-bytestring >=1.0,
bytestring >=0.10, bytestring >=0.10,
cereal >=0.3, cereal >=0.3,
...@@ -91,6 +91,9 @@ library ...@@ -91,6 +91,9 @@ library
if flag(binPkgDb) if flag(binPkgDb)
build-depends: bin-package-db build-depends: bin-package-db
if impl(ghc >= 8.0)
build-depends: ghc-boot >=8.0 && <8.1
exposed-modules: IHaskell.Display exposed-modules: IHaskell.Display
IHaskell.Convert IHaskell.Convert
IHaskell.Convert.Args IHaskell.Convert.Args
...@@ -137,7 +140,7 @@ executable ihaskell ...@@ -137,7 +140,7 @@ executable ihaskell
default-language: Haskell2010 default-language: Haskell2010
build-depends: build-depends:
ihaskell -any, ihaskell -any,
base >=4.6 && < 4.9, base >=4.6 && < 4.10,
text >=0.11, text >=0.11,
transformers -any, transformers -any,
ghc >=7.6 || < 7.11, ghc >=7.6 || < 7.11,
......
...@@ -34,7 +34,7 @@ library ...@@ -34,7 +34,7 @@ library
other-extensions: OverloadedStrings other-extensions: OverloadedStrings
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010
build-depends: base >=4.6 && < 4.9, build-depends: base >=4.6 && < 4.10,
aeson >=0.6 && < 0.12, aeson >=0.6 && < 0.12,
bytestring >=0.10, bytestring >=0.10,
cereal >=0.3, cereal >=0.3,
...@@ -56,7 +56,7 @@ executable simple-calc-example ...@@ -56,7 +56,7 @@ executable simple-calc-example
hs-source-dirs: examples hs-source-dirs: examples
main-is: Calc.hs main-is: Calc.hs
build-depends: ipython-kernel, build-depends: ipython-kernel,
base >=4.6 && <4.9, base >=4.6 && <4.10,
filepath >=1.2, filepath >=1.2,
mtl >=2.1, mtl >=2.1,
parsec >=3.1, parsec >=3.1,
...@@ -70,7 +70,7 @@ executable fun-calc-example ...@@ -70,7 +70,7 @@ executable fun-calc-example
hs-source-dirs: examples hs-source-dirs: examples
main-is: Simple.hs main-is: Simple.hs
build-depends: ipython-kernel, build-depends: ipython-kernel,
base >=4.6 && <4.9, base >=4.6 && <4.10,
filepath >=1.2, filepath >=1.2,
mtl >=2.1, mtl >=2.1,
parsec >=3.1, parsec >=3.1,
......
...@@ -78,7 +78,9 @@ import GHC.Enum as X ...@@ -78,7 +78,9 @@ import GHC.Enum as X
import GHC.Num as X import GHC.Num as X
import GHC.Real as X import GHC.Real as X
import GHC.Err as X hiding (absentErr) import GHC.Err as X hiding (absentErr)
#if MIN_VERSION_ghc(7,10,0) #if MIN_VERSION_ghc(8,0,0)
import GHC.Base as X hiding (Any, mapM, foldr, sequence, many, (<|>), Module(..))
#elif MIN_VERSION_ghc(7,10,0)
import GHC.Base as X hiding (Any, mapM, foldr, sequence, many, (<|>)) import GHC.Base as X hiding (Any, mapM, foldr, sequence, many, (<|>))
#else #else
import GHC.Base as X hiding (Any) import GHC.Base as X hiding (Any)
......
...@@ -128,7 +128,8 @@ runKernel kernelOpts profileSrc = do ...@@ -128,7 +128,8 @@ runKernel kernelOpts profileSrc = do
useStack = kernelSpecUseStack kernelOpts useStack = kernelSpecUseStack kernelOpts
-- Parse the profile file. -- Parse the profile file.
Just profile <- liftM decode $ LBS.readFile profileSrc let profileErr = error $ "ihaskell: "++profileSrc++": Failed to parse profile file"
profile <- liftM (fromMaybe profileErr . decode) $ LBS.readFile profileSrc
-- Necessary for `getLine` and their ilk to work. -- Necessary for `getLine` and their ilk to work.
dir <- getIHaskellDir dir <- getIHaskellDir
......
...@@ -22,7 +22,7 @@ import qualified Data.ByteString.Char8 as CBS ...@@ -22,7 +22,7 @@ import qualified Data.ByteString.Char8 as CBS
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import Data.ByteString.UTF8 hiding (drop, take, lines, length) import Data.ByteString.UTF8 hiding (drop, take, lines, length)
import Data.Char import Data.Char
import Data.List (nub, init, last, head, elemIndex) import Data.List (nub, init, last, head, elemIndex, concatMap)
import qualified Data.List.Split as Split import qualified Data.List.Split as Split
import qualified Data.List.Split.Internals as Split import qualified Data.List.Split.Internals as Split
import Data.Maybe (fromJust) import Data.Maybe (fromJust)
...@@ -88,7 +88,11 @@ complete code posOffset = do ...@@ -88,7 +88,11 @@ complete code posOffset = do
let Just db = pkgDatabase flags let Just db = pkgDatabase flags
getNames = map (moduleNameString . exposedName) . exposedModules getNames = map (moduleNameString . exposedName) . exposedModules
#if MIN_VERSION_ghc(8,0,0)
moduleNames = nub $ concatMap getNames $ concatMap snd db
#else
moduleNames = nub $ concatMap getNames db moduleNames = nub $ concatMap getNames db
#endif
let target = completionTarget line pos let target = completionTarget line pos
completion = completionType line pos target completion = completionType line pos target
...@@ -124,7 +128,11 @@ complete code posOffset = do ...@@ -124,7 +128,11 @@ complete code posOffset = do
otherNames = ["-package", "-Wall", "-w"] otherNames = ["-package", "-Wall", "-w"]
fNames = map extName fFlags ++ fNames = map extName fFlags ++
#if MIN_VERSION_ghc(8,0,0)
map extName wWarningFlags ++
#else
map extName fWarningFlags ++ map extName fWarningFlags ++
#endif
map extName fLangFlags map extName fLangFlags
fNoNames = map ("no" ++) fNames fNoNames = map ("no" ++) fNames
fAllNames = map ("-f" ++) (fNames ++ fNoNames) fAllNames = map ("-f" ++) (fNames ++ fNoNames)
......
...@@ -26,6 +26,7 @@ import qualified Data.ByteString.Lazy as LBS ...@@ -26,6 +26,7 @@ import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Char8 as CBS import qualified Data.ByteString.Char8 as CBS
import Control.Concurrent (forkIO, threadDelay) import Control.Concurrent (forkIO, threadDelay)
import Data.Foldable (foldMap)
import Prelude (putChar, head, tail, last, init, (!!)) import Prelude (putChar, head, tail, last, init, (!!))
import Data.List (findIndex, and, foldl1, nubBy) import Data.List (findIndex, and, foldl1, nubBy)
import Text.Printf import Text.Printf
...@@ -77,7 +78,7 @@ import Module hiding (Module) ...@@ -77,7 +78,7 @@ import Module hiding (Module)
import qualified Pretty import qualified Pretty
import FastString import FastString
import Bag import Bag
import ErrUtils (errMsgShortDoc, errMsgExtraInfo) import qualified ErrUtils
import IHaskell.Types import IHaskell.Types
import IHaskell.IPython import IHaskell.IPython
...@@ -184,13 +185,29 @@ interpret libdir allowedStdin action = runGhc (Just libdir) $ do ...@@ -184,13 +185,29 @@ interpret libdir allowedStdin action = runGhc (Just libdir) $ do
-- Run the rest of the interpreter -- Run the rest of the interpreter
action hasSupportLibraries action hasSupportLibraries
#if MIN_VERSION_ghc(7,10,2)
packageIdString' dflags pkg_key = fromMaybe "(unknown)" (packageKeyPackageIdString dflags pkg_key) packageIdString' :: DynFlags -> PackageConfig -> String
packageIdString' dflags pkg_cfg =
#if MIN_VERSION_ghc(8,0,0)
fromMaybe "(unknown)" (unitIdPackageIdString dflags $ packageConfigId pkg_cfg)
#elif MIN_VERSION_ghc(7,10,2)
fromMaybe "(unknown)" (packageKeyPackageIdString dflags $ packageConfigId pkg_cfg)
#elif MIN_VERSION_ghc(7,10,0) #elif MIN_VERSION_ghc(7,10,0)
packageIdString' dflags = packageKeyPackageIdString dflags packageKeyPackageIdString dflags . packageConfigId
#else #else
packageIdString' dflags = packageIdString packageIdString . packageConfigId
#endif #endif
getPackageConfigs :: DynFlags -> [PackageConfig]
getPackageConfigs dflags =
#if MIN_VERSION_ghc(8,0,0)
foldMap snd pkgDb
#else
pkgDb
#endif
where
Just pkgDb = pkgDatabase dflags
-- | Initialize our GHC session with imports and a value for 'it'. Return whether the IHaskell -- | Initialize our GHC session with imports and a value for 'it'. Return whether the IHaskell
-- support libraries are available. -- support libraries are available.
initializeImports :: Interpreter Bool initializeImports :: Interpreter Bool
...@@ -200,19 +217,23 @@ initializeImports = do ...@@ -200,19 +217,23 @@ initializeImports = do
dflags <- getSessionDynFlags dflags <- getSessionDynFlags
broken <- liftIO getBrokenPackages broken <- liftIO getBrokenPackages
(dflags, _) <- liftIO $ initPackages dflags (dflags, _) <- liftIO $ initPackages dflags
let Just db = pkgDatabase dflags let db = getPackageConfigs dflags
packageNames = map (packageIdString' dflags . packageConfigId) db packageNames = map (packageIdString' dflags) db
initStr = "ihaskell-" initStr = "ihaskell-"
-- Name of the ihaskell package, e.g. "ihaskell-1.2.3.4" -- Name of the ihaskell package, e.g. "ihaskell-1.2.3.4"
iHaskellPkgName = initStr ++ intercalate "." (map show (versionBranch version)) iHaskellPkgName = initStr ++ intercalate "." (map show (versionBranch version))
#if !MIN_VERSION_ghc(8,0,0)
unitId = packageId
#endif
dependsOnRight pkg = not $ null $ do dependsOnRight pkg = not $ null $ do
pkg <- db pkg <- db
depId <- depends pkg depId <- depends pkg
dep <- filter ((== depId) . installedPackageId) db dep <- filter ((== depId) . unitId) db
let idString = packageIdString' dflags (packageConfigId dep) let idString = packageIdString' dflags dep
guard (iHaskellPkgName `isPrefixOf` idString) guard (iHaskellPkgName `isPrefixOf` idString)
displayPkgs = [ pkgName displayPkgs = [ pkgName
...@@ -411,6 +432,14 @@ flushWidgetMessages state evalMsgs widgetHandler = do ...@@ -411,6 +432,14 @@ flushWidgetMessages state evalMsgs widgetHandler = do
let commMessages = evalMsgs ++ messages let commMessages = evalMsgs ++ messages
widgetHandler state commMessages widgetHandler state commMessages
getErrMsgDoc :: ErrUtils.ErrMsg -> SDoc
#if MIN_VERSION_ghc(8,0,0)
getErrMsgDoc = ErrUtils.pprLocErrMsg
#else
getErrMsgDoc msg = ErrUtils.errMsgShortString msg $$ ErrUtils.errMsgContext msg
#endif
safely :: KernelState -> Interpreter EvalOut -> Interpreter EvalOut safely :: KernelState -> Interpreter EvalOut -> Interpreter EvalOut
safely state = ghandle handler . ghandle sourceErrorHandler safely state = ghandle handler . ghandle sourceErrorHandler
where where
...@@ -428,10 +457,7 @@ safely state = ghandle handler . ghandle sourceErrorHandler ...@@ -428,10 +457,7 @@ safely state = ghandle handler . ghandle sourceErrorHandler
sourceErrorHandler :: SourceError -> Interpreter EvalOut sourceErrorHandler :: SourceError -> Interpreter EvalOut
sourceErrorHandler srcerr = do sourceErrorHandler srcerr = do
let msgs = bagToList $ srcErrorMessages srcerr let msgs = bagToList $ srcErrorMessages srcerr
errStrs <- forM msgs $ \msg -> do errStrs <- forM msgs $ doc . getErrMsgDoc
shortStr <- doc $ errMsgShortDoc msg
contextStr <- doc $ errMsgExtraInfo msg
return $ unlines [shortStr, contextStr]
let fullErr = unlines errStrs let fullErr = unlines errStrs
...@@ -1027,7 +1053,11 @@ doLoadModule name modName = do ...@@ -1027,7 +1053,11 @@ doLoadModule name modName = do
setSessionDynFlags setSessionDynFlags
flags flags
{ hscTarget = objTarget flags { hscTarget = objTarget flags
#if MIN_VERSION_ghc(8,0,0)
, log_action = \dflags sev srcspan ppr _style msg -> modifyIORef' errRef (showSDoc flags msg :)
#else
, log_action = \dflags sev srcspan ppr msg -> modifyIORef' errRef (showSDoc flags msg :) , log_action = \dflags sev srcspan ppr msg -> modifyIORef' errRef (showSDoc flags msg :)
#endif
} }
-- Load the new target. -- Load the new target.
...@@ -1142,7 +1172,6 @@ capturedEval output stmt = do ...@@ -1142,7 +1172,6 @@ capturedEval output stmt = do
, voidpf "IHaskellIO.closeFd %s" writeVariable , voidpf "IHaskellIO.closeFd %s" writeVariable
, printf "let it = %s" itVariable , printf "let it = %s" itVariable
] ]
pipeExpr = printf "let %s = %s" (var "pipe_var_") readVariable
goStmt :: String -> Ghc RunResult goStmt :: String -> Ghc RunResult
goStmt s = runStmt s RunToCompletion goStmt s = runStmt s RunToCompletion
...@@ -1156,22 +1185,37 @@ capturedEval output stmt = do ...@@ -1156,22 +1185,37 @@ capturedEval output stmt = do
AnyException e -> RunException e AnyException e -> RunException e
-- Initialize evaluation context. -- Initialize evaluation context.
void $ forM initStmts goStmt results <- forM initStmts goStmt
#if __GLASGOW_HASKELL__ >= 800
-- This works fine on GHC 8.0 and newer
dyn <- dynCompileExpr readVariable
pipe <- case fromDynamic dyn of
Nothing -> fail "Evaluate: Bad pipe"
Just fd -> liftIO $ do
handle <- fdToHandle fd
hSetEncoding handle utf8
return handle
#else
-- Get the pipe to read printed output from. This is effectively the source code of dynCompileExpr -- Get the pipe to read printed output from. This is effectively the source code of dynCompileExpr
-- from GHC API's InteractiveEval. However, instead of using a `Dynamic` as an intermediary, it just -- from GHC API's InteractiveEval. However, instead of using a `Dynamic` as an intermediary, it just
-- directly reads the value. This is incredibly unsafe! However, for some reason the `getContext` -- directly reads the value. This is incredibly unsafe! However, for some reason the `getContext`
-- and `setContext` required by dynCompileExpr (to import and clear Data.Dynamic) cause issues with -- and `setContext` required by dynCompileExpr (to import and clear Data.Dynamic) cause issues with
-- data declarations being updated (e.g. it drops newer versions of data declarations for older ones -- data declarations being updated (e.g. it drops newer versions of data declarations for older ones
-- for unknown reasons). First, compile down to an HValue. -- for unknown reasons). First, compile down to an HValue.
let pipeExpr = printf "let %s = %s" (var "pipe_var_") readVariable
Just (_, hValues, _) <- withSession $ liftIO . flip hscStmt pipeExpr Just (_, hValues, _) <- withSession $ liftIO . flip hscStmt pipeExpr
-- Then convert the HValue into an executable bit, and read the value. -- Then convert the HValue into an executable bit, and read the value.
pipe <- liftIO $ do pipe <- liftIO $ do
fd <- head <$> unsafeCoerce hValues fds <- unsafeCoerce hValues
fd <- case fds of
fd : _ -> return fd
[] -> fail "Failed to evaluate pipes"
_ -> fail $ "Expected one fd, saw "++show (length fds)
handle <- fdToHandle fd handle <- fdToHandle fd
hSetEncoding handle utf8 hSetEncoding handle utf8
return handle return handle
#endif
-- Keep track of whether execution has completed. -- Keep track of whether execution has completed.
completed <- liftIO $ newMVar False completed <- liftIO $ newMVar False
finishedReading <- liftIO newEmptyMVar finishedReading <- liftIO newEmptyMVar
......
...@@ -59,6 +59,12 @@ import Data.List (nubBy) ...@@ -59,6 +59,12 @@ import Data.List (nubBy)
import StringUtils (replace) import StringUtils (replace)
#if MIN_VERSION_ghc(8,0,1)
import GHC.LanguageExtensions
type ExtensionFlag = Extension
#endif
-- | A extension flag that can be set or unset. -- | A extension flag that can be set or unset.
data ExtFlag = SetFlag ExtensionFlag data ExtFlag = SetFlag ExtensionFlag
| UnsetFlag ExtensionFlag | UnsetFlag ExtensionFlag
...@@ -97,10 +103,16 @@ pprDynFlags show_all dflags = ...@@ -97,10 +103,16 @@ pprDynFlags show_all dflags =
, O.text "other dynamic, non-language, flag settings:" O.$$ , O.text "other dynamic, non-language, flag settings:" O.$$
O.nest 2 (O.vcat (map (setting opt) others)) O.nest 2 (O.vcat (map (setting opt) others))
, O.text "warning settings:" O.$$ , O.text "warning settings:" O.$$
O.nest 2 (O.vcat (map (setting wopt) DynFlags.fWarningFlags)) O.nest 2 (O.vcat (map (setting wopt) warningFlags))
] ]
where where
#if MIN_VERSION_ghc(8,0,0)
warningFlags = DynFlags.wWarningFlags
#else
warningFlags = DynFlags.fWarningFlags
#endif
#if MIN_VERSION_ghc(7,8,0) #if MIN_VERSION_ghc(7,8,0)
opt = gopt opt = gopt
#else #else
...@@ -239,7 +251,11 @@ initGhci sandboxPackages = do ...@@ -239,7 +251,11 @@ initGhci sandboxPackages = do
originalFlags <- getSessionDynFlags originalFlags <- getSessionDynFlags
let flag = flip xopt_set let flag = flip xopt_set
unflag = flip xopt_unset unflag = flip xopt_unset
#if MIN_VERSION_ghc(8,0,0)
dflags = flag ExtendedDefaultRules . unflag MonomorphismRestriction $ originalFlags
#else
dflags = flag Opt_ExtendedDefaultRules . unflag Opt_MonomorphismRestriction $ originalFlags dflags = flag Opt_ExtendedDefaultRules . unflag Opt_MonomorphismRestriction $ originalFlags
#endif
pkgConfs = pkgConfs =
case sandboxPackages of case sandboxPackages of
Nothing -> extraPkgConfs originalFlags Nothing -> extraPkgConfs originalFlags
...@@ -323,8 +339,13 @@ cleanUpDuplicateInstances = modifySession $ \hscEnv -> ...@@ -323,8 +339,13 @@ cleanUpDuplicateInstances = modifySession $ \hscEnv ->
in hscEnv { hsc_IC = ic { ic_instances = (clsInsts', famInsts) } } in hscEnv { hsc_IC = ic { ic_instances = (clsInsts', famInsts) } }
where where
instEq :: ClsInst -> ClsInst -> Bool instEq :: ClsInst -> ClsInst -> Bool
#if MIN_VERSION_ghc(7,8,0) #if MIN_VERSION_ghc(8,0,0)
-- Only support replacing instances on GHC 7.8 and up -- Only support replacing instances on GHC 7.8 and up
instEq c1 c2
| ClsInst { is_tvs = tpl_tvs, is_tys = tpl_tys, is_cls = cls } <- c1,
ClsInst { is_tys = tpl_tys', is_cls = cls' } <- c2
= cls == cls' && isJust (tcMatchTys tpl_tys tpl_tys')
#elif MIN_VERSION_ghc(7,8,0)
instEq c1 c2 instEq c1 c2
| ClsInst { is_tvs = tpl_tvs, is_tys = tpl_tys, is_cls = cls } <- c1, | ClsInst { is_tvs = tpl_tvs, is_tys = tpl_tys, is_cls = cls } <- c1,
ClsInst { is_tys = tpl_tys', is_cls = cls' } <- c2 ClsInst { is_tys = tpl_tys', is_cls = cls' } <- c2
...@@ -333,6 +354,8 @@ cleanUpDuplicateInstances = modifySession $ \hscEnv -> ...@@ -333,6 +354,8 @@ cleanUpDuplicateInstances = modifySession $ \hscEnv ->
#else #else
instEq _ _ = False instEq _ _ = False
#endif #endif
-- | Get the type of an expression and convert it to a string. -- | Get the type of an expression and convert it to a string.
getType :: GhcMonad m => String -> m String getType :: GhcMonad m => String -> m String
getType expr = do getType expr = do
......
...@@ -78,7 +78,9 @@ import GHC.Enum as X ...@@ -78,7 +78,9 @@ import GHC.Enum as X
import GHC.Num as X import GHC.Num as X
import GHC.Real as X import GHC.Real as X
import GHC.Err as X hiding (absentErr) import GHC.Err as X hiding (absentErr)
#if MIN_VERSION_ghc(7,10,0) #if MIN_VERSION_ghc(8,0,0)
import GHC.Base as X hiding (Any, mapM, foldr, sequence, many, (<|>), Module(..))
#elif MIN_VERSION_ghc(7,10,0)
import GHC.Base as X hiding (Any, mapM, foldr, sequence, many, (<|>)) import GHC.Base as X hiding (Any, mapM, foldr, sequence, many, (<|>))
#else #else
import GHC.Base as X hiding (Any) import GHC.Base as X hiding (Any)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment