diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs
index def51f5010cc2f8dd6d12a28b4cdd38743fac249..1fbb7c8b2fdeae1182092a3ca7765d3a2b370b45 100644
--- a/compiler/coreSyn/CoreLint.hs
+++ b/compiler/coreSyn/CoreLint.hs
@@ -1571,6 +1571,10 @@ lintCoreRule fun fun_ty rule@(Rule { ru_name = name, ru_bndrs = bndrs
                                    , ru_args = args, ru_rhs = rhs })
   = lintBinders LambdaBind bndrs $ \ _ ->
     do { lhs_ty <- lintCoreArgs fun_ty args
+
+         -- Ensure template arguments contain no ticks
+       ; forM_ args $ \arg -> checkL (null $ stripTicksT (const True) arg)
+                                $ template_arg_with_tick_doc arg
        ; rhs_ty <- case isJoinId_maybe fun of
                      Just join_arity
                        -> do { checkL (args `lengthIs` join_arity) $
@@ -1591,6 +1595,9 @@ lintCoreRule fun fun_ty rule@(Rule { ru_name = name, ru_bndrs = bndrs
   where
     rule_doc = text "Rule" <+> doubleQuotes (ftext name) <> colon
 
+    template_arg_with_tick_doc arg =
+      rule_doc <+> text "Argument" <+> ppr arg <+> text "contains tick(s)"
+
     lhs_fvs = exprsFreeVars args
     rhs_fvs = exprFreeVars rhs
 
diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/coreSyn/CoreSubst.hs
index afb894642622f844301e0bbbd69e5c5c940d0534..43f9c358f6904fd99f6d60b798d79265ca4d18f9 100644
--- a/compiler/coreSyn/CoreSubst.hs
+++ b/compiler/coreSyn/CoreSubst.hs
@@ -687,7 +687,8 @@ substRule subst subst_ru_fn rule@(Rule { ru_bndrs = bndrs, ru_args = args
          , ru_fn    = if is_local
                         then subst_ru_fn fn_name
                         else fn_name
-         , ru_args  = map (substExpr doc subst') args
+         , ru_args  = map (stripTicksE (const True) . substExpr doc subst') args
+           -- See Note [Rule templates are devoid of ticks] in Rules.
          , ru_rhs   = substExpr (text "foo") subst' rhs }
            -- Do NOT optimise the RHS (previously we did simplOptExpr here)
            -- See Note [Substitute lazily]
diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs
index 408006f75aa23058b364dfc2b651c38158ac6868..225dc498c2f4fdc94abbcd871bf87305b9b6e3e5 100644
--- a/compiler/simplCore/Simplify.hs
+++ b/compiler/simplCore/Simplify.hs
@@ -3645,5 +3645,6 @@ simplRules env mb_new_id rules mb_cont
            ; rhs'  <- simplExprC rule_env rhs rhs_cont
            ; return (rule { ru_bndrs = bndrs'
                           , ru_fn    = fn_name'
-                          , ru_args  = args'
+                          , ru_args  = map (stripTicksE (const True)) args'
+                              -- See Note [Rule templates are devoid of ticks] in Rules.
                           , ru_rhs   = rhs' }) }
diff --git a/compiler/specialise/Rules.hs b/compiler/specialise/Rules.hs
index 72e293421cf5ab53439a6bc3ff12c967de3c3724..af9b46878b708b795820ef74104599655e35150e 100644
--- a/compiler/specialise/Rules.hs
+++ b/compiler/specialise/Rules.hs
@@ -1024,6 +1024,24 @@ tick scope, we can float them upwards to the rule application site.
 
 cf Note [Notes in call patterns] in SpecConstr
 
+Note [Rule templates are devoid of ticks]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+As mentioned in Note [Tick annotations in RULE matching], the matcher allows
+ticks only in very few cases. In particular, they are completely disallowed
+in the rule template. Core Lint checks this invariant.
+
+However, there are a few ways in which ticks can sneak in to the template.
+#17619 is one particularly tricky way:
+
+ 1. SpecConstr creates a rule on `f` with a free variable `x` in its template.
+ 2. CSE rewrites the RHS of `x` to `<tick> y`
+ 3. The simplifier unconditionally post-inlines `x`
+ 4. The simplifier simplifes `f`'s rules and, in so doing, substitutes `x ~>
+    <tick> y`, introducing a tick into the template of the rule.
+
+To avoid this, we strip ticks after substituting in to rule templates.
+
 Note [Matching lets]
 ~~~~~~~~~~~~~~~~~~~~
 Matching a let-expression.  Consider