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

[project @ 2000-04-03 13:48:37 by sewardj]

Deal with MachWords, which recently have started appearing for unknown reasons.
parent 4a57b131
No related merge requests found
......@@ -29,14 +29,14 @@ import ClosureInfo ( infoTableLabelFromCI, entryLabelFromCI,
fastLabelFromCI, closureUpdReqd,
staticClosureNeedsLink
)
import Literal ( Literal(..) )
import Literal ( Literal(..), word2IntLit )
import Maybes ( maybeToBool )
import PrimOp ( primOpNeedsWrapper, PrimOp(..) )
import PrimRep ( isFloatingRep, PrimRep(..) )
import StixInfo ( genCodeInfoTable, genBitmapInfoTable )
import StixMacro ( macroCode, checkCode )
import StixPrim ( primCode, amodeToStix, amodeToStix' )
import Outputable ( pprPanic )
import Outputable ( pprPanic, ppr )
import UniqSupply ( returnUs, thenUs, mapUs, getUniqueUs, UniqSM )
import Util ( naturalMergeSortLe )
import Panic ( panic )
......@@ -449,14 +449,15 @@ be tuned.)
intTag :: Literal -> Integer
intTag (MachChar c) = toInteger (ord c)
intTag (MachInt i) = i
intTag _ = panic "intTag"
intTag (MachInt i) = i
intTag (MachWord w) = intTag (word2IntLit (MachWord w))
intTag _ = panic "intTag"
fltTag :: Literal -> Rational
fltTag (MachFloat f) = f
fltTag (MachFloat f) = f
fltTag (MachDouble d) = d
fltTag _ = panic "fltTag"
fltTag x = pprPanic "fltTag" (ppr x)
{-
mkSimpleSwitches
......@@ -493,9 +494,10 @@ be tuned.)
floating = isFloatingRep (getAmodeRep am)
choices = length alts
(x@(MachChar _),_) `leAlt` (y,_) = intTag x <= intTag y
(x@(MachInt _), _) `leAlt` (y,_) = intTag x <= intTag y
(x,_) `leAlt` (y,_) = fltTag x <= fltTag y
(x@(MachChar _),_) `leAlt` (y,_) = intTag x <= intTag y
(x@(MachInt _), _) `leAlt` (y,_) = intTag x <= intTag y
(x@(MachWord _), _) `leAlt` (y,_) = intTag x <= intTag y
(x,_) `leAlt` (y,_) = fltTag x <= fltTag y
\end{code}
......
......@@ -16,7 +16,7 @@ import AbsCSyn hiding ( spRel )
import AbsCUtils ( getAmodeRep, mixedTypeLocn )
import Constants ( uF_UPDATEE )
import SMRep ( fixedHdrSize )
import Literal ( Literal(..) )
import Literal ( Literal(..), word2IntLit )
import CallConv ( cCallConv )
import PrimOp ( PrimOp(..), CCall(..), CCallTarget(..) )
import PrimRep ( PrimRep(..), isFloatingRep )
......@@ -390,8 +390,9 @@ amodeToStix (CLit core)
MachChar c -> StInt (toInteger (ord c))
MachStr s -> StString s
MachAddr a -> StInt a
MachInt i -> StInt (toInteger i)
MachLitLit s _ -> {-trace (_UNPK_ s ++ "\n")-} (litLitToStix (_UNPK_ s))
MachInt i -> StInt i
MachWord w -> case word2IntLit core of MachInt iw -> StInt iw
MachLitLit s _ -> litLitToStix (_UNPK_ s)
MachFloat d -> StDouble d
MachDouble d -> StDouble d
_ -> panic "amodeToStix:core literal"
......
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