@@ -748,6 +748,9 @@ test_that("symbols in formulas aren't treated as 'undefined global'", {
748748})
749749
750750test_that(" NSE-ish symbols after $/@ are ignored as sources for lints" , {
751+ linter <- object_usage_linter()
752+ lint_msg <- " no visible binding for global variable 'column'"
753+
751754 expect_lint(
752755 trim_some("
753756 foo <- function(x) {
@@ -757,12 +760,8 @@ test_that("NSE-ish symbols after $/@ are ignored as sources for lints", {
757760 )
758761 }
759762 " ),
760- list (
761- message = " no visible binding for global variable 'column'" ,
762- line_number = 4L ,
763- column_number = 22L
764- ),
765- object_usage_linter()
763+ list (lint_msg , line_number = 4L , column_number = 22L ),
764+ linter
766765 )
767766
768767 expect_lint(
@@ -774,12 +773,8 @@ test_that("NSE-ish symbols after $/@ are ignored as sources for lints", {
774773 )
775774 }
776775 " ),
777- list (
778- message = " no visible binding for global variable 'column'" ,
779- line_number = 4L ,
780- column_number = 22L
781- ),
782- object_usage_linter()
776+ list (lint_msg , line_number = 4L , column_number = 22L ),
777+ linter
783778 )
784779})
785780
@@ -798,53 +793,34 @@ test_that("functional lambda definitions are also caught", {
798793})
799794
800795test_that(" messages without location info are repaired" , {
796+ linter <- object_usage_linter()
797+ global_function_msg <- rex :: rex(" no visible global function definition for" , anything )
798+ global_variable_msg <- rex :: rex(" no visible binding for global variable" , anything )
799+ local_variable_msg <- rex :: rex(" local variable" , anything , " assigned but may not be used" )
800+
801801 # regression test for #1986
802802 expect_lint(
803- trim_some("
804- foo <- function() no_fun()
805- " ),
806- list (
807- message = rex :: rex(" no visible global function definition for" , anything ),
808- line_number = 1L ,
809- column_number = 19L
810- ),
811- object_usage_linter()
803+ " foo <- function() no_fun()" ,
804+ list (global_function_msg , line_number = 1L , column_number = 19L ),
805+ linter
812806 )
813807
814808 expect_lint(
815- trim_some("
816- foo <- function(a = no_fun()) a
817- " ),
818- list (
819- message = rex :: rex(" no visible global function definition for" , anything ),
820- line_number = 1L ,
821- column_number = 21L
822- ),
823- object_usage_linter()
809+ " foo <- function(a = no_fun()) a" ,
810+ list (global_function_msg , line_number = 1L , column_number = 21L ),
811+ linter
824812 )
825813
826814 expect_lint(
827- trim_some("
828- foo <- function() no_global
829- " ),
830- list (
831- message = rex :: rex(" no visible binding for global variable" , anything ),
832- line_number = 1L ,
833- column_number = 19L
834- ),
835- object_usage_linter()
815+ " foo <- function() no_global" ,
816+ list (global_variable_msg , line_number = 1L , column_number = 19L ),
817+ linter
836818 )
837819
838820 expect_lint(
839- trim_some("
840- foo <- function() unused_local <- 42L
841- " ),
842- list (
843- message = rex :: rex(" local variable" , anything , " assigned but may not be used" ),
844- line_number = 1L ,
845- column_number = 19L
846- ),
847- object_usage_linter()
821+ " foo <- function() unused_local <- 42L" ,
822+ list (local_variable_msg , line_number = 1L , column_number = 19L ),
823+ linter
848824 )
849825
850826 # More complex case with two lints and missing location info
@@ -854,17 +830,31 @@ test_that("messages without location info are repaired", {
854830 bar()
855831 " ),
856832 list (
857- list (
858- message = rex :: rex(" local variable" , anything , " assigned but may not be used" ),
859- line_number = 1L ,
860- column_number = 19L
861- ),
862- list (
863- message = rex :: rex(" no visible global function definition for" , anything ),
864- line_number = 2L ,
865- column_number = 3L
866- )
833+ list (local_variable_msg , line_number = 1L , column_number = 19L ),
834+ list (global_function_msg , line_number = 2L , column_number = 3L )
867835 ),
868- object_usage_linter()
836+ linter
837+ )
838+ })
839+
840+ test_that(" globals in scripts are found regardless of assignment operator" , {
841+ linter <- object_usage_linter()
842+
843+ expect_lint(
844+ trim_some("
845+ library(dplyr)
846+
847+ global_const_eq = 5
848+ global_const_la <- 6
849+ 7 -> global_const_ra
850+
851+ examplefunction <- function(df) {
852+ df %>%
853+ select(dist) %>%
854+ mutate(power = global_const_eq + global_const_ra + global_const_la)
855+ }
856+ " ),
857+ NULL ,
858+ linter
869859 )
870860})
0 commit comments