[project @ 2002-03-02 18:02:30 by sof]
[ghc-hetmet.git] / ghc / compiler / absCSyn / PprAbsC.lhs
index fd7daf8..dc072cc 100644 (file)
@@ -26,8 +26,8 @@ import AbsCUtils      ( getAmodeRep, nonemptyAbsC,
                          mixedPtrLocn, mixedTypeLocn
                        )
 
-import Constants       ( mIN_UPD_SIZE )
-import ForeignCall     ( CCallSpec(..), CCallTarget(..), playSafe, ccallConvAttribute )
+import ForeignCall     ( CCallSpec(..), CCallTarget(..), playSafe,
+                         playThreadSafe, ccallConvAttribute )
 import CLabel          ( externallyVisibleCLabel,
                          needsCDecl, pprCLabel,
                          mkReturnInfoLabel, mkReturnPtLabel, mkClosureTblLabel,
@@ -59,8 +59,7 @@ import StgSyn         ( StgOp(..) )
 import BitSet          ( BitSet, intBS )
 import Outputable
 import GlaExts
-import Util            ( nOfThem, lengthExceeds, listLengthCmp )
-import Maybe           ( isNothing, maybeToList )
+import Util            ( lengthExceeds, listLengthCmp )
 
 import ST
 
@@ -254,32 +253,7 @@ pprAbsC stmt@(COpStmt results (StgPrimOp op) args vol_regs) _
 
 -- NEW CASES FOR EXPANDED PRIMOPS
 
--- We have to deal with some of these specially
-pprAbsC (CMachOpStmt (Just res) (MO_ReadOSBI offw scaleRep)
-                     [baseAmode, indexAmode] maybe_vols) 
-        _
-  | isNothing maybe_vols
-  = hcat [ -- text " /* ReadOSBI */ ",
-           ppr_amode res, equals, 
-           ppr_array_expression offw scaleRep baseAmode indexAmode, 
-           semi ]
-  | otherwise
-  = panic "pprAbsC:MO_ReadOSBI -- out-of-line array indexing ?!?!"
-
-pprAbsC (CMachOpStmt Nothing (MO_WriteOSBI offw scaleRep)
-                     [baseAmode, indexAmode, vAmode] maybe_vols)
-        _
-  | isNothing maybe_vols
-  = hcat [ -- text " /* WriteOSBI */ ",
-           ppr_array_expression offw scaleRep baseAmode indexAmode, 
-           equals, pprAmode vAmode,
-           semi ]
-  | otherwise
-  = panic "pprAbsC:MO_WriteOSBI -- out-of-line array indexing ?!?!"
-
--- The rest generically.
-
-pprAbsC stmt@(CMachOpStmt (Just res) mop [arg1,arg2] maybe_vols) _
+pprAbsC stmt@(CMachOpStmt res mop [arg1,arg2] maybe_vols) _
   = let prefix_fn = mop `elem` [MO_Dbl_Pwr, MO_Flt_Pwr, MO_NatS_MulMayOflo]
     in
     case ppr_maybe_vol_regs maybe_vols of {(saves,restores) ->
@@ -294,7 +268,7 @@ pprAbsC stmt@(CMachOpStmt (Just res) mop [arg1,arg2] maybe_vols) _
     $$ restores
     }
 
-pprAbsC stmt@(CMachOpStmt (Just res) mop [arg1] maybe_vols) _
+pprAbsC stmt@(CMachOpStmt res mop [arg1] maybe_vols) _
   = case ppr_maybe_vol_regs maybe_vols of {(saves,restores) ->
     saves $$
     hcat [ppr_amode res, equals, 
@@ -442,8 +416,9 @@ pprAbsC (CInitHdr cl_info amode cost_centre size) _
                pp_paren_semi ]
   where
     info_lbl   = infoTableLabelFromCI cl_info
-  
-pprAbsC stmt@(CStaticClosure closure_lbl cl_info cost_centre amodes) _
+
+
+pprAbsC stmt@(CStaticClosure cl_info cost_centre amodes) _
   = case (pprTempAndExternDecls stmt) of { (_, pp_exts) ->
     vcat [
        pp_exts,
@@ -456,11 +431,12 @@ pprAbsC stmt@(CStaticClosure closure_lbl cl_info cost_centre amodes) _
                ppLocalnessMacro True{-include dyn-} info_lbl,
                char ')'
                ],
-       nest 2 (ppr_payload (amodes ++ padding_wds ++ static_link_field)),
+       nest 2 (ppr_payload amodes),
        ptext SLIT("};") ]
     }
   where
-    info_lbl = infoTableLabelFromCI cl_info
+    closure_lbl = closureLabelFromCI cl_info
+    info_lbl    = infoTableLabelFromCI cl_info
 
     ppr_payload [] = empty
     ppr_payload ls = comma <+> 
@@ -475,18 +451,6 @@ pprAbsC stmt@(CStaticClosure closure_lbl cl_info cost_centre amodes) _
       where 
        rep = getAmodeRep item
 
-    upd_reqd = closureUpdReqd cl_info
-
-    padding_wds
-       | not upd_reqd = []
-       | otherwise    = case max 0 (mIN_UPD_SIZE - length amodes) of { still_needed ->
-                        nOfThem still_needed (mkIntCLit 0) } -- a bunch of 0s
-
-       -- always have a static link field, it's used to save the closure's
-       -- info pointer when we're reverting CAFs (see comment in Storage.c)
-    static_link_field
-       | upd_reqd || staticClosureNeedsLink cl_info = [mkIntCLit 0]
-       | otherwise                                  = []
 
 pprAbsC stmt@(CClosureInfoAndCode cl_info slow maybe_fast cl_descr) _
   = vcat [
@@ -762,23 +726,8 @@ pprMachOp_for_C MO_8U_to_NatU    = text "(StgWord8)(StgWord)"
 pprMachOp_for_C MO_16U_to_NatU   = text "(StgWord16)(StgWord)"
 pprMachOp_for_C MO_32U_to_NatU   = text "(StgWord32)(StgWord)"
 
-pprMachOp_for_C (MO_ReadOSBI _ _)  = panic "pprMachOp_for_C:MO_ReadOSBI"
-pprMachOp_for_C (MO_WriteOSBI _ _) = panic "pprMachOp_for_C:MO_WriteOSBI"
-
-
--- Helper for printing array expressions.
-ppr_array_expression offw scaleRep baseAmode indexAmode
-   -- create:
-   -- * (scaleRep*) (
-   --      ((char*)baseAmode) + offw*bytes_per_word + indexAmode*bytes_per_scaleRep
-   --   )
-   = let offb  = parens (int offw <> char '*' <> text "sizeof(void*)")
-         indb  = parens (parens (pprAmode indexAmode) 
-                         <> char '*' <> int (getPrimRepArrayElemSize scaleRep))
-         baseb = text "(char*)" <> parens (pprAmode baseAmode)
-         addr  = parens baseb <+> char '+' <+> offb <+> char '+' <+> indb
-     in
-         char '*' <> parens (ppr scaleRep <> char '*') <> parens addr
+pprMachOp_for_C MO_8U_to_32U     = text "(StgWord32)"
+pprMachOp_for_C MO_32U_to_8U     = text "(StgWord8)"
 
 
 ppLocalness lbl
@@ -989,9 +938,14 @@ pprFCall call@(CCall (CCallSpec target cconv safety)) uniq args results vol_regs
     ]
   where
     (pp_saves, pp_restores) = ppr_vol_regs vol_regs
+
+    thread_macro_args = ppr_uniq_token <> comma <+> 
+                       text "rts" <> ppr (playThreadSafe safety)
+    ppr_uniq_token = text "tok_" <> ppr uniq
     (pp_save_context, pp_restore_context)
-       | playSafe safety = ( text "{ I_ id; SUSPEND_THREAD(id);"
-                           , text "RESUME_THREAD(id);}"
+       | playSafe safety = ( text "{ I_" <+> ppr_uniq_token <> 
+                               text "; SUSPEND_THREAD" <> parens thread_macro_args <> semi
+                           , text "RESUME_THREAD" <> parens thread_macro_args <> text ";}"
                            )
        | otherwise = ( pp_basic_saves $$ pp_saves,
                        pp_basic_restores $$ pp_restores)
@@ -1184,15 +1138,15 @@ Special treatment for floats and doubles, to avoid unwanted conversions.
 
 \begin{code}
 pprAssign FloatRep dest@(CVal reg_rel _) src
-  = hcat [ ptext SLIT("ASSIGN_FLT"),char '(', ppr_amode (CAddr reg_rel), comma, pprAmode src, pp_paren_semi ]
+  = hcat [ ptext SLIT("ASSIGN_FLT((W_*)"), parens (ppr_amode (CAddr reg_rel)), comma, pprAmode src, pp_paren_semi ]
 
 pprAssign DoubleRep dest@(CVal reg_rel _) src
-  = hcat [ ptext SLIT("ASSIGN_DBL"),char '(', ppr_amode (CAddr reg_rel), comma, pprAmode src, pp_paren_semi ]
+  = hcat [ ptext SLIT("ASSIGN_DBL((W_*)"), parens (ppr_amode (CAddr reg_rel)), comma, pprAmode src, pp_paren_semi ]
 
 pprAssign Int64Rep dest@(CVal reg_rel _) src
-  = hcat [ ptext SLIT("ASSIGN_Int64"),char '(', ppr_amode (CAddr reg_rel), comma, pprAmode src, pp_paren_semi ]
+  = hcat [ ptext SLIT("ASSIGN_Int64((W_*)"), parens (ppr_amode (CAddr reg_rel)), comma, pprAmode src, pp_paren_semi ]
 pprAssign Word64Rep dest@(CVal reg_rel _) src
-  = hcat [ ptext SLIT("ASSIGN_Word64"),char '(', ppr_amode (CAddr reg_rel), comma, pprAmode src, pp_paren_semi ]
+  = hcat [ ptext SLIT("ASSIGN_Word64((W_*)"), parens (ppr_amode (CAddr reg_rel)), comma, pprAmode src, pp_paren_semi ]
 \end{code}
 
 Lastly, the question is: will the C compiler think the types of the
@@ -1261,13 +1215,13 @@ question.)
 
 \begin{code}
 pprAmode (CVal reg_rel FloatRep)
-  = hcat [ text "PK_FLT(", ppr_amode (CAddr reg_rel), rparen ]
+  = hcat [ text "PK_FLT((W_*)", parens (ppr_amode (CAddr reg_rel)), rparen ]
 pprAmode (CVal reg_rel DoubleRep)
-  = hcat [ text "PK_DBL(", ppr_amode (CAddr reg_rel), rparen ]
+  = hcat [ text "PK_DBL((W_*)", parens (ppr_amode (CAddr reg_rel)), rparen ]
 pprAmode (CVal reg_rel Int64Rep)
-  = hcat [ text "PK_Int64(", ppr_amode (CAddr reg_rel), rparen ]
+  = hcat [ text "PK_Int64((W_*)", parens (ppr_amode (CAddr reg_rel)), rparen ]
 pprAmode (CVal reg_rel Word64Rep)
-  = hcat [ text "PK_Word64(", ppr_amode (CAddr reg_rel), rparen ]
+  = hcat [ text "PK_Word64((W_*)", parens (ppr_amode (CAddr reg_rel)), rparen ]
 \end{code}
 
 Next comes the case where there is some other cast need, and the
@@ -1300,10 +1254,6 @@ amode has kind2.
 ppr_amode CBytesPerWord
   = text "(sizeof(void*))"
 
-ppr_amode (CMem rep addr)
-  = let txt_rep = pprPrimKind rep
-    in  hcat [ char '*', parens (txt_rep <> char '*'), parens (ppr_amode addr) ]
-
 ppr_amode (CVal reg_rel@(CIndex _ _ _) kind)
   = case (pprRegRelative False{-no sign wanted-} reg_rel) of
        (pp_reg, Nothing)     -> panic "ppr_amode: CIndex"
@@ -1362,6 +1312,7 @@ cStmtMacroText PUSH_UPD_FRAME             = SLIT("PUSH_UPD_FRAME")
 cStmtMacroText PUSH_SEQ_FRAME          = SLIT("PUSH_SEQ_FRAME")
 cStmtMacroText UPDATE_SU_FROM_UPD_FRAME        = SLIT("UPDATE_SU_FROM_UPD_FRAME")
 cStmtMacroText SET_TAG                 = SLIT("SET_TAG")
+cStmtMacroText DATA_TO_TAGZH            = SLIT("dataToTagzh")
 cStmtMacroText REGISTER_FOREIGN_EXPORT = SLIT("REGISTER_FOREIGN_EXPORT")
 cStmtMacroText REGISTER_IMPORT         = SLIT("REGISTER_IMPORT")
 cStmtMacroText REGISTER_DIMPORT                = SLIT("REGISTER_DIMPORT")
@@ -1707,7 +1658,7 @@ ppr_decls_AbsC (CInitHdr cl_info reg_rel cost_centre _)
   where
     info_lbl = infoTableLabelFromCI cl_info
 
-ppr_decls_AbsC (CMachOpStmt res        _ args _) = ppr_decls_Amodes (maybeToList res ++ args)
+ppr_decls_AbsC (CMachOpStmt res        _ args _) = ppr_decls_Amodes (res : args)
 ppr_decls_AbsC (COpStmt        results _ args _) = ppr_decls_Amodes (results ++ args)
 
 ppr_decls_AbsC (CSimultaneous abc)       = ppr_decls_AbsC abc
@@ -1729,7 +1680,7 @@ ppr_decls_AbsC (CCallProfCtrMacro   _ amodes)     = ppr_decls_Amodes [] -- *****!!!
   -- no real reason to, anyway.
 ppr_decls_AbsC (CCallProfCCMacro    _ amodes)  = ppr_decls_Amodes amodes
 
-ppr_decls_AbsC (CStaticClosure closure_lbl closure_info cost_centre amodes)
+ppr_decls_AbsC (CStaticClosure closure_info cost_centre amodes)
        -- ToDo: strictly speaking, should chk "cost_centre" amode
   = ppr_decls_Amodes amodes