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
Alex D
GHC
Commits
a20c26e8
Commit
a20c26e8
authored
Mar 02, 1999
by
sof
Browse files
[project @ 1999-03-02 18:31:51 by sof]
import list adjustments
parent
b1b1d6cc
Changes
8
Hide whitespace changes
Inline
Side-by-side
ghc/compiler/hsSyn/HsImpExp.lhs
View file @
a20c26e8
...
...
@@ -8,7 +8,7 @@ module HsImpExp where
#include "HsVersions.h"
import
OccNam
e ( Module, pprModule, moduleIfaceFlavour, bootFlavour )
import
Modul
e ( Module, pprModule, moduleIfaceFlavour, bootFlavour )
import Outputable
import SrcLoc ( SrcLoc )
\end{code}
...
...
ghc/compiler/hsSyn/HsSyn.lhs
View file @
a20c26e8
...
...
@@ -45,7 +45,7 @@ import BasicTypes ( Fixity, Version, NewOrData )
import Outputable
import SrcLoc ( SrcLoc )
import Bag
import
OccNam
e ( Module, pprModule )
import
Modul
e ( Module, pprModule )
\end{code}
All we actually declare here is the top-level structure for a module.
...
...
ghc/compiler/parser/UgenUtil.lhs
View file @
a20c26e8
...
...
@@ -11,7 +11,7 @@ module UgenUtil (
#include "HsVersions.h"
import GlaExts
import
Name
import
Module ( Module, mkSrcModule )
import SrcLoc ( mkSrcLoc, noSrcLoc, SrcLoc )
import FastString ( FastString, mkFastCharString, mkFastCharString2 )
\end{code}
...
...
ghc/compiler/profiling/CostCentre.lhs
View file @
a20c26e8
...
...
@@ -29,8 +29,9 @@ module CostCentre (
import Var ( Id )
import Name ( UserFS, EncodedFS, encodeFS, decode,
Module,
getOccName, occNameFS
, pprModule, moduleUserString
getOccName, occNameFS
)
import Module ( Module, pprModule, moduleUserString )
import Outputable
import Util ( thenCmp )
\end{code}
...
...
ghc/compiler/profiling/SCCfinal.lhs
View file @
a20c26e8
...
...
@@ -33,7 +33,7 @@ import CmdLineOpts ( opt_AutoSccsOnIndividualCafs )
import CostCentre -- lots of things
import Const ( Con(..) )
import Id ( Id, mkSysLocal )
import
OccNam
e ( Module )
import
Modul
e ( Module )
import UniqSupply ( uniqFromSupply, splitUniqSupply, UniqSupply )
import Unique ( Unique )
import Util ( removeDups )
...
...
ghc/compiler/reader/Lex.lhs
View file @
a20c26e8
...
...
@@ -37,7 +37,7 @@ import List ( isSuffixOf )
import IdInfo ( InlinePragInfo(..) )
import Name ( isLowerISO, isUpperISO )
import
OccNam
e ( IfaceFlavour, hiFile, hiBootFile )
import
Modul
e ( IfaceFlavour, hiFile, hiBootFile )
import PrelMods ( mkTupNameStr, mkUbxTupNameStr )
import CmdLineOpts ( opt_IgnoreIfacePragmas, opt_HiVersion, opt_NoHiCheck )
import Demand ( Demand(..) {- instance Read -} )
...
...
@@ -60,7 +60,6 @@ import Word
#endif
import Addr
import PrelRead ( readRational__ ) -- Glasgow non-std
\end{code}
...
...
ghc/compiler/reader/ReadPrefix.lhs
View file @
a20c26e8
...
...
@@ -20,9 +20,10 @@ import PrefixToHs
import CallConv
import CmdLineOpts ( opt_NoImplicitPrelude, opt_GlasgowExts )
import OccName ( Module, mkSrcModuleFS, mkImportModuleFS,
hiFile, hiBootFile,
NameSpace, tcName, clsName, tcClsName, varName, dataName, tvName,
import Module ( Module, mkSrcModuleFS, mkImportModuleFS,
hiFile, hiBootFile
)
import OccName ( NameSpace, tcName, clsName, tcClsName, varName, dataName, tvName,
isLexCon
)
import RdrName ( RdrName, isRdrDataCon, mkSrcQual, mkSrcUnqual, mkPreludeQual,
...
...
ghc/compiler/simplCore/SimplCore.lhs
View file @
a20c26e8
...
...
@@ -39,8 +39,9 @@ import IdInfo ( InlinePragInfo(..), specInfo, setSpecInfo,
)
import VarEnv
import VarSet
import Module ( Module )
import Name ( mkLocalName, tidyOccName, tidyTopName, initTidyOccEnv, isExported,
Module,
NamedThing(..), OccName
NamedThing(..), OccName
)
import TyCon ( TyCon, isDataTyCon )
import PrimOp ( PrimOp(..) )
...
...
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