summaryrefslogtreecommitdiff
path: root/ghc/compiler/ghci
diff options
context:
space:
mode:
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