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

Johan Tibell johan.tibell at gmail.com
Thu Mar 8 04:50:14 CET 2012


On Wed, Mar 7, 2012 at 5:40 PM, Brandon Allbery <allbery.b at gmail.com> wrote:
>> 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



More information about the Glasgow-haskell-users mailing list