Skip to content
Snippets Groups Projects
Commit db0b3140 authored by Julian Seward's avatar Julian Seward
Browse files

[project @ 2000-01-25 20:08:33 by sewardj]

Print a useful panic msg if getRegister(x86) can't reduce a tree.
parent 70d8d35f
No related merge requests found
......@@ -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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment