@@ -32,6 +32,131 @@ rd_roclet_description <- function() {
32
32
)
33
33
}
34
34
35
+ # ' @export
36
+ roclet_process.roclet_rd <- function (x ,
37
+ blocks ,
38
+ env ,
39
+ base_path ,
40
+ global_options = list ()) {
41
+
42
+ # Convert each block into a topic, indexed by filename
43
+ topics <- RoxyTopics $ new()
44
+
45
+ for (block in blocks ) {
46
+ rd <- block_to_rd(block , base_path , env , global_options )
47
+ topics $ add(rd )
48
+ }
49
+ topics_process_family(topics , env )
50
+ topics_process_inherit(topics , env )
51
+ topics $ drop_invalid()
52
+ topics_fix_params_order(topics )
53
+ topics_add_default_description(topics )
54
+
55
+ topics $ topics
56
+ }
57
+
58
+ # ' @export
59
+ roclet_output.roclet_rd <- function (x , results , base_path , ... , is_first = FALSE ) {
60
+ man <- normalizePath(file.path(base_path , " man" ))
61
+
62
+ contents <- map_chr(results , format , wrap = FALSE )
63
+ paths <- file.path(man , names(results ))
64
+
65
+ # Always check for roxygen2 header before overwriting NAMESPACE (#436),
66
+ # even when running for the first time
67
+ mapply(write_if_different , paths , contents , MoreArgs = list (check = TRUE ))
68
+
69
+ if (! is_first ) {
70
+ # Automatically delete any files in man directory that were generated
71
+ # by roxygen in the past, but weren't generated in this sweep.
72
+
73
+ old_paths <- setdiff(dir(man , full.names = TRUE ), paths )
74
+ old_paths <- old_paths [! file.info(old_paths )$ isdir ]
75
+ old_roxygen <- Filter(made_by_roxygen , old_paths )
76
+ if (length(old_roxygen ) > 0 ) {
77
+ message(paste0(" Deleting " , basename(old_roxygen ), collapse = " \n " ))
78
+ unlink(old_roxygen )
79
+ }
80
+ }
81
+
82
+ paths
83
+ }
84
+
85
+ # ' @export
86
+ roclet_clean.roclet_rd <- function (x , base_path ) {
87
+ rd <- dir(file.path(base_path , " man" ), full.names = TRUE )
88
+ rd <- rd [! file.info(rd )$ isdir ]
89
+ unlink(purrr :: keep(rd , made_by_roxygen ))
90
+ }
91
+
92
+ # Does this block get an Rd file?
93
+ needs_doc <- function (block ) {
94
+ if (block_has_tags(block , " noRd" )) {
95
+ return (FALSE )
96
+ }
97
+
98
+ block_has_tags(block , c(
99
+ " description" , " param" , " return" , " title" , " example" ,
100
+ " examples" , " name" , " rdname" , " usage" , " details" , " introduction" ,
101
+ " inherit" , " describeIn" )
102
+ )
103
+ }
104
+
105
+ # Tag processing functions ------------------------------------------------
106
+
107
+ block_to_rd <- function (block , base_path , env , global_options = list ()) {
108
+ # Must start by processing templates
109
+ block <- process_templates(block , base_path , global_options )
110
+
111
+ if (! needs_doc(block )) {
112
+ return ()
113
+ }
114
+
115
+ name <- block_get_tag(block , " name" )$ val %|| % block $ object $ topic
116
+ if (is.null(name )) {
117
+ roxy_tag_warning(block $ tags [[1 ]], " Missing name" )
118
+ return ()
119
+ }
120
+
121
+ # Note that order of operations here doesn't matter: fields are
122
+ # ordered by RoxyFile$format()
123
+ rd <- RoxyTopic $ new()
124
+ topic_add_name_aliases(rd , block , name )
125
+
126
+ # Some fields added directly by roxygen internals
127
+ tags <- Filter(roxy_tag_is_field , block $ tags )
128
+ for (tag in tags ) {
129
+ rd $ add(tag $ val )
130
+ }
131
+
132
+ topic_add_backref(rd , block )
133
+ topic_add_doc_type(rd , block )
134
+ topic_add_eval_rd(rd , block , env )
135
+ topic_add_include_rmd(rd , block , base_path )
136
+ topic_add_examples(rd , block , base_path )
137
+ topic_add_fields(rd , block )
138
+ topic_add_inherit(rd , block )
139
+ topic_add_keyword(rd , block )
140
+ topic_add_methods(rd , block )
141
+ topic_add_params(rd , block )
142
+ topic_add_simple_tags(rd , block )
143
+ topic_add_sections(rd , block )
144
+ topic_add_slots(rd , block )
145
+ topic_add_usage(rd , block , old_usage = global_options $ old_usage )
146
+ topic_add_value(rd , block )
147
+
148
+ if (rd $ has_field(" description" ) && rd $ has_field(" reexport" )) {
149
+ roxy_tag_warning(block $ tags [[1 ]], " Can't use description when re-exporting" )
150
+ return ()
151
+ }
152
+
153
+ describe_rdname <- topic_add_describe_in(rd , block , env )
154
+ filename <- describe_rdname %|| % block_get_tag(block , " rdname" )$ val %|| % nice_name(name )
155
+ rd $ filename <- paste0(filename , " .Rd" )
156
+
157
+ rd
158
+ }
159
+
35
160
# ' @export
36
161
roxy_tag_parse.roxy_tag_aliases <- function (x ) tag_value(x )
37
162
# ' @export
@@ -113,28 +238,6 @@ roxy_tag_parse.roxy_tag_title <- function(x) tag_markdown(x)
113
238
# ' @export
114
239
roxy_tag_parse.roxy_tag_usage <- function (x ) tag_value(x )
115
240
116
- # ' @export
117
- roclet_process.roclet_rd <- function (x ,
118
- blocks ,
119
- env ,
120
- base_path ,
121
- global_options = list ()) {
122
-
123
- # Convert each block into a topic, indexed by filename
124
- topics <- RoxyTopics $ new()
125
-
126
- for (block in blocks ) {
127
- rd <- block_to_rd(block , base_path , env , global_options )
128
- topics $ add(rd )
129
- }
130
- topics_process_family(topics , env )
131
- topics_process_inherit(topics , env )
132
- topics $ drop_invalid()
133
- topics_fix_params_order(topics )
134
- topics_add_default_description(topics )
135
-
136
- topics $ topics
137
- }
138
241
139
242
topics_add_default_description <- function (topics ) {
140
243
for (topic in topics $ topics ) {
@@ -151,108 +254,6 @@ topics_add_default_description <- function(topics) {
151
254
}
152
255
153
256
154
- block_to_rd <- function (block , base_path , env , global_options = list ()) {
155
- # Must start by processing templates
156
- block <- process_templates(block , base_path , global_options )
157
-
158
- if (! needs_doc(block )) {
159
- return ()
160
- }
161
-
162
- name <- block_get_tag(block , " name" )$ val %|| % block $ object $ topic
163
- if (is.null(name )) {
164
- roxy_tag_warning(block $ tags [[1 ]], " Missing name" )
165
- return ()
166
- }
167
-
168
- # Note that order of operations here doesn't matter: fields are
169
- # ordered by RoxyFile$format()
170
- rd <- RoxyTopic $ new()
171
- topic_add_name_aliases(rd , block , name )
172
-
173
- # Some fields added directly by roxygen internals
174
- tags <- Filter(roxy_tag_is_field , block $ tags )
175
- for (tag in tags ) {
176
- rd $ add(tag $ val )
177
- }
178
-
179
- topic_add_backref(rd , block )
180
- topic_add_doc_type(rd , block )
181
- topic_add_eval_rd(rd , block , env )
182
- topic_add_include_rmd(rd , block , base_path )
183
- topic_add_examples(rd , block , base_path )
184
- topic_add_fields(rd , block )
185
- topic_add_inherit(rd , block )
186
- topic_add_keyword(rd , block )
187
- topic_add_methods(rd , block )
188
- topic_add_params(rd , block )
189
- topic_add_simple_tags(rd , block )
190
- topic_add_sections(rd , block )
191
- topic_add_slots(rd , block )
192
- topic_add_usage(rd , block , old_usage = global_options $ old_usage )
193
- topic_add_value(rd , block )
194
-
195
- if (rd $ has_field(" description" ) && rd $ has_field(" reexport" )) {
196
- roxy_tag_warning(block $ tags [[1 ]], " Can't use description when re-exporting" )
197
- return ()
198
- }
199
-
200
- describe_rdname <- topic_add_describe_in(rd , block , env )
201
- filename <- describe_rdname %|| % block_get_tag(block , " rdname" )$ val %|| % nice_name(name )
202
- rd $ filename <- paste0(filename , " .Rd" )
203
-
204
- rd
205
- }
206
-
207
- # ' @export
208
- roclet_output.roclet_rd <- function (x , results , base_path , ... , is_first = FALSE ) {
209
- man <- normalizePath(file.path(base_path , " man" ))
210
-
211
- contents <- map_chr(results , format , wrap = FALSE )
212
- paths <- file.path(man , names(results ))
213
-
214
- # Always check for roxygen2 header before overwriting NAMESPACE (#436),
215
- # even when running for the first time
216
- mapply(write_if_different , paths , contents , MoreArgs = list (check = TRUE ))
217
-
218
- if (! is_first ) {
219
- # Automatically delete any files in man directory that were generated
220
- # by roxygen in the past, but weren't generated in this sweep.
221
-
222
- old_paths <- setdiff(dir(man , full.names = TRUE ), paths )
223
- old_paths <- old_paths [! file.info(old_paths )$ isdir ]
224
- old_roxygen <- Filter(made_by_roxygen , old_paths )
225
- if (length(old_roxygen ) > 0 ) {
226
- message(paste0(" Deleting " , basename(old_roxygen ), collapse = " \n " ))
227
- unlink(old_roxygen )
228
- }
229
- }
230
-
231
- paths
232
- }
233
-
234
- # ' @export
235
- roclet_clean.roclet_rd <- function (x , base_path ) {
236
- rd <- dir(file.path(base_path , " man" ), full.names = TRUE )
237
- rd <- rd [! file.info(rd )$ isdir ]
238
- unlink(purrr :: keep(rd , made_by_roxygen ))
239
- }
240
-
241
- # Does this block get an Rd file?
242
- needs_doc <- function (block ) {
243
- if (block_has_tags(block , " noRd" )) {
244
- return (FALSE )
245
- }
246
-
247
- block_has_tags(block , c(
248
- " description" , " param" , " return" , " title" , " example" ,
249
- " examples" , " name" , " rdname" , " usage" , " details" , " introduction" ,
250
- " inherit" , " describeIn" )
251
- )
252
- }
253
-
254
- # Tag processing functions ------------------------------------------------
255
-
256
257
topic_add_backref <- function (topic , block ) {
257
258
tags <- block_get_tags(block , " backref" )
258
259
for (tag in tags ) {
0 commit comments