pkgsrc-Changes archive

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index][Old Index]

CVS commit: pkgsrc/pkgtools/R2pkg/files



Module Name:    pkgsrc
Committed By:   rillig
Date:           Thu Oct 17 17:14:34 UTC 2019

Modified Files:
        pkgsrc/pkgtools/R2pkg/files: R2pkg.R R2pkg_test.R

Log Message:
pkgtools/R2pkg: refactorings, small bugfixes, tests

find.Rcpp is now guaranteed to return a boolean.

Added some tests and many more templates that are still waiting to be
filled.


To generate a diff of this commit:
cvs rdiff -u -r1.9 -r1.10 pkgsrc/pkgtools/R2pkg/files/R2pkg.R
cvs rdiff -u -r1.2 -r1.3 pkgsrc/pkgtools/R2pkg/files/R2pkg_test.R

Please note that diffs are not public domain; they are subject to the
copyright notices on the relevant files.

Modified files:

Index: pkgsrc/pkgtools/R2pkg/files/R2pkg.R
diff -u pkgsrc/pkgtools/R2pkg/files/R2pkg.R:1.9 pkgsrc/pkgtools/R2pkg/files/R2pkg.R:1.10
--- pkgsrc/pkgtools/R2pkg/files/R2pkg.R:1.9     Thu Oct 17 01:21:12 2019
+++ pkgsrc/pkgtools/R2pkg/files/R2pkg.R Thu Oct 17 17:14:34 2019
@@ -1,4 +1,4 @@
-# $NetBSD: R2pkg.R,v 1.9 2019/10/17 01:21:12 rillig Exp $
+# $NetBSD: R2pkg.R,v 1.10 2019/10/17 17:14:34 rillig Exp $
 #
 # Copyright (c) 2014,2015,2016,2017,2018,2019
 #      Brook Milligan.  All rights reserved.
@@ -49,19 +49,12 @@ level.message <- function(...)
 level.warning <- function(...)
   level.message('WARNING: ', ...)
 
-R_version <- function()
-{
-  info <- R.Version()
-  version <- paste0(info[['major']],'.',info[['minor']])
-  version
-}
-
 trim.space <- function(s) gsub('[[:space:]]','',s)
 trim.blank <- function(s) gsub('[[:blank:]]','',s)
 one.space <- function(s) gsub('[[:blank:]]+',' ',s)
 one.line <- function(s) gsub('\n',' ',s)
 pkg.vers <- function(s) gsub('_','.',s)
-field <- function(key,value) paste(key,'=\t',value,sep='')
+varassign <- function(varname, value) paste0(varname, '=\t', value)
 
 # The list of "recommended packages which are to be included in all
 # binary distributions of R." (R FAQ 5.1.2 2018-10-18)
@@ -96,7 +89,7 @@ base.packages.other <- c(
   'stats',
   'tools',
   'utils')
-base.packages <- c('R',base.packages.FAQ.5.1.2,base.packages.other)
+base.packages <- c('R', base.packages.FAQ.5.1.2, base.packages.other)
 
 licenses <- list()
 licenses[['ACM']]                                    <- 'acm-license'
@@ -160,12 +153,8 @@ paste2 <- function(s1,s2)
   if (!is.na(s1) && !is.na(s2)) return (paste(s1,s2))
 }
 
-end.paragraph <- function(l,l1=l,l2=list())
-{
-  if (length(l1) > 0 || length(l2) > 0)
-    l <- append(l,'')
-  l
-}
+end.paragraph <- function(lines)
+  if (length(lines) > 0) append(lines, '') else lines
 
 as.sorted.list <- function(df)
 {
@@ -392,34 +381,23 @@ weakly.equals <- function(s1,s2)
   result
 }
 
-new.field.if.different <- function(filename,s)
+new.field.if.different <- function(filename, s)
 {
-  field <- field(filename,one.line(s))
+  field <- varassign(filename, one.line(s))
   field.list <- read.file.as.list(filename)
   if (length(field.list) == 1)
     {
       f <- field.list[[1]]
-      if (case.insensitive.equals(f,field))
+      if (case.insensitive.equals(f, field))
         field <- f
     }
   field
 }
 
-todo.license <- function(s)
-{
-  if (is.null(licenses[[s]]))
-    todo <- '# TODO: LICENSE'
-  else
-    todo <- 'LICENSE'
-  todo
-}
-
 pkgsrc.license <- function(s)
 {
   license <- licenses[[s]]
-  if (is.null(license))
-    license <- s
-  license
+  if (is.null(license)) license <- s else license
 }
 
 package <- function(s) one.line(s)
@@ -444,7 +422,8 @@ maintainer <- function(email)
   MAINTAINER
 }
 
-find.Rcpp <- function(imps, deps) grepl('Rcpp', paste(imps, deps))
+find.Rcpp <- function(imps, deps)
+  any(grepl('Rcpp', paste(imps, deps)))
 
 buildlink3.mk <- function(imps,deps)
 {
@@ -467,30 +446,17 @@ buildlink3.mk <- function(imps,deps)
   BUILDLINK3.MK
 }
 
-makefile.field <- function(key,value)
-{
-  # message('===> makefile.field(',key,',',value,'):')
-  field <- paste0(key,'=\t',value)
-  # print(field)
-  field
-}
-
-makefile.fields <- function(key,values)
+varassigns <- function(key, values)
 {
-  # message('===> makefile.fields():')
   fields <- list()
   for (l in values)
     {
       value <- unlist(l)
-      # message('===> value=',value,' ',length(value),' ',value == '')
-      # print(value)
       if (value != '')
-        fields <- append(fields,makefile.field(key,list(value)))
+        fields <- append(fields, varassign(key, list(value)))
       else
-        fields <- append(fields,list(''))
-      # print(fields)
+        fields <- append(fields, list(''))
     }
-  # print(fields)
   fields
 }
 
@@ -720,18 +686,11 @@ make.depends <- function(imps,deps)
   result
 }
 
-use.languages <- function(s1,s2)
+use.languages <- function(imps, deps)
 {
-#  message('===> use.languages(',s1,',',s2,'):')
-#  USE_LANGUAGES <- read.file.as.values('USE_LANGUAGES')
-#  if (length(USE_LANGUAGES) == 0)
-#    {
-#      if (find.Rcpp(s1,s2))
-#        USE_LANGUAGES <- append(USE_LANGUAGES,list('USE_LANGUAGES+=\tc c++'))
-#    }
   USE_LANGUAGES <- list()
-  if (find.Rcpp(s1,s2))
-    USE_LANGUAGES <- append(USE_LANGUAGES,list('c c++'))
+  if (find.Rcpp(imps, deps))
+    USE_LANGUAGES <- append(USE_LANGUAGES, list('c c++'))
   if (length(USE_LANGUAGES) == 0)
     USE_LANGUAGES <- '# none'
   USE_LANGUAGES <- end.paragraph(USE_LANGUAGES)
@@ -747,13 +706,13 @@ copy.description <- function(connection)
 write.Makefile <- function(metadata)
 {
   RCSID             <- paste0('# $','NetBSD$')
-  CATEGORIES        <- makefile.field('CATEGORIES',categories())
-  MAINTAINER        <- makefile.field('MAINTAINER',maintainer(arg.maintainer_email))
-  COMMENT           <- makefile.field('COMMENT',comment(metadata$Title))
-  LICENSE           <- makefile.field('LICENSE',license(metadata$License))
-  R_PKGNAME         <- makefile.field('R_PKGNAME',package(metadata$Package))
-  R_PKGVER          <- makefile.field('R_PKGVER',version(metadata$Version))
-  USE_LANGUAGES     <- makefile.fields('USE_LANGUAGES',use.languages(metadata$Imports,metadata$Depends))
+  CATEGORIES        <- varassign('CATEGORIES',categories())
+  MAINTAINER        <- varassign('MAINTAINER',maintainer(arg.maintainer_email))
+  COMMENT           <- varassign('COMMENT',comment(metadata$Title))
+  LICENSE           <- varassign('LICENSE',license(metadata$License))
+  R_PKGNAME         <- varassign('R_PKGNAME',package(metadata$Package))
+  R_PKGVER          <- varassign('R_PKGVER',version(metadata$Version))
+  USE_LANGUAGES     <- varassigns('USE_LANGUAGES',use.languages(metadata$Imports,metadata$Depends))
   DEPENDENCIES      <- make.depends(metadata$Imports,metadata$Depends)
   DEPENDS           <- DEPENDENCIES[1]
   BUILDLINK3.MK     <- DEPENDENCIES[2]
@@ -1044,11 +1003,11 @@ reassign.order <- function(df)
 
 conflicts <- function(pkg)
 {
-  conflict <- paste0('R>=',R_version())
+  conflict <- sprintf('R>=%s.%s', R.version$major, R.version$minor)
   conflicts <- list()
   if (pkg %in% base.packages)
     {
-      conflicts <- append(conflicts,makefile.field('CONFLICTS',conflict))
+      conflicts <- append(conflicts, varassign('CONFLICTS', conflict))
       conflicts <- end.paragraph(conflicts)
     }
   conflicts

Index: pkgsrc/pkgtools/R2pkg/files/R2pkg_test.R
diff -u pkgsrc/pkgtools/R2pkg/files/R2pkg_test.R:1.2 pkgsrc/pkgtools/R2pkg/files/R2pkg_test.R:1.3
--- pkgsrc/pkgtools/R2pkg/files/R2pkg_test.R:1.2        Sun Oct 13 19:13:47 2019
+++ pkgsrc/pkgtools/R2pkg/files/R2pkg_test.R    Thu Oct 17 17:14:34 2019
@@ -1,4 +1,4 @@
-# $NetBSD: R2pkg_test.R,v 1.2 2019/10/13 19:13:47 rillig Exp $
+# $NetBSD: R2pkg_test.R,v 1.3 2019/10/17 17:14:34 rillig Exp $
 #
 # Copyright (c) 2019
 #      Roland Illig.  All rights reserved.
@@ -40,50 +40,111 @@ expect_printed <- function(obj, expected
     expect_equal(out, expected)
 }
 
-test_that('make.imports', {
-    imports <- make.imports('first (>= 1.0)', 'second')
+# test_that('level.message', {
+# })
 
-    expect_equal(imports, c('first(>=1.0)', 'second'))
-})
+test_that('level.warning', {
+    output <- ''
+    mock_message <- function(...) output <<- paste0(output, ..., '\n')
 
-test_that('make.dependency', {
-    imports <- make.dependency('first(>=1.0)')
+    arg.level <<- 123  # XXX: should use with_environment instead
+    with_mock(message = mock_message, {
+        level.warning('mess', 'age', ' text')
+    })
 
-    expect_equal(imports, c('first', '>=1.0'))
+    expect_equal(output, '[ 123 ] WARNING: message text\n')
 })
 
-test_that('buildlink3.file with matching version number', {
-    local_dir(package.dir)
-    dependency <- make.dependency('bitops(>=0.1)')
+# test_that('trim.space', {
+# })
 
-    bl3 <- buildlink3.file(dependency)
+# test_that('trim.blank', {
+# })
 
-    expect_equal(bl3, '../../math/R-bitops/buildlink3.mk')
-})
+# test_that('one.space', {
+# })
 
-# 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)')
+# test_that('one.line', {
+# })
 
-    bl3 <- buildlink3.file(dependency)
+# test_that('pkg.vers', {
+# })
 
-    expect_equal(bl3, '../../math/R-bitops/buildlink3.mk')
+# test_that('varassign', {
+# })
+
+# test_that('adjacent.duplicates', {
+# })
+
+# test_that('paste2', {
+# })
+
+# test_that('end.paragraph', {
+# })
+
+# test_that('as.sorted.list', {
+# })
+
+test_that('read.file.as.dataframe', {
+    content <- textConnection('VAR=value\nVAR2=value2\n')
+
+    df <- read.file.as.dataframe(content)
+
+    expect_equal(length(df$line), 3)
+    expect_equal(df$line[[1]], 'VAR=value')
+    expect_equal(df$line[[2]], 'VAR2=value2')
+    expect_equal(df$line[[3]], '')
 })
 
-test_that('level.warning', {
-    output <- ''
-    mock_message <- function(...) output <<- paste0(output, ..., '\n')
+# test_that('categorize.key_value', {
+# })
 
-    arg.level <<- 123  # XXX: should use with_environment instead
-    with_mock(message = mock_message, {
-        level.warning('mess', 'age', ' text')
-    })
+# test_that('categorize.depends', {
+# })
 
-    expect_equal(output, '[ 123 ] WARNING: message text\n')
+# test_that('categorize.buildlink', {
+# })
+
+# test_that('fix.continued.lines', {
+# })
+
+test_that('read.Makefile.as.dataframe', {
+    lines <- c(
+    '# comment',
+    'VAR= value',
+    '',
+    '.include "other.mk"',
+    '.if 0',
+    '.endif'
+    )
+    content <- paste0(paste(lines, collapse = '\n'), '\n')
+    expect_equal(content, '# comment\nVAR= value\n\n.include "other.mk"\n.if 0\n.endif\n')
+
+    df <- read.Makefile.as.dataframe(textConnection(content))
+
+    expect_printed(df, c(
+    '                 line order category key_value  key depends buildlink3.mk',
+    '1           # comment     1       NA     FALSE <NA>   FALSE         FALSE',
+    '2          VAR= value     2       NA      TRUE  VAR   FALSE         FALSE',
+    '3                         3       NA     FALSE <NA>   FALSE         FALSE',
+    '4 .include "other.mk"     4       NA     FALSE <NA>   FALSE         FALSE',
+    '5               .if 0     5       NA     FALSE <NA>   FALSE         FALSE',
+    '6              .endif     6       NA     FALSE <NA>   FALSE         FALSE',
+    '7                         7       NA     FALSE <NA>   FALSE         FALSE',
+    '  operator delimiter old_value old_todo',
+    '1     <NA>      <NA>      <NA>     <NA>',
+    '2        =               value         ',
+    '3     <NA>      <NA>      <NA>     <NA>',
+    '4     <NA>      <NA>      <NA>     <NA>',
+    '5     <NA>      <NA>      <NA>     <NA>',
+    '6     <NA>      <NA>      <NA>     <NA>',
+    '7     <NA>      <NA>      <NA>     <NA>'
+    ))
 })
 
+# test_that('read.file.as.list', {
+# })
+
 test_that('read.file.as.value, exactly 1 variable assignment, no space', {
     filename <- ''
     local_tempfile('filename')
@@ -125,99 +186,329 @@ test_that('read.file.as.value, multiple 
     expect_equal(str, '')
 })
 
-test_that('read.file.as.dataframe', {
-    content <- textConnection('VAR=value\nVAR2=value2\n')
+# test_that('read.file.as.values', {
+# })
 
-    df <- read.file.as.dataframe(content)
+# test_that('simplify.whitespace', {
+# })
 
-    expect_equal(length(df$line), 3)
-    expect_equal(df$line[[1]], 'VAR=value')
-    expect_equal(df$line[[2]], 'VAR2=value2')
-    expect_equal(df$line[[3]], '')
+# test_that('remove.punctuation', {
+# })
+
+# test_that('remove.quotes', {
+# })
+
+# test_that('remove.articles', {
+# })
+
+# test_that('case.insensitive.equals', {
+# })
+
+# test_that('weakly.equals', {
+# })
+
+# test_that('new.field.if.different', {
+# })
+
+# test_that('pkgsrc.license', {
+# })
+
+# test_that('package', {
+# })
+
+# test_that('version', {
+# })
+
+# test_that('comment', {
+# })
+
+# test_that('use.tools', {
+# })
+
+# test_that('license', {
+# })
+
+# test_that('maintainer', {
+# })
+
+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('Rcpp'), list()), TRUE)
+    expect_equal(find.Rcpp(list(), list('Rcpp')), TRUE)
 })
 
-test_that('read.Makefile.as.dataframe', {
-    lines <- c(
-        '# comment',
-        'VAR= value',
-        '',
-        '.include "other.mk"',
-        '.if 0',
-        '.endif'
-    )
-    content <- paste0(paste(lines, collapse = '\n'), '\n')
-    expect_equal(content, '# comment\nVAR= value\n\n.include "other.mk"\n.if 0\n.endif\n')
+# test_that('buildlink3.mk', {
+# })
 
-    df <- read.Makefile.as.dataframe(textConnection(content))
+test_that('varassigns', {
+    expect_equal(
+    varassigns('VARNAME', c('value1', 'value2', '', 'value3')),
+    list(
+    'VARNAME=\tvalue1',
+    'VARNAME=\tvalue2',  # FIXME: This doesn't make sense.
+    '',
+    'VARNAME=\tvalue3'))
+})
 
-    expect_printed(df, c(
-        '                 line order category key_value  key depends buildlink3.mk',
-        '1           # comment     1       NA     FALSE <NA>   FALSE         FALSE',
-        '2          VAR= value     2       NA      TRUE  VAR   FALSE         FALSE',
-        '3                         3       NA     FALSE <NA>   FALSE         FALSE',
-        '4 .include "other.mk"     4       NA     FALSE <NA>   FALSE         FALSE',
-        '5               .if 0     5       NA     FALSE <NA>   FALSE         FALSE',
-        '6              .endif     6       NA     FALSE <NA>   FALSE         FALSE',
-        '7                         7       NA     FALSE <NA>   FALSE         FALSE',
-        '  operator delimiter old_value old_todo',
-        '1     <NA>      <NA>      <NA>     <NA>',
-        '2        =               value         ',
-        '3     <NA>      <NA>      <NA>     <NA>',
-        '4     <NA>      <NA>      <NA>     <NA>',
-        '5     <NA>      <NA>      <NA>     <NA>',
-        '6     <NA>      <NA>      <NA>     <NA>',
-        '7     <NA>      <NA>      <NA>     <NA>'
-    ))
+# test_that('categories', {
+# })
+
+# test_that('description', {
+# })
+
+# test_that('filter.imports', {
+# })
+
+test_that('make.imports', {
+    imports <- make.imports('first (>= 1.0)', 'second')
+
+    expect_equal(imports, c('first(>=1.0)', 'second'))
+})
+
+test_that('make.dependency', {
+    imports <- make.dependency('first(>=1.0)')
+
+    expect_equal(imports, c('first', '>=1.0'))
+})
+
+# test_that('depends', {
+# })
+
+# test_that('depends.pkg', {
+# })
+
+# test_that('new.depends.pkg', {
+# })
+
+# test_that('depends.pkg.fullname', {
+# })
+
+# test_that('depends.pkg.name', {
+# })
+
+# test_that('depends.pkg.vers', {
+# })
+
+# test_that('depends.vers', {
+# })
+
+# test_that('depends.vers.2', {
+# })
+
+# test_that('depends.dir', {
+# })
+
+# test_that('depends.line', {
+# })
+
+# test_that('depends.line.2', {
+# })
+
+test_that('buildlink3.file with matching version number', {
+    local_dir(package.dir)
+    dependency <- make.dependency('bitops(>=0.1)')
+
+    bl3 <- buildlink3.file(dependency)
+
+    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)')
+
+    bl3 <- buildlink3.file(dependency)
+
+    expect_equal(bl3, '../../math/R-bitops/buildlink3.mk')
 })
 
+# test_that('buildlink3.line', {
+# })
+
+# test_that('dependency.dir', {
+# })
+
+# test_that('message.wip.dependency', {
+# })
+
+# test_that('message.too.many.dependencies', {
+# })
+
+# test_that('update.dependency', {
+# })
+
+# test_that('make.depends', {
+# })
+
+# test_that('use.languages', {
+# })
+
+# test_that('copy.description', {
+# })
+
+# test_that('write.Makefile', {
+# })
+
+# test_that('construct.line', {
+# })
+
+# test_that('element', {
+# })
+
+# test_that('make.categories', {
+# })
+
+# test_that('make.maintainer', {
+# })
+
+# test_that('make.comment', {
+# })
+
+# test_that('make.new_license', {
+# })
+
+# test_that('license.marked.todo', {
+# })
+
+# test_that('license.in.pkgsrc', {
+# })
+
+# test_that('make.license', {
+# })
+
+# test_that('make.r_pkgver', {
+# })
+
+# test_that('find.order', {
+# })
+
+# test_that('write.makefile', {
+# })
+
 test_that('update.Makefile.with.metadata', {
     df <- read.Makefile.as.dataframe(textConnection(paste0(
-        'CATEGORIES=\n',
-        'MAINTAINER=\n',
-        'COMMENT=\n',
-        'R_PKGVER=\n'
+    'CATEGORIES=\n',
+    'MAINTAINER=\n',
+    'COMMENT=\n',
+    'R_PKGVER=\n'
     )))
     metadata = list(Title = 'Package comment', Version = '19.3', License = 'license')
 
     updated <- update.Makefile.with.metadata(df, metadata)
 
     expect_printed(updated, c(
-        '         line order category key_value        key depends buildlink3.mk',
-        '1 CATEGORIES=     1       NA      TRUE CATEGORIES   FALSE         FALSE',
-        '2 MAINTAINER=     2       NA      TRUE MAINTAINER   FALSE         FALSE',
-        '3    COMMENT=     3       NA      TRUE    COMMENT   FALSE         FALSE',
-        '4   R_PKGVER=     4       NA      TRUE   R_PKGVER   FALSE         FALSE',
-        '5                 5       NA     FALSE       <NA>   FALSE         FALSE',
-        '  operator delimiter old_value old_todo       new_value',
-        '1        =                                        R2pkg',
-        '2        =                                             ',
-        '3        =                              Package comment',
-        '4        =                                         19.3',
-        '5     <NA>      <NA>      <NA>     <NA>            <NA>'
+    '         line order category key_value        key depends buildlink3.mk',
+    '1 CATEGORIES=     1       NA      TRUE CATEGORIES   FALSE         FALSE',
+    '2 MAINTAINER=     2       NA      TRUE MAINTAINER   FALSE         FALSE',
+    '3    COMMENT=     3       NA      TRUE    COMMENT   FALSE         FALSE',
+    '4   R_PKGVER=     4       NA      TRUE   R_PKGVER   FALSE         FALSE',
+    '5                 5       NA     FALSE       <NA>   FALSE         FALSE',
+    '  operator delimiter old_value old_todo       new_value',
+    '1        =                                        R2pkg',
+    '2        =                                             ',
+    '3        =                              Package comment',
+    '4        =                                         19.3',
+    '5     <NA>      <NA>      <NA>     <NA>            <NA>'
     ))
 })
 
 # If the variable has been removed from the Makefile, it is not updated.
 test_that('update.Makefile.with.metadata without CATEGORIES', {
     df <- read.Makefile.as.dataframe(textConnection(paste0(
-        'MAINTAINER=\n',
-        'COMMENT=\n',
-        'R_PKGVER=\n'
+    'MAINTAINER=\n',
+    'COMMENT=\n',
+    'R_PKGVER=\n'
     )))
     metadata = list(Title = 'Package comment', Version = '19.3', License = 'license')
 
     updated <- update.Makefile.with.metadata(df, metadata)
 
     expect_printed(updated, c(
-        '         line order category key_value        key depends buildlink3.mk',
-        '1 MAINTAINER=     1       NA      TRUE MAINTAINER   FALSE         FALSE',
-        '2    COMMENT=     2       NA      TRUE    COMMENT   FALSE         FALSE',
-        '3   R_PKGVER=     3       NA      TRUE   R_PKGVER   FALSE         FALSE',
-        '4                 4       NA     FALSE       <NA>   FALSE         FALSE',
-        '  operator delimiter old_value old_todo       new_value',
-        '1        =                                             ',
-        '2        =                              Package comment',
-        '3        =                                         19.3',
-        '4     <NA>      <NA>      <NA>     <NA>            <NA>'
+    '         line order category key_value        key depends buildlink3.mk',
+    '1 MAINTAINER=     1       NA      TRUE MAINTAINER   FALSE         FALSE',
+    '2    COMMENT=     2       NA      TRUE    COMMENT   FALSE         FALSE',
+    '3   R_PKGVER=     3       NA      TRUE   R_PKGVER   FALSE         FALSE',
+    '4                 4       NA     FALSE       <NA>   FALSE         FALSE',
+    '  operator delimiter old_value old_todo       new_value',
+    '1        =                                             ',
+    '2        =                              Package comment',
+    '3        =                                         19.3',
+    '4     <NA>      <NA>      <NA>     <NA>            <NA>'
     ))
 })
+
+# test_that('update.Makefile.with.new.values', {
+# })
+
+# test_that('update.Makefile.with.new.line', {
+# })
+
+# test_that('annotate.distname.in.Makefile', {
+# })
+
+# test_that('annotate.Makefile', {
+# })
+
+# test_that('remove.master.sites.from.Makefile', {
+# })
+
+# test_that('remove.homepage.from.Makefile', {
+# })
+
+# test_that('remove.buildlink.abi.depends.from.Makefile', {
+# })
+
+# test_that('remove.buildlink.api.depends.from.Makefile', {
+# })
+
+# test_that('remove.lines.from.Makefile', {
+# })
+
+# test_that('reassign.order', {
+# })
+
+test_that('conflicts', {
+    expect_equal(conflicts('UnknownPackage'), list())
+
+    expect_equal(
+        conflicts('lattice'),
+        list('CONFLICTS=\tR>=3.6.1', ''))
+
+    expect_equal(
+        conflicts(c('lattice', 'methods', 'general', 'UnknownPackage')),
+        list('CONFLICTS=\tR>=3.6.1', ''))
+})
+
+# test_that('conflicts.order', {
+# })
+
+# test_that('make.df.conflicts', {
+# })
+
+# test_that('make.df.depends', {
+# })
+
+# test_that('make.df.buildlink3', {
+# })
+
+# test_that('make.df.makefile', {
+# })
+
+# test_that('update.Makefile', {
+# })
+
+# test_that('create.Makefile', {
+# })
+
+# test_that('create.DESCR', {
+# })
+
+# test_that('make.metadata', {
+# })
+
+# test_that('main', {
+# })



Home | Main Index | Thread Index | Old Index