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 /compiler/prelude | |
parent | 1c446220250dcada51d4bb33a0cc7d8ce572e8b6 (diff) | |
download | haskell-1941ef4f050c0dfcb68229641fcbbde3a10f1072.tar.gz |
Modules: Types (#13009)
Update Haddock submodule
Metric Increase:
haddock.compiler
Diffstat (limited to 'compiler/prelude')
-rw-r--r-- | compiler/prelude/ForeignCall.hs | 348 | ||||
-rw-r--r-- | compiler/prelude/KnownUniques.hs | 10 | ||||
-rw-r--r-- | compiler/prelude/KnownUniques.hs-boot | 6 | ||||
-rw-r--r-- | compiler/prelude/PrelInfo.hs | 18 | ||||
-rw-r--r-- | compiler/prelude/PrelNames.hs | 14 | ||||
-rw-r--r-- | compiler/prelude/PrelNames.hs-boot | 4 | ||||
-rw-r--r-- | compiler/prelude/PrimOp.hs | 22 | ||||
-rw-r--r-- | compiler/prelude/THNames.hs | 24 | ||||
-rw-r--r-- | compiler/prelude/TysPrim.hs | 8 | ||||
-rw-r--r-- | compiler/prelude/TysWiredIn.hs | 26 | ||||
-rw-r--r-- | compiler/prelude/TysWiredIn.hs-boot | 4 |
11 files changed, 68 insertions, 416 deletions
diff --git a/compiler/prelude/ForeignCall.hs b/compiler/prelude/ForeignCall.hs deleted file mode 100644 index c143b1ed1e..0000000000 --- a/compiler/prelude/ForeignCall.hs +++ /dev/null @@ -1,348 +0,0 @@ -{- -(c) The GRASP/AQUA Project, Glasgow University, 1992-1998 - -\section[Foreign]{Foreign calls} --} - -{-# LANGUAGE DeriveDataTypeable #-} - -module ForeignCall ( - ForeignCall(..), isSafeForeignCall, - Safety(..), playSafe, playInterruptible, - - CExportSpec(..), CLabelString, isCLabelString, pprCLabelString, - CCallSpec(..), - CCallTarget(..), isDynamicTarget, - CCallConv(..), defaultCCallConv, ccallConvToInt, ccallConvAttribute, - - Header(..), CType(..), - ) where - -import GhcPrelude - -import FastString -import Binary -import Outputable -import Module -import BasicTypes ( SourceText, pprWithSourceText ) - -import Data.Char -import Data.Data - -{- -************************************************************************ -* * -\subsubsection{Data types} -* * -************************************************************************ --} - -newtype ForeignCall = CCall CCallSpec - deriving Eq - -isSafeForeignCall :: ForeignCall -> Bool -isSafeForeignCall (CCall (CCallSpec _ _ safe)) = playSafe safe - --- We may need more clues to distinguish foreign calls --- but this simple printer will do for now -instance Outputable ForeignCall where - ppr (CCall cc) = ppr cc - -data Safety - = PlaySafe -- Might invoke Haskell GC, or do a call back, or - -- switch threads, etc. So make sure things are - -- tidy before the call. Additionally, in the threaded - -- RTS we arrange for the external call to be executed - -- by a separate OS thread, i.e., _concurrently_ to the - -- execution of other Haskell threads. - - | PlayInterruptible -- Like PlaySafe, but additionally - -- the worker thread running this foreign call may - -- be unceremoniously killed, so it must be scheduled - -- on an unbound thread. - - | PlayRisky -- None of the above can happen; the call will return - -- without interacting with the runtime system at all - deriving ( Eq, Show, Data ) - -- Show used just for Show Lex.Token, I think - -instance Outputable Safety where - ppr PlaySafe = text "safe" - ppr PlayInterruptible = text "interruptible" - ppr PlayRisky = text "unsafe" - -playSafe :: Safety -> Bool -playSafe PlaySafe = True -playSafe PlayInterruptible = True -playSafe PlayRisky = False - -playInterruptible :: Safety -> Bool -playInterruptible PlayInterruptible = True -playInterruptible _ = False - -{- -************************************************************************ -* * -\subsubsection{Calling C} -* * -************************************************************************ --} - -data CExportSpec - = CExportStatic -- foreign export ccall foo :: ty - SourceText -- of the CLabelString. - -- See note [Pragma source text] in BasicTypes - CLabelString -- C Name of exported function - CCallConv - deriving Data - -data CCallSpec - = CCallSpec CCallTarget -- What to call - CCallConv -- Calling convention to use. - Safety - deriving( Eq ) - --- The call target: - --- | How to call a particular function in C-land. -data CCallTarget - -- An "unboxed" ccall# to named function in a particular package. - = StaticTarget - SourceText -- of the CLabelString. - -- See note [Pragma source text] in BasicTypes - CLabelString -- C-land name of label. - - (Maybe UnitId) -- What package the function is in. - -- If Nothing, then it's taken to be in the current package. - -- Note: This information is only used for PrimCalls on Windows. - -- See CLabel.labelDynamic and CoreToStg.coreToStgApp - -- for the difference in representation between PrimCalls - -- and ForeignCalls. If the CCallTarget is representing - -- a regular ForeignCall then it's safe to set this to Nothing. - - -- The first argument of the import is the name of a function pointer (an Addr#). - -- Used when importing a label as "foreign import ccall "dynamic" ..." - Bool -- True => really a function - -- False => a value; only - -- allowed in CAPI imports - | DynamicTarget - - deriving( Eq, Data ) - -isDynamicTarget :: CCallTarget -> Bool -isDynamicTarget DynamicTarget = True -isDynamicTarget _ = False - -{- -Stuff to do with calling convention: - -ccall: Caller allocates parameters, *and* deallocates them. - -stdcall: Caller allocates parameters, callee deallocates. - Function name has @N after it, where N is number of arg bytes - e.g. _Foo@8. This convention is x86 (win32) specific. - -See: http://www.programmersheaven.com/2/Calling-conventions --} - --- any changes here should be replicated in the CallConv type in template haskell -data CCallConv = CCallConv | CApiConv | StdCallConv | PrimCallConv | JavaScriptCallConv - deriving (Eq, Data) - -instance Outputable CCallConv where - ppr StdCallConv = text "stdcall" - ppr CCallConv = text "ccall" - ppr CApiConv = text "capi" - ppr PrimCallConv = text "prim" - ppr JavaScriptCallConv = text "javascript" - -defaultCCallConv :: CCallConv -defaultCCallConv = CCallConv - -ccallConvToInt :: CCallConv -> Int -ccallConvToInt StdCallConv = 0 -ccallConvToInt CCallConv = 1 -ccallConvToInt CApiConv = panic "ccallConvToInt CApiConv" -ccallConvToInt (PrimCallConv {}) = panic "ccallConvToInt PrimCallConv" -ccallConvToInt JavaScriptCallConv = panic "ccallConvToInt JavaScriptCallConv" - -{- -Generate the gcc attribute corresponding to the given -calling convention (used by PprAbsC): --} - -ccallConvAttribute :: CCallConv -> SDoc -ccallConvAttribute StdCallConv = text "__attribute__((__stdcall__))" -ccallConvAttribute CCallConv = empty -ccallConvAttribute CApiConv = empty -ccallConvAttribute (PrimCallConv {}) = panic "ccallConvAttribute PrimCallConv" -ccallConvAttribute JavaScriptCallConv = panic "ccallConvAttribute JavaScriptCallConv" - -type CLabelString = FastString -- A C label, completely unencoded - -pprCLabelString :: CLabelString -> SDoc -pprCLabelString lbl = ftext lbl - -isCLabelString :: CLabelString -> Bool -- Checks to see if this is a valid C label -isCLabelString lbl - = all ok (unpackFS lbl) - where - ok c = isAlphaNum c || c == '_' || c == '.' - -- The '.' appears in e.g. "foo.so" in the - -- module part of a ExtName. Maybe it should be separate - --- Printing into C files: - -instance Outputable CExportSpec where - ppr (CExportStatic _ str _) = pprCLabelString str - -instance Outputable CCallSpec where - ppr (CCallSpec fun cconv safety) - = hcat [ whenPprDebug callconv, ppr_fun fun ] - where - callconv = text "{-" <> ppr cconv <> text "-}" - - gc_suf | playSafe safety = text "_GC" - | otherwise = empty - - ppr_fun (StaticTarget st _fn mPkgId isFun) - = text (if isFun then "__pkg_ccall" - else "__pkg_ccall_value") - <> gc_suf - <+> (case mPkgId of - Nothing -> empty - Just pkgId -> ppr pkgId) - <+> (pprWithSourceText st empty) - - ppr_fun DynamicTarget - = text "__dyn_ccall" <> gc_suf <+> text "\"\"" - --- The filename for a C header file --- Note [Pragma source text] in BasicTypes -data Header = Header SourceText FastString - deriving (Eq, Data) - -instance Outputable Header where - ppr (Header st h) = pprWithSourceText st (doubleQuotes $ ppr h) - --- | A C type, used in CAPI FFI calls --- --- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{-\# CTYPE'@, --- 'ApiAnnotation.AnnHeader','ApiAnnotation.AnnVal', --- 'ApiAnnotation.AnnClose' @'\#-}'@, - --- For details on above see note [Api annotations] in ApiAnnotation -data CType = CType SourceText -- Note [Pragma source text] in BasicTypes - (Maybe Header) -- header to include for this type - (SourceText,FastString) -- the type itself - deriving (Eq, Data) - -instance Outputable CType where - ppr (CType stp mh (stct,ct)) - = pprWithSourceText stp (text "{-# CTYPE") <+> hDoc - <+> pprWithSourceText stct (doubleQuotes (ftext ct)) <+> text "#-}" - where hDoc = case mh of - Nothing -> empty - Just h -> ppr h - -{- -************************************************************************ -* * -\subsubsection{Misc} -* * -************************************************************************ --} - -instance Binary ForeignCall where - put_ bh (CCall aa) = put_ bh aa - get bh = do aa <- get bh; return (CCall aa) - -instance Binary Safety where - put_ bh PlaySafe = do - putByte bh 0 - put_ bh PlayInterruptible = do - putByte bh 1 - put_ bh PlayRisky = do - putByte bh 2 - get bh = do - h <- getByte bh - case h of - 0 -> do return PlaySafe - 1 -> do return PlayInterruptible - _ -> do return PlayRisky - -instance Binary CExportSpec where - put_ bh (CExportStatic ss aa ab) = do - put_ bh ss - put_ bh aa - put_ bh ab - get bh = do - ss <- get bh - aa <- get bh - ab <- get bh - return (CExportStatic ss aa ab) - -instance Binary CCallSpec where - put_ bh (CCallSpec aa ab ac) = do - put_ bh aa - put_ bh ab - put_ bh ac - get bh = do - aa <- get bh - ab <- get bh - ac <- get bh - return (CCallSpec aa ab ac) - -instance Binary CCallTarget where - put_ bh (StaticTarget ss aa ab ac) = do - putByte bh 0 - put_ bh ss - put_ bh aa - put_ bh ab - put_ bh ac - put_ bh DynamicTarget = do - putByte bh 1 - get bh = do - h <- getByte bh - case h of - 0 -> do ss <- get bh - aa <- get bh - ab <- get bh - ac <- get bh - return (StaticTarget ss aa ab ac) - _ -> do return DynamicTarget - -instance Binary CCallConv where - put_ bh CCallConv = do - putByte bh 0 - put_ bh StdCallConv = do - putByte bh 1 - put_ bh PrimCallConv = do - putByte bh 2 - put_ bh CApiConv = do - putByte bh 3 - put_ bh JavaScriptCallConv = do - putByte bh 4 - get bh = do - h <- getByte bh - case h of - 0 -> do return CCallConv - 1 -> do return StdCallConv - 2 -> do return PrimCallConv - 3 -> do return CApiConv - _ -> do return JavaScriptCallConv - -instance Binary CType where - put_ bh (CType s mh fs) = do put_ bh s - put_ bh mh - put_ bh fs - get bh = do s <- get bh - mh <- get bh - fs <- get bh - return (CType s mh fs) - -instance Binary Header where - put_ bh (Header s h) = put_ bh s >> put_ bh h - get bh = do s <- get bh - h <- get bh - return (Header s h) diff --git a/compiler/prelude/KnownUniques.hs b/compiler/prelude/KnownUniques.hs index 1d292d899b..75b6719bba 100644 --- a/compiler/prelude/KnownUniques.hs +++ b/compiler/prelude/KnownUniques.hs @@ -31,11 +31,11 @@ import GhcPrelude import TysWiredIn import GHC.Core.TyCon import GHC.Core.DataCon -import Id -import BasicTypes +import GHC.Types.Id +import GHC.Types.Basic import Outputable -import Unique -import Name +import GHC.Types.Unique +import GHC.Types.Name import Util import Data.Bits @@ -65,7 +65,7 @@ knownUniqueName u = -- tag (used to identify the sum's TypeRep binding). -- -- This layout is chosen to remain compatible with the usual unique allocation --- for wired-in data constructors described in Unique.hs +-- for wired-in data constructors described in GHC.Types.Unique -- -- TyCon for sum of arity k: -- 00000000 kkkkkkkk 11111100 diff --git a/compiler/prelude/KnownUniques.hs-boot b/compiler/prelude/KnownUniques.hs-boot index b217c84aca..b43598cc17 100644 --- a/compiler/prelude/KnownUniques.hs-boot +++ b/compiler/prelude/KnownUniques.hs-boot @@ -1,9 +1,9 @@ module KnownUniques where import GhcPrelude -import Unique -import Name -import BasicTypes +import GHC.Types.Unique +import GHC.Types.Name +import GHC.Types.Basic -- Needed by TysWiredIn knownUniqueName :: Unique -> Maybe Name diff --git a/compiler/prelude/PrelInfo.hs b/compiler/prelude/PrelInfo.hs index 0b7a962f3f..1a47d59e38 100644 --- a/compiler/prelude/PrelInfo.hs +++ b/compiler/prelude/PrelInfo.hs @@ -49,26 +49,26 @@ module PrelInfo ( import GhcPrelude import KnownUniques -import Unique ( isValidKnownKeyUnique ) +import GHC.Types.Unique ( isValidKnownKeyUnique ) import GHC.Core.ConLike ( ConLike(..) ) import THNames ( templateHaskellNames ) import PrelNames import GHC.Core.Op.ConstantFold -import Avail +import GHC.Types.Avail import PrimOp import GHC.Core.DataCon -import Id -import Name -import NameEnv -import MkId +import GHC.Types.Id +import GHC.Types.Name +import GHC.Types.Name.Env +import GHC.Types.Id.Make import Outputable import TysPrim import TysWiredIn import GHC.Driver.Types import GHC.Core.Class import GHC.Core.TyCon -import UniqFM +import GHC.Types.Unique.FM import Util import TcTypeNats ( typeNatTyCons ) @@ -89,12 +89,12 @@ Note [About wired-in things] * Wired-in things are Ids\/TyCons that are completely known to the compiler. They are global values in GHC, (e.g. listTyCon :: TyCon). -* A wired in Name contains the thing itself inside the Name: +* A wired-in Name contains the thing itself inside the Name: see Name.wiredInNameTyThing_maybe (E.g. listTyConName contains listTyCon. * The name cache is initialised with (the names of) all wired-in things - (except tuples and sums; see Note [Known-]) + (except tuples and sums; see Note [Infinite families of known-key names]) * The type environment itself contains no wired in things. The type checker sees if the Name is wired in before looking up the name in diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index e0d957c00a..8452ac734c 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -139,7 +139,7 @@ this constructor directly (see CorePrep.lookupIntegerSDataConName) When GHC reads the package data base, it (internally only) pretends it has UnitId `integer-wired-in` instead of the actual UnitId (which includes the version number); just like for `base` and other packages, as described in -Note [Wired-in packages] in Module. This is done in Packages.findWiredInPackages. +Note [Wired-in packages] in GHC.Types.Module. This is done in Packages.findWiredInPackages. -} {-# LANGUAGE CPP #-} @@ -160,12 +160,12 @@ module PrelNames ( import GhcPrelude -import Module -import OccName -import RdrName -import Unique -import Name -import SrcLoc +import GHC.Types.Module +import GHC.Types.Name.Occurrence +import GHC.Types.Name.Reader +import GHC.Types.Unique +import GHC.Types.Name +import GHC.Types.SrcLoc import FastString {- diff --git a/compiler/prelude/PrelNames.hs-boot b/compiler/prelude/PrelNames.hs-boot index 0bd74d5577..9906496b37 100644 --- a/compiler/prelude/PrelNames.hs-boot +++ b/compiler/prelude/PrelNames.hs-boot @@ -1,7 +1,7 @@ module PrelNames where -import Module -import Unique +import GHC.Types.Module +import GHC.Types.Unique mAIN :: Module liftedTypeKindTyConKey :: Unique diff --git a/compiler/prelude/PrimOp.hs b/compiler/prelude/PrimOp.hs index 96160a27f3..0774edef63 100644 --- a/compiler/prelude/PrimOp.hs +++ b/compiler/prelude/PrimOp.hs @@ -31,22 +31,22 @@ import TysPrim import TysWiredIn import GHC.Cmm.Type -import Demand -import Id ( Id, mkVanillaGlobalWithInfo ) -import IdInfo ( vanillaIdInfo, setCafInfo, CafInfo(NoCafRefs) ) -import Name -import PrelNames ( gHC_PRIMOPWRAPPERS ) +import GHC.Types.Demand +import GHC.Types.Id ( Id, mkVanillaGlobalWithInfo ) +import GHC.Types.Id.Info ( vanillaIdInfo, setCafInfo, CafInfo(NoCafRefs) ) +import GHC.Types.Name +import PrelNames ( gHC_PRIMOPWRAPPERS ) import GHC.Core.TyCon ( TyCon, isPrimTyCon, PrimRep(..) ) import GHC.Core.Type import GHC.Types.RepType ( typePrimRep1, tyConPrimRep1 ) -import BasicTypes ( Arity, Fixity(..), FixityDirection(..), Boxity(..), - SourceText(..) ) -import SrcLoc ( wiredInSrcSpan ) -import ForeignCall ( CLabelString ) -import Unique ( Unique, mkPrimOpIdUnique, mkPrimOpWrapperUnique ) +import GHC.Types.Basic ( Arity, Fixity(..), FixityDirection(..), Boxity(..), + SourceText(..) ) +import GHC.Types.SrcLoc ( wiredInSrcSpan ) +import GHC.Types.ForeignCall ( CLabelString ) +import GHC.Types.Unique ( Unique, mkPrimOpIdUnique, mkPrimOpWrapperUnique ) +import GHC.Types.Module ( UnitId ) import Outputable import FastString -import Module ( UnitId ) {- ************************************************************************ diff --git a/compiler/prelude/THNames.hs b/compiler/prelude/THNames.hs index 7e131aa1ca..e2efbdaa0d 100644 --- a/compiler/prelude/THNames.hs +++ b/compiler/prelude/THNames.hs @@ -9,11 +9,11 @@ module THNames where import GhcPrelude () import PrelNames( mk_known_key_name ) -import Module( Module, mkModuleNameFS, mkModule, thUnitId ) -import Name( Name ) -import OccName( tcName, clsName, dataName, varName ) -import RdrName( RdrName, nameRdrName ) -import Unique +import GHC.Types.Module( Module, mkModuleNameFS, mkModule, thUnitId ) +import GHC.Types.Name( Name ) +import GHC.Types.Name.Occurrence( tcName, clsName, dataName, varName ) +import GHC.Types.Name.Reader( RdrName, nameRdrName ) +import GHC.Types.Unique import FastString -- To add a name, do three things @@ -170,13 +170,13 @@ mkTHModule :: FastString -> Module mkTHModule m = mkModule thUnitId (mkModuleNameFS m) libFun, libTc, thFun, thTc, thCls, thCon, qqFun :: FastString -> Unique -> Name -libFun = mk_known_key_name OccName.varName thLib -libTc = mk_known_key_name OccName.tcName thLib -thFun = mk_known_key_name OccName.varName thSyn -thTc = mk_known_key_name OccName.tcName thSyn -thCls = mk_known_key_name OccName.clsName thSyn -thCon = mk_known_key_name OccName.dataName thSyn -qqFun = mk_known_key_name OccName.varName qqLib +libFun = mk_known_key_name varName thLib +libTc = mk_known_key_name tcName thLib +thFun = mk_known_key_name varName thSyn +thTc = mk_known_key_name tcName thSyn +thCls = mk_known_key_name clsName thSyn +thCon = mk_known_key_name dataName thSyn +qqFun = mk_known_key_name varName qqLib -------------------- TH.Syntax ----------------------- liftClassName :: Name diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs index e9cdb81fc8..422ed27fe1 100644 --- a/compiler/prelude/TysPrim.hs +++ b/compiler/prelude/TysPrim.hs @@ -110,11 +110,11 @@ import {-# SOURCE #-} TysWiredIn , doubleElemRepDataConTy , mkPromotedListTy ) -import Var ( TyVar, mkTyVar ) -import Name +import GHC.Types.Var ( TyVar, mkTyVar ) +import GHC.Types.Name import GHC.Core.TyCon -import SrcLoc -import Unique +import GHC.Types.SrcLoc +import GHC.Types.Unique import PrelNames import FastString import Outputable diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 908b0e1566..8db8379131 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -16,7 +16,7 @@ module TysWiredIn ( mkWiredInTyConName, -- This is used in TcTypeNats to define the -- built-in functions for evaluation. - mkWiredInIdName, -- used in MkId + mkWiredInIdName, -- used in GHC.Types.Id.Make -- * All wired in things wiredInTyCons, isBuiltInOcc_maybe, @@ -132,7 +132,7 @@ module TysWiredIn ( import GhcPrelude -import {-# SOURCE #-} MkId( mkDataConWorkId, mkDictSelId ) +import {-# SOURCE #-} GHC.Types.Id.Make ( mkDataConWorkId, mkDictSelId ) -- friends: import PrelNames @@ -141,23 +141,23 @@ import {-# SOURCE #-} KnownUniques -- others: import GHC.Core.Coercion.Axiom -import Id +import GHC.Types.Id import Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE, mAX_SUM_SIZE ) -import Module ( Module ) +import GHC.Types.Module ( Module ) import GHC.Core.Type import GHC.Types.RepType import GHC.Core.DataCon import {-# SOURCE #-} GHC.Core.ConLike import GHC.Core.TyCon -import GHC.Core.Class ( Class, mkClass ) -import RdrName -import Name -import NameEnv ( NameEnv, mkNameEnv, lookupNameEnv, lookupNameEnv_NF ) -import NameSet ( NameSet, mkNameSet, elemNameSet ) -import BasicTypes -import ForeignCall -import SrcLoc ( noSrcSpan ) -import Unique +import GHC.Core.Class ( Class, mkClass ) +import GHC.Types.Name.Reader +import GHC.Types.Name as Name +import GHC.Types.Name.Env ( NameEnv, mkNameEnv, lookupNameEnv, lookupNameEnv_NF ) +import GHC.Types.Name.Set ( NameSet, mkNameSet, elemNameSet ) +import GHC.Types.Basic +import GHC.Types.ForeignCall +import GHC.Types.SrcLoc ( noSrcSpan ) +import GHC.Types.Unique import Data.Array import FastString import Outputable diff --git a/compiler/prelude/TysWiredIn.hs-boot b/compiler/prelude/TysWiredIn.hs-boot index 7fe222b825..426c1015a6 100644 --- a/compiler/prelude/TysWiredIn.hs-boot +++ b/compiler/prelude/TysWiredIn.hs-boot @@ -3,8 +3,8 @@ module TysWiredIn where import {-# SOURCE #-} GHC.Core.TyCon ( TyCon ) import {-# SOURCE #-} GHC.Core.TyCo.Rep (Type, Kind) -import BasicTypes (Arity, TupleSort) -import Name (Name) +import GHC.Types.Basic (Arity, TupleSort) +import GHC.Types.Name (Name) listTyCon :: TyCon typeNatKind, typeSymbolKind :: Type |