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

Commits:

4 changed files:

Changes:

  • compiler/GHC/Core/Opt/Specialise.hs
    ... ... @@ -2965,15 +2965,14 @@ singleCall spec_env id args
    2965 2965
                          unitBag (CI { ci_key  = args
    
    2966 2966
                                      , ci_fvs  = fvVarSet call_fvs }) }
    
    2967 2967
       where
    
    2968
    -    call_fvs | gopt Opt_PolymorphicSpecialisation (se_dflags spec_env)
    
    2969
    -             = specArgsFVs isLocalVar args
    
    2970
    -             | otherwise
    
    2971
    -             = specArgsFVs isLocalId args
    
    2968
    +    poly_spec = gopt Opt_PolymorphicSpecialisation (se_dflags spec_env)
    
    2972 2969
     
    
    2973
    -        -- specArgFreeIds: we specifically look for free Ids, not TyVars
    
    2974
    -        --    see (MP1) in Note [Specialising polymorphic dictionaries]
    
    2975
    -        --
    
    2976
    -        -- We don't include the 'id' itself.
    
    2970
    +    -- With -fpolymorphic-specialisation, keep just local /Ids/
    
    2971
    +    -- Otherwise, keep /all/ free vars including TyVars
    
    2972
    +    -- See (MP1) in Note [Specialising polymorphic dictionaries]
    
    2973
    +    -- But NB: we don't include the 'id' itself.
    
    2974
    +    call_fvs | poly_spec = specArgsFVs isLocalId args
    
    2975
    +             | otherwise = specArgsFVs isLocalVar args
    
    2977 2976
     
    
    2978 2977
     mkCallUDs :: SpecEnv -> OutExpr -> [OutExpr] -> UsageDetails
    
    2979 2978
     mkCallUDs env fun args
    
    ... ... @@ -3504,7 +3503,7 @@ What should we do when a value is specialised to a *strict* unboxed value?
    3504 3503
                                in h:t
    
    3505 3504
     
    
    3506 3505
     Could convert let to case:
    
    3507
    - 
    
    3506
    +
    
    3508 3507
             map_*_Int# f (x:xs) = case f x of h# ->
    
    3509 3508
                                   let t = map f xs
    
    3510 3509
                                   in h#:t
    

  • compiler/GHC/Tc/Gen/App.hs
    ... ... @@ -460,6 +460,7 @@ finishApp tc_head@(tc_fun,_) tc_args app_res_rho res_wrap
    460 460
            ; res_expr <- if isTagToEnum tc_fun
    
    461 461
                          then tcTagToEnum tc_head tc_args app_res_rho
    
    462 462
                          else return (rebuildHsApps tc_head tc_args)
    
    463
    +       ; traceTc "End tcApp }" (ppr tc_fun)
    
    463 464
            ; return (mkHsWrap res_wrap res_expr) }
    
    464 465
     
    
    465 466
     checkResultTy :: HsExpr GhcRn
    

  • compiler/GHC/Tc/Gen/Expr.hs
    ... ... @@ -1481,6 +1481,7 @@ expandRecordUpd record_expr possible_parents rbnds res_ty
    1481 1481
                 vcat [ text "relevant_con:" <+> ppr relevant_con
    
    1482 1482
                      , text "res_ty:" <+> ppr res_ty
    
    1483 1483
                      , text "ds_res_ty:" <+> ppr ds_res_ty
    
    1484
    +                 , text "ds_expr:" <+> ppr ds_expr
    
    1484 1485
                      ]
    
    1485 1486
     
    
    1486 1487
             ; return (ds_expr, ds_res_ty, RecordUpdCtxt relevant_cons upd_fld_names ex_tvs) }
    

  • compiler/GHC/Tc/Utils/Unify.hs
    ... ... @@ -583,7 +583,6 @@ alwaysBuildImplication :: SkolemInfoAnon -> Bool
    583 583
     -- See Note [When to build an implication]
    
    584 584
     alwaysBuildImplication (SigSkol ctxt _ _)
    
    585 585
       = case ctxt of
    
    586
    -      FunSigCtxt {} -> True  -- RHS of a binding with a signature
    
    587 586
           SpecInstCtxt  -> True  -- SpecInstCtxt: this is rather delicate
    
    588 587
           _             -> False
    
    589 588
     alwaysBuildImplication _ = False
    
    ... ... @@ -591,6 +590,10 @@ alwaysBuildImplication _ = False
    591 590
     {-  Commmented out for now while I figure out about error messages.
    
    592 591
         See #14185
    
    593 592
     
    
    593
    +Caution: we get some duplication of errors if we build more implications.
    
    594
    +Because we get one error for each function RHS, even if it's for
    
    595
    +the same class constraint.
    
    596
    +
    
    594 597
     alwaysBuildImplication (SigSkol ctxt _ _)
    
    595 598
       = case ctxt of
    
    596 599
           FunSigCtxt {} -> True  -- RHS of a binding with a signature