Complete GHC 9 support and CI

This commit is contained in:
Ari Fordsham 2021-08-12 13:23:54 +01:00
parent 48cbd70632
commit ed520491d4
30 changed files with 196 additions and 79 deletions

View File

@ -68,6 +68,23 @@ jobs:
- ~/.stack - ~/.stack
- .stack-work - .stack-work
build-ghc-9.0:
docker:
- image: circleci/rust:1.36-stretch
steps:
- checkout
- restore_cache:
keys:
- stack-cache-v2-ghc-8.10-{{ arch }}-{{ .Branch }}
- stack-cache-v2-ghc-8.10-{{ arch }}-master
- run: .circleci/install-stack.sh
- run: stack test --no-terminal --stack-yaml stack-9.0.yaml
- save_cache:
key: stack-cache-v2-ghc-9.0-{{ arch }}-{{ .Branch }}-{{ epoch }}
paths:
- ~/.stack
- .stack-work
build-success: build-success:
docker: docker:
- image: circleci/rust:1.36-stretch - image: circleci/rust:1.36-stretch
@ -82,9 +99,11 @@ workflows:
- build-13.23 - build-13.23
- build-15.13 - build-15.13
- build-ghc-8.10 - build-ghc-8.10
- build-ghc-9.0
- build-success: - build-success:
requires: requires:
- build-12.8 - build-12.8
- build-13.23 - build-13.23
- build-15.13 - build-15.13
- build-ghc-8.10 - build-ghc-8.10
- build-ghc-9.0

View File

@ -0,0 +1,2 @@
module GHC.Driver.Monad (module GhcMonad) where
import GhcMonad

View File

@ -0,0 +1,2 @@
module GHC.Driver.Session (module DynFlags) where
import DynFlags

View File

@ -0,0 +1,2 @@
module GHC.Hs.Type (module GHC.Hs.Types) where
import GHC.Hs.Types

View File

@ -0,0 +1,2 @@
module GHC.Plugins (module GhcPlugins) where
import GhcPlugins

View File

@ -0,0 +1,2 @@
module GHC.Tc.Types.Evidence (module TcEvidence) where
import TcEvidence

View File

@ -0,0 +1,2 @@
module GHC.Types.Basic (module BasicTypes) where
import BasicTypes

View File

@ -0,0 +1,2 @@
module GHC.Utils.Outputable (module Outputable) where
import Outputable

View File

@ -1,2 +1,2 @@
module GHC.Hs (module HsSyn) where module GHC.Hs (module HsSyn) where
import HsSyn import HsSyn

View File

@ -1,9 +1,2 @@
{-# LANGUAGE CPP #-} module GHC.Hs.Type (module HsTypes) where
module GHC.Hs.Type import HsTypes
#if MIN_VERSION_ghc(8,10,0)
(module GHC.Hs.Types) where
import GHC.Hs.Types
#else
(module HsTypes) where
import HsTypes
#endif

2
compat/GHC/Hs/Utils.hs Normal file
View File

@ -0,0 +1,2 @@
module GHC.Hs.Utils (module HsUtils) where
import HsUtils

2
compat/GHC/Plugins.hs Normal file
View File

@ -0,0 +1,2 @@
module GHC.Plugins (module GhcPlugins) where
import GhcPlugins

View File

@ -0,0 +1,2 @@
module GHC.Tc.Types.Evidence (module TcEvidence) where
import TcEvidence

View File

@ -0,0 +1,2 @@
module GHC.Types.Basic (module BasicTypes) where
import BasicTypes

View File

@ -13,6 +13,41 @@ import Data.Typeable (cast)
import System.Environment (getArgs) import System.Environment (getArgs)
import Text.PrettyPrint import Text.PrettyPrint
#if MIN_VERSION_ghc(9,0,1)
import GHC.Data.FastString
import GHC.Types.Name
( Name
, isExternalName
, isInternalName
, isSystemName
, isWiredInName
, nameOccName
, nameUnique
)
import GHC.Types.Name.Occurrence
( OccName
, occNameSpace
, occNameString
, NameSpace
, varName
, dataName
, tvName
, tcClsName
)
import qualified GHC.Driver.Session as GHC
import qualified GHC.Data.FastString as GHC
import qualified GHC as GHC
import qualified GHC.Driver.Monad as GHC
import qualified GHC.Parser.Header as GHC
import qualified GHC.Parser.Lexer as GHC
import qualified GHC.Parser as Parser
import qualified GHC.Types.SrcLoc as GHC
import qualified GHC.Data.StringBuffer as GHC
import GHC.Paths (libdir)
import qualified GHC.Utils.Error as Error
import GHC.Driver.Monad (liftIO)
#else
import FastString import FastString
import Name import Name
( Name ( Name
@ -45,12 +80,16 @@ import qualified SrcLoc as GHC
import qualified StringBuffer as GHC import qualified StringBuffer as GHC
import GHC.Paths (libdir) import GHC.Paths (libdir)
#if MIN_VERSION_ghc(8,10,0) #if MIN_VERSION_ghc(8,10,0)
import System.Exit (exitFailure)
import GhcMonad (liftIO) import GhcMonad (liftIO)
import qualified ErrUtils import qualified ErrUtils as Error
#else #else
import qualified Outputable as GHC import qualified Outputable as GHC
#endif #endif
#endif
#if MIN_VERSION_ghc(8,10,0)
import System.Exit (exitFailure)
#endif
main :: IO () main :: IO ()
main = do main = do
@ -58,7 +97,11 @@ main = do
result <- parseModule f result <- parseModule f
print $ gPrint result print $ gPrint result
#if MIN_VERSION_ghc(9,0,1)
parseModule :: FilePath -> IO GHC.HsModule
#else
parseModule :: FilePath -> IO (GHC.HsModule GHC.GhcPs) parseModule :: FilePath -> IO (GHC.HsModule GHC.GhcPs)
#endif
parseModule f = GHC.runGhc (Just libdir) $ do parseModule f = GHC.runGhc (Just libdir) $ do
dflags <- GHC.getDynFlags dflags <- GHC.getDynFlags
contents <- GHC.liftIO $ GHC.stringToStringBuffer <$> readFile f contents <- GHC.liftIO $ GHC.stringToStringBuffer <$> readFile f
@ -70,7 +113,7 @@ parseModule f = GHC.runGhc (Just libdir) $ do
#if MIN_VERSION_ghc(8,10,0) #if MIN_VERSION_ghc(8,10,0)
GHC.PFailed s -> liftIO $ do GHC.PFailed s -> liftIO $ do
let (_warnings, errors) = GHC.messages s dflags let (_warnings, errors) = GHC.messages s dflags
ErrUtils.printBagOfErrors dflags errors Error.printBagOfErrors dflags errors
exitFailure exitFailure
#else #else
GHC.PFailed GHC.PFailed

View File

@ -13,4 +13,4 @@ executables:
- base - base
- ghc - ghc
- ghc-paths - ghc-paths
- pretty - pretty

View File

@ -52,8 +52,26 @@ library:
- GHC.Hs.ImpExp - GHC.Hs.ImpExp
- GHC.Hs.Lit - GHC.Hs.Lit
- GHC.Hs.Pat - GHC.Hs.Pat
- GHC.Hs.Types - GHC.Hs.Type
- GHC.Hs.Utils
- GHC.Driver.Monad
- GHC.Driver.Session
- GHC.Utils.Outputable
- GHC.Types.Basic
- GHC.Plugins
- GHC.Tc.Types.Evidence
- condition: impl(ghc>=8.10) && impl(ghc<9.0)
source-dirs: compat-8.10
other-modules:
- GHC.Hs.Type
- GHC.Driver.Monad
- GHC.Driver.Session
- GHC.Utils.Outputable
- GHC.Types.Basic
- GHC.Plugins
- GHC.Tc.Types.Evidence
source-dirs: src source-dirs: src
other-modules: other-modules:
- GHC.SourceGen.Binds.Internal - GHC.SourceGen.Binds.Internal
@ -73,6 +91,12 @@ tests:
- tasty >= 1.0 && < 1.5 - tasty >= 1.0 && < 1.5
- tasty-hunit == 0.10.* - tasty-hunit == 0.10.*
when:
- condition: impl(ghc<9.0)
source-dirs: compat
other-modules:
- GHC.Utils.Outputable
# TODO: Fill out this test, and use it to replace pprint_examples. # TODO: Fill out this test, and use it to replace pprint_examples.
pprint_test: pprint_test:
main: pprint_test.hs main: pprint_test.hs
@ -83,6 +107,14 @@ tests:
- tasty >= 1.0 && < 1.5 - tasty >= 1.0 && < 1.5
- tasty-hunit == 0.10.* - tasty-hunit == 0.10.*
when:
- condition: impl(ghc<9.0)
source-dirs: compat
other-modules:
- GHC.Driver.Monad
- GHC.Driver.Session
- GHC.Utils.Outputable
name_test: name_test:
main: name_test.hs main: name_test.hs
source-dirs: tests source-dirs: tests

View File

@ -46,16 +46,16 @@ module GHC.SourceGen.Binds
, (<--) , (<--)
) where ) where
import BasicTypes (LexicalFixity(..)) import GHC.Types.Basic (LexicalFixity(..))
import Data.Bool (bool) import Data.Bool (bool)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import GHC.Hs.Binds import GHC.Hs.Binds
import GHC.Hs.Expr import GHC.Hs.Expr
import GHC.Hs.Types import GHC.Hs.Type
import GhcPlugins (isSymOcc) import GHC.Plugins (isSymOcc)
import TcEvidence (HsWrapper(WpHole)) #if !MIN_VERSION_ghc(9,0,1)
import GHC.Tc.Types.Evidence (HsWrapper(WpHole))
#endif #endif
import GHC.SourceGen.Binds.Internal import GHC.SourceGen.Binds.Internal
import GHC.SourceGen.Name import GHC.SourceGen.Name
import GHC.SourceGen.Name.Internal import GHC.SourceGen.Name.Internal
@ -97,7 +97,11 @@ typeSig n = typeSigs [n]
funBindsWithFixity :: HasValBind t => Maybe LexicalFixity -> OccNameStr -> [RawMatch] -> t funBindsWithFixity :: HasValBind t => Maybe LexicalFixity -> OccNameStr -> [RawMatch] -> t
funBindsWithFixity fixity name matches = bindB $ withPlaceHolder funBindsWithFixity fixity name matches = bindB $ withPlaceHolder
(noExt FunBind name' (noExt FunBind name'
(matchGroup context matches) WpHole) (matchGroup context matches)
#if !MIN_VERSION_ghc(9,0,1)
WpHole
#endif
)
[] []
where where
name' = valueRdrName $ unqual name name' = valueRdrName $ unqual name

View File

@ -63,6 +63,7 @@ import BasicTypes (DerivStrategy(..))
#endif #endif
import GHC.Hs.Binds import GHC.Hs.Binds
import GHC.Hs.Decls import GHC.Hs.Decls
import GHC.Hs.Type import GHC.Hs.Type
( ConDeclField(..) ( ConDeclField(..)
, FieldOcc(..) , FieldOcc(..)

View File

@ -6,7 +6,7 @@ import GHC.Hs.Pat (Pat(..))
import GHC.Hs.Type (HsConDetails(..)) import GHC.Hs.Type (HsConDetails(..))
import GHC.Types.SrcLoc (unLoc) import GHC.Types.SrcLoc (unLoc)
#else #else
import GHC.Hs.Types (HsConDetails(..)) import GHC.Hs.Type (HsConDetails(..))
import SrcLoc (unLoc) import SrcLoc (unLoc)
#endif #endif

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-- Copyright 2019 Google LLC -- Copyright 2019 Google LLC
-- --
-- Use of this source code is governed by a BSD-style -- Use of this source code is governed by a BSD-style
@ -19,7 +20,11 @@ import System.IO
hPutPpr :: Outputable a => Handle -> a -> Ghc () hPutPpr :: Outputable a => Handle -> a -> Ghc ()
hPutPpr h x = do hPutPpr h x = do
dflags <- getDynFlags dflags <- getDynFlags
liftIO $ printForUser dflags h neverQualify AllTheWay $ ppr x liftIO $ printForUser dflags h neverQualify
#if MIN_VERSION_ghc(9,0,1)
AllTheWay
#endif
$ ppr x
putPpr :: Outputable a => a -> Ghc () putPpr :: Outputable a => a -> Ghc ()
putPpr = hPutPpr stdout putPpr = hPutPpr stdout

View File

@ -52,7 +52,6 @@ import BasicTypes (DerivStrategy)
import GHC.Hs.Decls (HsDerivingClause) import GHC.Hs.Decls (HsDerivingClause)
import GHC.Hs.Pat import GHC.Hs.Pat
#if MIN_VERSION_ghc(9,0,0) #if MIN_VERSION_ghc(9,0,0)
import GHC.Types.Name.Reader (RdrName)
import GHC.Types.SrcLoc (SrcSpan, Located, GenLocated(..), mkGeneralSrcSpan) import GHC.Types.SrcLoc (SrcSpan, Located, GenLocated(..), mkGeneralSrcSpan)
#else #else
import RdrName (RdrName) import RdrName (RdrName)
@ -64,7 +63,7 @@ import GHC.Types.Basic (PromotionFlag(..))
#elif MIN_VERSION_ghc(8,8,0) #elif MIN_VERSION_ghc(8,8,0)
import BasicTypes (PromotionFlag(..)) import BasicTypes (PromotionFlag(..))
#else #else
import GHC.Hs.Types (Promoted(..)) import GHC.Hs.Type (Promoted(..))
#endif #endif
#if MIN_VERSION_ghc(8,10,0) #if MIN_VERSION_ghc(8,10,0)

View File

@ -22,10 +22,11 @@ module GHC.SourceGen.Type
) where ) where
import Data.String (fromString) import Data.String (fromString)
import GHC.Hs.Type
#if MIN_VERSION_ghc(9,0,0) #if MIN_VERSION_ghc(9,0,0)
import GHC.Hs.Type
import GHC.Parser.Annotation import GHC.Parser.Annotation
import GHC.Types.Var (Specificity(..)) #else
import GHC.Hs.Type
#endif #endif
import GHC.SourceGen.Syntax.Internal import GHC.SourceGen.Syntax.Internal
@ -77,8 +78,10 @@ forall' :: [HsTyVarBndrS'] -> HsType' -> HsType'
forall' ts = noExt HsForAllTy forall' ts = noExt HsForAllTy
#if MIN_VERSION_ghc(9,0,0) #if MIN_VERSION_ghc(9,0,0)
(mkHsForAllInvisTele (map builtLoc ts)) (mkHsForAllInvisTele (map builtLoc ts))
#elif MIN_VERSION_ghc(8,10,0) #else
#if MIN_VERSION_ghc(8,10,0)
ForallInvis -- "Invisible" forall, i.e., with a dot ForallInvis -- "Invisible" forall, i.e., with a dot
#endif
(map builtLoc ts) (map builtLoc ts)
#endif #endif
. builtLoc . builtLoc
@ -98,9 +101,9 @@ infixr 0 ==>
-- > x :: A -- > x :: A
-- > ===== -- > =====
-- > kindedVar "x" (var "A") -- > kindedVar "x" (var "A")
kindedVar :: OccNameStr -> HsType' -> HsTyVarBndrS' kindedVar :: OccNameStr -> HsType' -> HsTyVarBndr'
kindedVar v t = noExt KindedTyVar kindedVar v t = noExt KindedTyVar
#if MIN_VERSION_ghc(9,0,0) #if MIN_VERSION_ghc(9,0,0)
SpecifiedSpec ()
#endif #endif
(typeRdrName $ UnqualStr v) (builtLoc t) (typeRdrName $ UnqualStr v) (builtLoc t)

View File

@ -11,7 +11,7 @@ module GHC.SourceGen.Type.Internal where
import GHC.Hs.Type as Types import GHC.Hs.Type as Types
import GHC.Types.SrcLoc (Located, unLoc) import GHC.Types.SrcLoc (Located, unLoc)
#else #else
import GHC.Hs.Types as Types import GHC.Hs.Type as Types
import SrcLoc (Located, unLoc) import SrcLoc (Located, unLoc)
#endif #endif

View File

@ -1,43 +0,0 @@
# Copyright 2019 Google LLC
#
# Use of this source code is governed by a BSD-style
# license that can be found in the LICENSE file or at
# https://developers.google.com/open-source/licenses/bsd
resolver: ghc-8.10.1
packages:
- .
- ghc-show-ast
ghc-options:
"$locals": -Wall -Werror
setup-info:
ghc:
macosx:
8.10.1:
url: "https://downloads.haskell.org/~ghc/8.10.1/ghc-8.10.1-x86_64-apple-darwin.tar.xz"
content-length: 192889416
sha1: 64828a2a2f444cbb5d77d4a15b51a29f03b657f2
sha256: 65b1ca361093de4804a7e40b3e68178e1ef720f84f743641ec8d95e56a45b3a8
extra-deps:
- ghc-paths-0.1.0.12@sha256:85370fdc615d4be5e09d9269eebb9a3fc7017c40b1a9e0050b121d75908564bd,632
- QuickCheck-2.13.2@sha256:ad4e5adbd1c9dc0221a44307b992cb040c515f31095182e47aa7e974bc461df1,6952
- tasty-1.2.3@sha256:bba67074e5326d57e8f53fc1dabcb6841daa4dc51b053506eb7f40a6f49a0497,2517
- tasty-hunit-0.10.0.2@sha256:8e8bd5807cec650f5aebc5ada07b57620c863e69145e65249651c1b48d97bd70,1515
- tasty-quickcheck-0.10.1.1@sha256:b0a751bbe706447fd11cac21a7bbcf919631813aafaba3ce460a421348f6935c,1543
- ansi-terminal-0.10.3@sha256:e2fbcef5f980dc234c7ad8e2fa433b0e8109132c9e643bc40ea5608cd5697797,3226
- async-2.2.2@sha256:a178c166856da7ff22fe4500337b54812e94fd2059409452187d72e057ede9cd,2934
- call-stack-0.2.0@sha256:5ce796b78d5f964468ec6fe0717b4e7d0430817f37370c47b3e6b38e345b6643,1202
- clock-0.8@sha256:b4ae207e2d3761450060a0d0feb873269233898039c76fceef9cc1a544067767,4113
- optparse-applicative-0.15.1.0@sha256:a0b9924d88a17c36cd8e6839d7dd2138419dd8f08cbb4f9af18f3c367b0c69a3,4673
- random-1.1@sha256:7b67624fd76ddf97c206de0801dc7e888097e9d572974be9b9ea6551d76965df,1777
- splitmix-0.0.4@sha256:fb9bb8b54a2e76c8a021fe5c4c3798047e1f60e168379a1f80693047fe00ad0e,4813
- tagged-0.8.6@sha256:1f7ca84e6c88cbb923641c60041c9f56c34f1a889759cc073cdf10542b441ff9,2606
- unbounded-delays-0.1.1.0@sha256:8e57c6ffb72ed605b85c69d3b3a7ebbbbb70bfb5e9b9816309f1f733240838f2,1184
- wcwidth-0.0.2@sha256:77531eb6683c505c22ab3fa11bbc43d3ce1e7dac21401d4d5a19677d348bb5f3,1998
- ansi-wl-pprint-0.6.9@sha256:f6fd6dbd4adcad0432bf75e5f5b19bb1deda00a1d8056faf18090026e577652d,2388
- colour-2.3.5@sha256:b27db0a3ad40d70bdbd8510a104269f8707592e80757a1abc66a22ba25e5a42f,1801
- hashable-1.3.0.0@sha256:4c70f1407881059e93550d3742191254296b2737b793a742bd901348fb3e1fb1,5206
- transformers-compat-0.6.5@sha256:50b00c57bf3fc379ec2477bfc261a2aebc983084488478adb29854f193af4696,5490

34
stack-9.0.yaml Normal file
View File

@ -0,0 +1,34 @@
# Copyright 2019 Google LLC
#
# Use of this source code is governed by a BSD-style
# license that can be found in the LICENSE file or at
# https://developers.google.com/open-source/licenses/bsd
resolver: ghc-9.0.1
packages:
- .
- ghc-show-ast
allow-newer: true
ghc-options:
"$locals": -Wall -Werror
extra-deps:
- QuickCheck-2.14.2@sha256:4ce29211223d5e6620ebceba34a3ca9ccf1c10c0cf387d48aea45599222ee5aa,7736
- ghc-paths-0.1.0.12@sha256:afdfdb6584f39e821b2b7130e12007bf3ad87401d86f5105eead059c150dc81d,657
- tasty-1.4.1@sha256:69e90e965543faf0fc2c8e486d6c1d8cf81fd108e2c4541234c41490f392f94f,2638
- tasty-hunit-0.10.0.3@sha256:ba774024f3a26100c559dbef41e030bdf443408ed848691f7b9aa85b6fb218c3,1545
- tasty-quickcheck-0.10.1.2@sha256:45c8125e5de19570359784def5946dec759b7431e3beccc61cd09d661daf19ed,1613
- ansi-terminal-0.11@sha256:97470250c92aae14c4c810d7f664c532995ba8910e2ad797b29f22ad0d2d0194,3307
- call-stack-0.4.0@sha256:ac44d2c00931dc20b01750da8c92ec443eb63a7231e8550188cb2ac2385f7feb,1200
- clock-0.8.2@sha256:473ffd59765cc67634bdc55b63c699a85addf3a024089073ec2a862881e83e2a,4313
- optparse-applicative-0.16.1.0@sha256:16ebd7054b2265c1aad16c1d19dc503695fbfc67b35203d9952fd577d08c0110,4982
- random-1.2.0@sha256:195506fedaa7c31c1fa2a747e9b49b4a5d1f0b09dd8f1291f23a771656faeec3,6097
- splitmix-0.1.0.3@sha256:fc3aae74c467f4b608050bef53aec17904a618731df9407e655d8f3bf8c32d5c,6049
- tagged-0.8.6.1@sha256:29c67d98a4404607f024750ab9c7210dadcbbef4e1944c48c52902f2071b2662,2874
- unbounded-delays-0.1.1.1@sha256:d7a2a49f15bdff2a8bdbd76f9d204580ea4be5a9def500c6371d51d8111cbcbe,1209
- wcwidth-0.0.2@sha256:77531eb6683c505c22ab3fa11bbc43d3ce1e7dac21401d4d5a19677d348bb5f3,1998
- ansi-wl-pprint-0.6.9@sha256:20d30674f137d43aa0279c2c2cc5e45a5f1c3c57e301852494906158b6313bf7,2388
- colour-2.3.6@sha256:ebdcbf15023958838a527e381ab3c3b1e99ed12d1b25efeb7feaa4ad8c37664a,2378
- transformers-compat-0.7@sha256:c4cc2d01c4e490ba680e9a0b607a1a790137856a6b3af12f8bdc7788a567bcf5,5572

View File

@ -4,7 +4,7 @@
# license that can be found in the LICENSE file or at # license that can be found in the LICENSE file or at
# https://developers.google.com/open-source/licenses/bsd # https://developers.google.com/open-source/licenses/bsd
resolver: lts-15.13 resolver: lts-18.3
packages: packages:
- . - .
- ghc-show-ast - ghc-show-ast

View File

@ -1,9 +1,14 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Main (main) where module Main (main) where
import GHC.SourceGen.Name import GHC.SourceGen.Name
#if MIN_VERSION_ghc(9,0,1)
import GHC.Types.Name.Occurrence
#else
import OccName import OccName
#endif
import Data.List (intercalate) import Data.List (intercalate)
import Data.String (fromString) import Data.String (fromString)

View File

@ -11,7 +11,7 @@ module Main (main) where
import GHC.Paths (libdir) import GHC.Paths (libdir)
import GHC (runGhc) import GHC (runGhc)
import Outputable (Outputable) import GHC.Utils.Outputable (Outputable)
import GHC.SourceGen import GHC.SourceGen

View File

@ -1,11 +1,11 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Main(main) where module Main(main) where
import DynFlags (getDynFlags) import GHC.Driver.Session (getDynFlags)
import GhcMonad (liftIO) import GHC.Driver.Monad (liftIO)
import GHC.Paths (libdir) import GHC.Paths (libdir)
import GHC (runGhc, DynFlags) import GHC (runGhc, DynFlags)
import Outputable (Outputable) import GHC.Utils.Outputable (Outputable)
import Test.Tasty import Test.Tasty
import Test.Tasty.HUnit import Test.Tasty.HUnit