Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • compiler/GHC/Hs/Type.hs
    ... ... @@ -640,6 +640,9 @@ hsLTyVarName = hsTyVarName . unLoc
    640 640
     hsLTyVarNames :: [LHsTyVarBndr flag (GhcPass p)] -> [IdP (GhcPass p)]
    
    641 641
     hsLTyVarNames = mapMaybe hsLTyVarName
    
    642 642
     
    
    643
    +hsQTvExplicit :: LHsQTyVars (GhcPass p) -> [LHsTyVarBndr (HsBndrVis (GhcPass p)) (GhcPass p)]
    
    644
    +hsQTvExplicit = hsq_explicit
    
    645
    +
    
    643 646
     hsForAllTelescopeBndrs :: HsForAllTelescope (GhcPass p) -> [LHsTyVarBndr ForAllTyFlag (GhcPass p)]
    
    644 647
     hsForAllTelescopeBndrs (HsForAllVis   _ bndrs) = map (fmap (setHsTyVarBndrFlag Required)) bndrs
    
    645 648
     hsForAllTelescopeBndrs (HsForAllInvis _ bndrs) = map (fmap (updateHsTyVarBndrFlag Invisible)) bndrs
    

  • compiler/Language/Haskell/Syntax/Type.hs
    ... ... @@ -55,7 +55,6 @@ module Language.Haskell.Syntax.Type (
    55 55
             FieldOcc(..), LFieldOcc,
    
    56 56
     
    
    57 57
             mapHsOuterImplicit,
    
    58
    -        hsQTvExplicit,
    
    59 58
             isHsKindedTyVar
    
    60 59
         ) where
    
    61 60
     
    
    ... ... @@ -68,7 +67,6 @@ import Language.Haskell.Syntax.Specificity
    68 67
     
    
    69 68
     import GHC.Hs.Doc (LHsDoc)
    
    70 69
     import GHC.Data.FastString (FastString)
    
    71
    -import GHC.Utils.Panic( panic )
    
    72 70
     
    
    73 71
     import Data.Data hiding ( Fixity, Prefix, Infix )
    
    74 72
     import Data.Maybe
    
    ... ... @@ -326,10 +324,6 @@ data LHsQTyVars pass -- See Note [HsType binders]
    326 324
         }
    
    327 325
       | XLHsQTyVars !(XXLHsQTyVars pass)
    
    328 326
     
    
    329
    -hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr (HsBndrVis pass) pass]
    
    330
    -hsQTvExplicit (HsQTvs { hsq_explicit = explicit_tvs }) = explicit_tvs
    
    331
    -hsQTvExplicit (XLHsQTyVars {})                         = panic "hsQTvExplicit"
    
    332
    -
    
    333 327
     ------------------------------------------------
    
    334 328
     --            HsOuterTyVarBndrs
    
    335 329
     -- Used to quantify the outermost type variable binders of a type that obeys
    

  • utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs
    ... ... @@ -435,7 +435,7 @@ ppFamHeader
    435 435
             | associated = id
    
    436 436
             | otherwise = (<+> keyword "family")
    
    437 437
     
    
    438
    -      famName = ppAppDocNameTyVarBndrs unicode name (hsq_explicit tvs)
    
    438
    +      famName = ppAppDocNameTyVarBndrs unicode name (hsQTvExplicitBinders tvs)
    
    439 439
     
    
    440 440
           famSig = case result of
    
    441 441
             NoSig _ -> empty
    
    ... ... @@ -644,7 +644,7 @@ ppTyVars :: RenderableBndrFlag flag => Bool -> [LHsTyVarBndr flag DocNameI] -> [
    644 644
     ppTyVars unicode tvs = map (ppHsTyVarBndr unicode . unLoc) tvs
    
    645 645
     
    
    646 646
     tyvarNames :: LHsQTyVars DocNameI -> [Maybe Name]
    
    647
    -tyvarNames = map (fmap getName . hsLTyVarNameI) . hsQTvExplicit
    
    647
    +tyvarNames = map (fmap getName . hsLTyVarNameI) . hsQTvExplicitBinders
    
    648 648
     
    
    649 649
     declWithDoc :: LaTeX -> Maybe LaTeX -> LaTeX
    
    650 650
     declWithDoc decl doc =
    

  • utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
    ... ... @@ -468,7 +468,7 @@ ppTySyn
    468 468
           hdr =
    
    469 469
             hsep
    
    470 470
               ( [keyword "type", ppBinder summary occ]
    
    471
    -              ++ ppTyVars unicode qual (hsQTvExplicit ltyvars)
    
    471
    +              ++ ppTyVars unicode qual (hsQTvExplicitBinders ltyvars)
    
    472 472
               )
    
    473 473
           full = hdr <+> def
    
    474 474
           def = case unLoc ltype of
    
    ... ... @@ -595,7 +595,7 @@ ppFamHeader
    595 595
       qual =
    
    596 596
         hsep
    
    597 597
           [ ppFamilyLeader associated info
    
    598
    -      , ppAppDocNameTyVarBndrs summary unicode qual name (hsq_explicit tvs)
    
    598
    +      , ppAppDocNameTyVarBndrs summary unicode qual name (hsQTvExplicitBinders tvs)
    
    599 599
           , ppResultSig result unicode qual
    
    600 600
           , injAnn
    
    601 601
           , whereBit
    
    ... ... @@ -760,7 +760,7 @@ ppClassHdr
    760 760
     ppClassHdr summ lctxt n tvs fds unicode qual =
    
    761 761
       keyword "class"
    
    762 762
         <+> (if not (null $ fromMaybeContext lctxt) then ppLContext lctxt unicode qual HideEmptyContexts else noHtml)
    
    763
    -    <+> ppAppDocNameTyVarBndrs summ unicode qual n (hsQTvExplicit tvs)
    
    763
    +    <+> ppAppDocNameTyVarBndrs summ unicode qual n (hsQTvExplicitBinders tvs)
    
    764 764
         <+> ppFds fds unicode qual
    
    765 765
     
    
    766 766
     ppFds :: [LHsFunDep DocNameI] -> Unicode -> Qualification -> Html
    
    ... ... @@ -1656,7 +1656,7 @@ ppDataHeader
    1656 1656
           ppLContext ctxt unicode qual HideEmptyContexts
    
    1657 1657
           <+>
    
    1658 1658
           -- T a b c ..., or a :+: b
    
    1659
    -      ppAppDocNameTyVarBndrs summary unicode qual name (hsQTvExplicit tvs)
    
    1659
    +      ppAppDocNameTyVarBndrs summary unicode qual name (hsQTvExplicitBinders tvs)
    
    1660 1660
           <+> case ks of
    
    1661 1661
             Nothing -> mempty
    
    1662 1662
             Just (L _ x) -> dcolon unicode <+> ppKind unicode qual x
    

  • utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
    ... ... @@ -333,9 +333,12 @@ lHsQTyVarsToTypes tvs =
    333 333
       [ HsValArg noExtField $ noLocA (case hsLTyVarName tv of
    
    334 334
           Nothing -> HsWildCardTy noExtField
    
    335 335
           Just nm -> HsTyVar noAnn NotPromoted (noLocA $ noUserRdr nm))
    
    336
    -  | tv <- hsQTvExplicit tvs
    
    336
    +  | tv <- hsq_explicit tvs
    
    337 337
       ]
    
    338 338
     
    
    339
    +hsQTvExplicitBinders :: LHsQTyVars DocNameI -> [LHsTyVarBndr (HsBndrVis DocNameI) DocNameI]
    
    340
    +hsQTvExplicitBinders = hsq_explicit
    
    341
    +
    
    339 342
     --------------------------------------------------------------------------------
    
    340 343
     
    
    341 344
     -- * Making abstract declarations