X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FDemand.lhs;h=a038a23f6ac944046e361a56fa8344f19b223595;hb=8c4de43174d28741b5172397da3eb1c672cb876b;hp=21c22d46061fbe50d42397fdd3a5d67f5cc82598;hpb=bb521c6bba76f19474f12195b990b29eda66a4e8;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/Demand.lhs b/ghc/compiler/basicTypes/Demand.lhs index 21c22d4..a038a23 100644 --- a/ghc/compiler/basicTypes/Demand.lhs +++ b/ghc/compiler/basicTypes/Demand.lhs @@ -1,17 +1,33 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 +% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % \section[Demand]{@Demand@: the amount of demand on a value} \begin{code} -#include "HsVersions.h" +#ifndef OLD_STRICTNESS +module Demand () where +#else + +module Demand( + Demand(..), + + wwLazy, wwStrict, wwUnpack, wwPrim, wwEnum, + isStrict, isLazy, isPrim, + + pprDemands, seqDemand, seqDemands, -module Demand where + StrictnessInfo(..), + mkStrictnessInfo, + noStrictnessInfo, + ppStrictnessInfo, seqStrictnessInfo, + isBottomingStrictness, appIsBottom, + + ) where + +#include "HsVersions.h" -import PprStyle ( PprStyle ) import Outputable -import Pretty ( SYN_IE(Pretty), PrettyRep, ppStr ) -import Util ( panic ) +import Util ( listLengthCmp ) \end{code} @@ -33,8 +49,9 @@ data Demand -- (does not imply worker's existence or any -- calling-convention magic) - | WwUnpack -- Argument is strict & a single-constructor - [Demand] -- type; its constituent parts (whose StrictInfos + | WwUnpack -- Argument is strict & a single-constructor type + Bool -- True <=> wrapper unpacks it; False <=> doesn't + [Demand] -- Its constituent parts (whose StrictInfos -- are in the list) should be passed -- as arguments to the worker. @@ -45,17 +62,24 @@ data Demand | WwEnum -- Argument is strict & an enumeration type; -- an Int# representing the tag (start counting -- at zero) should be passed to the worker. - deriving (Eq, Ord) - -- we need Eq/Ord to cross-chk update infos in interfaces + deriving( Eq ) type MaybeAbsent = Bool -- True <=> not even used -- versions that don't worry about Absence: wwLazy = WwLazy False wwStrict = WwStrict -wwUnpack xs = WwUnpack xs +wwUnpack xs = WwUnpack False xs wwPrim = WwPrim wwEnum = WwEnum + +seqDemand :: Demand -> () +seqDemand (WwLazy a) = a `seq` () +seqDemand (WwUnpack b ds) = b `seq` seqDemands ds +seqDemand other = () + +seqDemands [] = () +seqDemands (d:ds) = seqDemand d `seq` seqDemands ds \end{code} @@ -66,13 +90,16 @@ wwEnum = WwEnum %************************************************************************ \begin{code} +isLazy :: Demand -> Bool +isLazy (WwLazy _) = True +isLazy _ = False + isStrict :: Demand -> Bool +isStrict d = not (isLazy d) -isStrict WwStrict = True -isStrict (WwUnpack _) = True -isStrict WwPrim = True -isStrict WwEnum = True -isStrict _ = False +isPrim :: Demand -> Bool +isPrim WwPrim = True +isPrim other = False \end{code} @@ -82,43 +109,100 @@ isStrict _ = False %* * %************************************************************************ + \begin{code} -#ifdef REALLY_HASKELL_1_3 -instance Read Demand where -#else -instance Text Demand where -#endif - readList str = read_em [{-acc-}] str - where - read_em acc ('L' : xs) = read_em (WwLazy False : acc) xs - read_em acc ('A' : xs) = read_em (WwLazy True : acc) xs - read_em acc ('S' : xs) = read_em (WwStrict : acc) xs - read_em acc ('P' : xs) = read_em (WwPrim : acc) xs - read_em acc ('E' : xs) = read_em (WwEnum : acc) xs - - read_em acc (')' : xs) = [(reverse acc, xs)] - read_em acc ( 'U' : '(' : xs) - = case (read_em [] xs) of - [(stuff, rest)] -> read_em (WwUnpack stuff : acc) rest - _ -> panic ("Text.Demand:"++str++"::"++xs) - - read_em acc rest = [(reverse acc, rest)] - -#ifdef REALLY_HASKELL_1_3 -instance Show Demand where -#endif - showList wrap_args rest = foldr show1 rest wrap_args - where - show1 (WwLazy False) rest = 'L' : rest - show1 (WwLazy True) rest = 'A' : rest - show1 WwStrict rest = 'S' : rest - show1 WwPrim rest = 'P' : rest - show1 WwEnum rest = 'E' : rest - show1 (WwUnpack args) rest = "U(" ++ showList args (')' : rest) +pprDemands demands bot = hcat (map pprDemand demands) <> pp_bot + where + pp_bot | bot = ptext SLIT("B") + | otherwise = empty + + +pprDemand (WwLazy False) = char 'L' +pprDemand (WwLazy True) = char 'A' +pprDemand WwStrict = char 'S' +pprDemand WwPrim = char 'P' +pprDemand WwEnum = char 'E' +pprDemand (WwUnpack wu args) = char ch <> parens (hcat (map pprDemand args)) + where + ch = if wu then 'U' else 'u' instance Outputable Demand where - ppr sty si = ppStr (showList [si] "") + ppr (WwLazy False) = empty + ppr other_demand = ptext SLIT("__D") <+> pprDemand other_demand + +instance Show Demand where + showsPrec p d = showsPrecSDoc p (ppr d) + +-- Reading demands is done in Lex.lhs \end{code} +%************************************************************************ +%* * +\subsection[strictness-IdInfo]{Strictness info about an @Id@} +%* * +%************************************************************************ + +We specify the strictness of a function by giving information about +each of the ``wrapper's'' arguments (see the description about +worker/wrapper-style transformations in the PJ/Launchbury paper on +unboxed types). + +The list of @Demands@ specifies: (a)~the strictness properties of a +function's arguments; and (b)~the type signature of that worker (if it +exists); i.e. its calling convention. +Note that the existence of a worker function is now denoted by the Id's +workerInfo field. + +\begin{code} +data StrictnessInfo + = NoStrictnessInfo + + | StrictnessInfo [Demand] -- Demands on the arguments. + + Bool -- True <=> the function diverges regardless of its arguments + -- Useful for "error" and other disguised variants thereof. + -- BUT NB: f = \x y. error "urk" + -- will have info SI [SS] True + -- but still (f) and (f 2) are not bot; only (f 3 2) is bot + deriving( Eq ) + + -- NOTA BENE: if the arg demands are, say, [S,L], this means that + -- (f bot) is not necy bot, only (f bot x) is bot + -- We simply cannot express accurately the strictness of a function + -- like f = \x -> case x of (a,b) -> \y -> ... + -- The up-side is that we don't need to restrict the strictness info + -- to the visible arity of the function. + +seqStrictnessInfo :: StrictnessInfo -> () +seqStrictnessInfo (StrictnessInfo ds b) = b `seq` seqDemands ds +seqStrictnessInfo other = () +\end{code} + +\begin{code} +mkStrictnessInfo :: ([Demand], Bool) -> StrictnessInfo + +mkStrictnessInfo (xs, is_bot) + | all totally_boring xs && not is_bot = NoStrictnessInfo -- Uninteresting + | otherwise = StrictnessInfo xs is_bot + where + totally_boring (WwLazy False) = True + totally_boring other = False + +noStrictnessInfo = NoStrictnessInfo + +isBottomingStrictness (StrictnessInfo _ bot) = bot +isBottomingStrictness NoStrictnessInfo = False + +-- appIsBottom returns true if an application to n args would diverge +appIsBottom (StrictnessInfo ds bot) n = bot && (listLengthCmp ds n /=GT) -- not more than 'n' elts in 'ds'. +appIsBottom NoStrictnessInfo n = False + +ppStrictnessInfo NoStrictnessInfo = empty +ppStrictnessInfo (StrictnessInfo wrapper_args bot) = hsep [pprDemands wrapper_args bot] +\end{code} + +\begin{code} +#endif /* OLD_STRICTNESS */ +\end{code}