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/deSugar | |
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/deSugar')
-rw-r--r-- | compiler/deSugar/Check.hs | 12 | ||||
-rw-r--r-- | compiler/deSugar/Desugar.hs | 2 | ||||
-rw-r--r-- | compiler/deSugar/DsBinds.hs | 10 | ||||
-rw-r--r-- | compiler/deSugar/DsExpr.hs | 4 | ||||
-rw-r--r-- | compiler/deSugar/DsMeta.hs | 2 | ||||
-rw-r--r-- | compiler/deSugar/DsMonad.hs | 2 | ||||
-rw-r--r-- | compiler/deSugar/DsUsage.hs | 2 | ||||
-rw-r--r-- | compiler/deSugar/DsUtils.hs | 8 | ||||
-rw-r--r-- | compiler/deSugar/Match.hs | 10 | ||||
-rw-r--r-- | compiler/deSugar/MatchCon.hs | 2 | ||||
-rw-r--r-- | compiler/deSugar/MatchLit.hs | 6 |
11 files changed, 30 insertions, 30 deletions
diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 81832c8982..db3a501fcf 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -1030,7 +1030,7 @@ translatePat fam_insts pat = case pat of -- -- - Otherwise, we treat the `ListPat` as ordinary view pattern. -- - -- See Trac #14547, especially comment#9 and comment#10. + -- See #14547, especially comment#9 and comment#10. -- -- Here we construct CanFailPmPat directly, rather can construct a view -- pattern and do further translation as an optimization, for the reason, @@ -1100,7 +1100,7 @@ from translation in pattern matcher. `HsOverLit` inside `NPat` to HsIntPrim/HsWordPrim. If we do the same thing in `translatePat` as in `tidyNPat`, the exhaustiveness checker will fail to match the literals patterns correctly. See - Trac #14546. + #14546. In Note [Undecidable Equality for Overloaded Literals], we say: "treat overloaded literals that look different as different", but previously we @@ -1121,7 +1121,7 @@ from translation in pattern matcher. in value position as PmOLit, but translate the 0 and 1 in pattern position as PmSLit. The inconsistency leads to the failure of eqPmLit to detect the equality and report warning of "Pattern match is redundant" on pattern 0, - as reported in Trac #14546. In this patch we remove the specialization of + as reported in #14546. In this patch we remove the specialization of OverLit patterns, and keep the overloaded number literal in pattern as it is to maintain the consistency. We know nothing about the `fromInteger` method (see Note [Undecidable Equality for Overloaded Literals]). Now we @@ -1141,7 +1141,7 @@ from translation in pattern matcher. non-overloaded string values are translated to PmSLit. However the string patterns, both overloaded and non-overloaded, are translated to list of characters. The inconsistency leads to wrong warnings about redundant and - non-exhaustive pattern matching warnings, as reported in Trac #14546. + non-exhaustive pattern matching warnings, as reported in #14546. In order to catch the redundant pattern in following case: @@ -1167,7 +1167,7 @@ from translation in pattern matcher. We must ensure that doing the same translation to literal values and patterns in `translatePat` and `hsExprToPmExpr`. The previous inconsistent work led to - Trac #14546. + #14546. -} -- | Translate a list of patterns (Note: each pattern is translated @@ -2511,7 +2511,7 @@ dsPmWarn dflags ctx@(DsMatchContext kind loc) pm_result {- Note [Inaccessible warnings for record updates] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Consider (Trac #12957) +Consider (#12957) data T a where T1 :: { x :: Int } -> T Bool T2 :: { x :: Int } -> T a diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index aa9748ee35..128722d5b5 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -533,7 +533,7 @@ by 'competesWith' Class methods have a built-in RULE to select the method from the dictionary, so you can't change the phase on this. That makes id very dubious to -match on class methods in RULE lhs's. See Trac #10595. I'm not happy +match on class methods in RULE lhs's. See #10595. I'm not happy about this. For example in Control.Arrow we have {-# RULES "compose/arr" forall f g . diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index d62706ef00..cf94a5edf3 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -776,7 +776,7 @@ we might have We might want to specialise 'f' so that we in turn specialise '$wf'. We can't even /name/ '$wf' in the source code, so we can't specialise -it even if we wanted to. Trac #10721 is a case in point. +it even if we wanted to. #10721 is a case in point. Note [Activation pragmas for SPECIALISE] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -792,7 +792,7 @@ We need two pragma-like things: * Activation of RULE: from SPECIALISE pragma (if activation given) otherwise from f's inline pragma -This is not obvious (see Trac #5237)! +This is not obvious (see #5237)! Examples Rule activation Inline prag on spec'd fn --------------------------------------------------------------------- @@ -875,7 +875,7 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs , not (v `elemVarSet` orig_bndr_set) , not (v == fn_id) ] -- fn_id: do not quantify over the function itself, which may - -- itself be a dictionary (in pathological cases, Trac #10251) + -- itself be a dictionary (in pathological cases, #10251) decompose (Var fn_id) args | not (fn_id `elemVarSet` orig_bndr_set) @@ -1018,7 +1018,7 @@ drop_dicts drops dictionary bindings on the LHS where possible. NB3: In the common case of a non-overloaded, but perhaps-polymorphic specialisation, we don't need to bind *any* dictionaries for use - in the RHS. For example (Trac #8331) + in the RHS. For example (#8331) {-# SPECIALIZE INLINE useAbstractMonad :: ReaderST s Int #-} useAbstractMonad :: MonadAbstractIOST m => m Int Here, deriving (MonadAbstractIOST (ReaderST s)) is a lot of code @@ -1026,7 +1026,7 @@ drop_dicts drops dictionary bindings on the LHS where possible. RULE forall s (d :: MonadAbstractIOST (ReaderT s)). useAbstractMonad (ReaderT s) d = $suseAbstractMonad s - Trac #8848 is a good example of where there are some interesting + #8848 is a good example of where there are some interesting dictionary bindings to discard. The drop_dicts algorithm is based on these observations: diff --git a/compiler/deSugar/DsExpr.hs b/compiler/deSugar/DsExpr.hs index c6ba18b1eb..89ca815ed5 100644 --- a/compiler/deSugar/DsExpr.hs +++ b/compiler/deSugar/DsExpr.hs @@ -122,7 +122,7 @@ ds_val_bind (NonRecursive, hsbinds) body -- f x = let p@(Ptr y) = ... in ... -- Here the binding for 'p' is polymorphic, but does -- not mix with an unlifted binding for 'y'. You should - -- use a bang pattern. Trac #6078. + -- use a bang pattern. #6078. else do { when (looksLazyPatBind bind) $ warnIfSetDs Opt_WarnUnbangedStrictPatterns (unlifted_must_be_bang bind) @@ -622,7 +622,7 @@ ds_expr _ expr@(RecordUpd { rupd_expr = record_expr, rupd_flds = fields -- Clone the Id in the HsRecField, because its Name is that -- of the record selector, and we must not make that a local binder -- else we shadow other uses of the record selector - -- Hence 'lcl_id'. Cf Trac #2735 + -- Hence 'lcl_id'. Cf #2735 ds_field (dL->L _ rec_field) = do { rhs <- dsLExpr (hsRecFieldArg rec_field) ; let fld_id = unLoc (hsRecUpdFieldId rec_field) diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index 2aaafad29f..5de954ae7d 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -524,7 +524,7 @@ repClsInstD (ClsInstDecl { cid_poly_ty = ty, cid_binds = binds -- But we do NOT bring the binders of 'binds' into scope -- because they are properly regarded as occurrences -- For example, the method names should be bound to - -- the selector Ids, not to fresh names (Trac #5410) + -- the selector Ids, not to fresh names (#5410) -- do { cxt1 <- repLContext cxt ; inst_ty1 <- repLTy inst_ty diff --git a/compiler/deSugar/DsMonad.hs b/compiler/deSugar/DsMonad.hs index f328322e68..8e3021fd8a 100644 --- a/compiler/deSugar/DsMonad.hs +++ b/compiler/deSugar/DsMonad.hs @@ -486,7 +486,7 @@ askNoErrsDs thing_inside ; env <- getGblEnv ; mb_res <- tryM $ -- Be careful to catch exceptions -- so that we propagate errors correctly - -- (Trac #13642) + -- (#13642) setGblEnv (env { ds_msgs = errs_var }) $ thing_inside diff --git a/compiler/deSugar/DsUsage.hs b/compiler/deSugar/DsUsage.hs index a6b94c98a0..7c8e24bbec 100644 --- a/compiler/deSugar/DsUsage.hs +++ b/compiler/deSugar/DsUsage.hs @@ -50,7 +50,7 @@ In this case, B's dep_orphs will contain A due to its SOURCE import of A. Consequently, A will contain itself in its imp_orphs due to its import of B. This fact would end up being recorded in A's interface file. This would then break the invariant asserted by calculateAvails that a module does not itself in -its dep_orphs. This was the cause of Trac #14128. +its dep_orphs. This was the cause of #14128. -} diff --git a/compiler/deSugar/DsUtils.hs b/compiler/deSugar/DsUtils.hs index f39d0f2594..d4ceb523df 100644 --- a/compiler/deSugar/DsUtils.hs +++ b/compiler/deSugar/DsUtils.hs @@ -411,7 +411,7 @@ mkErrorAppDs err_id ty msg = do {- 'mkCoreAppDs' and 'mkCoreAppsDs' hand the special-case desugaring of 'seq'. -Note [Desugaring seq (1)] cf Trac #1031 +Note [Desugaring seq (1)] cf #1031 ~~~~~~~~~~~~~~~~~~~~~~~~~ f x y = x `seq` (y `seq` (# x,y #)) @@ -427,7 +427,7 @@ But that is bad for two reasons: Seq is very, very special! So we recognise it right here, and desugar to case x of _ -> case y of _ -> (# x,y #) -Note [Desugaring seq (2)] cf Trac #2273 +Note [Desugaring seq (2)] cf #2273 ~~~~~~~~~~~~~~~~~~~~~~~~~ Consider let chp = case b of { True -> fst x; False -> 0 } @@ -467,7 +467,7 @@ And now all is well. The reason it's a hack is because if you define mySeq=seq, the hack won't work on mySeq. -Note [Desugaring seq (3)] cf Trac #2409 +Note [Desugaring seq (3)] cf #2409 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The isLocalId ensures that we don't turn True `seq` e @@ -879,7 +879,7 @@ Reason: we know that a failure point is always a "join point" and is entered at most once. Adding a dummy 'realWorld' token argument makes it clear that sharing is not an issue. And that in turn makes it more CPR-friendly. This matters a lot: if you don't get it right, you lose -the tail call property. For example, see Trac #3403. +the tail call property. For example, see #3403. ************************************************************************ diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index 0930a6e6f4..c057298420 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -154,7 +154,7 @@ Most of the matching functions take an Id or [Id] as argument. This Id is the scrutinee(s) of the match. The desugared expression may sometimes use that Id in a local binding or as a case binder. So it should not have an External name; Lint rejects non-top-level binders -with External names (Trac #13043). +with External names (#13043). See also Note [Localise pattern binders] in DsUtils -} @@ -515,7 +515,7 @@ tidy_bang_pat v o _ p@(SumPat {}) = tidy1 v o p tidy_bang_pat v o l p@(ConPatOut { pat_con = (dL->L _ (RealDataCon dc)) , pat_args = args , pat_arg_tys = arg_tys }) - -- Newtypes: push bang inwards (Trac #9844) + -- Newtypes: push bang inwards (#9844) = if isNewTyCon (dataConTyCon dc) then tidy1 v o (p { pat_args = push_bang_into_newtype_arg l ty args }) @@ -534,7 +534,7 @@ tidy_bang_pat v o l p@(ConPatOut { pat_con = (dL->L _ (RealDataCon dc)) -- NPlusKPat -- -- For LazyPat, remember that it's semantically like a VarPat --- i.e. !(~p) is not like ~p, or p! (Trac #8952) +-- i.e. !(~p) is not like ~p, or p! (#8952) -- -- NB: SigPatIn, ConPatIn should not happen @@ -568,7 +568,7 @@ Note [Bang patterns and newtypes] For the pattern !(Just pat) we can discard the bang, because the pattern is strict anyway. But for !(N pat), where newtype NT = N Int -we definitely can't discard the bang. Trac #9844. +we definitely can't discard the bang. #9844. So what we do is to push the bang inwards, in the hope that it will get discarded there. So we transform @@ -926,7 +926,7 @@ If we see ... where P is a pattern synonym, can we put (P a -> e1) and (P b -> e2) in the same group? We can if P is a constructor, but /not/ if P is a pattern synonym. -Consider (Trac #11224) +Consider (#11224) -- readMaybe :: Read a => String -> Maybe a pattern PRead :: Read a => () => a -> String pattern PRead a <- (readMaybe -> Just a) diff --git a/compiler/deSugar/MatchCon.hs b/compiler/deSugar/MatchCon.hs index f699792910..ce1f19f560 100644 --- a/compiler/deSugar/MatchCon.hs +++ b/compiler/deSugar/MatchCon.hs @@ -242,7 +242,7 @@ Consider f (T { y=True, x=False }) = ... We must match the patterns IN THE ORDER GIVEN, thus for the first -one we match y=True before x=False. See Trac #246; or imagine +one we match y=True before x=False. See #246; or imagine matching against (T { y=False, x=undefined }): should fail without touching the undefined. diff --git a/compiler/deSugar/MatchLit.hs b/compiler/deSugar/MatchLit.hs index d0db91d93a..d99ae7e443 100644 --- a/compiler/deSugar/MatchLit.hs +++ b/compiler/deSugar/MatchLit.hs @@ -287,7 +287,7 @@ warnAboutEmptyEnumerations dflags fromExpr mThnExpr toExpr getLHsIntegralLit :: LHsExpr GhcTc -> Maybe (Integer, Name) -- ^ See if the expression is an 'Integral' literal. --- Remember to look through automatically-added tick-boxes! (Trac #8384) +-- Remember to look through automatically-added tick-boxes! (#8384) getLHsIntegralLit (dL->L _ (HsPar _ e)) = getLHsIntegralLit e getLHsIntegralLit (dL->L _ (HsTick _ _ e)) = getLHsIntegralLit e getLHsIntegralLit (dL->L _ (HsBinTick _ _ _ e)) = getLHsIntegralLit e @@ -349,7 +349,7 @@ tidyNPat (OverLit (OverLitTc False ty) val _) mb_neg _eq outer_ty -- Once that is settled, look for cases where the type of the -- entire overloaded literal matches the type of the underlying literal, -- and in that case take the short cut - -- NB: Watch out for weird cases like Trac #3382 + -- NB: Watch out for weird cases like #3382 -- f :: Int -> Int -- f "blah" = 4 -- which might be ok if we have 'instance IsString Int' @@ -363,7 +363,7 @@ tidyNPat (OverLit (OverLitTc False ty) val _) mb_neg _eq outer_ty -- NB: do /not/ convert Float or Double literals to F# 3.8 or D# 5.3 -- If we do convert to the constructor form, we'll generate a case -- expression on a Float# or Double# and that's not allowed in Core; see - -- Trac #9238 and Note [Rules for floating-point comparisons] in PrelRules + -- #9238 and Note [Rules for floating-point comparisons] in PrelRules where -- Sometimes (like in test case -- overloadedlists/should_run/overloadedlistsrun04), the SyntaxExprs include |