Commit 8cc1371e authored by Vaibhav Sagar's avatar Vaibhav Sagar

ihaskell: update

parent 2081c717
...@@ -92,7 +92,7 @@ library ...@@ -92,7 +92,7 @@ library
build-depends: bin-package-db build-depends: bin-package-db
if impl(ghc >= 8.0) if impl(ghc >= 8.0)
build-depends: ghc-boot >=8.0 && <8.3 build-depends: ghc-boot >=8.0 && <8.5
exposed-modules: IHaskell.Display exposed-modules: IHaskell.Display
IHaskell.Convert IHaskell.Convert
...@@ -134,7 +134,7 @@ executable ihaskell ...@@ -134,7 +134,7 @@ executable ihaskell
default-language: Haskell2010 default-language: Haskell2010
build-depends: build-depends:
ihaskell -any, ihaskell -any,
base >=4.6 && < 4.11, base >=4.6 && < 4.12,
text >=0.11, text >=0.11,
transformers -any, transformers -any,
ghc >=7.6 || < 7.11, ghc >=7.6 || < 7.11,
......
...@@ -52,7 +52,11 @@ import qualified IHaskell.IPython.Stdin as Stdin ...@@ -52,7 +52,11 @@ import qualified IHaskell.IPython.Stdin as Stdin
import Paths_ihaskell(version) import Paths_ihaskell(version)
-- GHC API imports. -- GHC API imports.
#if MIN_VERSION_ghc(8,4,0)
import GHC hiding (extensions, language, convert)
#else
import GHC hiding (extensions, language) import GHC hiding (extensions, language)
#endif
-- | Compute the GHC API version number using the dist/build/autogen/cabal_macros.h -- | Compute the GHC API version number using the dist/build/autogen/cabal_macros.h
ghcVersionInts :: [Int] ghcVersionInts :: [Int]
......
...@@ -11,7 +11,6 @@ import qualified Data.ByteString.Lazy as LBS ...@@ -11,7 +11,6 @@ import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Char8 as CBS import qualified Data.ByteString.Char8 as CBS
import Data.Aeson (decode, Object, Value(Array, Object, String)) import Data.Aeson (decode, Object, Value(Array, Object, String))
import Data.Monoid ((<>), Monoid(mempty))
import Data.Vector (Vector) import Data.Vector (Vector)
import Data.HashMap.Strict (lookup) import Data.HashMap.Strict (lookup)
......
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-} {-# LANGUAGE CPP, NoImplicitPrelude, OverloadedStrings #-}
module IHaskell.Eval.Parser ( module IHaskell.Eval.Parser (
parseString, parseString,
...@@ -26,7 +26,11 @@ import Data.List (maximumBy, inits) ...@@ -26,7 +26,11 @@ import Data.List (maximumBy, inits)
import Prelude (head, tail) import Prelude (head, tail)
import Control.Monad (msum) import Control.Monad (msum)
#if MIN_VERSION_ghc(8,4,0)
import GHC hiding (Located, Parsed)
#else
import GHC hiding (Located) import GHC hiding (Located)
#endif
import Language.Haskell.GHC.Parser import Language.Haskell.GHC.Parser
import IHaskell.Eval.Util import IHaskell.Eval.Util
......
...@@ -59,6 +59,10 @@ import Data.List (nubBy) ...@@ -59,6 +59,10 @@ import Data.List (nubBy)
import StringUtils (replace) import StringUtils (replace)
#if MIN_VERSION_ghc(8,4,0)
import CmdLineParser (warnMsg)
#endif
#if MIN_VERSION_ghc(8,0,1) #if MIN_VERSION_ghc(8,0,1)
import GHC.LanguageExtensions import GHC.LanguageExtensions
...@@ -128,7 +132,11 @@ pprDynFlags show_all dflags = ...@@ -128,7 +132,11 @@ pprDynFlags show_all dflags =
is_on = test f dflags is_on = test f dflags
quiet = not show_all && test f default_dflags == is_on quiet = not show_all && test f default_dflags == is_on
#if MIN_VERSION_ghc(8,4,0)
default_dflags = defaultDynFlags (settings dflags) (llvmTargets dflags)
#else
default_dflags = defaultDynFlags (settings dflags) default_dflags = defaultDynFlags (settings dflags)
#endif
fstr, fnostr :: String -> O.SDoc fstr, fnostr :: String -> O.SDoc
fstr str = O.text "-f" O.<> O.text str fstr str = O.text "-f" O.<> O.text str
...@@ -176,7 +184,11 @@ pprLanguages show_all dflags = ...@@ -176,7 +184,11 @@ pprLanguages show_all dflags =
quiet = not show_all && test f default_dflags == is_on quiet = not show_all && test f default_dflags == is_on
default_dflags = default_dflags =
#if MIN_VERSION_ghc(8,4,0)
defaultDynFlags (settings dflags) (llvmTargets dflags) `lang_set`
#else
defaultDynFlags (settings dflags) `lang_set` defaultDynFlags (settings dflags) `lang_set`
#endif
case language dflags of case language dflags of
Nothing -> Just Haskell2010 Nothing -> Just Haskell2010
other -> other other -> other
...@@ -211,7 +223,11 @@ setFlags ext = do ...@@ -211,7 +223,11 @@ setFlags ext = do
-- Create the parse errors. -- Create the parse errors.
let noParseErrs = map (("Could not parse: " ++) . unLoc) unrecognized let noParseErrs = map (("Could not parse: " ++) . unLoc) unrecognized
#if MIN_VERSION_ghc(8,4,0)
allWarns = map (unLoc . warnMsg) warnings ++
#else
allWarns = map unLoc warnings ++ allWarns = map unLoc warnings ++
#endif
["-package not supported yet" | packageFlags flags /= packageFlags flags'] ["-package not supported yet" | packageFlags flags /= packageFlags flags']
warnErrs = map ("Warning: " ++) allWarns warnErrs = map ("Warning: " ++) allWarns
return $ noParseErrs ++ warnErrs return $ noParseErrs ++ warnErrs
...@@ -311,18 +327,30 @@ evalImport imports = do ...@@ -311,18 +327,30 @@ evalImport imports = do
where where
-- Check whether an import is the same as another import (same module). -- 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 importOf :: ImportDecl RdrName -> InteractiveImport -> Bool
#endif
importOf _ (IIModule _) = False importOf _ (IIModule _) = False
importOf imp (IIDecl decl) = importOf imp (IIDecl decl) =
((==) `on` (unLoc . ideclName)) decl imp && not (ideclQualified decl) ((==) `on` (unLoc . ideclName)) decl imp && not (ideclQualified decl)
-- Check whether an import is an *implicit* import of something. -- Check whether an import is an *implicit* import of something.
#if MIN_VERSION_ghc(8,4,0)
implicitImportOf :: ImportDecl GhcPs -> InteractiveImport -> Bool
#else
implicitImportOf :: ImportDecl RdrName -> InteractiveImport -> Bool implicitImportOf :: ImportDecl RdrName -> InteractiveImport -> Bool
#endif
implicitImportOf _ (IIModule _) = False implicitImportOf _ (IIModule _) = False
implicitImportOf imp (IIDecl decl) = ideclImplicit decl && imp `importOf` IIDecl decl implicitImportOf imp (IIDecl decl) = ideclImplicit decl && imp `importOf` IIDecl decl
-- Check whether an import is hidden. -- Check whether an import is hidden.
#if MIN_VERSION_ghc(8,4,0)
isHiddenImport :: ImportDecl GhcPs -> Bool
#else
isHiddenImport :: ImportDecl RdrName -> Bool isHiddenImport :: ImportDecl RdrName -> Bool
#endif
isHiddenImport imp = isHiddenImport imp =
case ideclHiding imp of case ideclHiding imp of
Just (True, _) -> True Just (True, _) -> True
...@@ -420,13 +448,21 @@ getDescription str = do ...@@ -420,13 +448,21 @@ getDescription str = do
getInfo' = getInfo getInfo' = getInfo
#endif #endif
#if MIN_VERSION_ghc(7,8,0) #if MIN_VERSION_ghc(8,4,0)
getType (theType, _, _, _, _) = theType
#elif MIN_VERSION_ghc(7,8,0)
getType (theType, _, _, _) = theType getType (theType, _, _, _) = theType
#else #else
getType (theType, _, _) = theType getType (theType, _, _) = theType
#endif #endif
#if MIN_VERSION_ghc(7,8,0) #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)
#elif MIN_VERSION_ghc(7,8,0)
printInfo (thing, fixity, classInstances, famInstances) = printInfo (thing, fixity, classInstances, famInstances) =
pprTyThingInContextLoc thing O.$$ pprTyThingInContextLoc thing O.$$
showFixity thing fixity O.$$ showFixity thing fixity O.$$
......
...@@ -12,7 +12,7 @@ module IHaskell.Flags ( ...@@ -12,7 +12,7 @@ module IHaskell.Flags (
help, help,
) where ) where
import IHaskellPrelude import IHaskellPrelude hiding (Arg(..))
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Lazy as LT import qualified Data.Text.Lazy as LT
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
......
...@@ -49,6 +49,7 @@ import Data.Aeson (Value, (.=), object) ...@@ -49,6 +49,7 @@ import Data.Aeson (Value, (.=), object)
import Data.Aeson.Types (emptyObject) import Data.Aeson.Types (emptyObject)
import qualified Data.ByteString.Char8 as Char import qualified Data.ByteString.Char8 as Char
import Data.Function (on) import Data.Function (on)
import Data.Semigroup
import Data.Serialize import Data.Serialize
import GHC.Generics import GHC.Generics
...@@ -127,12 +128,15 @@ data Display = Display [DisplayData] ...@@ -127,12 +128,15 @@ data Display = Display [DisplayData]
instance Serialize Display instance Serialize Display
instance Semigroup Display where
ManyDisplay a <> ManyDisplay b = ManyDisplay (a ++ b)
ManyDisplay a <> b = ManyDisplay (a ++ [b])
a <> ManyDisplay b = ManyDisplay (a : b)
a <> b = ManyDisplay [a, b]
instance Monoid Display where instance Monoid Display where
mempty = Display [] mempty = Display []
ManyDisplay a `mappend` ManyDisplay b = ManyDisplay (a ++ b) mappend = (<>)
ManyDisplay a `mappend` b = ManyDisplay (a ++ [b])
a `mappend` ManyDisplay b = ManyDisplay (a : b)
a `mappend` b = ManyDisplay [a, b]
-- | All state stored in the kernel between executions. -- | All state stored in the kernel between executions.
data KernelState = data KernelState =
......
...@@ -67,7 +67,8 @@ module IHaskellPrelude ( ...@@ -67,7 +67,8 @@ module IHaskellPrelude (
import Prelude import Prelude
import Data.Monoid as X import Data.Semigroup as X
import Data.Monoid as X hiding ((<>), First(..), Last(..))
import Data.Tuple as X import Data.Tuple as X
import Control.Monad as X import Control.Monad as X
import Data.Maybe as X import Data.Maybe as X
......
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