diff options
Diffstat (limited to 'ghc/compiler/nativeGen')
-rw-r--r-- | ghc/compiler/nativeGen/AbsCStixGen.lhs | 6 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/AsmCodeGen.lhs | 10 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/AsmRegAlloc.lhs | 3 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/MachCode.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/MachMisc.lhs | 6 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/MachRegs.lhs | 19 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/PprMach.lhs | 5 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/RegAllocInfo.lhs | 3 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/Stix.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/StixInfo.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/StixInteger.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/StixMacro.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/nativeGen/StixPrim.lhs | 8 |
13 files changed, 44 insertions, 30 deletions
diff --git a/ghc/compiler/nativeGen/AbsCStixGen.lhs b/ghc/compiler/nativeGen/AbsCStixGen.lhs index 90863433d3..830e450dfc 100644 --- a/ghc/compiler/nativeGen/AbsCStixGen.lhs +++ b/ghc/compiler/nativeGen/AbsCStixGen.lhs @@ -7,7 +7,7 @@ module AbsCStixGen ( genCodeAbstractC ) where -import Ubiq{-uitous-} +IMP_Ubiq(){-uitous-} import AbsCSyn import Stix @@ -33,6 +33,10 @@ import StixMacro ( macroCode ) import StixPrim ( primCode, amodeToStix, amodeToStix' ) import UniqSupply ( returnUs, thenUs, mapUs, getUnique, UniqSM(..) ) import Util ( naturalMergeSortLe, panic ) + +#ifdef REALLY_HASKELL_1_3 +ord = fromEnum :: Char -> Int +#endif \end{code} For each independent chunk of AbstractC code, we generate a list of diff --git a/ghc/compiler/nativeGen/AsmCodeGen.lhs b/ghc/compiler/nativeGen/AsmCodeGen.lhs index ac259c4fea..090e13fc68 100644 --- a/ghc/compiler/nativeGen/AsmCodeGen.lhs +++ b/ghc/compiler/nativeGen/AsmCodeGen.lhs @@ -7,7 +7,7 @@ module AsmCodeGen ( writeRealAsm, dumpRealAsm ) where -import Ubiq{-uitous-} +IMP_Ubiq(){-uitous-} import MachMisc import MachRegs @@ -23,7 +23,7 @@ import PrimRep ( PrimRep{-instance Eq-} ) import RegAllocInfo ( mkMRegsState, MRegsState ) import Stix ( StixTree(..), StixReg(..), CodeSegment ) import UniqSupply ( returnUs, thenUs, mapUs, UniqSM(..) ) -import Unpretty ( uppAppendFile, uppShow, uppAboves, Unpretty(..) ) +import Unpretty ( uppPutStr, uppShow, uppAboves, Unpretty(..) ) \end{code} The 96/03 native-code generator has machine-independent and @@ -73,10 +73,10 @@ The machine-dependent bits break down as follows: So, here we go: \begin{code} -writeRealAsm :: _FILE -> AbstractC -> UniqSupply -> IO () +writeRealAsm :: Handle -> AbstractC -> UniqSupply -> IO () -writeRealAsm file absC us - = uppAppendFile file 80 (runNCG absC us) +writeRealAsm handle absC us + = uppPutStr handle 80 (runNCG absC us) dumpRealAsm :: AbstractC -> UniqSupply -> String diff --git a/ghc/compiler/nativeGen/AsmRegAlloc.lhs b/ghc/compiler/nativeGen/AsmRegAlloc.lhs index 6f8df0b713..00d5d79e56 100644 --- a/ghc/compiler/nativeGen/AsmRegAlloc.lhs +++ b/ghc/compiler/nativeGen/AsmRegAlloc.lhs @@ -8,13 +8,14 @@ module AsmRegAlloc ( runRegAllocate, runHairyRegAllocate ) where -import Ubiq{-uitous-} +IMP_Ubiq(){-uitous-} import MachCode ( InstrList(..) ) import MachMisc ( Instr ) import MachRegs import RegAllocInfo +import AbsCSyn ( MagicId ) import BitSet ( BitSet ) import FiniteMap ( emptyFM, addListToFM, delListFromFM, lookupFM, keysFM ) import Maybes ( maybeToBool ) diff --git a/ghc/compiler/nativeGen/MachCode.lhs b/ghc/compiler/nativeGen/MachCode.lhs index 25d9be3f15..c9b671ebd6 100644 --- a/ghc/compiler/nativeGen/MachCode.lhs +++ b/ghc/compiler/nativeGen/MachCode.lhs @@ -14,7 +14,7 @@ structure should not be too overwhelming. module MachCode ( stmt2Instrs, asmVoid, InstrList(..) ) where -import Ubiq{-uitious-} +IMP_Ubiq(){-uitious-} import MachMisc -- may differ per-platform import MachRegs diff --git a/ghc/compiler/nativeGen/MachMisc.lhs b/ghc/compiler/nativeGen/MachMisc.lhs index 237b3343f1..54f761601d 100644 --- a/ghc/compiler/nativeGen/MachMisc.lhs +++ b/ghc/compiler/nativeGen/MachMisc.lhs @@ -41,9 +41,9 @@ module MachMisc ( #endif ) where -import Ubiq{-uitous-} -import AbsCLoop ( fixedHdrSizeInWords, varHdrSizeInWords ) -- paranoia -import NcgLoop ( underscorePrefix, fmtAsmLbl ) -- paranoia +IMP_Ubiq(){-uitous-} +IMPORT_DELOOPER(AbsCLoop) ( fixedHdrSizeInWords, varHdrSizeInWords ) -- paranoia +IMPORT_DELOOPER(NcgLoop) ( underscorePrefix, fmtAsmLbl ) -- paranoia import AbsCSyn ( MagicId(..) ) import AbsCUtils ( magicIdPrimRep ) diff --git a/ghc/compiler/nativeGen/MachRegs.lhs b/ghc/compiler/nativeGen/MachRegs.lhs index 32159f1dc9..7493de4e9f 100644 --- a/ghc/compiler/nativeGen/MachRegs.lhs +++ b/ghc/compiler/nativeGen/MachRegs.lhs @@ -59,7 +59,7 @@ module MachRegs ( #endif ) where -import Ubiq{-uitous-} +IMP_Ubiq(){-uitous-} import AbsCSyn ( MagicId(..) ) import AbsCUtils ( magicIdPrimRep ) @@ -331,16 +331,19 @@ cmp_i a1 a2 = if a1 == a2 then EQ_ else if a1 < a2 then LT_ else GT_ cmp_ihash :: FAST_INT -> FAST_INT -> TAG_ cmp_ihash a1 a2 = if a1 _EQ_ a2 then EQ_ else if a1 _LT_ a2 then LT_ else GT_ +instance Ord3 Reg where + cmp = cmpReg + instance Eq Reg where - a == b = case cmpReg a b of { EQ_ -> True; _ -> False } - a /= b = case cmpReg a b of { EQ_ -> False; _ -> True } + a == b = case (a `cmp` b) of { EQ_ -> True; _ -> False } + a /= b = case (a `cmp` b) of { EQ_ -> False; _ -> True } instance Ord Reg where - a <= b = case cmpReg a b of { LT_ -> True; EQ_ -> True; GT__ -> False } - a < b = case cmpReg a b of { LT_ -> True; EQ_ -> False; GT__ -> False } - a >= b = case cmpReg a b of { LT_ -> False; EQ_ -> True; GT__ -> True } - a > b = case cmpReg a b of { LT_ -> False; EQ_ -> False; GT__ -> True } - _tagCmp a b = case cmpReg a b of { LT_ -> _LT; EQ_ -> _EQ; GT__ -> _GT } + a <= b = case (a `cmp` b) of { LT_ -> True; EQ_ -> True; GT__ -> False } + a < b = case (a `cmp` b) of { LT_ -> True; EQ_ -> False; GT__ -> False } + a >= b = case (a `cmp` b) of { LT_ -> False; EQ_ -> True; GT__ -> True } + a > b = case (a `cmp` b) of { LT_ -> False; EQ_ -> False; GT__ -> True } + _tagCmp a b = case (a `cmp` b) of { LT_ -> _LT; EQ_ -> _EQ; GT__ -> _GT } instance Uniquable Reg where uniqueOf (UnmappedReg u _) = u diff --git a/ghc/compiler/nativeGen/PprMach.lhs b/ghc/compiler/nativeGen/PprMach.lhs index 65a5edc092..3d4d67954d 100644 --- a/ghc/compiler/nativeGen/PprMach.lhs +++ b/ghc/compiler/nativeGen/PprMach.lhs @@ -13,11 +13,12 @@ We start with the @pprXXX@s with some cross-platform commonality module PprMach ( pprInstr ) where -import Ubiq{-uitious-} +IMP_Ubiq(){-uitious-} import MachRegs -- may differ per-platform import MachMisc +import AbsCSyn ( MagicId ) import CLabel ( pprCLabel_asm, externallyVisibleCLabel ) import CStrings ( charToC ) import Maybes ( maybeToBool ) @@ -214,8 +215,8 @@ pprSize x = uppPStr (case x of #endif #if sparc_TARGET_ARCH B -> SLIT("sb") + BU -> SLIT("ub") -- HW -> SLIT("hw") UNUSED --- BU -> SLIT("ub") UNUSED -- HWU -> SLIT("uhw") UNUSED W -> SLIT("") F -> SLIT("") diff --git a/ghc/compiler/nativeGen/RegAllocInfo.lhs b/ghc/compiler/nativeGen/RegAllocInfo.lhs index 93cda5c3a1..e650837176 100644 --- a/ghc/compiler/nativeGen/RegAllocInfo.lhs +++ b/ghc/compiler/nativeGen/RegAllocInfo.lhs @@ -51,12 +51,13 @@ module RegAllocInfo ( freeRegSet ) where -import Ubiq{-uitous-} +IMP_Ubiq(){-uitous-} import MachMisc import MachRegs import MachCode ( InstrList(..) ) +import AbsCSyn ( MagicId ) import BitSet ( unitBS, mkBS, minusBS, unionBS, listBS, BitSet ) import CLabel ( pprCLabel_asm, CLabel{-instance Ord-} ) import FiniteMap ( addToFM, lookupFM ) diff --git a/ghc/compiler/nativeGen/Stix.lhs b/ghc/compiler/nativeGen/Stix.lhs index f187e9fe1d..2dd8169c55 100644 --- a/ghc/compiler/nativeGen/Stix.lhs +++ b/ghc/compiler/nativeGen/Stix.lhs @@ -15,7 +15,7 @@ module Stix ( getUniqLabelNCG ) where -import Ubiq{-uitous-} +IMP_Ubiq(){-uitous-} import AbsCSyn ( node, infoptr, MagicId(..) ) import AbsCUtils ( magicIdPrimRep ) diff --git a/ghc/compiler/nativeGen/StixInfo.lhs b/ghc/compiler/nativeGen/StixInfo.lhs index 82b88c6760..9afcec5480 100644 --- a/ghc/compiler/nativeGen/StixInfo.lhs +++ b/ghc/compiler/nativeGen/StixInfo.lhs @@ -7,7 +7,7 @@ module StixInfo ( genCodeInfoTable ) where -import Ubiq{-uitious-} +IMP_Ubiq(){-uitious-} import AbsCSyn ( AbstractC(..), CAddrMode, ReturnInfo, RegRelative, MagicId, CStmtMacro diff --git a/ghc/compiler/nativeGen/StixInteger.lhs b/ghc/compiler/nativeGen/StixInteger.lhs index fe9ec744e8..5c90139f2c 100644 --- a/ghc/compiler/nativeGen/StixInteger.lhs +++ b/ghc/compiler/nativeGen/StixInteger.lhs @@ -11,8 +11,8 @@ module StixInteger ( encodeFloatingKind, decodeFloatingKind ) where -import Ubiq{-uitous-} -import NcgLoop ( amodeToStix ) +IMP_Ubiq(){-uitous-} +IMPORT_DELOOPER(NcgLoop) ( amodeToStix ) import MachMisc import MachRegs diff --git a/ghc/compiler/nativeGen/StixMacro.lhs b/ghc/compiler/nativeGen/StixMacro.lhs index 4e7b47f8a0..62c5f9762a 100644 --- a/ghc/compiler/nativeGen/StixMacro.lhs +++ b/ghc/compiler/nativeGen/StixMacro.lhs @@ -7,8 +7,8 @@ module StixMacro ( macroCode, heapCheck ) where -import Ubiq{-uitious-} -import NcgLoop ( amodeToStix ) +IMP_Ubiq(){-uitious-} +IMPORT_DELOOPER(NcgLoop) ( amodeToStix ) import MachMisc import MachRegs diff --git a/ghc/compiler/nativeGen/StixPrim.lhs b/ghc/compiler/nativeGen/StixPrim.lhs index 01b0404176..c986b3117b 100644 --- a/ghc/compiler/nativeGen/StixPrim.lhs +++ b/ghc/compiler/nativeGen/StixPrim.lhs @@ -7,8 +7,8 @@ module StixPrim ( primCode, amodeToStix, amodeToStix' ) where -import Ubiq{-uitous-} -import NcgLoop -- paranoia checking only +IMP_Ubiq(){-uitous-} +IMPORT_DELOOPER(NcgLoop) -- paranoia checking only import MachMisc import MachRegs @@ -32,6 +32,10 @@ import StixInteger {- everything -} import UniqSupply ( returnUs, thenUs, UniqSM(..) ) import Unpretty ( uppBeside, uppPStr, uppInt ) import Util ( panic ) + +#ifdef REALLY_HASKELL_1_3 +ord = fromEnum :: Char -> Int +#endif \end{code} The main honcho here is primCode, which handles the guts of COpStmts. |