summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
authorsewardj <unknown>2000-01-25 20:08:33 +0000
committersewardj <unknown>2000-01-25 20:08:33 +0000
commitdb0b3140c96e2c0b7d1da074a35d3cb92a398953 (patch)
treed6301a818999cbca192c02f9d79757e5d7187006 /ghc/compiler
parent70d8d35f7636bd67d6bef0a73fafed7d09927da1 (diff)
downloadhaskell-db0b3140c96e2c0b7d1da074a35d3cb92a398953.tar.gz
[project @ 2000-01-25 20:08:33 by sewardj]
Print a useful panic msg if getRegister(x86) can't reduce a tree.
Diffstat (limited to 'ghc/compiler')
-rw-r--r--ghc/compiler/nativeGen/MachCode.lhs7
1 files changed, 5 insertions, 2 deletions
diff --git a/ghc/compiler/nativeGen/MachCode.lhs b/ghc/compiler/nativeGen/MachCode.lhs
index 599c132ba2..4df373d712 100644
--- a/ghc/compiler/nativeGen/MachCode.lhs
+++ b/ghc/compiler/nativeGen/MachCode.lhs
@@ -27,7 +27,7 @@ import PrimRep ( isFloatingRep, PrimRep(..) )
import PrimOp ( PrimOp(..) )
import CallConv ( cCallConv )
import Stix ( getUniqLabelNCG, StixTree(..),
- StixReg(..), CodeSegment(..)
+ StixReg(..), CodeSegment(..), pprStixTrees
)
import UniqSupply ( returnUs, thenUs, mapUs, mapAndUnzipUs,
mapAccumLUs, UniqSM
@@ -235,7 +235,7 @@ getRegister :: StixTree -> UniqSM Register
getRegister (StReg (StixMagicId stgreg))
= case (magicIdRegMaybe stgreg) of
Just reg -> returnUs (Fixed (magicIdPrimRep stgreg) reg id)
- -- cannae be Nothing
+ -- cannae be Nothing
getRegister (StReg (StixTemp u pk))
= returnUs (Fixed pk (UnmappedReg u pk) id)
@@ -889,6 +889,9 @@ getRegister leaf
code dst = mkSeqInstr (MOV L (OpImm imm__2) (OpReg dst))
in
returnUs (Any PtrRep code)
+ | otherwise
+ = pprPanic "getRegister(x86)" (pprStixTrees [leaf])
+
where
imm = maybeImm leaf
imm__2 = case imm of Just x -> x