diff --git a/NEWS.md b/NEWS.md
index ce71617a6..1fdf73651 100644
--- a/NEWS.md
+++ b/NEWS.md
@@ -47,6 +47,7 @@
 * `return_linter()` works on functions that happen to use braced expressions in their formals (#2616, @MichaelChirico).
 * `object_name_linter()` and `object_length_linter()` account for S3 class correctly when the generic is assigned with `=` (#2507, @MichaelChirico).
 * `assignment_linter()` with `operator = "="` does a better job of skipping implicit assignments, which are intended to be governed by `implicit_assignment_linter()` (#2765, @MichaelChirico).
+* `expect_true_false_linter()` is pipe-aware, so that `42 |> expect_identical(x, ignore_attr = TRUE)` no longer lints (#1520, @MichaelChirico).
 * `T_and_F_symbol_linter()` ignores `T` and `F` used as symbols in formulas (`y ~ T + F`), which can represent variables in data not controlled by the author (#2637, @MichaelChirico).
 
 ### Lint accuracy fixes: removing false negatives
diff --git a/R/expect_true_false_linter.R b/R/expect_true_false_linter.R
index bf540c0c8..af6234770 100644
--- a/R/expect_true_false_linter.R
+++ b/R/expect_true_false_linter.R
@@ -32,10 +32,14 @@
 #' @seealso [linters] for a complete list of linters available in lintr.
 #' @export
 expect_true_false_linter <- function() {
-  xpath <- "
-  following-sibling::expr[position() <= 2 and NUM_CONST[text() = 'TRUE' or text() = 'FALSE']]
+  pipe_cond <- glue("parent::expr/parent::expr[PIPE or SPECIAL[{xp_text_in_table(magrittr_pipes)}]]")
+  xpath <- glue("
+  following-sibling::expr[
+    NUM_CONST[text() = 'TRUE' or text() = 'FALSE']
+    and position() <= 2 - count({pipe_cond})
+  ]
     /parent::expr
-  "
+  ")
 
   Linter(linter_level = "expression", function(source_expression) {
     xml_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
diff --git a/tests/testthat/test-expect_true_false_linter.R b/tests/testthat/test-expect_true_false_linter.R
index 76ed5c42c..8afc0edfb 100644
--- a/tests/testthat/test-expect_true_false_linter.R
+++ b/tests/testthat/test-expect_true_false_linter.R
@@ -1,16 +1,22 @@
 test_that("expect_true_false_linter skips allowed usages", {
+  linter <- expect_true_false_linter()
   # expect_true is a scalar test; testing logical vectors with expect_equal is OK
-  expect_lint("expect_equal(x, c(TRUE, FALSE))", NULL, expect_true_false_linter())
+  expect_no_lint("expect_equal(x, c(TRUE, FALSE))", linter)
+
+  expect_no_lint("expect_equal(x, y, ignore_attr = TRUE)")
+
+  expect_no_lint("42 %>% expect_identical(42, ignore_attr = TRUE)", linter)
+  expect_no_lint("42 %>% expect_identical(42, TRUE)", linter)
+
+  skip_if_not_r_version("4.1.0")
+  expect_no_lint("42 |> expect_identical(42, ignore_attr = TRUE)", linter)
 })
 
 test_that("expect_true_false_linter blocks simple disallowed usages", {
   linter <- expect_true_false_linter()
+  lint_msg <- rex::rex("expect_true(x) is better than expect_equal(x, TRUE)")
 
-  expect_lint(
-    "expect_equal(foo(x), TRUE)",
-    rex::rex("expect_true(x) is better than expect_equal(x, TRUE)"),
-    linter
-  )
+  expect_lint("expect_equal(foo(x), TRUE)", lint_msg, linter)
 
   # expect_identical is treated the same as expect_equal
   expect_lint(
@@ -20,11 +26,12 @@ test_that("expect_true_false_linter blocks simple disallowed usages", {
   )
 
   # also caught when TRUE/FALSE is the first argument
-  expect_lint(
-    "expect_equal(TRUE, foo(x))",
-    rex::rex("expect_true(x) is better than expect_equal(x, TRUE)"),
-    linter
-  )
+  expect_lint("expect_equal(TRUE, foo(x))", lint_msg, linter)
+
+  expect_lint("42 %T>% expect_equal(TRUE)", lint_msg, linter)
+
+  skip_if_not_r_version("4.1.0")
+  expect_lint("42 |> expect_equal(TRUE)", lint_msg, linter)
 })
 
 test_that("lints vectorize", {