diff options
author | Sylvain Henry <sylvain@haskus.fr> | 2020-03-18 10:44:56 +0100 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2020-03-29 17:28:51 -0400 |
commit | 1941ef4f050c0dfcb68229641fcbbde3a10f1072 (patch) | |
tree | 8e25a61af77696d3022d35cc277b5db5af540f03 /testsuite/tests | |
parent | 1c446220250dcada51d4bb33a0cc7d8ce572e8b6 (diff) | |
download | haskell-1941ef4f050c0dfcb68229641fcbbde3a10f1072.tar.gz |
Modules: Types (#13009)
Update Haddock submodule
Metric Increase:
haddock.compiler
Diffstat (limited to 'testsuite/tests')
37 files changed, 61 insertions, 61 deletions
diff --git a/testsuite/tests/annotations/should_run/annrun01.hs b/testsuite/tests/annotations/should_run/annrun01.hs index fd2c7bc415..4a587afddc 100644 --- a/testsuite/tests/annotations/should_run/annrun01.hs +++ b/testsuite/tests/annotations/should_run/annrun01.hs @@ -6,7 +6,7 @@ import GHC import MonadUtils ( liftIO ) import Data.Maybe import GHC.Driver.Session ( defaultFatalMessager, defaultFlushOut ) -import Annotations ( AnnTarget(..), CoreAnnTarget ) +import GHC.Types.Annotations ( AnnTarget(..), CoreAnnTarget ) import GHC.Serialized ( deserializeWithData ) import Panic diff --git a/testsuite/tests/callarity/unittest/CallArity1.hs b/testsuite/tests/callarity/unittest/CallArity1.hs index 60afe5be05..c42232b5dd 100644 --- a/testsuite/tests/callarity/unittest/CallArity1.hs +++ b/testsuite/tests/callarity/unittest/CallArity1.hs @@ -1,25 +1,25 @@ {-# LANGUAGE TupleSections #-} import GHC.Core import GHC.Core.Utils -import Id +import GHC.Types.Id import GHC.Core.Type import GHC.Core.Make import GHC.Core.Op.CallArity (callArityRHS) -import MkId +import GHC.Types.Id.Make import SysTools import GHC.Driver.Session import ErrUtils import Outputable import TysWiredIn -import Literal +import GHC.Types.Literal import GHC import Control.Monad import Control.Monad.IO.Class import System.Environment( getArgs ) -import VarSet +import GHC.Types.Var.Set import GHC.Core.Ppr -import Unique -import UniqSet +import GHC.Types.Unique +import GHC.Types.Unique.Set import GHC.Core.Lint import FastString diff --git a/testsuite/tests/determinism/determ002/A.hs b/testsuite/tests/determinism/determ002/A.hs index 9a88f2c319..3ca3e8bc95 100644 --- a/testsuite/tests/determinism/determ002/A.hs +++ b/testsuite/tests/determinism/determ002/A.hs @@ -2,7 +2,7 @@ module A where -- This is a repro for the issue where to fingerprint a record, field labels -- were pulled from FastStringEnv in the order of Uniques which are known --- to have arbitrary order - see Note [Unique Determinism] in Unique. +-- to have arbitrary order - see Note [Unique Determinism] in GHC.Types.Unique. data B = C { e :: () diff --git a/testsuite/tests/ghc-api/T11579.hs b/testsuite/tests/ghc-api/T11579.hs index 493823b843..418057120c 100644 --- a/testsuite/tests/ghc-api/T11579.hs +++ b/testsuite/tests/ghc-api/T11579.hs @@ -4,7 +4,7 @@ import FastString import GHC import StringBuffer import Lexer -import SrcLoc +import GHC.Types.SrcLoc main :: IO () main = do diff --git a/testsuite/tests/ghc-api/T4891/T4891.hs b/testsuite/tests/ghc-api/T4891/T4891.hs index 7ef32aae02..f612093122 100644 --- a/testsuite/tests/ghc-api/T4891/T4891.hs +++ b/testsuite/tests/ghc-api/T4891/T4891.hs @@ -15,7 +15,7 @@ import GHC.Core.Type import TcRnMonad import TcType import Control.Applicative -import Name (getOccString) +import GHC.Types.Name (getOccString) import Unsafe.Coerce import Control.Monad import Data.Maybe diff --git a/testsuite/tests/ghc-api/T8628.hs b/testsuite/tests/ghc-api/T8628.hs index 983adf8636..c3461b2eb7 100644 --- a/testsuite/tests/ghc-api/T8628.hs +++ b/testsuite/tests/ghc-api/T8628.hs @@ -4,7 +4,7 @@ import System.IO import GHC.Driver.Session import GHC import Exception -import Module +import GHC.Types.Module import FastString import MonadUtils import Outputable diff --git a/testsuite/tests/ghc-api/T9595.hs b/testsuite/tests/ghc-api/T9595.hs index a4c3dea7e4..808fd8e79c 100644 --- a/testsuite/tests/ghc-api/T9595.hs +++ b/testsuite/tests/ghc-api/T9595.hs @@ -6,7 +6,7 @@ import GHC.Driver.Monad import Outputable import System.Environment import GHC.Driver.Session -import Module +import GHC.Types.Module main = do [libdir] <- getArgs diff --git a/testsuite/tests/ghc-api/annotations-literals/parsed.hs b/testsuite/tests/ghc-api/annotations-literals/parsed.hs index 352aae6e17..56add861ad 100644 --- a/testsuite/tests/ghc-api/annotations-literals/parsed.hs +++ b/testsuite/tests/ghc-api/annotations-literals/parsed.hs @@ -3,7 +3,7 @@ -- argument. module Main where -import BasicTypes +import GHC.Types.Basic import Data.Data import Data.List (intercalate) import System.IO diff --git a/testsuite/tests/ghc-api/annotations/CheckUtils.hs b/testsuite/tests/ghc-api/annotations/CheckUtils.hs index a43348bcda..473ded85ef 100644 --- a/testsuite/tests/ghc-api/annotations/CheckUtils.hs +++ b/testsuite/tests/ghc-api/annotations/CheckUtils.hs @@ -8,7 +8,7 @@ import Data.Data import Data.List import System.IO import GHC -import BasicTypes +import GHC.Types.Basic import GHC.Driver.Session import MonadUtils import Outputable diff --git a/testsuite/tests/ghc-api/annotations/listcomps.hs b/testsuite/tests/ghc-api/annotations/listcomps.hs index 5050a290c9..9f8fb4e6b4 100644 --- a/testsuite/tests/ghc-api/annotations/listcomps.hs +++ b/testsuite/tests/ghc-api/annotations/listcomps.hs @@ -9,7 +9,7 @@ import Data.Data import Data.List (intercalate) import System.IO import GHC -import BasicTypes +import GHC.Types.Basic import GHC.Driver.Session import MonadUtils import Outputable diff --git a/testsuite/tests/ghc-api/annotations/parseTree.hs b/testsuite/tests/ghc-api/annotations/parseTree.hs index be72c7f195..af2aeb6cb5 100644 --- a/testsuite/tests/ghc-api/annotations/parseTree.hs +++ b/testsuite/tests/ghc-api/annotations/parseTree.hs @@ -9,7 +9,7 @@ import Data.Data import Data.List (intercalate) import System.IO import GHC -import BasicTypes +import GHC.Types.Basic import GHC.Driver.Session import MonadUtils import Outputable diff --git a/testsuite/tests/ghc-api/annotations/stringSource.hs b/testsuite/tests/ghc-api/annotations/stringSource.hs index 698d93a6e2..02ce817566 100644 --- a/testsuite/tests/ghc-api/annotations/stringSource.hs +++ b/testsuite/tests/ghc-api/annotations/stringSource.hs @@ -11,10 +11,10 @@ import Data.Data import Data.List (intercalate) import System.IO import GHC -import BasicTypes +import GHC.Types.Basic import GHC.Driver.Session import FastString -import ForeignCall +import GHC.Types.ForeignCall import MonadUtils import Outputable import GHC.Hs.Decls diff --git a/testsuite/tests/ghc-api/annotations/t11430.hs b/testsuite/tests/ghc-api/annotations/t11430.hs index f1022805cf..aa51c4118e 100644 --- a/testsuite/tests/ghc-api/annotations/t11430.hs +++ b/testsuite/tests/ghc-api/annotations/t11430.hs @@ -11,10 +11,10 @@ import Data.Data hiding (Fixity) import Data.List (intercalate) import System.IO import GHC -import BasicTypes +import GHC.Types.Basic import GHC.Driver.Session import FastString -import ForeignCall +import GHC.Types.ForeignCall import MonadUtils import Outputable import GHC.Hs.Decls diff --git a/testsuite/tests/ghc-api/apirecomp001/myghc.hs b/testsuite/tests/ghc-api/apirecomp001/myghc.hs index fba7dd3d48..8c6f7b867b 100644 --- a/testsuite/tests/ghc-api/apirecomp001/myghc.hs +++ b/testsuite/tests/ghc-api/apirecomp001/myghc.hs @@ -12,7 +12,7 @@ module Main where import GHC import GHC.Driver.Session import MonadUtils ( MonadIO(..) ) -import BasicTypes ( failed ) +import GHC.Types.Basic ( failed ) import Bag ( bagToList ) import System.Environment import Control.Monad diff --git a/testsuite/tests/ghc-api/show-srcspan/showsrcspan.hs b/testsuite/tests/ghc-api/show-srcspan/showsrcspan.hs index bf73b59f18..9a2993f7a8 100644 --- a/testsuite/tests/ghc-api/show-srcspan/showsrcspan.hs +++ b/testsuite/tests/ghc-api/show-srcspan/showsrcspan.hs @@ -4,7 +4,7 @@ import Data.Data import System.IO import GHC import FastString -import SrcLoc +import GHC.Types.SrcLoc import MonadUtils import Outputable import Bag (filterBag,isEmptyBag) diff --git a/testsuite/tests/hiefile/should_run/PatTypes.hs b/testsuite/tests/hiefile/should_run/PatTypes.hs index 5d67639339..c38cacab80 100644 --- a/testsuite/tests/hiefile/should_run/PatTypes.hs +++ b/testsuite/tests/hiefile/should_run/PatTypes.hs @@ -3,10 +3,10 @@ module Main where import System.Environment -import NameCache -import SrcLoc -import UniqSupply -import Name +import GHC.Types.Name.Cache +import GHC.Types.SrcLoc +import GHC.Types.Unique.Supply +import GHC.Types.Name import GHC.Iface.Ext.Binary import GHC.Iface.Ext.Types diff --git a/testsuite/tests/package/all.T b/testsuite/tests/package/all.T index 8fe654fb7d..6aebce6ce5 100644 --- a/testsuite/tests/package/all.T +++ b/testsuite/tests/package/all.T @@ -16,7 +16,7 @@ test('package06e', normalise_version('ghc'), compile_fail, [incr_ghc]) test('package07e', normalise_version('ghc'), compile_fail, [incr_ghc + inc_ghc + hide_ghc]) test('package08e', normalise_version('ghc'), compile_fail, [incr_ghc + hide_ghc]) test('package09e', normal, compile_fail, ['-package "containers (Data.Map as M, Data.Set as M)"']) -test('package10', normal, compile, ['-hide-all-packages -package "ghc (UniqFM as Prelude)" ']) +test('package10', normal, compile, ['-hide-all-packages -package "ghc (GHC.Types.Unique.FM as Prelude)" ']) test('T4806', normalise_version('containers'), compile_fail, ['-ignore-package containers']) test('T4806a', normalise_version('containers'), compile_fail, ['-ignore-package deepseq']) diff --git a/testsuite/tests/package/package06e.hs b/testsuite/tests/package/package06e.hs index 35b6ceaa76..c130df9b86 100644 --- a/testsuite/tests/package/package06e.hs +++ b/testsuite/tests/package/package06e.hs @@ -1,3 +1,3 @@ module Package06e where import GHC.Hs.Types -import UniqFM +import GHC.Types.Unique.FM diff --git a/testsuite/tests/package/package06e.stderr b/testsuite/tests/package/package06e.stderr index 98f048c107..db6f8ab508 100644 --- a/testsuite/tests/package/package06e.stderr +++ b/testsuite/tests/package/package06e.stderr @@ -7,7 +7,7 @@ package06e.hs:2:1: error: Use -v (or `:set -v` in ghci) to see a list of the files searched for. package06e.hs:3:1: error: - Could not load module ‘UniqFM’ + Could not load module ‘GHC.Types.Unique.FM’ It is a member of the hidden package ‘ghc-8.7’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) diff --git a/testsuite/tests/package/package07e.hs b/testsuite/tests/package/package07e.hs index df13ed734e..5ab6ff626c 100644 --- a/testsuite/tests/package/package07e.hs +++ b/testsuite/tests/package/package07e.hs @@ -2,4 +2,4 @@ module Package07e where import GHC.Hs.MyTypes import GHC.Hs.Types import GHC.Hs.Utils -import UniqFM +import GHC.Types.Unique.FM diff --git a/testsuite/tests/package/package07e.stderr b/testsuite/tests/package/package07e.stderr index 5f5f0b9885..52046fc9bf 100644 --- a/testsuite/tests/package/package07e.stderr +++ b/testsuite/tests/package/package07e.stderr @@ -19,7 +19,7 @@ package07e.hs:4:1: error: Use -v (or `:set -v` in ghci) to see a list of the files searched for. package07e.hs:5:1: error: - Could not load module ‘UniqFM’ + Could not load module ‘GHC.Types.Unique.FM’ It is a member of the hidden package ‘ghc-8.7’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) diff --git a/testsuite/tests/package/package08e.hs b/testsuite/tests/package/package08e.hs index aba05de9ca..6e547e2dc5 100644 --- a/testsuite/tests/package/package08e.hs +++ b/testsuite/tests/package/package08e.hs @@ -2,4 +2,4 @@ module Package08e where import GHC.Hs.MyTypes import GHC.Hs.Types import GHC.Hs.Utils -import UniqFM +import GHC.Types.Unique.FM diff --git a/testsuite/tests/package/package08e.stderr b/testsuite/tests/package/package08e.stderr index 46d665bceb..1c2191be31 100644 --- a/testsuite/tests/package/package08e.stderr +++ b/testsuite/tests/package/package08e.stderr @@ -19,7 +19,7 @@ package08e.hs:4:1: error: Use -v (or `:set -v` in ghci) to see a list of the files searched for. package08e.hs:5:1: error: - Could not load module ‘UniqFM’ + Could not load module ‘GHC.Types.Unique.FM’ It is a member of the hidden package ‘ghc-8.7’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) diff --git a/testsuite/tests/parser/should_run/CountParserDeps.hs b/testsuite/tests/parser/should_run/CountParserDeps.hs index 0fedc62dca..1872c93ba8 100644 --- a/testsuite/tests/parser/should_run/CountParserDeps.hs +++ b/testsuite/tests/parser/should_run/CountParserDeps.hs @@ -11,7 +11,7 @@ module Main(main) where -- need exists to produce ASTs and nothing more. import GHC.Driver.Types -import Module +import GHC.Types.Module import GHC.Driver.Session import GHC.Driver.Main import GHC @@ -21,7 +21,7 @@ import Control.Monad import Control.Monad.IO.Class import System.Environment import System.Exit -import UniqSet +import GHC.Types.Unique.Set main :: IO () main = do diff --git a/testsuite/tests/parser/should_run/readRun004.hs b/testsuite/tests/parser/should_run/readRun004.hs index 698aa151af..9dc09dac55 100644 --- a/testsuite/tests/parser/should_run/readRun004.hs +++ b/testsuite/tests/parser/should_run/readRun004.hs @@ -3,7 +3,7 @@ -- should_run to make sure linking succeeds -- (curried unboxed tuples with both boxed -- and unboxed components). --- See #1509; also Note [Primop wrappers] in Id.lhs +-- See #1509; also Note [Primop wrappers] in GHC.Types.Id import GHC.Exts diff --git a/testsuite/tests/perf/should_run/UniqLoop.hs b/testsuite/tests/perf/should_run/UniqLoop.hs index d4455f99b6..bd86ba3360 100644 --- a/testsuite/tests/perf/should_run/UniqLoop.hs +++ b/testsuite/tests/perf/should_run/UniqLoop.hs @@ -2,8 +2,8 @@ module Main where -import UniqSupply -import Unique +import GHC.Types.Unique.Supply +import GHC.Types.Unique -- Generate a lot of uniques main = do diff --git a/testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs b/testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs index ab3a1e26e3..1e047eea7e 100644 --- a/testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs +++ b/testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs @@ -1,7 +1,7 @@ {-# OPTIONS_GHC -Wall #-} module Hooks.Plugin (plugin) where -import BasicTypes +import GHC.Types.Basic import GHC.Plugins import GHC.Hs.Expr import GHC.Hs.Extension diff --git a/testsuite/tests/plugins/simple-plugin/Simple/Plugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/Plugin.hs index 91ecb6d44b..f3ba8ff8df 100644 --- a/testsuite/tests/plugins/simple-plugin/Simple/Plugin.hs +++ b/testsuite/tests/plugins/simple-plugin/Simple/Plugin.hs @@ -2,7 +2,7 @@ module Simple.Plugin(plugin) where -import UniqFM +import GHC.Types.Unique.FM import GHC.Plugins import qualified ErrUtils diff --git a/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs index 4ca8d3fee3..2d1c2f7eba 100644 --- a/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs +++ b/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs @@ -10,13 +10,13 @@ import TcRnTypes import GHC.Hs.Extension import GHC.Hs.Expr import Outputable -import SrcLoc +import GHC.Types.SrcLoc import GHC.Hs import GHC.Hs.Binds -import OccName -import RdrName -import Name -import Avail +import GHC.Types.Name.Occurrence +import GHC.Types.Name.Reader +import GHC.Types.Name +import GHC.Types.Avail import GHC.Hs.Dump plugin :: Plugin diff --git a/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs index c16eea0c64..d58c69f375 100644 --- a/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs +++ b/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs @@ -7,7 +7,7 @@ import GHC.Driver.Plugins import GHC.Driver.Types import TcRnTypes import GHC.Hs.Extension -import Avail +import GHC.Types.Avail import GHC.Hs.Expr import Outputable import GHC.Hs.ImpExp diff --git a/testsuite/tests/plugins/static-plugins.hs b/testsuite/tests/plugins/static-plugins.hs index 77d451451a..3a0f3dfb08 100644 --- a/testsuite/tests/plugins/static-plugins.hs +++ b/testsuite/tests/plugins/static-plugins.hs @@ -1,6 +1,6 @@ module Main where -import Avail +import GHC.Types.Avail import Control.Monad.IO.Class import GHC.Driver.Session (getDynFlags, parseDynamicFlagsCmdLine, defaultFatalMessager, defaultFlushOut) diff --git a/testsuite/tests/pmcheck/should_compile/T11195.hs b/testsuite/tests/pmcheck/should_compile/T11195.hs index 3e45f24c23..ff3e5ae6fa 100644 --- a/testsuite/tests/pmcheck/should_compile/T11195.hs +++ b/testsuite/tests/pmcheck/should_compile/T11195.hs @@ -8,8 +8,8 @@ import GHC.Core.Type hiding( substTyVarBndr, substTy, extendTCvSubst ) import GHC.Core.InstEnv import GHC.Core.Coercion.Axiom import TcType ( exactTyCoVarsOfType ) -import VarSet -import VarEnv +import GHC.Types.Var.Set +import GHC.Types.Var.Env import Pair type NormalCo = Coercion diff --git a/testsuite/tests/pmcheck/should_compile/pmc009.hs b/testsuite/tests/pmcheck/should_compile/pmc009.hs index 95999b2de5..6f089b86e9 100644 --- a/testsuite/tests/pmcheck/should_compile/pmc009.hs +++ b/testsuite/tests/pmcheck/should_compile/pmc009.hs @@ -1,6 +1,6 @@ module HsUtils where import GHC.Hs.Binds -import SrcLoc +import GHC.Types.SrcLoc addPatSynSelector:: LHsBind p -> [a] addPatSynSelector bind diff --git a/testsuite/tests/quasiquotation/T7918.hs b/testsuite/tests/quasiquotation/T7918.hs index da770f11c1..d322a7f11e 100644 --- a/testsuite/tests/quasiquotation/T7918.hs +++ b/testsuite/tests/quasiquotation/T7918.hs @@ -5,9 +5,9 @@ import GHC import GHC.Driver.Session import Outputable import MonadUtils -import NameSet -import Var -import SrcLoc +import GHC.Types.Name.Set +import GHC.Types.Var +import GHC.Types.SrcLoc as SrcLoc import Data.Data diff --git a/testsuite/tests/regalloc/regalloc_unit_tests.hs b/testsuite/tests/regalloc/regalloc_unit_tests.hs index 2b018fc0e1..a7e93259ca 100644 --- a/testsuite/tests/regalloc/regalloc_unit_tests.hs +++ b/testsuite/tests/regalloc/regalloc_unit_tests.hs @@ -31,16 +31,16 @@ import GHC.Cmm.Pipeline import GHC.Cmm.Parser import GHC.Cmm.Info import GHC.Cmm -import Module +import GHC.Types.Module import GHC.Cmm.DebugBlock import GHC import GHC.Driver.Monad -import UniqFM -import UniqSupply +import GHC.Types.Unique.FM +import GHC.Types.Unique.Supply import GHC.Driver.Session import ErrUtils import Outputable -import BasicTypes +import GHC.Types.Basic import Stream (collect, yield) diff --git a/testsuite/tests/simplCore/should_run/SeqRule.hs b/testsuite/tests/simplCore/should_run/SeqRule.hs index 406add55ca..536ecb59c6 100644 --- a/testsuite/tests/simplCore/should_run/SeqRule.hs +++ b/testsuite/tests/simplCore/should_run/SeqRule.hs @@ -2,7 +2,7 @@ -- This test checks that the magic treatment of RULES -- for 'seq' works right. -- --- See Note [User-defined RULES for seq] in MkId for more details +-- See Note [User-defined RULES for seq] in GHC.Types.Id.Make for more details module Main where diff --git a/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs b/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs index 1614b7ce42..5794875556 100644 --- a/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs +++ b/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs @@ -1,14 +1,14 @@ module Main where -import BasicTypes +import GHC.Types.Basic import GHC import GHC.Driver.Monad import Outputable import GHC.Types.RepType import TysPrim import TysWiredIn -import UniqSet -import Unique +import GHC.Types.Unique.Set +import GHC.Types.Unique import qualified Control.Exception as E import Control.Monad |