summaryrefslogtreecommitdiff
path: root/ghc/compiler/main
diff options
context:
space:
mode:
authorsimonmar <unknown>2002-04-29 14:04:11 +0000
committersimonmar <unknown>2002-04-29 14:04:11 +0000
commitb085ee40c7f265a5977ea6ec1c415e573be5ff8c (patch)
treeab849b59a7eb6a57bc89559706cd71256b5898e4 /ghc/compiler/main
parentf6124b6ca2ec9820f7eb454dbcffbf4b8b790d4f (diff)
downloadhaskell-b085ee40c7f265a5977ea6ec1c415e573be5ff8c.tar.gz
[project @ 2002-04-29 14:03:38 by simonmar]
FastString cleanup, stage 1. The FastString type is no longer a mixture of hashed strings and literal strings, it contains hashed strings only with O(1) comparison (except for UnicodeStr, but that will also go away in due course). To create a literal instance of FastString, use FSLIT(".."). By far the most common use of the old literal version of FastString was in the pattern ptext SLIT("...") this combination still works, although it doesn't go via FastString any more. The next stage will be to remove the need to use this special combination at all, using a RULE. To convert a FastString into an SDoc, now use 'ftext' instead of 'ptext'. I've also removed all the FAST_STRING related macros from HsVersions.h except for SLIT and FSLIT, just use the relevant functions from FastString instead.
Diffstat (limited to 'ghc/compiler/main')
-rw-r--r--ghc/compiler/main/CmdLineOpts.lhs4
-rw-r--r--ghc/compiler/main/HscMain.lhs5
-rw-r--r--ghc/compiler/main/MkIface.lhs11
-rw-r--r--ghc/compiler/main/ParsePkgConf.y2
4 files changed, 12 insertions, 10 deletions
diff --git a/ghc/compiler/main/CmdLineOpts.lhs b/ghc/compiler/main/CmdLineOpts.lhs
index 94dd35464d..c93dc2f779 100644
--- a/ghc/compiler/main/CmdLineOpts.lhs
+++ b/ghc/compiler/main/CmdLineOpts.lhs
@@ -544,7 +544,7 @@ unpacked_opts :: [String]
unpacked_opts =
concat $
map (expandAts) $
- map _UNPK_ argv -- NOT ARGV any more: v_Static_hsc_opts
+ map unpackFS argv -- NOT ARGV any more: v_Static_hsc_opts
where
expandAts ('@':fname) = words (unsafePerformIO (readFile fname))
expandAts l = [l]
@@ -601,7 +601,7 @@ opt_MaxWorkerArgs = lookup_def_int "-fmax-worker-args" (10::Int)
The Prelude, for example is compiled with '-inpackage std'
-}
opt_InPackage = case lookup_str "-inpackage=" of
- Just p -> _PK_ p
+ Just p -> mkFastString p
Nothing -> FSLIT("Main") -- The package name if none is specified
opt_EmitCExternDecls = lookUp FSLIT("-femit-extern-decls")
diff --git a/ghc/compiler/main/HscMain.lhs b/ghc/compiler/main/HscMain.lhs
index 2b2ad0a903..fd99a5e10b 100644
--- a/ghc/compiler/main/HscMain.lhs
+++ b/ghc/compiler/main/HscMain.lhs
@@ -85,6 +85,7 @@ import OccName ( OccName )
import Name ( Name, nameModule, nameOccName, getName )
import NameEnv ( emptyNameEnv, mkNameEnv )
import Module ( Module )
+import FastString
import IOExts ( newIORef, readIORef, writeIORef,
unsafePerformIO )
@@ -321,7 +322,7 @@ hscRecomp ghci_mode dflags have_object
--
foreign_headers =
unlines
- . map (\fname -> "#include \"" ++ _UNPK_ fname ++ "\"")
+ . map (\fname -> "#include \"" ++ unpackFS fname ++ "\"")
. reverse
$ headers
@@ -486,7 +487,7 @@ myParseModule dflags src_filename
let exts = ExtFlags {glasgowExtsEF = dopt Opt_GlasgowExts dflags,
parrEF = dopt Opt_PArr dflags}
- loc = mkSrcLoc (_PK_ src_filename) 1
+ loc = mkSrcLoc (mkFastString src_filename) 1
case parseModule buf (mkPState loc exts) of {
diff --git a/ghc/compiler/main/MkIface.lhs b/ghc/compiler/main/MkIface.lhs
index 8fe9e6611d..f2b908e2c7 100644
--- a/ghc/compiler/main/MkIface.lhs
+++ b/ghc/compiler/main/MkIface.lhs
@@ -61,6 +61,7 @@ import Util ( sortLt, dropList )
import Binary ( getBinFileWithDict )
import BinIface ( writeBinIface )
import ErrUtils ( dumpIfSet_dyn )
+import FastString
import Monad ( when )
import Maybe ( catMaybes )
@@ -377,7 +378,7 @@ ifaceRule (id, Rule name act bndrs args rhs)
bogusIfaceRule :: (NamedThing a) => a -> RuleDecl Name pat
bogusIfaceRule id
- = IfaceRule SLIT("bogus") NeverActive [] (getName id) [] (UfVar (getName id)) noSrcLoc
+ = IfaceRule FSLIT("bogus") NeverActive [] (getName id) [] (UfVar (getName id)) noSrcLoc
\end{code}
@@ -554,7 +555,7 @@ dump_rules rs = vcat [ptext SLIT("{-# RULES"),
pprIface :: ModIface -> SDoc
pprIface iface
= vcat [ ptext SLIT("__interface")
- <+> doubleQuotes (ptext (mi_package iface))
+ <+> doubleQuotes (ftext (mi_package iface))
<+> ppr (mi_module iface) <+> ppr (vers_module version_info)
<+> pp_sub_vers
<+> (if mi_orphan iface then char '!' else empty)
@@ -671,11 +672,11 @@ pprRulesAndDeprecs rules deprecs
pp_deprecs deprecs = ptext SLIT("__D") <+> guts
where
guts = case deprecs of
- DeprecAll txt -> doubleQuotes (ptext txt)
+ DeprecAll txt -> doubleQuotes (ftext txt)
DeprecSome env -> ppr_deprec_env env
-ppr_deprec_env :: NameEnv (Name, FAST_STRING) -> SDoc
+ppr_deprec_env :: NameEnv (Name, FastString) -> SDoc
ppr_deprec_env env = vcat (punctuate semi (map pp_deprec (nameEnvElts env)))
where
- pp_deprec (name, txt) = pprOcc name <+> doubleQuotes (ptext txt)
+ pp_deprec (name, txt) = pprOcc name <+> doubleQuotes (ftext txt)
\end{code}
diff --git a/ghc/compiler/main/ParsePkgConf.y b/ghc/compiler/main/ParsePkgConf.y
index f710b150dd..995d3009be 100644
--- a/ghc/compiler/main/ParsePkgConf.y
+++ b/ghc/compiler/main/ParsePkgConf.y
@@ -81,7 +81,7 @@ happyError buf PState{ loc = loc } = PFailed (srcParseErr buf loc)
loadPackageConfig :: FilePath -> IO [PackageConfig]
loadPackageConfig conf_filename = do
buf <- hGetStringBuffer conf_filename
- let loc = mkSrcLoc (_PK_ conf_filename) 1
+ let loc = mkSrcLoc (mkFastString conf_filename) 1
exts = ExtFlags {glasgowExtsEF = False,
parrEF = False}
case parse buf (mkPState loc exts) of