Skip to content
Snippets Groups Projects
Commit 8d2eb272 authored by sof's avatar sof
Browse files

[project @ 1998-02-09 12:53:44 by sof]

- commented out unused code (upp_cc_uf)
- don't include module name when dumping
  scc name inside CC_DECLARE.
parent 75dffefc
No related merge requests found
...@@ -34,7 +34,6 @@ import Name ( OccName, getOccString, moduleString ) ...@@ -34,7 +34,6 @@ import Name ( OccName, getOccString, moduleString )
import Outputable import Outputable
import Util ( panic, panic#, assertPanic, thenCmp ) import Util ( panic, panic#, assertPanic, thenCmp )
pprIdInUnfolding = panic "Whoops"
\end{code} \end{code}
\begin{code} \begin{code}
...@@ -351,36 +350,37 @@ uppCostCentre print_as_string OverheadCC ...@@ -351,36 +350,37 @@ uppCostCentre print_as_string OverheadCC
uppCostCentre print_as_string cc uppCostCentre print_as_string cc
= getPprStyle $ \ sty -> = getPprStyle $ \ sty ->
let let
friendly_sty = userStyle sty || debugStyle sty -- i.e. probably for human consumption
prefix_CC = ptext SLIT("CC_") prefix_CC = ptext SLIT("CC_")
basic_thing = do_cc friendly_sty cc basic_thing = do_cc sty cc
basic_thing_string = stringToC basic_thing basic_thing_string = stringToC basic_thing
in in
if print_as_string then if print_as_string then
hcat [char '"', text basic_thing_string, char '"'] hcat [char '"', text basic_thing_string, char '"']
else if friendly_sty then else if (friendly_sty sty) then
text basic_thing text basic_thing
else else
hcat [prefix_CC, identToC (_PK_ basic_thing)] hcat [prefix_CC, identToC (_PK_ basic_thing)]
where where
do_cc friendly_sty DontCareCC = "DONT_CARE" friendly_sty sty = userStyle sty || debugStyle sty -- i.e. probably for human consumption
do_cc friendly_sty (AllCafsCC m _) = if print_as_string
then "CAFs_in_..." do_cc sty DontCareCC = "DONT_CARE"
else "CAFs." ++ _UNPK_ m do_cc sty (AllCafsCC m _) = if print_as_string
do_cc friendly_sty (AllDictsCC m _ d) = do_dupd friendly_sty d ( then "CAFs_in_..."
if print_as_string else "CAFs." ++ _UNPK_ m
then "DICTs_in_..." do_cc sty (AllDictsCC m _ d) = do_dupd sty d (
else "DICTs." ++ _UNPK_ m) if print_as_string
do_cc friendly_sty PreludeCafsCC = if print_as_string then "DICTs_in_..."
then "CAFs_in_..." else "DICTs." ++ _UNPK_ m)
else "CAFs" do_cc sty PreludeCafsCC = if print_as_string
do_cc friendly_sty (PreludeDictsCC d) = do_dupd friendly_sty d ( then "CAFs_in_..."
if print_as_string else "CAFs"
then "DICTs_in_..." do_cc sty (PreludeDictsCC d) = do_dupd sty d (
else "DICTs") if print_as_string
then "DICTs_in_..."
do_cc friendly_sty (NormalCC kind mod_name grp_name is_dupd is_caf) else "DICTs")
do_cc sty (NormalCC kind mod_name grp_name is_dupd is_caf)
= let = let
basic_kind = do_kind kind basic_kind = do_kind kind
module_kind = do_caf is_caf (moduleString mod_name ++ '/': module_kind = do_caf is_caf (moduleString mod_name ++ '/':
...@@ -391,17 +391,23 @@ uppCostCentre print_as_string cc ...@@ -391,17 +391,23 @@ uppCostCentre print_as_string cc
('/' : _UNPK_ grp_str) ++ ('/' : _UNPK_ grp_str) ++
('/' : basic_kind)) ('/' : basic_kind))
in in
if friendly_sty then if (friendly_sty sty) then
do_dupd friendly_sty is_dupd full_kind do_dupd sty is_dupd full_kind
else else if codeStyle sty && print_as_string then
module_kind {-
drop the module name when printing
out SCC label in CC declaration
-}
basic_kind
else
module_kind
where where
do_caf IsCafCC ls = "CAF:" ++ ls do_caf IsCafCC ls = "CAF:" ++ ls
do_caf _ ls = ls do_caf _ ls = ls
do_kind (UserCC name) = _UNPK_ name do_kind (UserCC name) = _UNPK_ name
do_kind (AutoCC id) = do_id id ++ (if friendly_sty then "/AUTO" else "") do_kind (AutoCC id) = do_id id ++ (if (friendly_sty sty) then "/AUTO" else "")
do_kind (DictCC id) = do_id id ++ (if friendly_sty then "/DICT" else "") do_kind (DictCC id) = do_id id ++ (if (friendly_sty sty) then "/DICT" else "")
{- {-
do_id is only applied in a (not print_as_string) context for local ids, do_id is only applied in a (not print_as_string) context for local ids,
...@@ -411,8 +417,8 @@ uppCostCentre print_as_string cc ...@@ -411,8 +417,8 @@ uppCostCentre print_as_string cc
do_id id = getOccString id do_id id = getOccString id
--------------- ---------------
do_dupd friendly_sty ADupdCC str = if friendly_sty then str ++ "/DUPD" else str do_dupd sty ADupdCC str = if (friendly_sty sty) then str ++ "/DUPD" else str
do_dupd _ _ str = str do_dupd _ _ str = str
\end{code} \end{code}
Printing unfoldings is sufficiently weird that we do it separately. Printing unfoldings is sufficiently weird that we do it separately.
...@@ -422,6 +428,7 @@ This should only apply to CostCentres that can be ``set to'' (cf ...@@ -422,6 +428,7 @@ This should only apply to CostCentres that can be ``set to'' (cf
Dict \tr{_scc_}s may cross module boundaries to show ``scope'' info; Dict \tr{_scc_}s may cross module boundaries to show ``scope'' info;
even if we won't ultimately do a \tr{SET_CCC} from it. even if we won't ultimately do a \tr{SET_CCC} from it.
\begin{code} \begin{code}
{- UNUSED
upp_cc_uf (PreludeDictsCC d) upp_cc_uf (PreludeDictsCC d)
= hsep [ptext SLIT("_PRELUDE_DICTS_CC_"), upp_dupd d] = hsep [ptext SLIT("_PRELUDE_DICTS_CC_"), upp_dupd d]
upp_cc_uf (AllDictsCC m g d) upp_cc_uf (AllDictsCC m g d)
...@@ -450,8 +457,11 @@ upp_cc_uf cc@(NormalCC cc_kind m g is_dupd is_caf) ...@@ -450,8 +457,11 @@ upp_cc_uf cc@(NormalCC cc_kind m g is_dupd is_caf)
upp_cc_uf other = panic ("upp_cc_uf:"++(showCostCentre True other)) upp_cc_uf other = panic ("upp_cc_uf:"++(showCostCentre True other))
#endif #endif
pprIdInUnfolding = panic "Whoops"
upp_dupd AnOriginalCC = ptext SLIT("_N_") upp_dupd AnOriginalCC = ptext SLIT("_N_")
upp_dupd ADupdCC = ptext SLIT("_D_") upp_dupd ADupdCC = ptext SLIT("_D_")
-}
\end{code} \end{code}
\begin{code} \begin{code}
......
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