diff options
author | simonmar <unknown> | 2005-03-31 10:16:46 +0000 |
---|---|---|
committer | simonmar <unknown> | 2005-03-31 10:16:46 +0000 |
commit | 853e20a3eb86137cdb8accf69c6caa9db83a3d34 (patch) | |
tree | 803e7b469d073d88fa7644dccbaeedbd986bd462 /ghc/compiler/codeGen | |
parent | ca739e852566d7e0bfd594e6d7bf08da04f78d3c (diff) | |
download | haskell-853e20a3eb86137cdb8accf69c6caa9db83a3d34.tar.gz |
[project @ 2005-03-31 10:16:33 by simonmar]
Tweaks to get the GHC sources through Haddock. Doesn't quite work
yet, because Haddock complains about the recursive modules. Haddock
needs to understand SOURCE imports (it can probably just ignore them
as a first attempt).
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r-- | ghc/compiler/codeGen/Bitmap.hs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgBindery.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgCase.lhs | 8 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgClosure.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgHeapery.lhs | 8 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgInfoTbls.hs | 6 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgPrimOp.hs | 20 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgTailCall.lhs | 6 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CodeGen.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/SMRep.lhs | 4 |
10 files changed, 32 insertions, 32 deletions
diff --git a/ghc/compiler/codeGen/Bitmap.hs b/ghc/compiler/codeGen/Bitmap.hs index 36915e07d2..c0b490978c 100644 --- a/ghc/compiler/codeGen/Bitmap.hs +++ b/ghc/compiler/codeGen/Bitmap.hs @@ -66,9 +66,9 @@ intsToReverseBitmap size slots{- must be sorted -} | size >= wORD_SIZE_IN_BITS = complement 0 | otherwise = (1 `shiftL` size) - 1 -{-| +{- | Magic number, must agree with @BITMAP_BITS_SHIFT@ in InfoTables.h. -Some kinds of bitmap pack a size/bitmap into a single word if +Some kinds of bitmap pack a size\/bitmap into a single word if possible, or fall back to an external pointer when the bitmap is too large. This value represents the largest size of bitmap that can be packed into a single word. diff --git a/ghc/compiler/codeGen/CgBindery.lhs b/ghc/compiler/codeGen/CgBindery.lhs index e6e1043a47..e4ca141c9e 100644 --- a/ghc/compiler/codeGen/CgBindery.lhs +++ b/ghc/compiler/codeGen/CgBindery.lhs @@ -165,7 +165,7 @@ idInfoToAmode info VirStkLoc sp_off -> do { sp_rel <- getSpRelOffset sp_off ; return (CmmLoad sp_rel mach_rep) } - VirStkLNE sp_off -> getSpRelOffset sp_off ; + VirStkLNE sp_off -> getSpRelOffset sp_off VoidLoc -> return $ pprPanic "idInfoToAmode: void" (ppr (cg_id info)) -- We return a 'bottom' amode, rather than panicing now diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs index fad78d8215..58a43f489c 100644 --- a/ghc/compiler/codeGen/CgCase.lhs +++ b/ghc/compiler/codeGen/CgCase.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgCase.lhs,v 1.73 2005/03/18 13:37:38 simonmar Exp $ +% $Id: CgCase.lhs,v 1.74 2005/03/31 10:16:34 simonmar Exp $ % %******************************************************** %* * @@ -171,7 +171,7 @@ cgCase (StgOpApp op@(StgFCallOp fcall _) args _) live_in_whole_case live_in_alts bndr srt alt_type alts | unsafe_foreign_call = ASSERT( isSingleton alts ) - do -- *must* be an unboxed tuple alt. + do -- *must* be an unboxed tuple alt. -- exactly like the cgInlinePrimOp case for unboxed tuple alts.. { res_tmps <- mapFCs bindNewToTemp non_void_res_ids ; let res_hints = map (typeHint.idType) non_void_res_ids @@ -471,7 +471,7 @@ are inlined alternatives. \begin{code} cgAlgAlts :: GCFlag -> Maybe VirtualSpOffset - -> AltType -- ** AlgAlt or PolyAlt only ** + -> AltType -- ** AlgAlt or PolyAlt only ** -> [StgAlt] -- The alternatives -> FCode ( [(ConTagZ, CgStmts)], -- The branches Maybe CgStmts ) -- The default case @@ -491,7 +491,7 @@ cgAlgAlts gc_flag cc_slot alt_type alts cgAlgAlt :: GCFlag -> Maybe VirtualSpOffset -- Turgid state - -> AltType -- ** AlgAlt or PolyAlt only ** + -> AltType -- ** AlgAlt or PolyAlt only ** -> StgAlt -> FCode (AltCon, CgStmts) diff --git a/ghc/compiler/codeGen/CgClosure.lhs b/ghc/compiler/codeGen/CgClosure.lhs index 3c3d4e2494..401da80103 100644 --- a/ghc/compiler/codeGen/CgClosure.lhs +++ b/ghc/compiler/codeGen/CgClosure.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgClosure.lhs,v 1.67 2005/03/18 13:37:40 simonmar Exp $ +% $Id: CgClosure.lhs,v 1.68 2005/03/31 10:16:34 simonmar Exp $ % \section[CgClosure]{Code generation for closures} @@ -155,7 +155,7 @@ cgRhsClosure bndr cc bndr_info srt fvs upd_flag args body = do -- it in the closure. Instead, just bind it to Node on entry. -- NB we can be sure that Node will point to it, because we -- havn't told mkClosureLFInfo about this; so if the binder - -- *was* a free var of its RHS, mkClosureLFInfo thinks it *is* + -- _was_ a free var of its RHS, mkClosureLFInfo thinks it *is* -- stored in the closure itself, so it will make sure that -- Node points to it... let diff --git a/ghc/compiler/codeGen/CgHeapery.lhs b/ghc/compiler/codeGen/CgHeapery.lhs index e154bed545..82276898bc 100644 --- a/ghc/compiler/codeGen/CgHeapery.lhs +++ b/ghc/compiler/codeGen/CgHeapery.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgHeapery.lhs,v 1.44 2005/03/18 13:37:42 simonmar Exp $ +% $Id: CgHeapery.lhs,v 1.45 2005/03/31 10:16:34 simonmar Exp $ % \section[CgHeapery]{Heap management functions} @@ -138,8 +138,8 @@ layOutConstr is_static dflags data_con args = (mkConInfo dflags is_static data_con tot_wds ptr_wds, things_w_offsets) where - (tot_wds, -- #ptr_wds + #nonptr_wds - ptr_wds, -- #ptr_wds + (tot_wds, -- #ptr_wds + #nonptr_wds + ptr_wds, -- #ptr_wds things_w_offsets) = mkVirtHeapOffsets args \end{code} @@ -150,7 +150,7 @@ list \begin{code} mkVirtHeapOffsets :: [(CgRep,a)] -- Things to make offsets for - -> (WordOff, -- *Total* number of words allocated + -> (WordOff, -- _Total_ number of words allocated WordOff, -- Number of words allocated for *pointers* [(a, VirtualHpOffset)]) -- Things with their offsets from start of diff --git a/ghc/compiler/codeGen/CgInfoTbls.hs b/ghc/compiler/codeGen/CgInfoTbls.hs index 940852d078..adfdb1a3de 100644 --- a/ghc/compiler/codeGen/CgInfoTbls.hs +++ b/ghc/compiler/codeGen/CgInfoTbls.hs @@ -191,9 +191,9 @@ mkFunGenInfoExtraBits fun_type arity srt_label liveness slow_entry -- <srt slot> -- <forward vector table> -- --- * The vector table is only present for vectored returns +-- * The vector table is only present for vectored returns -- --- * The SRT slot is only there if either +-- * The SRT slot is only there if either -- (a) there is SRT info to record, OR -- (b) if the return is vectored -- The latter (b) is necessary so that the vector is in a @@ -346,7 +346,7 @@ emitDirectReturnInstr = do { info_amode <- getSequelAmode ; stmtC (CmmJump (entryCode info_amode) []) } -emitVectoredReturnInstr :: CmmExpr -- *Zero-indexed* constructor tag +emitVectoredReturnInstr :: CmmExpr -- _Zero-indexed_ constructor tag -> Code emitVectoredReturnInstr zero_indexed_tag = do { info_amode <- getSequelAmode diff --git a/ghc/compiler/codeGen/CgPrimOp.hs b/ghc/compiler/codeGen/CgPrimOp.hs index 52f65510d0..db01ee837b 100644 --- a/ghc/compiler/codeGen/CgPrimOp.hs +++ b/ghc/compiler/codeGen/CgPrimOp.hs @@ -121,7 +121,7 @@ emitPrimOp [res] ForeignObjToAddrOp [fo] live emitPrimOp [] WriteForeignObjOp [fo,addr] live = stmtC (CmmStore (cmmOffsetW fo fixedHdrSize) addr) --- #define sizzeofByteArrayzh(r,a) \ +-- #define sizzeofByteArrayzh(r,a) \ -- r = (((StgArrWords *)(a))->words * sizeof(W_)) emitPrimOp [res] SizeofByteArrayOp [arg] live = stmtC $ @@ -130,25 +130,25 @@ emitPrimOp [res] SizeofByteArrayOp [arg] live CmmLit (mkIntCLit wORD_SIZE) ]) --- #define sizzeofMutableByteArrayzh(r,a) \ +-- #define sizzeofMutableByteArrayzh(r,a) \ -- r = (((StgArrWords *)(a))->words * sizeof(W_)) emitPrimOp [res] SizeofMutableByteArrayOp [arg] live = emitPrimOp [res] SizeofByteArrayOp [arg] live --- #define touchzh(o) /* nothing */ +-- #define touchzh(o) /* nothing */ emitPrimOp [] TouchOp [arg] live = nopC --- #define byteArrayContentszh(r,a) r = BYTE_ARR_CTS(a) +-- #define byteArrayContentszh(r,a) r = BYTE_ARR_CTS(a) emitPrimOp [res] ByteArrayContents_Char [arg] live = stmtC (CmmAssign res (cmmOffsetB arg arrWordsHdrSize)) --- #define stableNameToIntzh(r,s) (r = ((StgStableName *)s)->sn) +-- #define stableNameToIntzh(r,s) (r = ((StgStableName *)s)->sn) emitPrimOp [res] StableNameToIntOp [arg] live = stmtC (CmmAssign res (cmmLoadIndexW arg fixedHdrSize)) --- #define eqStableNamezh(r,sn1,sn2) \ +-- #define eqStableNamezh(r,sn1,sn2) \ -- (r = (((StgStableName *)sn1)->sn == ((StgStableName *)sn2)->sn)) emitPrimOp [res] EqStableNameOp [arg1,arg2] live = stmtC (CmmAssign res (CmmMachOp mo_wordEq [ @@ -160,11 +160,11 @@ emitPrimOp [res] EqStableNameOp [arg1,arg2] live emitPrimOp [res] ReallyUnsafePtrEqualityOp [arg1,arg2] live = stmtC (CmmAssign res (CmmMachOp mo_wordEq [arg1,arg2])) --- #define addrToHValuezh(r,a) r=(P_)a +-- #define addrToHValuezh(r,a) r=(P_)a emitPrimOp [res] AddrToHValueOp [arg] live = stmtC (CmmAssign res arg) --- #define dataToTagzh(r,a) r=(GET_TAG(((StgClosure *)a)->header.info)) +-- #define dataToTagzh(r,a) r=(GET_TAG(((StgClosure *)a)->header.info)) emitPrimOp [res] DataToTagOp [arg] live = stmtC (CmmAssign res (getConstrTag arg)) @@ -173,7 +173,7 @@ emitPrimOp [res] DataToTagOp [arg] live objects, even if they are in old space. When they become immutable, they can be removed from this scavenge list. -} --- #define unsafeFreezzeArrayzh(r,a) +-- #define unsafeFreezzeArrayzh(r,a) -- { -- SET_INFO((StgClosure *)a,&stg_MUT_ARR_PTRS_FROZEN0_info); -- r = a; @@ -182,7 +182,7 @@ emitPrimOp [res] UnsafeFreezeArrayOp [arg] live = stmtsC [ setInfo arg (CmmLit (CmmLabel mkMAP_FROZEN_infoLabel)), CmmAssign res arg ] --- #define unsafeFreezzeByteArrayzh(r,a) r=(a) +-- #define unsafeFreezzeByteArrayzh(r,a) r=(a) emitPrimOp [res] UnsafeFreezeByteArrayOp [arg] live = stmtC (CmmAssign res arg) diff --git a/ghc/compiler/codeGen/CgTailCall.lhs b/ghc/compiler/codeGen/CgTailCall.lhs index 0b77823560..9932613b14 100644 --- a/ghc/compiler/codeGen/CgTailCall.lhs +++ b/ghc/compiler/codeGen/CgTailCall.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgTailCall.lhs,v 1.41 2004/11/26 16:20:12 simonmar Exp $ +% $Id: CgTailCall.lhs,v 1.42 2005/03/31 10:16:34 simonmar Exp $ % %******************************************************** %* * @@ -97,7 +97,7 @@ performTailCall :: CgIdInfo -- The function -> [(CgRep,CmmExpr)] -- Args -> CmmStmts -- Pending simultaneous assignments - -- *** GUARANTEED to contain only stack assignments. + -- *** GUARANTEED to contain only stack assignments. -> Code performTailCall fun_info arg_amodes pending_assts @@ -372,7 +372,7 @@ tailCallPrimOp op args -- ----------------------------------------------------------------------------- -- Return Addresses --- | We always push the return address just before performing a tail call +-- We always push the return address just before performing a tail call -- or return. The reason we leave it until then is because the stack -- slot that the return address is to go into might contain something -- useful. diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs index 11dafdd363..0c8e314fcc 100644 --- a/ghc/compiler/codeGen/CodeGen.lhs +++ b/ghc/compiler/codeGen/CodeGen.lhs @@ -135,7 +135,7 @@ codeGen dflags this_mod type_env foreign_stubs imported_mods startupHaskell() must supply the name of the init function for the "top" module in the program, and we don't want to require that this name has the version and way info appended to it. - -------------------------------------------------------------------------- */ + -------------------------------------------------------------------------- */ We initialise the module tree by keeping a work-stack, * pointed to by Sp diff --git a/ghc/compiler/codeGen/SMRep.lhs b/ghc/compiler/codeGen/SMRep.lhs index 1ffbcda56d..da446b6c54 100644 --- a/ghc/compiler/codeGen/SMRep.lhs +++ b/ghc/compiler/codeGen/SMRep.lhs @@ -251,8 +251,8 @@ data SMRep = GenericRep -- GC routines consult sizes in info tbl Bool -- True <=> This is a static closure. Affects how -- we garbage-collect it - !Int -- # ptr words - !Int -- # non-ptr words + !Int -- # ptr words + !Int -- # non-ptr words ClosureType -- closure type | BlackHoleRep |