Change in demand analysis results between 7.10.2 and RC1 (not fixed in RC2 and HEAD)

Ömer Sinan Ağacan omeragacan at gmail.com
Sat Feb 27 03:12:48 UTC 2016


Hi all,

While working on demand analyzer today we realized that there has been some
changes in demand analysis results between GHC 7.10.2 and 8.0-rc2. Here's a
minimal example:

    {-# LANGUAGE BangPatterns #-}

    module Main where

    data Prod a = Prod !a !a

    addProd :: Prod Int -> Prod Int -> Prod Int
    addProd (Prod i1 i2) (Prod i3 i4) = Prod i1 (i2 + i4)

    main = return ()

Compiled with 7.10.2:

    addProd :: Prod Int -> Prod Int -> Prod Int
    [GblId,
     Arity=2,
     Caf=NoCafRefs,
     Str=DmdType <S(SS),1*U(U,U(U))><S(SS),1*U(1*H,U(U))>m,
     ...}}}}]
    addProd =
      \ (ds_dzH :: Prod Int) (ds1_dzI :: Prod Int) ->
        case ds_dzH of _ [Occ=Dead] { Prod i1_an2 i2_an3 ->
        case i2_an3 of _ [Occ=Dead] { GHC.Types.I# x_s2B4 ->
        case ds1_dzI of _ [Occ=Dead] { Prod i3_an4 i4_an5 ->
        case i4_an5 of _ [Occ=Dead] { GHC.Types.I# y_s2B7 ->
        Main.Prod @ Int i1_an2 (GHC.Types.I# (GHC.Prim.+# x_s2B4 y_s2B7))
        }
        }
        }
        }

Compiled with 8.0-rc2:

    -- RHS size: {terms: 20, types: 17, coercions: 0}
    addProd :: Prod Int -> Prod Int -> Prod Int
    [GblId,
     Arity=2,
     Caf=NoCafRefs,
     Str=DmdType <S(SS),1*U(U,U(U))><S(LS),1*U(A,U(U))>m,
     ...}}}}]
    addProd =
      \ (ds_dQL :: Prod Int) (ds1_dQM :: Prod Int) ->
        case ds_dQL of _ [Occ=Dead] { Prod i1_avS i2_avT ->
        case i2_avT of _ [Occ=Dead] { GHC.Types.I# x_s1vO ->
        case ds1_dQM of _ [Occ=Dead] { Prod i3_avU i4_avV ->
        case i4_avV of _ [Occ=Dead] { GHC.Types.I# y_s1vR ->
        Main.Prod @ Int i1_avS (GHC.Types.I# (GHC.Prim.+# x_s1vO y_s1vR))
        }
        }
        }
        }

To highlight the difference,

    GHC 7.10.2:  <S(SS),1*U(U,U(U))><S(SS),1*U(1*H,U(U))>
    GHC 8.0-rc2: <S(SS),1*U(U,U(U))><S(LS),1*U(A,U(U))>

(NOTE: Also tried with HEAD and rc1 just now, the results are the same as rc2)

The demand put on the second argument is more strict in GHC 7.10. Was that an
intentional change? Any ideas on why this might be happening?

In our case, we prefer the result in 7.10.2 of course, because that's a more
precise demand and it gives us more opportunities for optimizations. But I
guess this could potentially reveal itself in some other situations and make
some programs slower? Any ideas?

Thanks..


More information about the ghc-devs mailing list