diff options
Diffstat (limited to 'pkgtools/R2pkg')
-rw-r--r-- | pkgtools/R2pkg/files/R2pkg.R | 551 | ||||
-rw-r--r-- | pkgtools/R2pkg/files/R2pkg_test.R | 1079 |
2 files changed, 776 insertions, 854 deletions
diff --git a/pkgtools/R2pkg/files/R2pkg.R b/pkgtools/R2pkg/files/R2pkg.R index 00aecf7f1bf..f2a16dabb06 100644 --- a/pkgtools/R2pkg/files/R2pkg.R +++ b/pkgtools/R2pkg/files/R2pkg.R @@ -1,4 +1,4 @@ -# $NetBSD: R2pkg.R,v 1.26 2019/10/19 22:10:58 rillig Exp $ +# $NetBSD: R2pkg.R,v 1.27 2019/10/25 19:00:16 rillig Exp $ # # Copyright (c) 2014,2015,2016,2017,2018,2019 # Brook Milligan. All rights reserved. @@ -141,41 +141,37 @@ licenses[['POSTGRESQL']] <- 'postgresql-license' adjacent.duplicates <- function(lines) c(FALSE, lines[-length(lines)] == lines[-1]) -paste2 <- function(s1,s2) -{ - if (is.na(s1) && is.na(s2)) return ('') - if (is.na(s1) && !is.na(s2)) return (s2) - if (!is.na(s1) && is.na(s2)) return (s1) - if (!is.na(s1) && !is.na(s2)) return (paste(s1,s2)) +paste2 <- function(s1, s2) { + if (is.na(s1) && is.na(s2)) return('') + if (is.na(s1) && !is.na(s2)) return(s2) + if (!is.na(s1) && is.na(s2)) return(s1) + if (!is.na(s1) && !is.na(s2)) return(paste(s1, s2)) } end.paragraph <- function(lines) if (length(lines) > 0) append(lines, '') else lines -as.sorted.list <- function(df) -{ +as.sorted.list <- function(df) { l <- list() df <- df[!duplicated(df),] if (nrow(df) > 0) - { - key <- as.vector(df[,1]) - value <- as.vector(df[,2]) - key <- order(key,value) - l <- as.list(value[key]) - } + { + key <- as.vector(df[, 1]) + value <- as.vector(df[, 2]) + key <- order(key, value) + l <- as.list(value[key]) + } l } -mklines.get_value <- function(mklines, varname, default = '') -{ +mklines.get_value <- function(mklines, varname, default = '') { values <- mklines$old_value[mklines$key == varname] if (length(values) == 0) values <- mklines$old_value[mklines$key == paste0('#', varname)] if (length(values) == 1) values[1] else default } -categorize.key_value <- function(df,line='line') -{ +categorize.key_value <- function(df, line='line') { re_varassign <- paste0( '^', ' *', @@ -198,8 +194,7 @@ categorize.key_value <- function(df,line='line') df } -categorize.depends <- function(df, line='line') -{ +categorize.depends <- function(df, line='line') { df$depends <- df$key_value & df$key == 'DEPENDS' df$category[df$depends] <- unlist(relpath_category(df[df$depends, line])) df @@ -212,32 +207,29 @@ categorize.buildlink <- function(df, line='line') df } -fix.continued.lines <- function(df,line='line') -{ +fix.continued.lines <- function(df, line='line') { if (nrow(df) < 2) return(df) continued <- grepl('\\\\$', df[, line]) continued_key_value <- df$key_value & continued - if (FALSE %in% df[continued,'key_value']) + if (FALSE %in% df[continued, 'key_value']) level.warning('unhandled continued line(s)') - for (i in 1 : (nrow(df) - 1)) - { - if (!continued_key_value[i]) - next + for (i in 1:(nrow(df) - 1)) { + if (!continued_key_value[i]) + next - df[i, line] <- sub('[\t ]*\\\\$', '', df[i, line]) - df$key_value[i + 1] <- TRUE - df$key[i + 1] <- df$key[i] - df[i + 1, line] <- paste0(df$key[i], '+=', df[i + 1, line]) - } + df[i, line] <- sub('[\t ]*\\\\$', '', df[i, line]) + df$key_value[i + 1] <- TRUE + df$key[i + 1] <- df$key[i] + df[i + 1, line] <- paste0(df$key[i], '+=', df[i + 1, line]) + } df } -read_mklines <- function(filename) -{ +read_mklines <- function(filename) { df <- data.frame() for (line in as.list(readLines(filename))) df <- rbind(df, data.frame(line = line, stringsAsFactors = FALSE)) @@ -252,16 +244,14 @@ read_mklines <- function(filename) df } -read.file.as.list <- function(filename) -{ +read.file.as.list <- function(filename) { result <- list() info <- file.info(filename) - size <- info[filename,'size'] - if (!is.na(size) && size > 0) - { - contents <- readLines(filename) - result <- as.list(contents) - } + size <- info[filename, 'size'] + if (!is.na(size) && size > 0) { + contents <- readLines(filename) + result <- as.list(contents) + } result } @@ -270,22 +260,19 @@ remove.punctuation <- function(s) gsub('[,-]', '', s) remove.quotes <- function(s) gsub('[\'`"]', '', s) remove.articles <- function(s) gsub('\\b[Aa]n?\\b', '\\1', s) -case.insensitive.equals <- function(s1,s2) -{ +case.insensitive.equals <- function(s1, s2) { s1.lower <- tolower(simplify.whitespace(s1)) s2.lower <- tolower(simplify.whitespace(s2)) s1.lower == s2.lower } -weakly.equals <- function(s1,s2) -{ +weakly.equals <- function(s1, s2) { case.insensitive.equals( remove.articles(remove.quotes(remove.punctuation(s1))), remove.articles(remove.quotes(remove.punctuation(s2)))) } -license <- function(mklines, s) -{ +license <- function(mklines, s) { license <- licenses[[s]] if (is.null(license)) license <- s @@ -298,68 +285,59 @@ license <- function(mklines, s) find.Rcpp <- function(imps, deps) any(grepl('Rcpp', paste(imps, deps))) -buildlink3.mk <- function(imps,deps) -{ +buildlink3.mk <- function(imps, deps) { BUILDLINK3.MK <- data.frame() buildlink3.mk.list <- read.file.as.list('BUILDLINK3.MK') - for (line in buildlink3.mk.list) - { - fields <- strsplit(line[[1]],'/',fixed=TRUE) - key <- fields[[1]][3] - value <- line - BUILDLINK3.MK <- rbind(BUILDLINK3.MK,data.frame(key=key,value=value)) - } - if (find.Rcpp(imps,deps)) - { - buildlink3.line <- '.include "../../devel/R-Rcpp/buildlink3.mk"' - key <- 'devel' - value <- buildlink3.line - BUILDLINK3.MK <- rbind(BUILDLINK3.MK,data.frame(key=key,value=value)) - } + for (line in buildlink3.mk.list) { + fields <- strsplit(line[[1]], '/', fixed = TRUE) + key <- fields[[1]][3] + value <- line + BUILDLINK3.MK <- rbind(BUILDLINK3.MK, data.frame(key = key, value = value)) + } + if (find.Rcpp(imps, deps)) { + buildlink3.line <- '.include "../../devel/R-Rcpp/buildlink3.mk"' + key <- 'devel' + value <- buildlink3.line + BUILDLINK3.MK <- rbind(BUILDLINK3.MK, data.frame(key = key, value = value)) + } BUILDLINK3.MK } -varassigns <- function(key, values) -{ +varassigns <- function(key, values) { fields <- list() - for (l in values) - { - value <- unlist(l) - if (value != '') - fields <- append(fields, varassign(key, list(value))) - else - fields <- append(fields, list('')) - } + for (l in values) { + value <- unlist(l) + if (value != '') + fields <- append(fields, varassign(key, list(value))) + else + fields <- append(fields, list('')) + } fields } categories <- function() basename(dirname(getwd())) -filter.imports <- function(s) -{ - for (pkg in base.packages) - { - re.pkg <- paste('^',pkg,sep='') - s <- s[!grepl(re.pkg,s)] - } +filter.imports <- function(s) { + for (pkg in base.packages) { + re.pkg <- paste('^', pkg, sep = '') + s <- s[!grepl(re.pkg, s)] + } s } -make.imports <- function(s1,s2) -{ - s <- paste2(s1,s2) - s <- gsub('([[:alnum:]]+)[[:blank:]]+(\\([^\\)]*\\))?[[:blank:]]*,?','\\1 \\2,',s) - imports <- na.omit(unlist(strsplit(s,',[[:blank:]]*'))) +make.imports <- function(s1, s2) { + s <- paste2(s1, s2) + s <- gsub('([[:alnum:]]+)[[:blank:]]+(\\([^\\)]*\\))?[[:blank:]]*,?', '\\1 \\2,', s) + imports <- na.omit(unlist(strsplit(s, ',[[:blank:]]*'))) imports <- trim.space(imports) imports <- filter.imports(imports) imports } -make.dependency <- function(s) -{ - s <- gsub('\\)','',s) - s <- gsub('-','.',s) - unlist(strsplit(s,'\\(')) +make.dependency <- function(s) { + s <- gsub('\\)', '', s) + s <- gsub('-', '.', s) + unlist(strsplit(s, '\\(')) } depends <- function(dependency) dependency[1] @@ -370,20 +348,17 @@ depends.pkg <- function(dependency) new.depends.pkg <- function(dependency) Sys.glob(paste0('../../wip/R-', depends(dependency))) -depends.pkg.fullname <- function(dependency,index=1) -{ - result <- system(paste('cd',depends.pkg(dependency)[index],'&& bmake show-var VARNAME=PKGNAME'),intern=TRUE) +depends.pkg.fullname <- function(dependency, index=1) { + result <- system(paste('cd', depends.pkg(dependency)[index], '&& bmake show-var VARNAME=PKGNAME'), intern = TRUE) result } -depends.pkg.vers <- function(dependency,index=1) -{ - result <- sub('^(.*)-([^-]*)$','\\2',depends.pkg.fullname(dependency,index)) +depends.pkg.vers <- function(dependency, index=1) { + result <- sub('^(.*)-([^-]*)$', '\\2', depends.pkg.fullname(dependency, index)) result } -depends.vers <- function(dependency, index=1) -{ +depends.vers <- function(dependency, index=1) { if (length(dependency) == 2) trim.space(dependency[2]) else @@ -393,23 +368,20 @@ depends.vers <- function(dependency, index=1) depends.vers.2 <- function(dependency) ifelse(length(dependency) == 2, trim.space(dependency[2]), '>=???') -depends.dir <- function(dependency, index=1) -{ +depends.dir <- function(dependency, index=1) { fields <- strsplit(depends.pkg(dependency)[index], '/', fixed = TRUE) fields[[1]][3] } -depends.line <- function(dependency,index=1) -{ +depends.line <- function(dependency, index=1) { paste0('DEPENDS+=\tR-', depends(dependency), depends.vers(dependency, index), ':', depends.pkg(dependency)[index]) } -depends.line.2 <- function(dependency) -{ - result <- paste0('DEPENDS+=\tR-',depends,depends.vers.2(dependency),':../../???/R-',depends) - result <- paste0(result,'\t# XXX - found') +depends.line.2 <- function(dependency) { + result <- paste0('DEPENDS+=\tR-', depends, depends.vers.2(dependency), ':../../???/R-', depends) + result <- paste0(result, '\t# XXX - found') for (pkg in depends.pkg(dependency)) - result <- paste(result,pkg) + result <- paste(result, pkg) result } @@ -419,23 +391,20 @@ buildlink3.file <- function(dependency, index=1) buildlink3.line <- function(dependency, index=1) sprintf('.include "%s"', buildlink3.file(dependency, index)) -dependency.dir <- function(dependency) -{ - result <- paste0('../../wip/R-',depends(dependency)) +dependency.dir <- function(dependency) { + result <- paste0('../../wip/R-', depends(dependency)) result } -message.wip.dependency <- function(dependency,index=1) -{ - dir <- depends.dir(dependency,index) - dir.in.wip <- grepl('wip',dir) - wd.in.wip <- grepl('/wip/',getwd()) +message.wip.dependency <- function(dependency, index=1) { + dir <- depends.dir(dependency, index) + dir.in.wip <- grepl('wip', dir) + wd.in.wip <- grepl('/wip/', getwd()) if (dir.in.wip && !wd.in.wip) - level.warning('R-',arg.rpkg,' should not depend on a wip package: ',depends.pkg(dependency)[index]) + level.warning('R-', arg.rpkg, ' should not depend on a wip package: ', depends.pkg(dependency)[index]) } -update.dependency <- function(dependency, index=1) -{ +update.dependency <- function(dependency, index=1) { level.message('updating dependency for ', depends(dependency), ': ', depends.pkg(dependency)[index]) command <- sprintf( 'grep -E -q -e "%s" %s || (cd %s && %s %s %s)', @@ -446,92 +415,76 @@ update.dependency <- function(dependency, index=1) level.warning('error updating dependency for ', depends(dependency)) } -make.depends <- function(imps,deps) -{ +make.depends <- function(imps, deps) { warn_too_many_dependencies <- function(dependency) { level.warning(sprintf('too many dependencies found for %s: %s', - depends(dependency), paste(depends.pkg(dependency)))) + depends(dependency), paste(depends.pkg(dependency)))) } - imports <- make.imports(imps,deps) - # XXX message('===> imports:') - # XXX print(imports) + imports <- make.imports(imps, deps) +# XXX message('===> imports:') +# XXX print(imports) DEPENDS <- data.frame() - BUILDLINK3.MK <- buildlink3.mk(imps,deps) - if (length(imports) > 0) - { - for (i in 1:length(imports)) - { - dependency <- make.dependency(imports[i]) - depdirs <- depends.pkg(dependency) - # XXX message('[ ',${LEVEL},' ] ===> ',i,' / ',length(imports),': ',depends(dependency)) - if (length(depdirs) == 0) # a dependency cannot be found - { - level.message('0 dependencies match ',dependency) - if (arg.recursive) - { - dir.create(path=dependency.dir(dependency),recursive=TRUE) - update.dependency(dependency) - } - else - level.warning('dependency needed for ',depends(dependency)) - } - else if (length(depdirs) == 1) # a unique dependency found - { - level.message('1 dependency matches ',dependency,': ',depdirs) - message.wip.dependency(dependency) - if (arg.recursive && arg.update) - update.dependency(dependency) - if (file.exists(buildlink3.file(dependency))) - BUILDLINK3.MK <- rbind(BUILDLINK3.MK,data.frame(key=depends.dir(dependency),value=buildlink3.line(dependency))) - else - DEPENDS <- rbind(DEPENDS,data.frame(key=depends.dir(dependency),value=depends.line(dependency))) - } - else if (length(depdirs) == 2) # two dependencies found - { - index <- grep('/wip/',depdirs,invert=TRUE) - level.message('2 dependencies match ',dependency,':',paste(' ',depdirs)) - # message('===> depends(dependency): ',depends(dependency)) - # message('===> depends.pkg(dependency):',paste(' ',d)) - # message('===> index: ',index) - # message('===> buildlink3.line(): ',buildlink3.line(dependency,index)) - if (length(index) == 1) # a unique, non-wip, dependency found - { - level.message('choosing unique non-wip dependency for ',dependency,': ',depdirs[index]) - if (arg.recursive && arg.update) - update.dependency(dependency,index) - if (file.exists(buildlink3.file(dependency,index))) - BUILDLINK3.MK <- rbind(BUILDLINK3.MK,data.frame(key=depends.dir(dependency,index),value=buildlink3.line(dependency,index))) - else - DEPENDS <- rbind(DEPENDS,data.frame(key=depends.dir(dependency,index),value=depends.line(dependency,index))) - } - else - { - level.message('no unique non-wip dependency matches') - warn_too_many_dependencies(dependency) - DEPENDS <- rbind(DEPENDS,data.frame(key='???',value=depends.line.2(dependency))) - } - } - else # more than 2 dependencies found - { - level.message(length(depdirs),' dependencies match ',dependency,':',paste(' ',depdirs)) - warn_too_many_dependencies(dependency) - DEPENDS <- rbind(DEPENDS,data.frame(key='???',value=depends.line.2(dependency))) - } - if (length(new.depends.pkg(dependency)) > 0) - system(paste('echo', depends(dependency), arg.rpkg, '>>', arg.dependency_list)) + BUILDLINK3.MK <- buildlink3.mk(imps, deps) + if (length(imports) > 0) { + for (i in 1:length(imports)) { + dependency <- make.dependency(imports[i]) + depdirs <- depends.pkg(dependency) + # XXX message('[ ',${LEVEL},' ] ===> ',i,' / ',length(imports),': ',depends(dependency)) + if (length(depdirs) == 0) { # a dependency cannot be found + level.message('0 dependencies match ', dependency) + if (arg.recursive) { + dir.create(path = dependency.dir(dependency), recursive = TRUE) + update.dependency(dependency) + } else + level.warning('dependency needed for ', depends(dependency)) + } else if (length(depdirs) == 1) { # a unique dependency found + level.message('1 dependency matches ', dependency, ': ', depdirs) + message.wip.dependency(dependency) + if (arg.recursive && arg.update) + update.dependency(dependency) + if (file.exists(buildlink3.file(dependency))) + BUILDLINK3.MK <- rbind(BUILDLINK3.MK, data.frame(key = depends.dir(dependency), value = buildlink3.line(dependency))) + else + DEPENDS <- rbind(DEPENDS, data.frame(key = depends.dir(dependency), value = depends.line(dependency))) + } else if (length(depdirs) == 2) { # two dependencies found + index <- grep('/wip/', depdirs, invert = TRUE) + level.message('2 dependencies match ', dependency, ':', paste(' ', depdirs)) + # message('===> depends(dependency): ',depends(dependency)) + # message('===> depends.pkg(dependency):',paste(' ',d)) + # message('===> index: ',index) + # message('===> buildlink3.line(): ',buildlink3.line(dependency,index)) + if (length(index) == 1) { # a unique, non-wip, dependency found + level.message('choosing unique non-wip dependency for ', dependency, ': ', depdirs[index]) + if (arg.recursive && arg.update) + update.dependency(dependency, index) + if (file.exists(buildlink3.file(dependency, index))) + BUILDLINK3.MK <- rbind(BUILDLINK3.MK, data.frame(key = depends.dir(dependency, index), value = buildlink3.line(dependency, index))) + else + DEPENDS <- rbind(DEPENDS, data.frame(key = depends.dir(dependency, index), value = depends.line(dependency, index))) + } else { + level.message('no unique non-wip dependency matches') + warn_too_many_dependencies(dependency) + DEPENDS <- rbind(DEPENDS, data.frame(key = '???', value = depends.line.2(dependency))) } + } else { # more than 2 dependencies found + level.message(length(depdirs), ' dependencies match ', dependency, ':', paste(' ', depdirs)) + warn_too_many_dependencies(dependency) + DEPENDS <- rbind(DEPENDS, data.frame(key = '???', value = depends.line.2(dependency))) + } + if (length(new.depends.pkg(dependency)) > 0) + system(paste('echo', depends(dependency), arg.rpkg, '>>', arg.dependency_list)) } + } DEPENDS <- end.paragraph(as.sorted.list(DEPENDS)) BUILDLINK3.MK <- as.sorted.list(BUILDLINK3.MK) - list(DEPENDS,BUILDLINK3.MK) + list(DEPENDS, BUILDLINK3.MK) } use_languages <- function(imps, deps) if (find.Rcpp(imps, deps)) 'c c++' else '# none' -write.Makefile <- function(orig_mklines, metadata) -{ +write.Makefile <- function(orig_mklines, metadata) { maintainer <- mklines.get_value(orig_mklines, 'MAINTAINER', arg.maintainer_email) license <- license(orig_mklines, metadata$License) use_languages <- use_languages(metadata$Imports, metadata$Depends) @@ -559,24 +512,21 @@ write.Makefile <- function(orig_mklines, metadata) writeLines(lines, 'Makefile') } -element <- function(mklines, varname, field, quiet=FALSE) -{ +element <- function(mklines, varname, field, quiet=FALSE) { i <- match(varname, mklines$key, 0) if (i != 0 && mklines$key_value[i]) return(mklines[i, field]) - if (!quiet) - { - if (i == 0) - level.warning(varname, ' not found') - else - level.warning(varname, ' is not a key-value field') - } + if (!quiet) { + if (i == 0) + level.warning(varname, ' not found') + else + level.warning(varname, ' is not a key-value field') + } '???' } -make.categories <- function(mklines) -{ +make.categories <- function(mklines) { directory <- basename(dirname(getwd())) categories <- unlist(element(mklines, 'CATEGORIES', 'old_value')) categories <- unlist(strsplit(categories, '[[:blank:]]+')) @@ -588,15 +538,13 @@ make.categories <- function(mklines) paste(categories, collapse = ' ') } -make.maintainer <- function(mklines) -{ +make.maintainer <- function(mklines) { old.maintainer <- element(mklines, 'MAINTAINER', 'old_value') new.maintainer <- element(mklines, 'MAINTAINER', 'new_value') if (old.maintainer == '') new.maintainer else old.maintainer } -make.comment <- function(mklines) -{ +make.comment <- function(mklines) { old.comment <- element(mklines, 'COMMENT', 'old_value') new.comment <- element(mklines, 'COMMENT', 'new_value') if (weakly.equals(old.comment, new.comment)) @@ -605,23 +553,21 @@ make.comment <- function(mklines) paste0(old.comment, '\t# [R2pkg] updated to: ', new.comment) } -make.new_license <- function(df,license) -{ +make.new_license <- function(df, license) { new_license <- licenses[[license]] if (is.null(new_license)) - new_license <- license + new_license <- license df$new_value[df$key == 'LICENSE'] <- new_license df } license.in.pkgsrc <- function(license) license %in% sapply(licenses, '[', 1) -make.license <- function(df) -{ +make.license <- function(df) { # message('===> make.license():') - old_license <- element(df,'LICENSE','old_value') - old_todo <- element(df,'LICENSE','old_todo') - new_license <- element(df,'LICENSE','new_value') + old_license <- element(df, 'LICENSE', 'old_value') + old_todo <- element(df, 'LICENSE', 'old_todo') + new_license <- element(df, 'LICENSE', 'new_value') old_known <- license.in.pkgsrc(old_license) new_known <- license.in.pkgsrc(new_license) @@ -641,17 +587,15 @@ make.license <- function(df) df } -find.order <- function(df,key,field) -{ - x <- df[,key] - value <- match(TRUE,x) +find.order <- function(df, key, field) { + x <- df[, key] + value <- match(TRUE, x) if (!is.na(value)) - value <- df[value,field] + value <- df[value, field] value } -mklines.update_with_metadata <- function(df, metadata) -{ +mklines.update_with_metadata <- function(df, metadata) { df$new_value <- NA df <- make.new_license(df, metadata$License) @@ -663,8 +607,7 @@ mklines.update_with_metadata <- function(df, metadata) df } -mklines.update_value <- function(df) -{ +mklines.update_value <- function(df) { df$value <- NA df$todo <- '' df <- make.license(df) @@ -675,8 +618,7 @@ mklines.update_value <- function(df) df } -mklines.update_new_line <- function(df) -{ +mklines.update_new_line <- function(df) { df$new_line <- df$line va <- df$key_value & !is.na(df$value) @@ -686,8 +628,7 @@ mklines.update_new_line <- function(df) df } -mklines.annotate_distname <- function(mklines) -{ +mklines.annotate_distname <- function(mklines) { match <- grepl('^[[:blank:]]*DISTNAME', mklines$new_line) line <- mklines$new_line[match] value <- sub('^[[:blank:]]*DISTNAME[[:blank:]]*=[[:blank:]]*', '', line) @@ -699,109 +640,97 @@ mklines.annotate_distname <- function(mklines) mklines } -mklines.remove_lines_before_update <- function(mklines) -{ +mklines.remove_lines_before_update <- function(mklines) { remove <- ( grepl('^[[:blank:]]*MASTER_SITES', mklines$new_line) | - grepl('^[[:blank:]]*HOMEPAGE', mklines$new_line) | - grepl('^[[:blank:]]*BUILDLINK_ABI_DEPENDS', mklines$new_line) | - grepl('^[[:blank:]]*BUILDLINK_API_DEPENDS', mklines$new_line)) + grepl('^[[:blank:]]*HOMEPAGE', mklines$new_line) | + grepl('^[[:blank:]]*BUILDLINK_ABI_DEPENDS', mklines$new_line) | + grepl('^[[:blank:]]*BUILDLINK_API_DEPENDS', mklines$new_line)) mklines[!remove,] } -mklines.reassign_order <- function(mklines) -{ +mklines.reassign_order <- function(mklines) { r_pkgname.order <- element(mklines, 'R_PKGNAME', 'order') categories.order <- element(mklines, 'CATEGORIES', 'order') - if (r_pkgname.order > categories.order) - { - r_pkgname.index <- mklines$key == 'R_PKGNAME' - r_pkgname.index[is.na(r_pkgname.index)] <- FALSE - r_pkgver.index <- mklines$key == 'R_PKGVER' - r_pkgver.index[is.na(r_pkgver.index)] <- FALSE - mklines[r_pkgname.index, 'order'] <- categories.order - 0.2 - mklines[r_pkgver.index, 'order'] <- categories.order - 0.1 - } + if (r_pkgname.order > categories.order) { + r_pkgname.index <- mklines$key == 'R_PKGNAME' + r_pkgname.index[is.na(r_pkgname.index)] <- FALSE + r_pkgver.index <- mklines$key == 'R_PKGVER' + r_pkgver.index[is.na(r_pkgver.index)] <- FALSE + mklines[r_pkgname.index, 'order'] <- categories.order - 0.2 + mklines[r_pkgver.index, 'order'] <- categories.order - 0.1 + } mklines } -conflicts <- function(pkg) -{ +conflicts <- function(pkg) { conflict <- sprintf('R>=%s.%s', R.version$major, R.version$minor) conflicts <- list() - if (pkg %in% base.packages) - { - conflicts <- append(conflicts, varassign('CONFLICTS', conflict)) - conflicts <- end.paragraph(conflicts) - } + if (pkg %in% base.packages) { + conflicts <- append(conflicts, varassign('CONFLICTS', conflict)) + conflicts <- end.paragraph(conflicts) + } conflicts } -make.df.conflicts <- function(df,metadata) -{ +make.df.conflicts <- function(df, metadata) { df.conflicts <- data.frame() - conflicts.exist <- element(df,'CONFLICTS','old_value',quiet=TRUE) != '???' - if (!conflicts.exist) - { - c <- conflicts(metadata$Package) - order <- element(df, 'COMMENT', 'order') + 2.5 - i <- 0 - for (conflict in c) - { - i <- i + 1 - category <- as.character(i) - depends <- FALSE - buildlink3.mk <- FALSE - x <- data.frame(new_line=conflict,order=order,category=category,depends=depends,buildlink3.mk=buildlink3.mk) - df.conflicts <- rbind(df.conflicts,x) - } + conflicts.exist <- element(df, 'CONFLICTS', 'old_value', quiet = TRUE) != '???' + if (!conflicts.exist) { + c <- conflicts(metadata$Package) + order <- element(df, 'COMMENT', 'order') + 2.5 + i <- 0 + for (conflict in c) { + i <- i + 1 + category <- as.character(i) + depends <- FALSE + buildlink3.mk <- FALSE + x <- data.frame(new_line = conflict, order = order, category = category, depends = depends, buildlink3.mk = buildlink3.mk) + df.conflicts <- rbind(df.conflicts, x) } + } df.conflicts } -make.df.depends <- function(df,DEPENDS) -{ +make.df.depends <- function(df, DEPENDS) { # message('===> make.df.depends():') # str(df) # print(df) df.depends <- data.frame() if (TRUE %in% df$depends) - df.depends <- data.frame(new_line=df[df$depends,'line'],stringsAsFactors=FALSE) + df.depends <- data.frame(new_line = df[df$depends, 'line'], stringsAsFactors = FALSE) for (line in DEPENDS) - df.depends <- rbind(df.depends,data.frame(new_line=line,stringsAsFactors=FALSE)) - if (nrow(df.depends) > 0) - { - df.depends$category <- NA - df.depends$buildlink3.mk <- FALSE - df.depends <- categorize.key_value(df.depends,'new_line') - df.depends <- categorize.depends(df.depends,'new_line') - df.depends$key_value <- NULL - df.depends$key <- NULL - df.depends <- df.depends[!duplicated(df.depends),] - df.depends$order <- find.order(df,'depends','order') - } + df.depends <- rbind(df.depends, data.frame(new_line = line, stringsAsFactors = FALSE)) + if (nrow(df.depends) > 0) { + df.depends$category <- NA + df.depends$buildlink3.mk <- FALSE + df.depends <- categorize.key_value(df.depends, 'new_line') + df.depends <- categorize.depends(df.depends, 'new_line') + df.depends$key_value <- NULL + df.depends$key <- NULL + df.depends <- df.depends[!duplicated(df.depends),] + df.depends$order <- find.order(df, 'depends', 'order') + } # message('===> df.depends:') # str(df.depends) # print(df.depends) df.depends } -make.df.buildlink3 <- function(df,BUILDLINK3.MK) -{ +make.df.buildlink3 <- function(df, BUILDLINK3.MK) { # message('===> make.df.buildlink3():') df.buildlink3.mk <- data.frame() if (TRUE %in% df$buildlink3.mk) - df.buildlink3.mk <- data.frame(new_line=df[df$buildlink3.mk,'line'],stringsAsFactors=FALSE) + df.buildlink3.mk <- data.frame(new_line = df[df$buildlink3.mk, 'line'], stringsAsFactors = FALSE) for (line in BUILDLINK3.MK) - df.buildlink3.mk <- rbind(df.buildlink3.mk,data.frame(new_line=line,stringsAsFactors=FALSE)) - if (nrow(df.buildlink3.mk) > 0) - { - df.buildlink3.mk$category <- NA - df.buildlink3.mk$depends <- FALSE - df.buildlink3.mk <- categorize.buildlink(df.buildlink3.mk,'new_line') - df.buildlink3.mk <- df.buildlink3.mk[!duplicated(df.buildlink3.mk),] - df.buildlink3.mk$order <- find.order(df,'buildlink3.mk','order') - } + df.buildlink3.mk <- rbind(df.buildlink3.mk, data.frame(new_line = line, stringsAsFactors = FALSE)) + if (nrow(df.buildlink3.mk) > 0) { + df.buildlink3.mk$category <- NA + df.buildlink3.mk$depends <- FALSE + df.buildlink3.mk <- categorize.buildlink(df.buildlink3.mk, 'new_line') + df.buildlink3.mk <- df.buildlink3.mk[!duplicated(df.buildlink3.mk),] + df.buildlink3.mk$order <- find.order(df, 'buildlink3.mk', 'order') + } # str(df.buildlink3.mk) # print(df.buildlink3.mk) df.buildlink3.mk @@ -809,18 +738,16 @@ make.df.buildlink3 <- function(df,BUILDLINK3.MK) #' updates the dependencies and returns the lines to be written to the #' updated package Makefile. -mklines.lines <- function(mklines, df.conflicts, df.depends, df.buildlink3.mk) -{ +mklines.lines <- function(mklines, df.conflicts, df.depends, df.buildlink3.mk) { fields <- c('new_line', 'order', 'category', 'depends', 'buildlink3.mk') - lines <- mklines[! mklines$depends & ! mklines$buildlink3.mk, fields] + lines <- mklines[!mklines$depends & !mklines$buildlink3.mk, fields] lines <- rbind(lines, df.conflicts, df.depends, df.buildlink3.mk) lines <- lines[order(lines$order, lines$category, lines$new_line),] - lines <- lines[! adjacent.duplicates(lines$new_line),] + lines <- lines[!adjacent.duplicates(lines$new_line),] lines$new_line } -update.Makefile <- function(mklines, metadata) -{ +update.Makefile <- function(mklines, metadata) { DEPENDENCIES <- make.depends(metadata$Imports, metadata$Depends) DEPENDS <- DEPENDENCIES[[1]] BUILDLINK3.MK <- DEPENDENCIES[[2]] @@ -840,8 +767,7 @@ update.Makefile <- function(mklines, metadata) write(lines, 'Makefile') } -create.Makefile <- function(metadata) -{ +create.Makefile <- function(metadata) { if (arg.update && file.exists('Makefile.orig')) update.Makefile(read_mklines('Makefile.orig'), metadata) else @@ -853,25 +779,22 @@ create.DESCR <- function(metadata) { write(descr, 'DESCR') } -make.metadata <- function(description.filename) -{ +make.metadata <- function(description.filename) { fields <- c('Package', 'Version', 'Title', 'Description', 'License', 'Imports', 'Depends') metadata <- as.list(read.dcf(description.filename, fields)) names(metadata) <- fields metadata } -main <- function() -{ +main <- function() { Sys.setlocale('LC_ALL', 'C') - error <- download.file(url=arg.rpkg_description_url,destfile='DESCRIPTION',quiet=arg.quiet_curl,method='curl') - if (error) - { - message('ERROR: Downloading the DESCRIPTION file for ',arg.rpkg,' failed;') - message(' perhaps the package no longer exists?') - quit(save='no',status=error) - } + error <- download.file(url = arg.rpkg_description_url, destfile = 'DESCRIPTION', quiet = arg.quiet_curl, method = 'curl') + if (error) { + message('ERROR: Downloading the DESCRIPTION file for ', arg.rpkg, ' failed;') + message(' perhaps the package no longer exists?') + quit(save = 'no', status = error) + } metadata <- make.metadata('DESCRIPTION') create.Makefile(metadata) diff --git a/pkgtools/R2pkg/files/R2pkg_test.R b/pkgtools/R2pkg/files/R2pkg_test.R index a995f60cd3e..906c4d59613 100644 --- a/pkgtools/R2pkg/files/R2pkg_test.R +++ b/pkgtools/R2pkg/files/R2pkg_test.R @@ -1,4 +1,4 @@ -# $NetBSD: R2pkg_test.R,v 1.21 2019/10/19 22:10:58 rillig Exp $ +# $NetBSD: R2pkg_test.R,v 1.22 2019/10/25 19:00:16 rillig Exp $ # # Copyright (c) 2019 # Roland Illig. All rights reserved. @@ -41,340 +41,340 @@ package_dir <- file.path(Sys.getenv('PKGSRCDIR'), 'pkgtools', 'R2pkg') #' don't use tabs in the output; see https://stackoverflow.com/q/58465177 expect_printed <- function(obj, ...) { - out <- '' - with_output_sink(textConnection('out', 'w', local = TRUE), { - print(obj, right = FALSE) - }) - exp <- c(...) - if (! identical(out, exp)) { - write(out, file.path(original_wd, 'R2pkg_test.out.txt')) - write(exp, file.path(original_wd, 'R2pkg_test.exp.txt')) - } - expect_equal(length(out), length(exp)) - expect_equal(!!out, !!exp) + out <- '' + with_output_sink(textConnection('out', 'w', local = TRUE), { + print(obj, right = FALSE) + }) + exp <- c(...) + if (!identical(out, exp)) { + write(out, file.path(original_wd, 'R2pkg_test.out.txt')) + write(exp, file.path(original_wd, 'R2pkg_test.exp.txt')) + } + expect_equal(length(out), length(exp)) + expect_equal(!!out, !!exp) } linesConnection <- function(...) - textConnection(paste0(c(...), collapse = '\n')) + textConnection(paste0(c(...), collapse = '\n')) make_mklines <- function(...) - read_mklines(linesConnection(...)) + read_mklines(linesConnection(...)) mocked_system <- function() { - commands <- list() - mock <- function(cmd) { - commands <<- append(commands, cmd) - 0 - } - get_commands <- function() - unlist(commands) - expect_commands <- function(...) - expect_equal(!!get_commands(), !!c(...)) - list( - mock = mock, - commands = get_commands, - expect_commands = expect_commands) + commands <- list() + mock <- function(cmd) { + commands <<- append(commands, cmd) + 0 + } + get_commands <- function() + unlist(commands) + expect_commands <- function(...) + expect_equal(!!get_commands(), !!c(...)) + list( + mock = mock, + commands = get_commands, + expect_commands = expect_commands) } mocked_message <- function() { - messages <- list() - mock <- function(...) - messages <<- append(messages, paste0(...)) - get_messages <- function() - unlist(messages) - expect_messages <- function(...) - expect_equal(!!get_messages(), !!c(...)) - list( - mock = mock, - messages = get_messages, - expect_messages = expect_messages) + messages <- list() + mock <- function(...) + messages <<- append(messages, paste0(...)) + get_messages <- function() + unlist(messages) + expect_messages <- function(...) + expect_equal(!!get_messages(), !!c(...)) + list( + mock = mock, + messages = get_messages, + expect_messages = expect_messages) } test_that('linesConnection', { - lines <- readLines(linesConnection('1', '2', '3')) + lines <- readLines(linesConnection('1', '2', '3')) - expect_equal(lines, c('1', '2', '3')) + expect_equal(lines, c('1', '2', '3')) }) test_that('level.message', { - message <- mocked_message() - local_mock(message = message$mock) - arg.level <<- 123 # XXX: should use with_environment instead + message <- mocked_message() + local_mock(message = message$mock) + arg.level <<- 123 # XXX: should use with_environment instead - level.message('mess', 'age', ' text') + level.message('mess', 'age', ' text') - message$expect_messages( - '[ 123 ] message text') + message$expect_messages( + '[ 123 ] message text') }) test_that('level.warning', { - message <- mocked_message() - local_mock(message = message$mock) - arg.level <<- 321 # XXX: should use with_environment instead + message <- mocked_message() + local_mock(message = message$mock) + arg.level <<- 321 # XXX: should use with_environment instead - level.warning('mess', 'age', ' text') + level.warning('mess', 'age', ' text') - message$expect_messages( - '[ 321 ] WARNING: message text') + message$expect_messages( + '[ 321 ] WARNING: message text') }) test_that('trim.space', { - expect_equal(trim.space(' hello, \t\nworld '), 'hello,world') + expect_equal(trim.space(' hello, \t\nworld '), 'hello,world') }) test_that('one.line', { - expect_equal( - one.line(' \t\nhello, \t\nworld \t\n'), - ' \t hello, \t world \t ') + expect_equal( + one.line(' \t\nhello, \t\nworld \t\n'), + ' \t hello, \t world \t ') }) test_that('pkg.vers', { - expect_equal(pkg.vers('1_0-2.3'), '1.0-2.3') + expect_equal(pkg.vers('1_0-2.3'), '1.0-2.3') }) test_that('varassign', { - expect_equal(varassign('VAR', 'value'), 'VAR=\tvalue') + expect_equal(varassign('VAR', 'value'), 'VAR=\tvalue') }) test_that('relpath_category', { - expect_equal(relpath_category('../../other/pkgbase'), 'other') - expect_equal(relpath_category('../../wip/pkgbase/Makefile'), 'wip') + expect_equal(relpath_category('../../other/pkgbase'), 'other') + expect_equal(relpath_category('../../wip/pkgbase/Makefile'), 'wip') - expect_equal( - relpath_category(c( - '../../wip/pkgbase/Makefile', - '../../other/pkgbase')), - c( - 'wip', - 'other')) + expect_equal( + relpath_category(c( + '../../wip/pkgbase/Makefile', + '../../other/pkgbase')), + c( + 'wip', + 'other')) - # undefined behavior - expect_equal(relpath_category('..'), NA_character_) +# undefined behavior + expect_equal(relpath_category('..'), NA_character_) }) test_that('adjacent.duplicates', { - expect_equal( - adjacent.duplicates(c(1, 2, 2, 2, 3, 3, 4)), - c(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, FALSE)) + expect_equal( + adjacent.duplicates(c(1, 2, 2, 2, 3, 3, 4)), + c(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, FALSE)) }) test_that('paste2', { - expect_equal(paste2(NA, NA), '') - expect_equal(paste2('', NA), '') - expect_equal(paste2(NA, ''), '') - expect_equal(paste2('', ''), ' ') - expect_equal(paste2('one', 'two'), 'one two') + expect_equal(paste2(NA, NA), '') + expect_equal(paste2('', NA), '') + expect_equal(paste2(NA, ''), '') + expect_equal(paste2('', ''), ' ') + expect_equal(paste2('one', 'two'), 'one two') }) test_that('end.paragraph', { - expect_equal(end.paragraph(list()), list()) - expect_equal(end.paragraph(list('line')), list('line', '')) + expect_equal(end.paragraph(list()), list()) + expect_equal(end.paragraph(list('line')), list('line', '')) }) test_that('as.sorted.list', { - expect_equal(as.sorted.list(data.frame()), list()) + expect_equal(as.sorted.list(data.frame()), list()) - expect_equal( + expect_equal( as.sorted.list(data.frame( - varnames = c('A', 'B', 'B', 'B', 'A'), - values = c('1', '3', '2', '1', '1'))), + varnames = c('A', 'B', 'B', 'B', 'A'), + values = c('1', '3', '2', '1', '1'))), list('1', '1', '2', '3')) }) test_that('categorize.key_value', { - mklines <- make_mklines( - '\tPATH=/bin echo', - 'DEPENDS+= R-ellipsis>=0:../../math/R-ellipsis', - '.include "../../math/R-ellipsis/buildlink3.mk"') - - expect_printed( - data.frame( - key_value = mklines$key_value, - key = mklines$key, - old_value = mklines$old_value), - ' key_value key old_value ', - '1 FALSE <NA> <NA> ', - '2 TRUE DEPENDS R-ellipsis>=0:../../math/R-ellipsis', - '3 FALSE <NA> <NA> ') + mklines <- make_mklines( + '\tPATH=/bin echo', + 'DEPENDS+= R-ellipsis>=0:../../math/R-ellipsis', + '.include "../../math/R-ellipsis/buildlink3.mk"') + + expect_printed( + data.frame( + key_value = mklines$key_value, + key = mklines$key, + old_value = mklines$old_value), + ' key_value key old_value ', + '1 FALSE <NA> <NA> ', + '2 TRUE DEPENDS R-ellipsis>=0:../../math/R-ellipsis', + '3 FALSE <NA> <NA> ') }) test_that('categorize.depends', { - mklines <- make_mklines( - 'DEPENDS+=\tR-ellipsis>=0:../../math/R-ellipsis', - '.include "../../math/R-ellipsis/buildlink3.mk"') + mklines <- make_mklines( + 'DEPENDS+=\tR-ellipsis>=0:../../math/R-ellipsis', + '.include "../../math/R-ellipsis/buildlink3.mk"') - expect_equal(mklines$depends, c(TRUE, FALSE)) + expect_equal(mklines$depends, c(TRUE, FALSE)) }) test_that('categorize.buildlink', { - mklines <- make_mklines( - 'DEPENDS+=\tR-ellipsis>=0:../../math/R-ellipsis', - '.include "../../math/R-ellipsis/buildlink3.mk"') + mklines <- make_mklines( + 'DEPENDS+=\tR-ellipsis>=0:../../math/R-ellipsis', + '.include "../../math/R-ellipsis/buildlink3.mk"') - expect_equal(mklines$buildlink3.mk, c(FALSE, TRUE)) + expect_equal(mklines$buildlink3.mk, c(FALSE, TRUE)) }) test_that('fix.continued.lines', { - message <- mocked_message() - local_mock(message = message$mock) - - mklines <- make_mklines( - '# comment \\', - 'continued=comment', - 'VAR1= \\', - '\tvalue', - 'VAR2=\tvalue') - - expect_equal(mklines$key_value, c(FALSE, TRUE, TRUE, TRUE, TRUE)) - expect_equal(mklines$line, c( - '# comment \\', - 'continued=comment', # FIXME: continuation from line 1 - 'VAR1=', - 'VAR1+=\tvalue', # FIXME: extra space at the beginning - 'VAR2=\tvalue')) - message$expect_messages( - '[ 321 ] WARNING: unhandled continued line(s)') + message <- mocked_message() + local_mock(message = message$mock) + + mklines <- make_mklines( + '# comment \\', + 'continued=comment', + 'VAR1= \\', + '\tvalue', + 'VAR2=\tvalue') + + expect_equal(mklines$key_value, c(FALSE, TRUE, TRUE, TRUE, TRUE)) + expect_equal(mklines$line, c( + '# comment \\', + 'continued=comment', # FIXME: continuation from line 1 + 'VAR1=', + 'VAR1+=\tvalue', # FIXME: extra space at the beginning + 'VAR2=\tvalue')) + message$expect_messages( + '[ 321 ] WARNING: unhandled continued line(s)') }) test_that('fix.continued.lines, single continued line at EOF', { - mklines <- make_mklines( - 'VAR= \\') + mklines <- make_mklines( + 'VAR= \\') - expect_equal(mklines$line, 'VAR= \\') + expect_equal(mklines$line, 'VAR= \\') }) test_that('fix.continued.lines, no continued lines', { - mklines <- make_mklines( - 'VAR= value', - 'VAR= value', - 'VAR= value') + mklines <- make_mklines( + 'VAR= value', + 'VAR= value', + 'VAR= value') - expect_equal(mklines$line, rep('VAR= value',3)) + expect_equal(mklines$line, rep('VAR= value', 3)) }) test_that('read_mklines', { - mklines <- make_mklines( - '# comment', - 'VAR= value', - '', - '.include "other.mk"', - '.if 0', - '.endif') - - expect_printed(mklines, - ' line order key_value old_todo key operator delimiter', - '1 # comment 1 FALSE <NA> <NA> <NA> <NA> ', - '2 VAR= value 2 TRUE VAR = ', - '3 3 FALSE <NA> <NA> <NA> <NA> ', - '4 .include "other.mk" 4 FALSE <NA> <NA> <NA> <NA> ', - '5 .if 0 5 FALSE <NA> <NA> <NA> <NA> ', - '6 .endif 6 FALSE <NA> <NA> <NA> <NA> ', - ' old_value category depends buildlink3.mk', - '1 <NA> NA FALSE FALSE ', - '2 value NA FALSE FALSE ', - '3 <NA> NA FALSE FALSE ', - '4 <NA> NA FALSE FALSE ', - '5 <NA> NA FALSE FALSE ', - '6 <NA> NA FALSE FALSE ') + mklines <- make_mklines( + '# comment', + 'VAR= value', + '', + '.include "other.mk"', + '.if 0', + '.endif') + + expect_printed(mklines, + ' line order key_value old_todo key operator delimiter', + '1 # comment 1 FALSE <NA> <NA> <NA> <NA> ', + '2 VAR= value 2 TRUE VAR = ', + '3 3 FALSE <NA> <NA> <NA> <NA> ', + '4 .include "other.mk" 4 FALSE <NA> <NA> <NA> <NA> ', + '5 .if 0 5 FALSE <NA> <NA> <NA> <NA> ', + '6 .endif 6 FALSE <NA> <NA> <NA> <NA> ', + ' old_value category depends buildlink3.mk', + '1 <NA> NA FALSE FALSE ', + '2 value NA FALSE FALSE ', + '3 <NA> NA FALSE FALSE ', + '4 <NA> NA FALSE FALSE ', + '5 <NA> NA FALSE FALSE ', + '6 <NA> NA FALSE FALSE ') }) test_that('read.file.as.list can read an empty file', { - filename <- '' - local_tempfile('filename') - file.create(filename) + filename <- '' + local_tempfile('filename') + file.create(filename) - lines <- read.file.as.list(filename) + lines <- read.file.as.list(filename) - expect_equal(lines, list()) + expect_equal(lines, list()) }) test_that('read.file.as.list can read lines from a file', { - filename <- '' - local_tempfile('filename') - writeLines(c('first', 'second \\', 'third'), filename) + filename <- '' + local_tempfile('filename') + writeLines(c('first', 'second \\', 'third'), filename) - lines <- read.file.as.list(filename) + lines <- read.file.as.list(filename) - expect_equal(lines, list('first', 'second \\', 'third')) + expect_equal(lines, list('first', 'second \\', 'third')) }) test_that('mklines.get_value, exactly 1 variable assignment, no space', { - mklines <- make_mklines( - 'VAR=value') + mklines <- make_mklines( + 'VAR=value') - str <- mklines.get_value(mklines, 'VAR') + str <- mklines.get_value(mklines, 'VAR') - expect_equal(str, 'value') + expect_equal(str, 'value') }) test_that('read.file.as.value, exactly 1 variable assignment', { - mklines <- make_mklines( - 'VAR=\tvalue') + mklines <- make_mklines( + 'VAR=\tvalue') - str <- mklines.get_value(mklines, 'VAR') + str <- mklines.get_value(mklines, 'VAR') - expect_equal(str, 'value') + expect_equal(str, 'value') }) test_that('read.file.as.value, commented variable assignment', { - mklines <- make_mklines( - '#VAR=\tvalue') + mklines <- make_mklines( + '#VAR=\tvalue') - str <- mklines.get_value(mklines, 'VAR') + str <- mklines.get_value(mklines, 'VAR') - # TODO: Check whether commented variables should really be considered. - expect_equal(str, 'value') +# TODO: Check whether commented variables should really be considered. + expect_equal(str, 'value') }) test_that('read.file.as.value, multiple variable assignments', { - mklines <- make_mklines( - 'VAR=\tvalue', - 'VAR=\tvalue2') + mklines <- make_mklines( + 'VAR=\tvalue', + 'VAR=\tvalue2') - str <- mklines.get_value(mklines, 'VAR') + str <- mklines.get_value(mklines, 'VAR') - expect_equal(str, '') + expect_equal(str, '') }) # test_that('read.file.as.values', { # }) test_that('simplify.whitespace', { - expect_equal(simplify.whitespace('\t \nword \t\n\f'), ' \nword \n\f') + expect_equal(simplify.whitespace('\t \nword \t\n\f'), ' \nword \n\f') }) test_that('remove.punctuation', { - expect_equal(remove.punctuation('+,-./'), '+./') + expect_equal(remove.punctuation('+,-./'), '+./') }) test_that('remove.quotes', { - expect_equal(remove.quotes('"\'hello`,,'), 'hello,,') + expect_equal(remove.quotes('"\'hello`,,'), 'hello,,') }) test_that('remove.articles', { - expect_equal(remove.articles('Get a life'), 'Get life') - expect_equal(remove.articles('An apple a day'), ' apple day') # TODO: uppercase the first letter - expect_equal(remove.articles('Annnnnnnnnn apple'), 'Annnnnnnnnn apple') - expect_equal(remove.articles('Grade A'), 'Grade ') - expect_equal(remove.articles('Grade A is best'), 'Grade is best') + expect_equal(remove.articles('Get a life'), 'Get life') + expect_equal(remove.articles('An apple a day'), ' apple day') # TODO: uppercase the first letter + expect_equal(remove.articles('Annnnnnnnnn apple'), 'Annnnnnnnnn apple') + expect_equal(remove.articles('Grade A'), 'Grade ') + expect_equal(remove.articles('Grade A is best'), 'Grade is best') }) test_that('case.insensitive.equals', { - expect_equal(case.insensitive.equals('HELLO', 'hello'), TRUE) - expect_equal(case.insensitive.equals('HELLO', 'hellx'), FALSE) - expect_equal(case.insensitive.equals(' "HELLO"', 'hello'), FALSE) - expect_equal(case.insensitive.equals(' "HELLO"', ' hello'), FALSE) - expect_equal(case.insensitive.equals(' HELLO', 'hello'), FALSE) - expect_equal(case.insensitive.equals(' HELLO', ' hello'), TRUE) + expect_equal(case.insensitive.equals('HELLO', 'hello'), TRUE) + expect_equal(case.insensitive.equals('HELLO', 'hellx'), FALSE) + expect_equal(case.insensitive.equals(' "HELLO"', 'hello'), FALSE) + expect_equal(case.insensitive.equals(' "HELLO"', ' hello'), FALSE) + expect_equal(case.insensitive.equals(' HELLO', 'hello'), FALSE) + expect_equal(case.insensitive.equals(' HELLO', ' hello'), TRUE) }) test_that('weakly.equals', { - expect_equal(weakly.equals('HELLO', 'hello'), TRUE) - expect_equal(weakly.equals('HELLO', 'hellx'), FALSE) - expect_equal(weakly.equals(' "HELLO"', 'hello'), FALSE) - expect_equal(weakly.equals(' "HELLO"', ' hello'), TRUE) - expect_equal(weakly.equals(' HELLO', 'hello'), FALSE) - expect_equal(weakly.equals(' HELLO', ' hello'), TRUE) + expect_equal(weakly.equals('HELLO', 'hello'), TRUE) + expect_equal(weakly.equals('HELLO', 'hellx'), FALSE) + expect_equal(weakly.equals(' "HELLO"', 'hello'), FALSE) + expect_equal(weakly.equals(' "HELLO"', ' hello'), TRUE) + expect_equal(weakly.equals(' HELLO', 'hello'), FALSE) + expect_equal(weakly.equals(' HELLO', ' hello'), TRUE) }) # test_that('pkgsrc.license', { @@ -390,24 +390,24 @@ test_that('weakly.equals', { # }) test_that('find.Rcpp', { - expect_equal(find.Rcpp(list(), list()), FALSE) - expect_equal(find.Rcpp(list('Other'), list('Other')), FALSE) + expect_equal(find.Rcpp(list(), list()), FALSE) + expect_equal(find.Rcpp(list('Other'), list('Other')), FALSE) - expect_equal(find.Rcpp(list('Rcpp'), list()), TRUE) - expect_equal(find.Rcpp(list(), list('Rcpp')), TRUE) + expect_equal(find.Rcpp(list('Rcpp'), list()), TRUE) + expect_equal(find.Rcpp(list(), list('Rcpp')), TRUE) }) # test_that('buildlink3.mk', { # }) test_that('varassigns', { - expect_equal( + expect_equal( varassigns('VARNAME', c('value1', 'value2', '', 'value3')), list( - 'VARNAME=\tvalue1', - 'VARNAME=\tvalue2', # FIXME: This doesn't make sense. - '', - 'VARNAME=\tvalue3')) + 'VARNAME=\tvalue1', + 'VARNAME=\tvalue2', # FIXME: This doesn't make sense. + '', + 'VARNAME=\tvalue3')) }) # test_that('categories', { @@ -420,52 +420,52 @@ test_that('varassigns', { # }) test_that('make.imports', { - expect_equal( - make.imports(NA_character_, NA_character_), - character(0)) + expect_equal( + make.imports(NA_character_, NA_character_), + character(0)) - expect_equal( - make.imports('first (>= 1.0)', 'second'), - c('first(>=1.0)', 'second')) + expect_equal( + make.imports('first (>= 1.0)', 'second'), + c('first(>=1.0)', 'second')) - expect_equal( - make.imports('first(>=1)', 'second(>=1)'), - c('first(>=1)second(>=1)')) + expect_equal( + make.imports('first(>=1)', 'second(>=1)'), + c('first(>=1)second(>=1)')) - expect_equal( - make.imports('first(>=1) second(>=1)', NA_character_), - c('first(>=1)second(>=1)')) + expect_equal( + make.imports('first(>=1) second(>=1)', NA_character_), + c('first(>=1)second(>=1)')) }) test_that('make.dependency', { - expect_equal(make.dependency('pkgname'), c('pkgname')) - expect_equal(make.dependency('pkgname(>=1.0)'), c('pkgname', '>=1.0')) + expect_equal(make.dependency('pkgname'), c('pkgname')) + expect_equal(make.dependency('pkgname(>=1.0)'), c('pkgname', '>=1.0')) - # undefined behavior - expect_equal(make.dependency('pkgname (>= 1.0)'), c('pkgname ', '>= 1.0')) +# undefined behavior + expect_equal(make.dependency('pkgname (>= 1.0)'), c('pkgname ', '>= 1.0')) }) test_that('depends', { - expect_equal(depends(make.dependency('pkg')), 'pkg') - expect_equal(depends(make.dependency('pkg(>=1.0)')), 'pkg') - expect_equal(depends(make.dependency('ellipsis(>=1.0)')), 'ellipsis') + expect_equal(depends(make.dependency('pkg')), 'pkg') + expect_equal(depends(make.dependency('pkg(>=1.0)')), 'pkg') + expect_equal(depends(make.dependency('ellipsis(>=1.0)')), 'ellipsis') - # undefined behavior - expect_equal(depends(make.dependency('pkg (>= 1.0)')), 'pkg ') - expect_equal(depends(make.dependency('ellipsis (>= 1.0)')), 'ellipsis ') +# undefined behavior + expect_equal(depends(make.dependency('pkg (>= 1.0)')), 'pkg ') + expect_equal(depends(make.dependency('ellipsis (>= 1.0)')), 'ellipsis ') }) test_that('depends.pkg', { - local_dir(package_dir) + local_dir(package_dir) - expect_equal(depends.pkg('ellipsis'), '../../math/R-ellipsis') + expect_equal(depends.pkg('ellipsis'), '../../math/R-ellipsis') }) test_that('new.depends.pkg', { - local_dir(package_dir) + local_dir(package_dir) - if (dir.exists('../../wip')) - expect_equal(new.depends.pkg('C50'), '../../wip/R-C50') + if (dir.exists('../../wip')) + expect_equal(new.depends.pkg('C50'), '../../wip/R-C50') }) # test_that('depends.pkg.fullname', { @@ -493,36 +493,36 @@ test_that('new.depends.pkg', { # }) test_that('buildlink3.file with matching version number', { - local_dir(package_dir) - dependency <- make.dependency('bitops(>=0.1)') + local_dir(package_dir) + dependency <- make.dependency('bitops(>=0.1)') - bl3 <- buildlink3.file(dependency) + bl3 <- buildlink3.file(dependency) - expect_equal(bl3, '../../math/R-bitops/buildlink3.mk') + expect_equal(bl3, '../../math/R-bitops/buildlink3.mk') }) # The version number of the dependency is not checked against # the resolved buildlink3 file. test_that('buildlink3.file with too high version number', { - local_dir(package_dir) - dependency <- make.dependency('bitops(>=1000.0)') + local_dir(package_dir) + dependency <- make.dependency('bitops(>=1000.0)') - bl3 <- buildlink3.file(dependency) + bl3 <- buildlink3.file(dependency) - expect_equal(bl3, '../../math/R-bitops/buildlink3.mk') + expect_equal(bl3, '../../math/R-bitops/buildlink3.mk') }) test_that('buildlink3.line', { - local_dir(package_dir) + local_dir(package_dir) - expect_equal( - buildlink3.line(make.dependency('ellipsis')), - '.include "../../math/R-ellipsis/buildlink3.mk"') + expect_equal( + buildlink3.line(make.dependency('ellipsis')), + '.include "../../math/R-ellipsis/buildlink3.mk"') - # undefined behavior - expect_equal( - buildlink3.line(make.dependency('not-found')), - '.include "NA/buildlink3.mk"') +# undefined behavior + expect_equal( + buildlink3.line(make.dependency('not-found')), + '.include "NA/buildlink3.mk"') }) # test_that('dependency.dir', { @@ -532,79 +532,78 @@ test_that('buildlink3.line', { # }) test_that('update.dependency', { - system <- mocked_system() - message <- mocked_message() - local_mock(system = system$mock, message = message$mock) - local_dir(package_dir) - arg.packages_list <<- 'already-updated' - arg.r2pkg <<- 'pkg/bin/R2pkg' - arg.args <<- '-u' + system <- mocked_system() + message <- mocked_message() + local_mock(system = system$mock, message = message$mock) + local_dir(package_dir) + arg.packages_list <<- 'already-updated' + arg.r2pkg <<- 'pkg/bin/R2pkg' + arg.args <<- '-u' - update.dependency(make.dependency('assertthat')) + update.dependency(make.dependency('assertthat')) - system$expect_commands( - paste0( - 'grep -E -q -e "assertthat" already-updated ', - '|| ', - '(cd ../../devel/R-assertthat && pkg/bin/R2pkg -u assertthat)')) - message$expect_messages( - "[ 321 ] updating dependency for assertthat: ../../devel/R-assertthat") + system$expect_commands( + paste0( + 'grep -E -q -e "assertthat" already-updated ', + '|| ', + '(cd ../../devel/R-assertthat && pkg/bin/R2pkg -u assertthat)')) + message$expect_messages( + "[ 321 ] updating dependency for assertthat: ../../devel/R-assertthat") }) # test_that('make.depends', { # }) test_that('use_languages without Rcpp as dependency', { - languages <- use_languages(list(), list()) + languages <- use_languages(list(), list()) - expect_equal(languages, '# none') + expect_equal(languages, '# none') }) test_that('use_languages with Rcpp as dependency', { - languages <- use_languages(list('Rcpp(>=0)'), list()) + languages <- use_languages(list('Rcpp(>=0)'), list()) - expect_equal(languages, 'c c++') + expect_equal(languages, 'c c++') }) test_that('write.Makefile', { - tmpdir <- paste(tempdir(), 'category', 'pkgdir', sep = '/') - dir.create(tmpdir, recursive = TRUE) - local_dir(tmpdir) - metadata <- make.metadata(linesConnection( - 'Package: pkgname', - 'Version: 1.3', - 'Depends: ellipsis')) - orig <- make_mklines() - - write.Makefile(orig, metadata) - - expect_equal(readLines('Makefile'),c( - mkcvsid, - '', - 'R_PKGNAME=\tpkgname', - 'R_PKGVER=\t1.3', - 'CATEGORIES=\tcategory', - '', - 'MAINTAINER=\t', # FIXME - 'COMMENT=\tNA', # FIXME - 'LICENSE=\tNA', # FIXME - '', - 'USE_LANGUAGES=\t# none', - '', - '.include "../../math/R/Makefile.extension"', - '.include "../../mk/bsd.pkg.mk"' - )) + tmpdir <- paste(tempdir(), 'category', 'pkgdir', sep = '/') + dir.create(tmpdir, recursive = TRUE) + local_dir(tmpdir) + metadata <- make.metadata(linesConnection( + 'Package: pkgname', + 'Version: 1.3', + 'Depends: ellipsis')) + orig <- make_mklines() + + write.Makefile(orig, metadata) + + expect_equal(readLines('Makefile'), c( + mkcvsid, + '', + 'R_PKGNAME=\tpkgname', + 'R_PKGVER=\t1.3', + 'CATEGORIES=\tcategory', + '', + 'MAINTAINER=\t', # FIXME + 'COMMENT=\tNA', # FIXME + 'LICENSE=\tNA', # FIXME + '', + 'USE_LANGUAGES=\t# none', + '', + '.include "../../math/R/Makefile.extension"', + '.include "../../mk/bsd.pkg.mk"')) }) test_that('element', { - mklines <- make_mklines( - 'COMMENT=\tThe comment', - 'EMPTY=') + mklines <- make_mklines( + 'COMMENT=\tThe comment', + 'EMPTY=') - expect_equal(element(mklines, 'COMMENT', 'order'), 1) - expect_equal(element(mklines, 'COMMENT', 'old_value'), 'The comment') - expect_equal(element(mklines, 'UNKNOWN', 'order'), '???') # FIXME: should be a number - expect_equal(element(mklines, 'EMPTY', 'old_value'), '') + expect_equal(element(mklines, 'COMMENT', 'order'), 1) + expect_equal(element(mklines, 'COMMENT', 'old_value'), 'The comment') + expect_equal(element(mklines, 'UNKNOWN', 'order'), '???') # FIXME: should be a number + expect_equal(element(mklines, 'EMPTY', 'old_value'), '') }) # test_that('make.categories', { @@ -614,14 +613,14 @@ test_that('element', { # }) test_that('make.comment', { - mklines <- make_mklines( - 'COMMENT=\tOld comment') + mklines <- make_mklines( + 'COMMENT=\tOld comment') - mklines$new_value[[1]] <- 'New comment' - expect_equal(make.comment(mklines), 'Old comment\t# [R2pkg] updated to: New comment') + mklines$new_value[[1]] <- 'New comment' + expect_equal(make.comment(mklines), 'Old comment\t# [R2pkg] updated to: New comment') - mklines$new_value[[1]] <- 'old Comment' - expect_equal(make.comment(mklines), 'Old comment') + mklines$new_value[[1]] <- 'old Comment' + expect_equal(make.comment(mklines), 'Old comment') }) # test_that('make.new_license', { @@ -634,231 +633,231 @@ test_that('make.comment', { # }) test_that('make.license, old and new known and equal', { - mklines <- make_mklines( - 'LICENSE=\tgnu-gpl-v2') - mklines$new_value <- 'gnu-gpl-v2' + mklines <- make_mklines( + 'LICENSE=\tgnu-gpl-v2') + mklines$new_value <- 'gnu-gpl-v2' - updated <- make.license(mklines) + updated <- make.license(mklines) - expect_equal(updated$value, 'gnu-gpl-v2') - expect_equal(updated$todo, '') + expect_equal(updated$value, 'gnu-gpl-v2') + expect_equal(updated$todo, '') }) test_that('make.license, old and new known and changed', { - mklines <- make_mklines( - 'LICENSE=\tgnu-gpl-v2') - mklines$new_value <- 'gnu-gpl-v3' + mklines <- make_mklines( + 'LICENSE=\tgnu-gpl-v2') + mklines$new_value <- 'gnu-gpl-v3' - updated <- make.license(mklines) + updated <- make.license(mklines) - expect_equal(updated$value, 'gnu-gpl-v3\t# [R2pkg] previously: gnu-gpl-v2') - expect_equal(updated$todo, '') + expect_equal(updated$value, 'gnu-gpl-v3\t# [R2pkg] previously: gnu-gpl-v2') + expect_equal(updated$todo, '') }) test_that('make.license, old known, new unknown', { - mklines <- make_mklines( - 'LICENSE=\tgnu-gpl-v2') - mklines$new_value <- 'unknown-license' + mklines <- make_mklines( + 'LICENSE=\tgnu-gpl-v2') + mklines$new_value <- 'unknown-license' - updated <- make.license(mklines) + updated <- make.license(mklines) - expect_equal(updated$value, 'gnu-gpl-v2\t# [R2pkg] updated to: unknown-license') - expect_equal(updated$todo, '# TODO: ') + expect_equal(updated$value, 'gnu-gpl-v2\t# [R2pkg] updated to: unknown-license') + expect_equal(updated$todo, '# TODO: ') }) test_that('make.license, old unknown, new known', { - mklines <- make_mklines( - 'LICENSE=\tunknown-license') - mklines$new_value <- 'gnu-gpl-v2' + mklines <- make_mklines( + 'LICENSE=\tunknown-license') + mklines$new_value <- 'gnu-gpl-v2' - updated <- make.license(mklines) + updated <- make.license(mklines) - expect_equal(updated$value, 'gnu-gpl-v2\t# [R2pkg] previously: unknown-license') - expect_equal(updated$todo, '') + expect_equal(updated$value, 'gnu-gpl-v2\t# [R2pkg] previously: unknown-license') + expect_equal(updated$todo, '') }) test_that('make.license, old unknown, new also unknown', { - mklines <- make_mklines( - 'LICENSE=\tunknown-license') - mklines$new_value <- 'new-unknown' + mklines <- make_mklines( + 'LICENSE=\tunknown-license') + mklines$new_value <- 'new-unknown' - updated <- make.license(mklines) + updated <- make.license(mklines) - expect_equal(updated$value, 'new-unknown\t# [R2pkg] previously: unknown-license') - expect_equal(updated$todo, '# TODO: ') + expect_equal(updated$value, 'new-unknown\t# [R2pkg] previously: unknown-license') + expect_equal(updated$todo, '# TODO: ') }) test_that('find.order', { - mklines <- make_mklines( - 'CATEGORIES=', - 'HOMEPAGE=', - 'USE_TOOLS+=', - '.include "other.mk"', - '# comment') + mklines <- make_mklines( + 'CATEGORIES=', + 'HOMEPAGE=', + 'USE_TOOLS+=', + '.include "other.mk"', + '# comment') - vars_order <- find.order(mklines, 'key_value', 'order') - include_order <- find.order(mklines, 'buildlink3.mk', 'order') + vars_order <- find.order(mklines, 'key_value', 'order') + include_order <- find.order(mklines, 'buildlink3.mk', 'order') - expect_equal(mklines[, 'key_value'], c(TRUE, TRUE, TRUE, FALSE, FALSE)) - expect_equal(mklines[, 'buildlink3.mk'], c(FALSE, FALSE, FALSE, FALSE, FALSE)) - expect_equal(vars_order, c(1)) - expect_equal(include_order, NA_integer_) + expect_equal(mklines[, 'key_value'], c(TRUE, TRUE, TRUE, FALSE, FALSE)) + expect_equal(mklines[, 'buildlink3.mk'], c(FALSE, FALSE, FALSE, FALSE, FALSE)) + expect_equal(vars_order, c(1)) + expect_equal(include_order, NA_integer_) }) test_that('mklines.update_with_metadata with CATEGORIES', { - local_dir(package_dir) # to get a realistic category - arg.maintainer_email <<- 'with-categories@example.org' - df <- make_mklines( - 'CATEGORIES=\told categories', - 'MAINTAINER=\told_maintainer@example.org', - 'COMMENT=\told comment', - 'R_PKGVER=\t1.0') - metadata = list(Title = 'Package comment', Version = '19.3', License = 'license') + local_dir(package_dir) # to get a realistic category + arg.maintainer_email <<- 'with-categories@example.org' + df <- make_mklines( + 'CATEGORIES=\told categories', + 'MAINTAINER=\told_maintainer@example.org', + 'COMMENT=\told comment', + 'R_PKGVER=\t1.0') + metadata = list(Title = 'Package comment', Version = '19.3', License = 'license') - updated <- mklines.update_with_metadata(df, metadata) + updated <- mklines.update_with_metadata(df, metadata) - expect_printed(data.frame(varname = updated$key, new_value = updated$new_value), - ' varname new_value ', - '1 CATEGORIES pkgtools ', - '2 MAINTAINER with-categories@example.org', # FIXME: Should not always be reset. - '3 COMMENT Package comment ', - '4 R_PKGVER 19.3 ') + expect_printed(data.frame(varname = updated$key, new_value = updated$new_value), + ' varname new_value ', + '1 CATEGORIES pkgtools ', + '2 MAINTAINER with-categories@example.org', # FIXME: Should not always be reset. + '3 COMMENT Package comment ', + '4 R_PKGVER 19.3 ') }) # If the variable has been removed from the Makefile, it is not updated. test_that('mklines.update_with_metadata without CATEGORIES', { - arg.maintainer_email <<- 'without-categories@example.org' - df <- make_mklines( - 'MAINTAINER=', - 'COMMENT=', - 'R_PKGVER=') - metadata = list(Title = 'Package comment', Version = '19.3', License = 'license') + arg.maintainer_email <<- 'without-categories@example.org' + df <- make_mklines( + 'MAINTAINER=', + 'COMMENT=', + 'R_PKGVER=') + metadata = list(Title = 'Package comment', Version = '19.3', License = 'license') - updated <- mklines.update_with_metadata(df, metadata) + updated <- mklines.update_with_metadata(df, metadata) - expect_printed(data.frame(varname = updated$key, new_value = updated$new_value), - ' varname new_value ', - '1 MAINTAINER without-categories@example.org', - '2 COMMENT Package comment ', - '3 R_PKGVER 19.3 ') + expect_printed(data.frame(varname = updated$key, new_value = updated$new_value), + ' varname new_value ', + '1 MAINTAINER without-categories@example.org', + '2 COMMENT Package comment ', + '3 R_PKGVER 19.3 ') }) test_that('mklines.update_value', { - local_dir(package_dir) - - mklines <- make_mklines( - 'R_PKGVER=\t1.0', - 'CATEGORIES=\told categories', - 'MAINTAINER=\told_maintainer@example.org', - 'COMMENT=\tOld comment', - 'LICENSE=\told-license') - mklines$new_value <- mklines$old_value - - updated <- mklines.update_value(mklines) - - expect_equal(updated$value, c( - '1.0', - 'pkgtools old categories', - 'old_maintainer@example.org', - 'Old comment', - 'old-license\t# [R2pkg] previously: old-license')) # FIXME: no comment necessary - expect_equal(updated$todo, c( - '', - '', - '', - '', - '# TODO: ')) + local_dir(package_dir) + + mklines <- make_mklines( + 'R_PKGVER=\t1.0', + 'CATEGORIES=\told categories', + 'MAINTAINER=\told_maintainer@example.org', + 'COMMENT=\tOld comment', + 'LICENSE=\told-license') + mklines$new_value <- mklines$old_value + + updated <- mklines.update_value(mklines) + + expect_equal(updated$value, c( + '1.0', + 'pkgtools old categories', + 'old_maintainer@example.org', + 'Old comment', + 'old-license\t# [R2pkg] previously: old-license')) # FIXME: no comment necessary + expect_equal(updated$todo, c( + '', + '', + '', + '', + '# TODO: ')) }) test_that('mklines.update_new_line', { - mklines <- make_mklines( - 'VALUE=\tvalue', - 'VALUE_WITH_COMMENT=\tvalue # comment', - 'VALUE_NA=\tvalue', - '#COMMENTED=\tcommented value') - mklines <- mklines.update_value(mklines) - mklines$value[mklines$key == 'VALUE'] <- 'new value' - mklines$value[mklines$key == 'VALUE_WITH_COMMENT'] <- 'new value # new comment' - mklines$value[mklines$key == '#COMMENTED'] <- 'new commented' + mklines <- make_mklines( + 'VALUE=\tvalue', + 'VALUE_WITH_COMMENT=\tvalue # comment', + 'VALUE_NA=\tvalue', + '#COMMENTED=\tcommented value') + mklines <- mklines.update_value(mklines) + mklines$value[mklines$key == 'VALUE'] <- 'new value' + mklines$value[mklines$key == 'VALUE_WITH_COMMENT'] <- 'new value # new comment' + mklines$value[mklines$key == '#COMMENTED'] <- 'new commented' - updated <- mklines.update_new_line(mklines) + updated <- mklines.update_new_line(mklines) - expect_equal(updated$new_line, c( - 'VALUE=\tnew value', - 'VALUE_WITH_COMMENT=\tnew value # new comment', - 'VALUE_NA=\tvalue', - '#COMMENTED=\tnew commented')) + expect_equal(updated$new_line, c( + 'VALUE=\tnew value', + 'VALUE_WITH_COMMENT=\tnew value # new comment', + 'VALUE_NA=\tvalue', + '#COMMENTED=\tnew commented')) }) test_that('mklines.annotate_distname', { - mklines <- make_mklines( - 'DISTNAME=\tpkg_1.0') - mklines$new_line <- mklines$line + mklines <- make_mklines( + 'DISTNAME=\tpkg_1.0') + mklines$new_line <- mklines$line - annotated <- mklines.annotate_distname(mklines) + annotated <- mklines.annotate_distname(mklines) - expect_equal( - annotated$new_line, - 'DISTNAME=\tpkg_1.0\t# [R2pkg] replace this line with R_PKGNAME=pkg and R_PKGVER=1.0 as first stanza') + expect_equal( + annotated$new_line, + 'DISTNAME=\tpkg_1.0\t# [R2pkg] replace this line with R_PKGNAME=pkg and R_PKGVER=1.0 as first stanza') }) test_that('mklines.remove_lines_before_update', { - mklines <- make_mklines( - 'MASTER_SITES=', - 'HOMEPAGE=', - 'BUILDLINK_API_DEPENDS.dependency+=', - 'BUILDLINK_ABI_DEPENDS.dependency+=', - 'COMMENT=') - mklines$new_line <- mklines$line + mklines <- make_mklines( + 'MASTER_SITES=', + 'HOMEPAGE=', + 'BUILDLINK_API_DEPENDS.dependency+=', + 'BUILDLINK_ABI_DEPENDS.dependency+=', + 'COMMENT=') + mklines$new_line <- mklines$line - cleaned <- mklines.remove_lines_before_update(mklines) + cleaned <- mklines.remove_lines_before_update(mklines) - expect_equal(cleaned$key, c( - 'COMMENT')) + expect_equal(cleaned$key, c( + 'COMMENT')) }) test_that('mklines.reassign_order, no change necessary', { - mklines <- make_mklines( - 'R_PKGNAME= ellipsis', - 'R_PKGVER= 0.1', - 'CATEGORIES= pkgtools') + mklines <- make_mklines( + 'R_PKGNAME= ellipsis', + 'R_PKGVER= 0.1', + 'CATEGORIES= pkgtools') - updated <- mklines.reassign_order(mklines) + updated <- mklines.reassign_order(mklines) - expect_equal(updated, mklines) + expect_equal(updated, mklines) }) test_that('mklines.reassign_order, reordered', { - mklines <- make_mklines( - 'CATEGORIES= pkgtools', - 'R_PKGNAME= ellipsis', - 'R_PKGVER= 0.1') + mklines <- make_mklines( + 'CATEGORIES= pkgtools', + 'R_PKGNAME= ellipsis', + 'R_PKGVER= 0.1') - expect_printed(data.frame(varname = mklines$key, order = mklines$order), - ' varname order', - '1 CATEGORIES 1 ', - '2 R_PKGNAME 2 ', - '3 R_PKGVER 3 ') + expect_printed(data.frame(varname = mklines$key, order = mklines$order), + ' varname order', + '1 CATEGORIES 1 ', + '2 R_PKGNAME 2 ', + '3 R_PKGVER 3 ') - updated <- mklines.reassign_order(mklines) + updated <- mklines.reassign_order(mklines) - expect_printed(data.frame(varname = updated$key, order = updated$order), - ' varname order', - '1 CATEGORIES 1.0 ', - '2 R_PKGNAME 0.8 ', - '3 R_PKGVER 0.9 ') + expect_printed(data.frame(varname = updated$key, order = updated$order), + ' varname order', + '1 CATEGORIES 1.0 ', + '2 R_PKGNAME 0.8 ', + '3 R_PKGVER 0.9 ') }) test_that('conflicts', { - expect_equal(conflicts('UnknownPackage'), list()) + expect_equal(conflicts('UnknownPackage'), list()) - expect_equal( - conflicts('lattice'), - list('CONFLICTS=\tR>=3.6.1', '')) + expect_equal( + conflicts('lattice'), + list('CONFLICTS=\tR>=3.6.1', '')) - expect_equal( - conflicts(c('lattice', 'methods', 'general', 'UnknownPackage')), - list('CONFLICTS=\tR>=3.6.1', '')) + expect_equal( + conflicts(c('lattice', 'methods', 'general', 'UnknownPackage')), + list('CONFLICTS=\tR>=3.6.1', '')) }) # test_that('make.df.conflicts', { @@ -874,93 +873,93 @@ test_that('conflicts', { # }) test_that('update.Makefile', { - local_dir(tempdir()) - system <- mocked_system() - local_mock(system = system$mock) - writeLines( - c( - mkcvsid, - '', - '.include "../../mk/bsd.pkg.mk"'), - 'Makefile.orig') - orig <- read_mklines('Makefile.orig') - metadata <- make.metadata(linesConnection( - 'Package: pkgname', - 'Version: 1.0', - 'Depends: dep1 dep2(>=2.0)')) - expect_printed( - as.data.frame(metadata), - ' Package Version Title Description License Imports Depends ', - '1 pkgname 1.0 <NA> <NA> <NA> <NA> dep1 dep2(>=2.0)') - expect_printed(metadata$Imports, '[1] NA') - expect_printed(metadata$Depends, '[1] "dep1 dep2(>=2.0)"') - expect_printed( - paste2(metadata$Imports, metadata$Depends), - '[1] "dep1 dep2(>=2.0)"') - expect_printed( - make.imports(metadata$Imports, metadata$Depends), - '[1] "dep1" "dep2(>=2.0)"') - FALSE && expect_printed( # FIXME - make.depends(metadata$Imports, metadata$Depends), - '[1] "dep1" "dep2(>=2.0)"') - - FALSE && update.Makefile(orig, metadata) # FIXME - - FALSE && expect_equal( # FIXME - c( - mkcvsid, - '', - 'asdf'), - readLines('Makefile')) - system$expect_commands(c()) + local_dir(tempdir()) + system <- mocked_system() + local_mock(system = system$mock) + writeLines( + c( + mkcvsid, + '', + '.include "../../mk/bsd.pkg.mk"'), + 'Makefile.orig') + orig <- read_mklines('Makefile.orig') + metadata <- make.metadata(linesConnection( + 'Package: pkgname', + 'Version: 1.0', + 'Depends: dep1 dep2(>=2.0)')) + expect_printed( + as.data.frame(metadata), + ' Package Version Title Description License Imports Depends ', + '1 pkgname 1.0 <NA> <NA> <NA> <NA> dep1 dep2(>=2.0)') + expect_printed(metadata$Imports, '[1] NA') + expect_printed(metadata$Depends, '[1] "dep1 dep2(>=2.0)"') + expect_printed( + paste2(metadata$Imports, metadata$Depends), + '[1] "dep1 dep2(>=2.0)"') + expect_printed( + make.imports(metadata$Imports, metadata$Depends), + '[1] "dep1" "dep2(>=2.0)"') + FALSE && expect_printed(# FIXME + make.depends(metadata$Imports, metadata$Depends), + '[1] "dep1" "dep2(>=2.0)"') + + FALSE && update.Makefile(orig, metadata) # FIXME + + FALSE && expect_equal(# FIXME + c( + mkcvsid, + '', + 'asdf'), + readLines('Makefile')) + system$expect_commands(c()) }) # test_that('create.Makefile', { # }) test_that('create.DESCR', { - local_dir(tempdir()) - metadata <- make.metadata(linesConnection( - 'Description: First line', - ' .', - ' Second paragraph', - ' has 2 lines')) - - create.DESCR(metadata) - - lines <- readLines('DESCR', encoding = 'UTF-8') - expect_equal(lines, c( - 'First line', - '', - 'Second paragraph has 2 lines' - )) + local_dir(tempdir()) + metadata <- make.metadata(linesConnection( + 'Description: First line', + ' .', + ' Second paragraph', + ' has 2 lines')) + + create.DESCR(metadata) + + lines <- readLines('DESCR', encoding = 'UTF-8') + expect_equal(lines, c( + 'First line', + '', + 'Second paragraph has 2 lines' + )) }) test_that('create.DESCR for a package without Description', { - local_dir(tempdir()) - metadata <- make.metadata(linesConnection('Package: pkgname')) + local_dir(tempdir()) + metadata <- make.metadata(linesConnection('Package: pkgname')) - create.DESCR(metadata) + create.DESCR(metadata) - lines <- readLines('DESCR', encoding = 'UTF-8') - expect_equal(lines, c('NA')) # FIXME + lines <- readLines('DESCR', encoding = 'UTF-8') + expect_equal(lines, c('NA')) # FIXME }) test_that('make.metadata', { - description <- paste( - c( - 'Package: pkgname', - 'Version: 1.0', - 'Imports: dep1 other' - ), - collapse = '\n') - - metadata <- make.metadata(textConnection(description)) - - expect_equal(metadata$Package, 'pkgname') - expect_equal(metadata$Version, '1.0') - expect_equal(metadata$Imports, 'dep1 other') - expect_equal(metadata$Depends, NA_character_) + description <- paste( + c( + 'Package: pkgname', + 'Version: 1.0', + 'Imports: dep1 other' + ), + collapse = '\n') + + metadata <- make.metadata(textConnection(description)) + + expect_equal(metadata$Package, 'pkgname') + expect_equal(metadata$Version, '1.0') + expect_equal(metadata$Imports, 'dep1 other') + expect_equal(metadata$Depends, NA_character_) }) # test_that('main', { |