Remove some ifdefs in favour of Haskell tests
[ghc-hetmet.git] / compiler / ghci / ByteCodeAsm.lhs
index 0fa7c62..2c7473b 100644 (file)
@@ -6,6 +6,7 @@ ByteCodeLink: Bytecode assembler and linker
 
 \begin{code}
 {-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
+{-# LANGUAGE BangPatterns #-}
 
 module ByteCodeAsm (
         assembleBCOs, assembleBCO,
@@ -30,6 +31,7 @@ import Constants
 import FastString
 import SMRep
 import Outputable
+import Config
 
 import Control.Monad    ( foldM )
 import Control.Monad.ST ( runST )
@@ -43,6 +45,7 @@ import Data.Char        ( ord )
 import Data.List
 import Data.Map (Map)
 import qualified Data.Map as Map
+import Distribution.System
 
 import GHC.Base         ( ByteArray#, MutableByteArray#, RealWorld )
 
@@ -309,8 +312,8 @@ mkBits findLabel st proto_insns
                ENTER              -> instr1 st bci_ENTER
                RETURN             -> instr1 st bci_RETURN
                RETURN_UBX rep     -> instr1 st (return_ubx rep)
-               CCALL off m_addr   -> do (np, st2) <- addr st m_addr
-                                        instr3 st2 bci_CCALL off np
+               CCALL off m_addr int -> do (np, st2) <- addr st m_addr
+                                          instr4 st2 bci_CCALL off np int
                BRK_FUN array index info -> do
                   (p1, st2) <- ptr st  (BCOPtrArray array)
                   (p2, st3) <- ptr st2 (BCOPtrBreakInfo info)
@@ -394,12 +397,11 @@ mkBits findLabel st proto_insns
           = do st_l1 <- addToSS st_l0 (BCONPtrItbl (getName dcon))
                return (sizeSS16 st_l0, (st_i0,st_l1,st_p0))
 
-#ifdef mingw32_TARGET_OS
        literal st (MachLabel fs (Just sz) _)
+        | cTargetOS == Windows
             = litlabel st (appendFS fs (mkFastString ('@':show sz)))
         -- On Windows, stdcall labels have a suffix indicating the no. of
         -- arg words, e.g. foo@8.  testcase: ffi012(ghci)
-#endif
        literal st (MachLabel fs _ _) = litlabel st fs
        literal st (MachWord w)     = int st (fromIntegral w)
        literal st (MachInt j)      = int st (fromIntegral j)
@@ -478,7 +480,7 @@ instrSize16s instr
         ENTER{}                 -> 1
         RETURN{}                -> 1
         RETURN_UBX{}            -> 1
-        CCALL{}                 -> 3
+        CCALL{}                 -> 4
         SWIZZLE{}               -> 3
         BRK_FUN{}               -> 4