diff options
author | Zubin Duggal <zubin.duggal@gmail.com> | 2022-03-02 14:21:58 +0530 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2022-03-29 13:07:22 -0400 |
commit | 789add55e0f5648981ffba77135b2a525369bf79 (patch) | |
tree | 0ada054d9b11af3c650a53f7b076db1cfb147d64 /compiler/GHC/Tc | |
parent | 2c12627caba908153bf0af92459d08e399aa8aad (diff) | |
download | haskell-789add55e0f5648981ffba77135b2a525369bf79.tar.gz |
Fix all invalid haddock comments in the compiler
Fixes #20935 and #20924
Diffstat (limited to 'compiler/GHC/Tc')
-rw-r--r-- | compiler/GHC/Tc/Deriv.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Errors.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Errors/Ppr.hs | 15 | ||||
-rw-r--r-- | compiler/GHC/Tc/Gen/App.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Tc/Gen/Export.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Tc/Gen/Splice.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Module.hs | 8 | ||||
-rw-r--r-- | compiler/GHC/Tc/TyCl/Utils.hs | 16 |
8 files changed, 30 insertions, 29 deletions
diff --git a/compiler/GHC/Tc/Deriv.hs b/compiler/GHC/Tc/Deriv.hs index 29a58d9c01..272d7b6d4e 100644 --- a/compiler/GHC/Tc/Deriv.hs +++ b/compiler/GHC/Tc/Deriv.hs @@ -247,7 +247,7 @@ tcDeriving deriv_infos deriv_decls ; return (addTcgDUs gbl_env all_dus, inst_info, rn_aux_binds) } } where ddump_deriving :: Bag (InstInfo GhcRn) -> HsValBinds GhcRn - -> [FamInst] -- ^ Associated type family instances + -> [FamInst] -- Associated type family instances -> SDoc ddump_deriving inst_infos extra_binds famInsts = hang (text "Derived class instances:") diff --git a/compiler/GHC/Tc/Errors.hs b/compiler/GHC/Tc/Errors.hs index 2deec2bbd6..9b9eb8077b 100644 --- a/compiler/GHC/Tc/Errors.hs +++ b/compiler/GHC/Tc/Errors.hs @@ -403,7 +403,7 @@ warnRedundantConstraints ctxt env info ev_vars -- and we don't want to say it twice. Seems a bit ad-hoc = report_redundant_msg False where - report_redundant_msg :: Bool -- ^ whether to add "In ..." to the diagnostic + report_redundant_msg :: Bool -- whether to add "In ..." to the diagnostic -> TcRn () report_redundant_msg show_info = do { lcl_env <- getLclEnv diff --git a/compiler/GHC/Tc/Errors/Ppr.hs b/compiler/GHC/Tc/Errors/Ppr.hs index 29da277c8d..de8d893f80 100644 --- a/compiler/GHC/Tc/Errors/Ppr.hs +++ b/compiler/GHC/Tc/Errors/Ppr.hs @@ -526,9 +526,10 @@ instance Diagnostic TcRnMessage where quotes (ppr_name child)) 2 (pprNameProvenance gre)) - -- DuplicateRecordFields means that nameOccName might be a mangled - -- $sel-prefixed thing, in which case show the correct OccName alone - -- (but otherwise show the Name so it will have a module qualifier) + -- DuplicateRecordFields means that nameOccName might be a + -- mangled $sel-prefixed thing, in which case show the correct OccName + -- alone (but otherwise show the Name so it will have a module + -- qualifier) ppr_name (FieldGreName fl) | flIsOverloaded fl = ppr fl | otherwise = ppr (flSelector fl) ppr_name (NormalGreName name) = ppr name @@ -2984,8 +2985,8 @@ expandSynonymsToMatch ty1 ty2 = (ty1_ret, ty2_ret) where (ty1_ret, ty2_ret) = go ty1 ty2 - -- | Returns (type synonym expanded version of first type, - -- type synonym expanded version of second type) + -- Returns (type synonym expanded version of first type, + -- type synonym expanded version of second type) go :: Type -> Type -> (Type, Type) go t1 t2 | t1 `pickyEqType` t2 = @@ -3039,7 +3040,7 @@ expandSynonymsToMatch ty1 ty2 = (ty1_ret, ty2_ret) (if t1_exps > t2_exps then drop dif t1_exp_tys else t1_exp_tys) (if t2_exps > t1_exps then drop dif t2_exp_tys else t2_exp_tys) - -- | Expand the top layer type synonyms repeatedly, collect expansions in a + -- Expand the top layer type synonyms repeatedly, collect expansions in a -- list. The list does not include the original type. -- -- Example, if you have: @@ -3059,7 +3060,7 @@ expandSynonymsToMatch ty1 ty2 = (ty1_ret, ty2_ret) tyExpansions :: Type -> [Type] tyExpansions = unfoldr (\t -> (\x -> (x, x)) `fmap` tcView t) - -- | Drop the type pairs until types in a pair look alike (i.e. the outer + -- Drop the type pairs until types in a pair look alike (i.e. the outer -- constructors are the same). followExpansions :: [(Type, Type)] -> (Type, Type) followExpansions [] = pprPanic "followExpansions" empty diff --git a/compiler/GHC/Tc/Gen/App.hs b/compiler/GHC/Tc/Gen/App.hs index 743587ed25..c2df311b30 100644 --- a/compiler/GHC/Tc/Gen/App.hs +++ b/compiler/GHC/Tc/Gen/App.hs @@ -569,11 +569,11 @@ hasFixedRuntimeRep_remainingValArgs applied_args app_res_rho = \case traceTc "tcApp remainingValArgs check_thing" (debug_msg thing arity) go (nb_applied_vis_val_args + 1) (nb_applied_val_args + 1) arg_tys where - go :: Int -- ^ visible value argument index, starting from 1 + go :: Int -- visible value argument index, starting from 1 -- only used to report the argument position in error messages - -> Int -- ^ value argument index, starting from 1 + -> Int -- value argument index, starting from 1 -- used to count up to the arity to ensure we don't check too many argument types - -> [(Type, AnonArgFlag)] -- ^ run-time argument types + -> [(Type, AnonArgFlag)] -- run-time argument types -> TcM () go _ i_val _ | i_val > arity diff --git a/compiler/GHC/Tc/Gen/Export.hs b/compiler/GHC/Tc/Gen/Export.hs index 26b765a9d1..47be72763a 100644 --- a/compiler/GHC/Tc/Gen/Export.hs +++ b/compiler/GHC/Tc/Gen/Export.hs @@ -611,9 +611,9 @@ checkPatSynParent parent NoParent gname selErr = exportErrCtxt "pattern synonym record selector" handle_pat_syn :: SDoc - -> TyCon -- ^ Parent TyCon - -> PatSyn -- ^ Corresponding bundled PatSyn - -- and pretty printed origin + -> TyCon -- Parent TyCon + -> PatSyn -- Corresponding bundled PatSyn + -- and pretty printed origin -> TcM () handle_pat_syn doc ty_con pat_syn diff --git a/compiler/GHC/Tc/Gen/Splice.hs b/compiler/GHC/Tc/Gen/Splice.hs index 6860eba567..1f2c9b66eb 100644 --- a/compiler/GHC/Tc/Gen/Splice.hs +++ b/compiler/GHC/Tc/Gen/Splice.hs @@ -1404,7 +1404,7 @@ lookupThInstName th_type = do <+> ppr_th th_type <+> text "to add documentation to" - -- | Get the name of the class for the instance we are documenting + -- Get the name of the class for the instance we are documenting -- > inst_cls_name (Monad Maybe) == Monad -- > inst_cls_name C = C inst_cls_name :: TH.Type -> TcM TH.Name @@ -1443,7 +1443,7 @@ lookupThInstName th_type = do <+> ppr_th th_type <+> text "is supposed to be" - -- | Basically does the opposite of 'mkThAppTs' + -- Basically does the opposite of 'mkThAppTs' -- > inst_arg_types (Monad Maybe) == [Maybe] -- > inst_arg_types C == [] inst_arg_types :: TH.Type -> [TH.Type] diff --git a/compiler/GHC/Tc/Module.hs b/compiler/GHC/Tc/Module.hs index d8ec1e1b16..d9bb0dba17 100644 --- a/compiler/GHC/Tc/Module.hs +++ b/compiler/GHC/Tc/Module.hs @@ -1284,7 +1284,7 @@ checkBootTyCon is_boot tc1 tc2 -- -- See also 'HowAbstract' and Note [Skolem abstract data]. - -- | Given @type T tvs = ty@, where @ty@ decomposes into @tc2' args@, + -- Given @type T tvs = ty@, where @ty@ decomposes into @tc2' args@, -- check that this synonym is an acceptable implementation of @tc1@. -- See Note [Synonyms implement abstract data] checkSynAbsData :: [TyVar] -> Type -> TyCon -> [Type] -> Maybe SDoc @@ -1715,9 +1715,9 @@ tcMissingParentClassWarn warnFlag isName shouldName }} where -- Check whether the desired superclass exists in a given environment. - checkShouldInst :: Class -- ^ Class of existing instance - -> Class -- ^ Class there should be an instance of - -> ClsInst -- ^ Existing instance + checkShouldInst :: Class -- Class of existing instance + -> Class -- Class there should be an instance of + -> ClsInst -- Existing instance -> TcM () checkShouldInst isClass shouldClass isInst = do { instEnv <- tcGetInstEnvs diff --git a/compiler/GHC/Tc/TyCl/Utils.hs b/compiler/GHC/Tc/TyCl/Utils.hs index 7abde66296..e102507d63 100644 --- a/compiler/GHC/Tc/TyCl/Utils.hs +++ b/compiler/GHC/Tc/TyCl/Utils.hs @@ -971,14 +971,14 @@ mkOneRecordSelector all_cons idDetails fl has_sel eq_subst = mkTvSubstPrs (map eqSpecPair eq_spec) -- inst_tys corresponds to one of the following: -- - -- * The arguments to the user-written return type (for GADT constructors). - -- In this scenario, eq_subst provides a mapping from the universally - -- quantified type variables to the argument types. Note that eq_subst - -- does not need to be applied to any other part of the DataCon - -- (see Note [The dcEqSpec domain invariant] in GHC.Core.DataCon). - -- * The universally quantified type variables - -- (for Haskell98-style constructors and pattern synonyms). In these - -- scenarios, eq_subst is an empty substitution. + -- * The arguments to the user-written return type (for GADT constructors). + -- In this scenario, eq_subst provides a mapping from the universally + -- quantified type variables to the argument types. Note that eq_subst + -- does not need to be applied to any other part of the DataCon + -- (see Note [The dcEqSpec domain invariant] in GHC.Core.DataCon). + -- * The universally quantified type variables + -- (for Haskell98-style constructors and pattern synonyms). In these + -- scenarios, eq_subst is an empty substitution. inst_tys = substTyVars eq_subst univ_tvs unit_rhs = mkLHsTupleExpr [] noExtField |