Ben Gamari pushed to branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • compiler/GHC/Core/Coercion/Opt.hs
    ... ... @@ -208,10 +208,12 @@ optCoercion' env co
    208 208
         in
    
    209 209
         warnPprTrace (not (isReflCo out_co) && isReflexiveCo out_co)
    
    210 210
                      "optCoercion: reflexive but not refl" details $
    
    211
    ---    assertPpr (substTyUnchecked env in_ty1 `eqType` out_ty1 &&
    
    212
    ---               substTyUnchecked env in_ty2 `eqType` out_ty2 &&
    
    213
    ---               in_role == out_role)
    
    214
    ---              (hang (text "optCoercion changed types!") 2 details) $
    
    211
    +    -- The coercion optimiser should usually optimise
    
    212
    +    --     co:ty~ty   -->  Refl ty
    
    213
    +    -- But given a silly `newtype N = MkN N`, the axiom has type (N ~ N),
    
    214
    +    -- and so that can trigger this warning (e.g. test str002).
    
    215
    +    -- Maybe we should optimise that coercion to (Refl N), but it
    
    216
    +    -- just doesn't seem worth the bother
    
    215 217
         out_co
    
    216 218
     
    
    217 219
       | otherwise
    

  • compiler/GHC/Core/Utils.hs
    ... ... @@ -2730,8 +2730,10 @@ normSplitTyConApp_maybe fam_envs ty
    2730 2730
       | let Reduction co ty1 = topNormaliseType_maybe fam_envs ty
    
    2731 2731
                                `orElse` (mkReflRedn Representational ty)
    
    2732 2732
       , Just (tc, tc_args) <- splitTyConApp_maybe ty1
    
    2733
    -  = assertPpr (not (isNewTyCon tc)) (ppr ty $$ ppr ty1) $  -- Check post-condition
    
    2734
    -    Just (tc, tc_args, co)
    
    2733
    +  , not (isNewTyCon tc)  -- How can tc be a newtype, after `topNormaliseType`?
    
    2734
    +                         -- Answer: if it is a recursive newtype, `topNormaliseType`
    
    2735
    +                         --         may be a no-op.   Example: tc226
    
    2736
    +  = Just (tc, tc_args, co)
    
    2735 2737
     normSplitTyConApp_maybe _ _ = Nothing
    
    2736 2738
     
    
    2737 2739
     {-