Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
jberryman
GHC
Commits
73c0472d
Commit
73c0472d
authored
Oct 27, 2000
by
simonpj
Browse files
[project @ 2000-10-27 16:43:24 by simonpj]
Wibble
parent
3fe733ed
Changes
11
Hide whitespace changes
Inline
Side-by-side
ghc/compiler/basicTypes/DataCon.lhs
View file @
73c0472d
...
...
@@ -28,10 +28,10 @@ module DataCon (
import {-# SOURCE #-} Subst( substTy, mkTyVarSubst )
import CmdLineOpts ( opt_DictsStrict )
import Type ( Type,
ThetaType,
TauType, ClassContext,
import Type ( Type, TauType, ClassContext,
mkForAllTys, mkFunTys, mkTyConApp,
mkTyVarTys, mkDictTys,
splitTyConApp_maybe
, classesToPreds
splitTyConApp_maybe
)
import TyCon ( TyCon, tyConDataCons, tyConDataConsIfAvailable, isDataTyCon, isProductTyCon,
isTupleTyCon, isUnboxedTupleTyCon, isRecursiveTyCon )
...
...
ghc/compiler/basicTypes/Module.lhs
View file @
73c0472d
...
...
@@ -24,7 +24,8 @@ module Module
Module, moduleName
-- abstract, instance of Eq, Ord, Outputable
, ModuleName
, isModuleInThisPackage, mkModuleInThisPackage
, isModuleInThisPackage, mkModuleInThisPackage,
, printModulePrefix
, moduleNameString -- :: ModuleName -> EncodedString
, moduleNameUserString -- :: ModuleName -> UserString
...
...
@@ -98,6 +99,12 @@ data PackageInfo
-- as the one being compiled
| AnotherPackage PackageName -- A module from a different package
| DunnoYet -- This is used when we don't yet know
-- Main case: we've come across Foo.x in an interface file
-- but we havn't yet opened Foo.hi. We need a Name for Foo.x
-- Later on (in RnEnv.newTopBinder) we'll update the cache
-- to have the right PackageInfo
type PackageName = FastString -- No encoding at all
preludePackage :: PackageName
...
...
@@ -106,6 +113,7 @@ preludePackage = SLIT("std")
instance Outputable PackageInfo where
-- Just used in debug prints of lex tokens and in debug modde
ppr ThisPackage = ptext SLIT("<THIS>")
ppr DunnoYet = ptext SLIT("<?>")
ppr (AnotherPackage p) = ptext p
\end{code}
...
...
@@ -235,7 +243,7 @@ mkHomeModule mod_nm = Module mod_nm ThisPackage
-- file, but before we've opened Foo.hi.
-- (Until we've opened Foo.hi we don't know what the PackageInfo is.)
mkVanillaModule :: ModuleName -> Module
mkVanillaModule name =
mk
Module name
(panic "mkVanillaModule:
un
k
no
wn mod_kind field")
mkVanillaModule name = Module name
D
unno
Yet
mkPrelModule :: ModuleName -> Module
mkPrelModule name = mkModule name preludePackage
...
...
@@ -252,8 +260,14 @@ moduleUserString (Module mod _) = moduleNameUserString mod
isModuleInThisPackage :: Module -> Bool
isModuleInThisPackage (Module nm ThisPackage) = True
isModuleInThisPackage _ = False
printModulePrefix :: Module -> Bool
-- When printing, say M.x
printModulePrefix (Module nm ThisPackage) = False
printModulePrefix _ = True
\end{code}
%************************************************************************
%* *
\subsection{@ModuleEnv@s}
...
...
ghc/compiler/basicTypes/Name.lhs
View file @
73c0472d
...
...
@@ -42,7 +42,7 @@ module Name (
import OccName -- All of it
import Module ( Module, moduleName, mkVanillaModule,
isModuleInThisPackage )
printModulePrefix,
isModuleInThisPackage )
import RdrName ( RdrName, mkRdrQual, mkRdrUnqual, rdrNameOcc,
rdrNameModule )
import CmdLineOpts ( opt_Static, opt_PprStyle_NoPrags,
...
...
@@ -446,7 +446,7 @@ pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
global m | codeStyle sty
= ppr (moduleName m) <> char '_' <> pprOccName occ
| debugStyle sty ||
not (isModuleInThisPackage
m
)
| debugStyle sty ||
printModulePrefix
m
= ppr (moduleName m) <> dot <> pprOccName occ
| otherwise
= pprOccName occ
...
...
ghc/compiler/main/HscTypes.lhs
View file @
73c0472d
...
...
@@ -65,7 +65,7 @@ import HsSyn ( DeprecTxt )
import RdrHsSyn ( RdrNameHsDecl, RdrNameTyClDecl )
import RnHsSyn ( RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl )
import CoreSyn (
CoreRule,
IdCoreRule )
import CoreSyn ( IdCoreRule )
import Type ( Type )
import FiniteMap ( FiniteMap, emptyFM, addToFM, lookupFM, foldFM )
...
...
ghc/compiler/rename/ParseIface.y
View file @
73c0472d
...
...
@@ -257,7 +257,7 @@ is_boot : { False }
whats_imported
::
{
WhatsImported
OccName
}
whats_imported
:
{
NothingAtAll
}
|
'::'
version
{
Everything
$
2
}
|
'::'
version
version
name_version_pairs
version
{
Specifically
$
2
(
Just
$
3
)
$
4
$
5
}
|
'::'
version
version
version
name_version_pairs
{
Specifically
$
2
(
Just
$
3
)
$
5
$
4
}
name_version_pairs
::
{
[(
OccName
,
Version
)]
}
name_version_pairs
:
{
[]
}
...
...
ghc/compiler/rename/RnIfaces.lhs
View file @
73c0472d
...
...
@@ -40,7 +40,7 @@ import Name ( Name {-instance NamedThing-}, nameOccName,
NamedThing(..),
elemNameEnv
)
import Module ( Module, ModuleEnv,
import Module ( Module, ModuleEnv,
mkVanillaModule,
moduleName, isModuleInThisPackage,
ModuleName, WhereFrom(..),
emptyModuleEnv, lookupModuleEnvByName,
...
...
@@ -79,7 +79,8 @@ getInterfaceExports mod_name from
Just mi -> returnRn (mi_module mi, mi_exports mi) ;
-- loadInterface always puts something in the map
-- even if it's a fake
Nothing -> pprPanic "getInterfaceExports" (ppr mod_name)
Nothing -> returnRn (mkVanillaModule mod_name, [])
-- pprPanic "getInterfaceExports" (ppr mod_name)
}
where
doc_str = sep [ppr mod_name, ptext SLIT("is directly imported")]
...
...
ghc/compiler/specialise/Rules.lhs
View file @
73c0472d
...
...
@@ -25,10 +25,8 @@ import Subst ( Subst, InScopeSet, mkInScopeSet, lookupSubst, extendSubst,
substEnv, setSubstEnv, emptySubst, isInScope,
bindSubstList, unBindSubstList, substInScope, uniqAway
)
import Id ( Id, idUnfolding, zapLamIdInfo,
idSpecialisation, setIdSpecialisation
)
import Var ( isTyVar, isId )
import Id ( Id, idUnfolding, idSpecialisation, setIdSpecialisation )
import Var ( isId )
import VarSet
import VarEnv
import Type ( mkTyVarTy )
...
...
ghc/compiler/types/Class.lhs
View file @
73c0472d
...
...
@@ -23,7 +23,6 @@ import Name ( NamedThing(..), Name )
import BasicTypes ( Arity )
import Unique ( Unique, Uniquable(..) )
import Outputable
import Util
\end{code}
%************************************************************************
...
...
ghc/compiler/types/PprType.lhs
View file @
73c0472d
...
...
@@ -27,18 +27,16 @@ import Type ( PredType(..), ThetaType,
isDictTy, splitTyConApp_maybe, splitFunTy_maybe,
splitUsForAllTys, predRepTy
)
import Var ( TyVar, tyVarKind,
tyVarName, setTyVarName
)
import Var ( TyVar, tyVarKind )
import TyCon ( TyCon, isPrimTyCon, isTupleTyCon, isUnboxedTupleTyCon,
maybeTyConSingleCon, isEnumerationTyCon,
tyConArity
, tyConUnique
tyConArity
)
import Class ( Class
, className
)
import Class ( Class )
-- others:
import Maybes ( maybeToBool )
import Name ( getOccString
, NamedThing(..)
)
import Name ( getOccString )
import Outputable
import PprEnv
import Unique ( Uniquable(..) )
...
...
@@ -217,9 +215,6 @@ ppr_ty env ctxt_prec (NoteTy (UsgNote u) ty)
ppr_ty env ctxt_prec (PredTy p) = braces (ppr_pred env p)
ppr_theta env [] = empty
ppr_theta env theta = braces (hsep (punctuate comma (map (ppr_pred env) theta)))
ppr_pred env (Class clas tys) = ppr clas <+>
hsep (map (ppr_ty env tYCON_PREC) tys)
ppr_pred env (IParam n ty) = hsep [char '?' <> ppr n, text "::",
...
...
ghc/compiler/types/TyCon.lhs
View file @
73c0472d
...
...
@@ -57,7 +57,7 @@ import {-# SOURCE #-} DataCon ( DataCon, isExistentialDataCon )
import Class ( Class, ClassContext )
import Var ( TyVar, Id )
import BasicTypes ( Arity,
NewOrData(..),
RecFlag(..), Boxity(..),
import BasicTypes ( Arity, RecFlag(..), Boxity(..),
isBoxed, EP(..) )
import Name ( Name, nameUnique, NamedThing(getName) )
import PrelNames ( Unique, Uniquable(..), anyBoxConKey )
...
...
ghc/compiler/types/TypeRep.lhs
View file @
73c0472d
...
...
@@ -28,7 +28,7 @@ import VarEnv
import VarSet
import Name ( Name, mkGlobalName, mkKindOccFS, tcName )
import OccName (
mkOccFS,
tcName )
import OccName ( tcName )
import TyCon ( TyCon, KindCon,
mkFunTyCon, mkKindCon, mkSuperKindCon,
)
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment