1
- # Processed first
2
- ns_tags_import <- c(
3
- " import" ,
4
- " importFrom" ,
5
- " importClassesFrom" ,
6
- " importMethodsFrom" ,
7
- " useDynLib" ,
8
- " rawNamespace"
9
- )
10
- ns_tags <- c(
11
- ns_tags_import ,
12
- " evalNamespace" ,
13
- " export" ,
14
- " exportClass" ,
15
- " exportMethod" ,
16
- " exportS3Method" ,
17
- " exportPattern"
18
- )
19
-
20
1
# ' Roclet: make `NAMESPACE`
21
2
# '
22
3
# ' @description
@@ -55,15 +36,15 @@ roclet_preprocess.roclet_namespace <- function(x,
55
36
base_path ,
56
37
global_options = list ()) {
57
38
58
- lines <- blocks_to_ns(blocks , env , tag_set = ns_tags_import )
39
+ lines <- blocks_to_ns(blocks , env , import_only = TRUE )
59
40
NAMESPACE <- file.path(base_path , " NAMESPACE" )
60
41
61
42
if (length(lines ) == 0 && ! made_by_roxygen(NAMESPACE )) {
62
43
return (x )
63
44
}
64
45
65
46
results <- c(made_by(" #" ), lines )
66
- write_if_different(NAMESPACE , results , check = FALSE )
47
+ write_if_different(NAMESPACE , results , check = TRUE )
67
48
68
49
invisible (x )
69
50
}
@@ -77,30 +58,6 @@ roclet_process.roclet_namespace <- function(x,
77
58
blocks_to_ns(blocks , env )
78
59
}
79
60
80
- # ' @export
81
- roxy_tag_parse.roxy_tag_evalNamespace <- function (x ) tag_code(x )
82
- # ' @export
83
- roxy_tag_parse.roxy_tag_export <- function (x ) tag_words_line(x )
84
- # ' @export
85
- roxy_tag_parse.roxy_tag_exportClass <- function (x ) tag_words(x , 1 )
86
- # ' @export
87
- roxy_tag_parse.roxy_tag_exportS3Method <- function (x ) tag_words(x , min = 0 , max = 2 )
88
- # ' @export
89
- roxy_tag_parse.roxy_tag_exportMethod <- function (x ) tag_words(x , min = 1 )
90
- # ' @export
91
- roxy_tag_parse.roxy_tag_exportPattern <- function (x ) tag_words(x , min = 1 )
92
- # ' @export
93
- roxy_tag_parse.roxy_tag_import <- function (x ) tag_words(x , min = 1 )
94
- # ' @export
95
- roxy_tag_parse.roxy_tag_importClassesFrom <- function (x ) tag_words(x , min = 2 )
96
- # ' @export
97
- roxy_tag_parse.roxy_tag_importFrom <- function (x ) tag_words(x , min = 2 )
98
- # ' @export
99
- roxy_tag_parse.roxy_tag_importMethodsFrom <- function (x ) tag_words(x , min = 2 )
100
- # ' @export
101
- roxy_tag_parse.roxy_tag_rawNamespace <- function (x ) tag_code(x )
102
- # ' @export
103
- roxy_tag_parse.roxy_tag_useDynLib <- function (x ) tag_words(x , min = 1 )
104
61
105
62
# ' @export
106
63
roclet_output.roclet_namespace <- function (x , results , base_path , ... ) {
@@ -124,86 +81,185 @@ roclet_clean.roclet_namespace <- function(x, base_path) {
124
81
125
82
# NAMESPACE generation ----------------------------------------------------
126
83
127
- blocks_to_ns <- function (blocks , env , tag_set = ns_tags ) {
128
- lines <- map(blocks , block_to_ns , env = env , tag_set = tag_set )
84
+ blocks_to_ns <- function (blocks , env , import_only = FALSE ) {
85
+ lines <- map(blocks , block_to_ns , env = env , import_only = import_only )
129
86
lines <- unlist(lines ) %|| % character ()
130
87
131
88
sort_c(unique(lines ))
132
89
}
133
90
134
- block_to_ns <- function (block , env , tag_set = ns_tags ) {
135
- tags <- block_get_tags(block , tag_set )
91
+ block_to_ns <- function (block , env , import_only = FALSE ) {
92
+ map(block $ tags , roxy_tag_ns , block = block , env = env , import_only = import_only )
93
+ }
94
+
95
+ # Namespace tag methods ---------------------------------------------------
136
96
137
- map(tags , function (tag ) {
138
- exec(paste0(" ns_" , tag $ tag ), tag , block , env )
139
- })
97
+ roxy_tag_ns <- function (x , block , env , import_only = FALSE ) {
98
+ UseMethod(" roxy_tag_ns" )
140
99
}
141
100
142
- ns_export <- function (tag , block , env ) {
143
- if (identical(tag $ val , " " )) {
101
+ # ' @export
102
+ roxy_tag_ns.default <- function (x , block , env , import_only = FALSE ) {
103
+
104
+ }
105
+
106
+ # ' @export
107
+ roxy_tag_parse.roxy_tag_evalNamespace <- function (x ) {
108
+ tag_code(x )
109
+ }
110
+ # ' @export
111
+ roxy_tag_ns.roxy_tag_evalNamespace <- function (x , block , env , import_only = FALSE ) {
112
+ roxy_tag_eval(x , env )
113
+ }
114
+
115
+ # ' @export
116
+ roxy_tag_parse.roxy_tag_export <- function (x ) {
117
+ tag_words_line(x )
118
+ }
119
+ # ' @export
120
+ roxy_tag_ns.roxy_tag_export <- function (x , block , env , import_only = FALSE ) {
121
+ if (import_only ) {
122
+ return ()
123
+ }
124
+
125
+ if (identical(x $ val , " " )) {
144
126
# FIXME: check for empty exports (i.e. no name)
145
127
default_export(block $ object , block )
146
128
} else {
147
- export(tag $ val )
129
+ export(x $ val )
148
130
}
149
131
}
150
132
151
- ns_exportClass <- function (tag , block , env ) export_class(tag $ val )
152
- ns_exportMethod <- function (tag , block , env ) export_s4_method(tag $ val )
153
- ns_exportPattern <- function (tag , block , env ) one_per_line(" exportPattern" , tag $ val )
154
- ns_import <- function (tag , block , env ) one_per_line(" import" , tag $ val )
155
- ns_importFrom <- function (tag , block , env ) repeat_first(" importFrom" , tag $ val )
156
- ns_importClassesFrom <- function (tag , block , env ) repeat_first(" importClassesFrom" , tag $ val )
157
- ns_importMethodsFrom <- function (tag , block , env ) repeat_first(" importMethodsFrom" , tag $ val )
133
+ # ' @export
134
+ roxy_tag_parse.roxy_tag_exportClass <- function (x ) {
135
+ tag_words(x , 1 )
136
+ }
137
+ # ' @export
138
+ roxy_tag_ns.roxy_tag_exportClass <- function (x , block , env , import_only = FALSE ) {
139
+ if (import_only ) {
140
+ return ()
141
+ }
158
142
159
- ns_exportS3Method <- function (tag , block , env ) {
160
- obj <- block $ object
143
+ export_class(x $ val )
144
+ }
145
+
146
+ # ' @export
147
+ roxy_tag_parse.roxy_tag_exportMethod <- function (x ) {
148
+ tag_words(x , min = 1 )
149
+ }
150
+ # ' @export
151
+ roxy_tag_ns.roxy_tag_exportMethod <- function (x , block , env , import_only = FALSE ) {
152
+ if (import_only ) {
153
+ return ()
154
+ }
155
+ export_s4_method(x $ val )
156
+ }
161
157
162
- if (length(tag $ val ) < 2 && ! inherits(obj , " s3method" )) {
163
- roxy_tag_warning(tag ,
158
+ # ' @export
159
+ roxy_tag_parse.roxy_tag_exportPattern <- function (x ) {
160
+ tag_words(x , min = 1 )
161
+ }
162
+ # ' @export
163
+ roxy_tag_ns.roxy_tag_exportPattern <- function (x , block , env , import_only = FALSE ) {
164
+ if (import_only ) {
165
+ return ()
166
+ }
167
+ one_per_line(" exportPattern" , x $ val )
168
+ }
169
+
170
+ # ' @export
171
+ roxy_tag_parse.roxy_tag_exportS3Method <- function (x ) {
172
+ tag_words(x , min = 0 , max = 2 )
173
+ }
174
+ # ' @export
175
+ roxy_tag_ns.roxy_tag_exportS3Method <- function (x , block , env , import_only = FALSE ) {
176
+ if (import_only ) {
177
+ return ()
178
+ }
179
+
180
+ obj <- block $ object
181
+ if (length(x $ val ) < 2 && ! inherits(obj , " s3method" )) {
182
+ roxy_tag_warning(x ,
164
183
" `@exportS3Method` and `@exportS3Method generic` must be used with an S3 method"
165
184
)
166
185
return ()
167
186
}
168
187
169
- if (identical(tag $ val , " " )) {
188
+ if (identical(x $ val , " " )) {
170
189
method <- attr(obj $ value , " s3method" )
171
- } else if (length(tag $ val ) == 1 ) {
172
- method <- c(tag $ val , attr(obj $ value , " s3method" )[[2 ]])
190
+ } else if (length(x $ val ) == 1 ) {
191
+ method <- c(x $ val , attr(obj $ value , " s3method" )[[2 ]])
173
192
} else {
174
- method <- tag $ val
193
+ method <- x $ val
175
194
}
176
195
177
196
export_s3_method(method )
178
197
}
179
198
180
- ns_useDynLib <- function (tag , block , env ) {
181
- if (length(tag $ val ) == 1 ) {
182
- return (paste0(" useDynLib(" , auto_quote(tag $ val ), " )" ))
199
+ # ' @export
200
+ roxy_tag_parse.roxy_tag_import <- function (x ) {
201
+ tag_words(x , min = 1 )
202
+ }
203
+ # ' @export
204
+ roxy_tag_ns.roxy_tag_import <- function (x , block , env , import_only = FALSE ) {
205
+ one_per_line(" import" , x $ val )
206
+ }
207
+
208
+ # ' @export
209
+ roxy_tag_parse.roxy_tag_importClassesFrom <- function (x ) {
210
+ tag_words(x , min = 2 )
211
+ }
212
+ # ' @export
213
+ roxy_tag_ns.roxy_tag_importClassesFrom <- function (x , block , env , import_only = FALSE ) {
214
+ repeat_first(" importClassesFrom" , x $ val )
215
+ }
216
+
217
+ # ' @export
218
+ roxy_tag_parse.roxy_tag_importFrom <- function (x ) {
219
+ tag_words(x , min = 2 )
220
+ }
221
+ # ' @export
222
+ roxy_tag_ns.roxy_tag_importFrom <- function (x , block , env , import_only = FALSE ) {
223
+ repeat_first(" importFrom" , x $ val )
224
+ }
225
+
226
+ # ' @export
227
+ roxy_tag_parse.roxy_tag_importMethodsFrom <- function (x ) {
228
+ tag_words(x , min = 2 )
229
+ }
230
+ # ' @export
231
+ roxy_tag_ns.roxy_tag_importMethodsFrom <- function (x , block , env , import_only = FALSE ) {
232
+ repeat_first(" importMethodsFrom" , x $ val )
233
+ }
234
+
235
+ # ' @export
236
+ roxy_tag_parse.roxy_tag_rawNamespace <- function (x ) {
237
+ tag_code(x )
238
+ }
239
+ # ' @export
240
+ roxy_tag_ns.roxy_tag_rawNamespace <- function (x , block , env , import_only = FALSE ) {
241
+ x $ val
242
+ }
243
+
244
+ # ' @export
245
+ roxy_tag_parse.roxy_tag_useDynLib <- function (x ) {
246
+ tag_words(x , min = 1 )
247
+ }
248
+ # ' @export
249
+ roxy_tag_ns.roxy_tag_useDynLib <- function (x , block , env , import_only = FALSE ) {
250
+ if (length(x $ val ) == 1 ) {
251
+ return (paste0(" useDynLib(" , auto_quote(x $ val ), " )" ))
183
252
}
184
253
185
- if (any(grepl(" ," , tag $ val ))) {
254
+ if (any(grepl(" ," , x $ val ))) {
186
255
# If there's a comma in list, don't quote output. This makes it possible
187
256
# for roxygen2 to support other NAMESPACE forms not otherwise mapped
188
- args <- paste0(tag $ val , collapse = " " )
257
+ args <- paste0(x $ val , collapse = " " )
189
258
paste0(" useDynLib(" , args , " )" )
190
259
} else {
191
- repeat_first(" useDynLib" , tag $ val )
260
+ repeat_first(" useDynLib" , x $ val )
192
261
}
193
262
}
194
- ns_rawNamespace <- function (tag , block , env ) tag $ val
195
- ns_evalNamespace <- function (tag , block , env ) {
196
- roxy_tag_eval(tag , env )
197
- }
198
-
199
- # Functions used by both default_export and ns_* functions
200
- export <- function (x ) one_per_line(" export" , x )
201
- export_class <- function (x ) one_per_line(" exportClasses" , x )
202
- export_s4_method <- function (x ) one_per_line(" exportMethods" , x )
203
- export_s3_method <- function (x ) {
204
- args <- paste0(auto_backtick(x ), collapse = " ," )
205
- paste0(" S3method(" , args , " )" )
206
- }
207
263
208
264
# Default export methods --------------------------------------------------
209
265
@@ -223,9 +279,16 @@ default_export.default <- function(x, block) export(x$alias)
223
279
# ' @export
224
280
default_export.NULL <- function (x , block ) export(block_get_tag_value(block , " name" ))
225
281
226
-
227
282
# Helpers -----------------------------------------------------------------
228
283
284
+ export <- function (x ) one_per_line(" export" , x )
285
+ export_class <- function (x ) one_per_line(" exportClasses" , x )
286
+ export_s4_method <- function (x ) one_per_line(" exportMethods" , x )
287
+ export_s3_method <- function (x ) {
288
+ args <- paste0(auto_backtick(x ), collapse = " ," )
289
+ paste0(" S3method(" , args , " )" )
290
+ }
291
+
229
292
one_per_line <- function (name , x ) {
230
293
paste0(name , " (" , auto_backtick(x ), " )" )
231
294
}
0 commit comments