Interpreting the strictness annotations output by ghc --show-iface

Hi, If someone could clearly specify the exact interpretation of these LLSL(ULL) strictness/demand annotations shown by ghc --show-iface I'd like to try to write a little tool that highlights the function argument binding in an IDE (e.g. Emacs) with this information. Anyone care to explain the syntax? Cheers, Johan

L = lazy
S = strict
A = absent
f :: Int -> (Char,Char) -> Int -> Char
LS(S,L)A
means that it is lazy in the first int, strict in the tuple, strict in
the first argument of the tuple but lazy in the second and the third
argument is not used at all. I have a paper that describes it
somewhere. I modeled the jhc strictness analyzer after the ghc one
(with minor hindsight improvements) so pored over the ghc one for
quite a while once upon a time.
John
On Wed, Mar 7, 2012 at 3:21 PM, Johan Tibell
Hi,
If someone could clearly specify the exact interpretation of these LLSL(ULL) strictness/demand annotations shown by ghc --show-iface I'd like to try to write a little tool that highlights the function argument binding in an IDE (e.g. Emacs) with this information. Anyone care to explain the syntax?
Cheers, Johan
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Wed, Mar 7, 2012 at 3:26 PM, John Meacham
L = lazy S = strict A = absent
f :: Int -> (Char,Char) -> Int -> Char
LS(S,L)A
means that it is lazy in the first int, strict in the tuple, strict in the first argument of the tuple but lazy in the second and the third argument is not used at all. I have a paper that describes it somewhere. I modeled the jhc strictness analyzer after the ghc one (with minor hindsight improvements) so pored over the ghc one for quite a while once upon a time.
Oh, and the (..) works for all CPR types, not just tuples. John

Check out compiler/basicTypes/Demand.lhs Cheers, Edward Excerpts from Johan Tibell's message of Wed Mar 07 18:21:56 -0500 2012:
Hi,
If someone could clearly specify the exact interpretation of these LLSL(ULL) strictness/demand annotations shown by ghc --show-iface I'd like to try to write a little tool that highlights the function argument binding in an IDE (e.g. Emacs) with this information. Anyone care to explain the syntax?
Cheers, Johan

Ah, looks like it got a bit more complicated since I looked at it last... time to update jhc :) Actually. not sure if the Eval/Box split is relevant to my core. hmm.... John

Edward, I have looked at that file before and it didn't make me much wiser, because I cannot map it to the output. I find it's the parenthesis that confuses me the most. What does this mean? C(U(LU(L))) what about this? U(SLLAA)LL -- Johan

On Wed, Mar 7, 2012 at 18:41, Johan Tibell
Edward, I have looked at that file before and it didn't make me much wiser, because I cannot map it to the output.
I find it's the parenthesis that confuses me the most. What does this mean?
C(U(LU(L)))
I think the original type signature is needed to figure it out. In the earlier example it indicated ghc drilling down into the type (a tuple) and determining the strictness of the constituents. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On Wed, Mar 7, 2012 at 4:38 PM, Brandon Allbery
I think the original type signature is needed to figure it out. In the earlier example it indicated ghc drilling down into the type (a tuple) and determining the strictness of the constituents.
I parenthesis were for tuples I would never expect to see e.g. U(L).

On Wed, Mar 7, 2012 at 5:01 PM, Johan Tibell
On Wed, Mar 7, 2012 at 4:38 PM, Brandon Allbery
wrote: I think the original type signature is needed to figure it out. In the earlier example it indicated ghc drilling down into the type (a tuple) and determining the strictness of the constituents.
I parenthesis were for tuples I would never expect to see e.g. U(L).
They are for all CPR types, not just tuples. so that could be data Foo = Foo Int It also may omit values for which is has no information for, I can't recall if ghc does that or not. John

On Wed, Mar 7, 2012 at 20:01, Johan Tibell
On Wed, Mar 7, 2012 at 4:38 PM, Brandon Allbery
wrote: I think the original type signature is needed to figure it out. In the earlier example it indicated ghc drilling down into the type (a tuple) and determining the strictness of the constituents.
I parenthesis were for tuples I would never expect to see e.g. U(L).
Right, the tuple was just that example.
Data F = F Int
would give you something that could produce U(L), the U for the F constructor, the L for the contained Int. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On Wed, Mar 7, 2012 at 5:40 PM, Brandon Allbery
Data F = F Int
would give you something that could produce U(L), the U for the F constructor, the L for the contained Int.
Some experimentation suggests U is for unboxed. For example, module Test where f :: Int -> Int f x = x g :: Int -> Int g x = x + 1 gives this core Test.f :: Int -> Int Test.f = \ (x :: Int) -> x Test.g :: Int -> Int Test.g = \ (x :: Int) -> case x of _ { I# x# -> I# (+# x# 1) } and these strictness annotations f :: GHC.Types.Int -> GHC.Types.Int {- Arity: 1, HasNoCafRefs, Strictness: S, Unfolding: (\ x :: GHC.Types.Int -> x) -} g :: GHC.Types.Int -> GHC.Types.Int {- Arity: 1, HasNoCafRefs, Strictness: U(L)m, Unfolding: InlineRule (1, True, False) (\ x :: GHC.Types.Int -> case x of wild { GHC.Types.I# x1 -> GHC.Types.I# (GHC.Prim.+# x1 1) }) -} f is strict in its argument and so is g (U implies S.) The unboxed field is "lazy", but that's the annotation kind # things always get. I'm not sure but the trailing "m" in g's signature. Cheers, Johan

| I'm not sure but the trailing "m" in g's signature. That says that the result has the CPR property. S

This is the important bit of code in the file: instance Outputable Demand where ppr Top = char 'T' ppr Abs = char 'A' ppr Bot = char 'B' ppr (Defer ds) = char 'D' <> ppr ds ppr (Eval ds) = char 'U' <> ppr ds ppr (Box (Eval ds)) = char 'S' <> ppr ds ppr (Box Abs) = char 'L' ppr (Box Bot) = char 'X' ppr d@(Box _) = pprPanic "ppr: Bad boxed demand" (ppr d) ppr (Call d) = char 'C' <> parens (ppr d) instance Outputable Demands where ppr (Poly Abs) = empty ppr (Poly d) = parens (ppr d <> char '*') ppr (Prod ds) = parens (hcat (map ppr ds)) You do need to be able to read the pretty printing combinators. Here's a quick cheat sheet; check http://hackage.haskell.org/packages/archive/pretty/1.0.1.0/doc/html/Text-Pre... the basic idea. char ==> print a single character <> ==> concatenate without adding a space parens x ==> put parentheses around x hcat ==> concatenate a list without adding a space Cheers, Edward Excerpts from Johan Tibell's message of Wed Mar 07 18:41:42 -0500 2012:
Edward, I have looked at that file before and it didn't make me much wiser, because I cannot map it to the output.
I find it's the parenthesis that confuses me the most. What does this mean?
C(U(LU(L)))
what about this?
U(SLLAA)LL
-- Johan

Thanks Edward. I'll try to summarize this in human readable form and publish it on the wiki. -- Johan

Arguably, what should happen is we redo the format for machine-parseability and use that in future versions of GHC. Edward Excerpts from Johan Tibell's message of Wed Mar 07 23:38:06 -0500 2012:
Thanks Edward. I'll try to summarize this in human readable form and publish it on the wiki.
-- Johan

The "C" is a call demand: C(d) means "this function is called and its result is consumed with d. U(ddd) means "this three-field product is evaluated, and its three field are evaluated with d,d,d | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell- | users-bounces@haskell.org] On Behalf Of Johan Tibell | Sent: 07 March 2012 23:42 | To: john@repetae.net | Cc: glasgow-haskell-users | Subject: Re: Interpreting the strictness annotations output by ghc --show- | iface | | Edward, I have looked at that file before and it didn't make me much | wiser, because I cannot map it to the output. | | I find it's the parenthesis that confuses me the most. What does this mean? | | C(U(LU(L))) | | what about this? | | U(SLLAA)LL | | -- Johan | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (5)
-
Brandon Allbery
-
Edward Z. Yang
-
Johan Tibell
-
John Meacham
-
Simon Peyton-Jones