Simon Peyton Jones pushed to branch wip/T23109 at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • compiler/GHC/Core/Opt/Specialise.hs
    ... ... @@ -1900,12 +1900,15 @@ Suppose we have a function with a complicated type:
    1900 1900
     
    
    1901 1901
     and suppose it is called at:
    
    1902 1902
     
    
    1903
    -    f 7 @T1 @T2 @T3 dEqT1 ($dfShow dShowT2) t3
    
    1903
    +    f @T1 @T2 @T3 7 dEqT1 ($dfShow dShowT2) t3
    
    1904 1904
     
    
    1905 1905
     This call is described as a 'CallInfo' whose 'ci_key' is:
    
    1906 1906
     
    
    1907
    -    [ SpecType T1, SpecType T2, UnspecType, UnspecArg, SpecDict dEqT1
    
    1908
    -    , SpecDict ($dfShow dShowT2), UnspecArg ]
    
    1907
    +    [ SpecType T1, SpecType T2, UnspecType
    
    1908
    +    , UnspecArg
    
    1909
    +    , SpecDict dEqT1
    
    1910
    +    , SpecDict ($dfShow dShowT2)
    
    1911
    +    , UnspecArg ]
    
    1909 1912
     
    
    1910 1913
     Why are 'a' and 'b' identified as 'SpecType', while 'c' is 'UnspecType'?
    
    1911 1914
     Because we must specialise the function on type variables that appear
    

  • compiler/GHC/Core/Unfold/Make.hs
    ... ... @@ -197,6 +197,9 @@ specUnfolding opts spec_bndrs spec_app rule_lhs_args
    197 197
                        spec_app (mkLams old_bndrs arg)
    
    198 198
                        -- The beta-redexes created by spec_app will be
    
    199 199
                        -- simplified away by simplOptExpr
    
    200
    +                   -- ToDo: this is VERY DELICATE for type args.  We make
    
    201
    +                   --        (\@a @b x y. TYPE ty) ty1 ty2 d1 d2
    
    202
    +                   -- and rely on it simplifyign to ty[ty1/a, ty2/b]
    
    200 203
     
    
    201 204
     specUnfolding opts spec_bndrs spec_app rule_lhs_args
    
    202 205
                   (CoreUnfolding { uf_src = src, uf_tmpl = tmpl
    

  • compiler/GHC/HsToCore/Binds.hs
    ... ... @@ -1113,7 +1113,9 @@ dsSpec_help poly_nm poly_id poly_rhs inl bndrs ds_call
    1113 1113
                  spec_bndrs = filterOut (`elemVarSet` const_bndrs) rule_bndrs
    
    1114 1114
     
    
    1115 1115
                  mk_spec_body fn_body = mkLets spec_const_binds  $
    
    1116
    -                                    mkCoreApps fn_body rule_lhs_args
    
    1116
    +                                    mkApps fn_body rule_lhs_args
    
    1117
    +                                    -- ToDo: not mkCoreApps!  That uses exprType on fun which
    
    1118
    +                                    --       fails in specUnfolding, sigh
    
    1117 1119
     
    
    1118 1120
            ; tracePm "dsSpec(new route)" $
    
    1119 1121
              vcat [ text "poly_id" <+> ppr poly_id