summaryrefslogtreecommitdiff
path: root/ghc/compiler/ghci
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/ghci
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/ghci')
-rw-r--r--ghc/compiler/ghci/ByteCodeGen.lhs2
-rw-r--r--ghc/compiler/ghci/ByteCodeLink.lhs12
2 files changed, 7 insertions, 7 deletions
diff --git a/ghc/compiler/ghci/ByteCodeGen.lhs b/ghc/compiler/ghci/ByteCodeGen.lhs
index eeb1580ae6..56f64fcc3d 100644
--- a/ghc/compiler/ghci/ByteCodeGen.lhs
+++ b/ghc/compiler/ghci/ByteCodeGen.lhs
@@ -883,7 +883,7 @@ generateCCall d0 s p ccall_spec@(CCallSpec target cconv safety) fn args_r_to_l
DynamicTarget
-> returnBc (False, panic "ByteCodeGen.generateCCall(dyn)")
StaticTarget target
- -> let sym_to_find = _UNPK_ target in
+ -> let sym_to_find = unpackFS target in
ioToBc (lookupSymbol sym_to_find) `thenBc` \res ->
case res of
Just aa -> returnBc (True, aa)
diff --git a/ghc/compiler/ghci/ByteCodeLink.lhs b/ghc/compiler/ghci/ByteCodeLink.lhs
index 6c0ed01cda..04e84339f8 100644
--- a/ghc/compiler/ghci/ByteCodeLink.lhs
+++ b/ghc/compiler/ghci/ByteCodeLink.lhs
@@ -123,7 +123,7 @@ linkSomeBCOs toplevs_only ie ce_in ul_bcos
data UnlinkedBCO
= UnlinkedBCO Name
(SizedSeq Word16) -- insns
- (SizedSeq (Either Word FAST_STRING)) -- literals
+ (SizedSeq (Either Word FastString)) -- literals
-- Either literal words or a pointer to a asciiz
-- string, denoting a label whose *address* should
-- be determined at link time
@@ -195,7 +195,7 @@ assembleBCO (ProtoBCO nm instrs origin malloced)
in
do -- pass 2: generate the instruction, ptr and nonptr bits
insns <- return emptySS :: IO (SizedSeq Word16)
- lits <- return emptySS :: IO (SizedSeq (Either Word FAST_STRING))
+ lits <- return emptySS :: IO (SizedSeq (Either Word FastString))
ptrs <- return emptySS :: IO (SizedSeq (Either Name PrimOp))
itbls <- return emptySS :: IO (SizedSeq Name)
let init_asm_state = (insns,lits,ptrs,itbls)
@@ -216,7 +216,7 @@ assembleBCO (ProtoBCO nm instrs origin malloced)
-- instrs nonptrs ptrs itbls
type AsmState = (SizedSeq Word16,
- SizedSeq (Either Word FAST_STRING),
+ SizedSeq (Either Word FastString),
SizedSeq (Either Name PrimOp),
SizedSeq Name)
@@ -578,10 +578,10 @@ newBCO a b c d
= IO (\s -> case newBCO# a b c d s of (# s1, bco #) -> (# s1, BCO bco #))
-lookupLiteral :: Either Word FAST_STRING -> IO Word
+lookupLiteral :: Either Word FastString -> IO Word
lookupLiteral (Left w) = return w
lookupLiteral (Right addr_of_label_string)
- = do let label_to_find = _UNPK_ addr_of_label_string
+ = do let label_to_find = unpackFS addr_of_label_string
m <- lookupSymbol label_to_find
case m of
-- Can't be bothered to find the official way to convert Addr# to Word#;
@@ -649,7 +649,7 @@ linkFail who what
-- HACKS!!! ToDo: cleaner
nameToCLabel :: Name -> String{-suffix-} -> String
nameToCLabel n suffix
- = _UNPK_(moduleNameFS (rdrNameModule rn))
+ = unpackFS(moduleNameFS (rdrNameModule rn))
++ '_':occNameString(rdrNameOcc rn) ++ '_':suffix
where rn = toRdrName n