summaryrefslogtreecommitdiff
path: root/compiler/parser
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-03-18 10:44:56 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-03-29 17:28:51 -0400
commit1941ef4f050c0dfcb68229641fcbbde3a10f1072 (patch)
tree8e25a61af77696d3022d35cc277b5db5af540f03 /compiler/parser
parent1c446220250dcada51d4bb33a0cc7d8ce572e8b6 (diff)
downloadhaskell-1941ef4f050c0dfcb68229641fcbbde3a10f1072.tar.gz
Modules: Types (#13009)
Update Haddock submodule Metric Increase: haddock.compiler
Diffstat (limited to 'compiler/parser')
-rw-r--r--compiler/parser/ApiAnnotation.hs4
-rw-r--r--compiler/parser/HaddockUtils.hs2
-rw-r--r--compiler/parser/Lexer.x12
-rw-r--r--compiler/parser/Parser.y18
-rw-r--r--compiler/parser/RdrHsSyn.hs16
5 files changed, 26 insertions, 26 deletions
diff --git a/compiler/parser/ApiAnnotation.hs b/compiler/parser/ApiAnnotation.hs
index 52905902b6..5ad598da94 100644
--- a/compiler/parser/ApiAnnotation.hs
+++ b/compiler/parser/ApiAnnotation.hs
@@ -15,9 +15,9 @@ module ApiAnnotation (
import GhcPrelude
-import RdrName
+import GHC.Types.Name.Reader
import Outputable
-import SrcLoc
+import GHC.Types.SrcLoc
import qualified Data.Map as Map
import Data.Data
diff --git a/compiler/parser/HaddockUtils.hs b/compiler/parser/HaddockUtils.hs
index b8e0c564a6..73429ec14a 100644
--- a/compiler/parser/HaddockUtils.hs
+++ b/compiler/parser/HaddockUtils.hs
@@ -5,7 +5,7 @@ module HaddockUtils where
import GhcPrelude
import GHC.Hs
-import SrcLoc
+import GHC.Types.SrcLoc
import Control.Monad
diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 5fa0af85ad..a99a62913e 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -97,7 +97,7 @@ import Bag
import Outputable
import StringBuffer
import FastString
-import UniqFM
+import GHC.Types.Unique.FM
import Util ( readRational, readHexRational )
-- compiler/main
@@ -105,11 +105,11 @@ import ErrUtils
import GHC.Driver.Session as DynFlags
-- compiler/basicTypes
-import SrcLoc
-import Module
-import BasicTypes ( InlineSpec(..), RuleMatchInfo(..),
- IntegralLit(..), FractionalLit(..),
- SourceText(..) )
+import GHC.Types.SrcLoc
+import GHC.Types.Module
+import GHC.Types.Basic ( InlineSpec(..), RuleMatchInfo(..),
+ IntegralLit(..), FractionalLit(..),
+ SourceText(..) )
-- compiler/parser
import Ctype
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 88422f9b3f..e87cad6dae 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -62,12 +62,12 @@ import Maybes ( isJust, orElse )
import Outputable
-- compiler/basicTypes
-import RdrName
-import OccName ( varName, dataName, tcClsName, tvName, startsWithUnderscore )
-import GHC.Core.DataCon ( DataCon, dataConName )
-import SrcLoc
-import Module
-import BasicTypes
+import GHC.Types.Name.Reader
+import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore )
+import GHC.Core.DataCon ( DataCon, dataConName )
+import GHC.Types.SrcLoc
+import GHC.Types.Module
+import GHC.Types.Basic
-- compiler/types
import GHC.Core.Type ( funTyCon )
@@ -83,7 +83,7 @@ import ApiAnnotation
import TcEvidence ( emptyTcEvBinds )
-- compiler/prelude
-import ForeignCall
+import GHC.Types.ForeignCall
import TysPrim ( eqPrimTyCon )
import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nilDataCon,
unboxedUnitTyCon, unboxedUnitDataCon,
@@ -2188,8 +2188,8 @@ When the user write Zero instead of 'Zero in types, we parse it a
HsTyVar ("Zero", TcClsName) instead of HsTyVar ("Zero", DataName). We
deal with this in the renamer. If a HsTyVar ("Zero", TcClsName) is not
bounded in the type level, then we look for it in the term level (we
-change its namespace to DataName, see Note [Demotion] in OccName). And
-both become a HsTyVar ("Zero", DataName) after the renamer.
+change its namespace to DataName, see Note [Demotion] in GHC.Types.Names.OccName).
+And both become a HsTyVar ("Zero", DataName) after the renamer.
-}
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index 599846398b..485d1bf80e 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -108,20 +108,20 @@ import GHC.Core.TyCon ( TyCon, isTupleTyCon, tyConSingleDataCon_maybe )
import GHC.Core.DataCon ( DataCon, dataConTyCon )
import GHC.Core.ConLike ( ConLike(..) )
import GHC.Core.Coercion.Axiom ( Role, fsFromRole )
-import RdrName
-import Name
-import BasicTypes
+import GHC.Types.Name.Reader
+import GHC.Types.Name
+import GHC.Types.Basic
import Lexer
-import Lexeme ( isLexCon )
+import GHC.Utils.Lexeme ( isLexCon )
import GHC.Core.Type ( TyThing(..), funTyCon )
import TysWiredIn ( cTupleTyConName, tupleTyCon, tupleDataCon,
nilDataConName, nilDataConKey,
listTyConName, listTyConKey, eqTyCon_RDR,
tupleTyConName, cTupleTyConNameArity_maybe )
-import ForeignCall
+import GHC.Types.ForeignCall
import PrelNames ( allNameStrings )
-import SrcLoc
-import Unique ( hasKey )
+import GHC.Types.SrcLoc
+import GHC.Types.Unique ( hasKey )
import OrdList ( OrdList, fromOL )
import Bag ( emptyBag, consBag )
import Outputable
@@ -2548,7 +2548,7 @@ mkInlinePragma :: SourceText -> (InlineSpec, RuleMatchInfo) -> Maybe Activation
-- The (Maybe Activation) is because the user can omit
-- the activation spec (and usually does)
mkInlinePragma src (inl, match_info) mb_act
- = InlinePragma { inl_src = src -- Note [Pragma source text] in BasicTypes
+ = InlinePragma { inl_src = src -- Note [Pragma source text] in GHC.Types.Basic
, inl_inline = inl
, inl_sat = Nothing
, inl_act = act