diff options
author | Ryan Scott <ryan.gl.scott@gmail.com> | 2019-03-12 18:15:38 -0400 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2019-03-15 10:17:54 -0400 |
commit | 610ec224a49e092c802a336570fd9613ea15ef3c (patch) | |
tree | cc79ac561669b51099eb37f222e8179d48a54d59 /compiler/hsSyn | |
parent | afc80730fd235f5c5b2d0b9fc5a10c16ef9865f6 (diff) | |
download | haskell-610ec224a49e092c802a336570fd9613ea15ef3c.tar.gz |
Update Trac ticket URLs to point to GitLab
This moves all URL references to Trac tickets to their corresponding
GitLab counterparts.
Diffstat (limited to 'compiler/hsSyn')
-rw-r--r-- | compiler/hsSyn/Convert.hs | 8 | ||||
-rw-r--r-- | compiler/hsSyn/HsBinds.hs | 4 | ||||
-rw-r--r-- | compiler/hsSyn/HsDecls.hs | 2 | ||||
-rw-r--r-- | compiler/hsSyn/HsExpr.hs | 6 | ||||
-rw-r--r-- | compiler/hsSyn/HsPat.hs | 4 | ||||
-rw-r--r-- | compiler/hsSyn/HsTypes.hs | 8 | ||||
-rw-r--r-- | compiler/hsSyn/HsUtils.hs | 8 |
7 files changed, 20 insertions, 20 deletions
diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs index 7113905bd9..77ffebe021 100644 --- a/compiler/hsSyn/Convert.hs +++ b/compiler/hsSyn/Convert.hs @@ -1570,7 +1570,7 @@ points so that the code is readable with its original meaning. So scattered through Convert.hs are various points where parens are added. -See (among other closed issued) https://ghc.haskell.org/trac/ghc/ticket/14289 +See (among other closed issued) https://gitlab.haskell.org/ghc/ghc/issues/14289 -} -- --------------------------------------------------------------------- @@ -1730,7 +1730,7 @@ mkHsForAllTy tvs loc fvf tvs' rho_ty -- It's important that we don't build an HsQualTy if the context is empty, -- as the pretty-printer for HsType _always_ prints contexts, even if --- they're empty. See Trac #13183. +-- they're empty. See #13183. mkHsQualTy :: TH.Cxt -- ^ The original Template Haskell context -> SrcSpan @@ -1820,7 +1820,7 @@ thRdrName :: SrcSpan -> OccName.NameSpace -> String -> TH.NameFlavour -> RdrName -- -- We pass in a SrcSpan (gotten from the monad) because this function -- is used for *binders* and if we make an Exact Name we want it --- to have a binding site inside it. (cf Trac #5434) +-- to have a binding site inside it. (cf #5434) -- -- ToDo: we may generate silly RdrNames, by passing a name space -- that doesn't match the string, like VarName ":+", @@ -1842,7 +1842,7 @@ thRdrName loc ctxt_ns th_occ th_name occ = mk_occ ctxt_ns th_occ -- Return an unqualified exact RdrName if we're dealing with built-in syntax. --- See Trac #13776. +-- See #13776. thOrigRdrName :: String -> TH.NameSpace -> PkgName -> ModName -> RdrName thOrigRdrName occ th_ns pkg mod = let occ' = mk_occ (mk_ghc_ns th_ns) occ diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 110c0fb488..8e3448d0f0 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -549,7 +549,7 @@ case we'd prefer to generate the (more direct) (# fromInteger $dNum 3, fromInteger $dNum 4 #) A similar thing happens with representation-polymorphic defns -(Trac #11405): +(#11405): undef :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => a undef = error "undef" @@ -798,7 +798,7 @@ instance (idR ~ GhcPass pr,OutputableBndrId idL, OutputableBndrId idR, pprTicks :: SDoc -> SDoc -> SDoc -- Print stuff about ticks only when -dppr-debug is on, to avoid --- them appearing in error messages (from the desugarer); see Trac # 3263 +-- them appearing in error messages (from the desugarer); see # 3263 -- Also print ticks in dumpStyle, so that -ddump-hpc actually does -- something useful. pprTicks pp_no_debug pp_when_debug diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs index f8709fbe1e..d4742f5052 100644 --- a/compiler/hsSyn/HsDecls.hs +++ b/compiler/hsSyn/HsDecls.hs @@ -855,7 +855,7 @@ NOTE THAT not be bound after it.) This last point is much more debatable than the others; see - Trac #15142 comment:22 + #15142 comment:22 -} diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs index 37d71821c0..bd63150c02 100644 --- a/compiler/hsSyn/HsExpr.hs +++ b/compiler/hsSyn/HsExpr.hs @@ -247,7 +247,7 @@ When it calls RnEnv.unknownNameSuggestions to identify these alternatives, the typechecker must provide a GlobalRdrEnv. If it provided the current one, which contains top-level declarations for the entire module, the error message would incorrectly suggest the out-of-scope `bar` and `bad` as possible alternatives -for `bar` (see Trac #11680). Instead, the typechecker must use the same +for `bar` (see #11680). Instead, the typechecker must use the same GlobalRdrEnv the renamer used when it determined that `bar` is out-of-scope. To obtain this GlobalRdrEnv, can the typechecker simply use the out-of-scope @@ -2012,7 +2012,7 @@ Note [The type of bind in Stmts] Some Stmts, notably BindStmt, keep the (>>=) bind operator. We do NOT assume that it has type (>>=) :: m a -> (a -> m b) -> m b -In some cases (see Trac #303, #1537) it might have a more +In some cases (see #303, #1537) it might have a more exotic type, such as (>>=) :: m i j a -> (a -> m j k b) -> m i k b So we must be careful not to make assumptions about the type. @@ -2306,7 +2306,7 @@ pprComp quals -- Prints: body | qual1, ..., qualn -- one, we simply treat it like a normal list. This does arise -- occasionally in code that GHC generates, e.g., in implementations of -- 'range' for derived 'Ix' instances for product datatypes with exactly - -- one constructor (e.g., see Trac #12583). + -- one constructor (e.g., see #12583). then ppr body else hang (ppr body <+> vbar) 2 (pprQuals initStmts) | otherwise diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 91be1492a8..bce65ba25a 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -292,7 +292,7 @@ type instance XParPat (GhcPass _) = NoExt type instance XBangPat (GhcPass _) = NoExt -- Note: XListPat cannot be extended when using GHC 8.0.2 as the bootstrap --- compiler, as it triggers https://ghc.haskell.org/trac/ghc/ticket/14396 for +-- compiler, as it triggers https://gitlab.haskell.org/ghc/ghc/issues/14396 for -- `SyntaxExpr` type instance XListPat GhcPs = NoExt type instance XListPat GhcRn = Maybe (SyntaxExpr GhcRn) @@ -735,7 +735,7 @@ isIrrefutableHsPat = isJust (tyConSingleDataCon_maybe (dataConTyCon con)) -- NB: tyConSingleDataCon_maybe, *not* isProductTyCon, because - -- the latter is false of existentials. See Trac #4439 + -- the latter is false of existentials. See #4439 && all goL (hsConPatArgs details) go (ConPatOut { pat_con = (dL->L _ (PatSynCon _pat)) }) diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs index ba961b53d0..9bb73c361b 100644 --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@ -213,7 +213,7 @@ Note carefully: Or even: f :: forall _a. _a -> _b Here _a is an ordinary forall'd binder, but (With NamedWildCards) - _b is a named wildcard. (See the comments in Trac #10982) + _b is a named wildcard. (See the comments in #10982) * Named wildcards are bound by the HsWildCardBndrs construct, which wraps types that are allowed to have wildcards. Unnamed wildcards however are left @@ -757,7 +757,7 @@ After renaming Qualified currently behaves exactly as Implicit, but it is deprecated to use it for implicit quantification. In this case, GHC 7.10 gives a warning; see -Note [Context quantification] in RnTypes, and Trac #4426. +Note [Context quantification] in RnTypes, and #4426. In GHC 8.0, Qualified will no longer bind variables and this will become an error. @@ -1065,7 +1065,7 @@ mkHsAppKindTy ext ty k -- Breaks up any parens in the result type: -- splitHsFunType (a -> (b -> c)) = ([a,b], c) -- Also deals with (->) t1 t2; that is why it only works on LHsType Name --- (see Trac #9096) +-- (see #9096) splitHsFunType :: LHsType GhcRn -> ([LHsType GhcRn], LHsType GhcRn) splitHsFunType (L _ (HsParTy _ ty)) = splitHsFunType ty @@ -1483,7 +1483,7 @@ pprConDeclFields fields = braces (sep (punctuate comma (map ppr_fld fields))) {- Note [Printing KindedTyVars] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Trac #3830 reminded me that we should really only print the kind +#3830 reminded me that we should really only print the kind signature on a KindedTyVar if the kind signature was put there by the programmer. During kind inference GHC now adds a PostTcKind to UserTyVars, rather than converting to KindedTyVars as before. diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index 62c153ef52..fa8ec1416c 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -611,7 +611,7 @@ mkHsSigEnv get_info sigs `extendNameEnvList` (mk_pairs gen_dm_sigs) -- The subtlety is this: in a class decl with a -- default-method signature as well as a method signature - -- we want the latter to win (Trac #12533) + -- we want the latter to win (#12533) -- class C x where -- op :: forall a . x a -> x a -- default op :: forall b . x b -> x b @@ -693,7 +693,7 @@ typeToLHsType ty go (CoercionTy co) = pprPanic "toLHsSigWcType" (ppr co) -- Source-language types have _invisible_ kind arguments, - -- so we must remove them here (Trac #8563) + -- so we must remove them here (#8563) go_tv :: TyVar -> LHsTyVarBndr GhcPs go_tv tv = noLoc $ KindedTyVar noExt (noLoc (getRdrName tv)) @@ -703,7 +703,7 @@ typeToLHsType ty Note [Kind signatures in typeToLHsType] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ There are types that typeToLHsType can produce which require explicit kind -signatures in order to kind-check. Here is an example from Trac #14579: +signatures in order to kind-check. Here is an example from #14579: -- type P :: forall {k} {t :: k}. Proxy t type P = 'Proxy @@ -1302,7 +1302,7 @@ main name (the TyCon of a type declaration etc), we want to give it the @SrcSpan@ of the whole /declaration/, not just the name itself (which is how it appears in the syntax tree). This SrcSpan (for the entire declaration) is used as the SrcSpan for the Name that is -finally produced, and hence for error messages. (See Trac #8607.) +finally produced, and hence for error messages. (See #8607.) Note [Binders in family instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |