1 get_dependencies <- function(pkg,extra_deps,verbose=TRUE) {
2 # determine dependencies
3 dependencies <- r_dependencies_of(description=pkg$description)
5 # these are used for generating the Depends fields
6 as_deb <- function(r,build) {
7 return(pkgname_as_debian(paste(dependencies[r,]$name)
8 ,version=dependencies[r,]$version
12 depends$bin <- lapply(rownames(dependencies), as_deb, build=F)
13 depends$build <- lapply(rownames(dependencies), as_deb, build=T)
14 # add the command line dependencies
15 depends$bin = c(extra_deps$deb,depends$bin)
16 depends$build = c(extra_deps$deb,depends$build)
17 # add the system requirements
18 if ('SystemRequirements' %in% colnames(pkg$description)) {
19 sysreq <- sysreqs_as_debian(pkg$description[1,'SystemRequirements'],verbose=verbose)
20 if (!is.null(sysreq) && is.list(sysreq)) {
21 depends$bin = c(sysreq$bin,depends$bin)
22 depends$build = c(sysreq$build,depends$build)
24 if (verbose) {cat("sysreq:"); print(sysreq)}
25 fail('Cannot interpret system dependency, fix package.\n')
29 forced <- forced_deps_as_debian(pkg$name)
31 notice('forced build dependencies:',paste(forced$build, collapse=', '))
32 notice('forced binary dependencies:',paste(forced$bin, collapse=', '))
33 depends$bin = c(forced$bin,depends$bin)
34 depends$build = c(forced$build,depends$build)
37 # make sure we depend upon R in some way...
38 if (!length(grep('^r-base',depends$build))) {
39 depends$build = c(depends$build,pkgname_as_debian('R',version='>= 2.7.0',build=T))
40 depends$bin = c(depends$bin, pkgname_as_debian('R',version='>= 2.7.0',build=F))
42 # also include stuff to allow tcltk to build (suggested by Dirk)
43 depends$build = c(depends$build,'xvfb','xauth','xfonts-base')
45 # make all bin dependencies build dependencies.
46 depends$build = c(depends$build, depends$bin)
49 depends <- lapply(depends,unique)
51 # append the Debian dependencies
52 depends$build=c(depends$build,'debhelper (>> 4.1.0)','cdbs')
53 if (file.exists(file.path(patch_dir, pkg$name))) {
54 depends$build <- c(depends$build,'dpatch')
57 depends$bin=c(depends$bin,'${shlibs:Depends}')
60 # the names of dependent source packages (to find the .changes file to
61 # upload via dput). these can be found recursively.
62 depends$r = r_dependency_closure(dependencies)
63 # append command line dependencies
64 depends$r = c(extra_deps$r, depends$r)
68 sysreqs_as_debian <- function(sysreq_text,verbose=FALSE) {
69 # form of this field is unspecified (ugh) but most people seem to stick
73 sysreq_text = gsub('[Nn][Oo][Tt][Ee]:\\s.*','',sysreq_text)
74 # conversion from and to commata and lower case
75 sysreq_text <- gsub('[[:space:]]and[[:space:]]',' , ',tolower(sysreq_text))
76 for (sysreq in strsplit(sysreq_text,'[[:space:]]*,[[:space:]]*')[[1]]) {
77 if (verbose) cat("sysreq to investigate: '",sysreq,"'.\n",sep="")
79 # constant case (redundant)
80 sysreq = tolower(sysreq)
81 # drop version information/comments for now
82 sysreq = gsub('[[][^])]*[]]','',sysreq)
83 sysreq = gsub('\\([^)]*\\)','',sysreq)
84 sysreq = gsub('[[][^])]*[]]','',sysreq)
85 sysreq = gsub('version','',sysreq)
86 sysreq = gsub('from','',sysreq)
87 sysreq = gsub('[<>=]*[[:space:]]*[[:digit:]]+[[:digit:].+:~-]*','',sysreq)
89 sysreq = gsub('(ht|f)tps?://[[:alnum:]!?*"\'(),%$_@.&+/=-]*','',sysreq)
90 # squish out space -- this does not work for me (did not want to touch, though), Steffen
91 sysreq = chomp(gsub('[[:space:]]+',' ',sysreq))
92 # no final dot and neither final blanks
93 sysreq = gsub('\\.?\\s*$','',sysreq)
94 if (nchar(sysreq) == 0) {
95 notice('part of the SystemRequirement became nothing')
98 alias <- db_sysreq_override(sysreq)
100 error('do not know what to do with SystemRequirement:',sysreq)
101 error('original SystemRequirement:',startreq)
102 fail('unmet system requirement')
104 notice(paste("mapped SystemRequirement '",startreq,"' onto '",alias,"' via '",sysreq,"'.",sep=""))
105 aliases = c(aliases,alias)
107 return(map_aliases_to_debian(aliases))
110 forced_deps_as_debian <- function(r_name) {
111 aliases <- db_get_forced_depends(r_name)
112 return(map_aliases_to_debian(aliases))
115 map_aliases_to_debian <- function(aliases) {
116 if (!length(aliases)) {
120 debs$bin = unlist(sapply(aliases, db_get_depends))
121 debs$build = unlist(sapply(aliases, db_get_depends, build=T))
122 debs$bin = debs$bin[debs$bin != 'build-essential']
123 debs$build = debs$build[debs$build != 'build-essential']
127 generate_control <- function(pkg) {
128 # construct control file
130 control <- data.frame()
131 control[1,'Source'] <- pkg$srcname
132 control[1,'Section'] <- 'gnu-r'
133 control[1,'Priority'] <- 'optional'
134 control[1,'Maintainer'] <- maintainer
135 control[1,'Build-Depends'] <- paste(pkg$depends$build, collapse=', ')
136 control[1,'Standards-Version'] <- '3.9.1'
137 if ('URL' %in% colnames(pkg$description)) {
138 control[1,'Homepage'] <- pkg$description[1,'URL']
141 control[2,'Package'] <- pkg$debname
142 control[2,'Architecture'] <- 'all'
144 control[2,'Architecture'] <- 'any'
146 control[2,'Depends'] <- paste(pkg$depends$bin,collapse=', ',sep='')
148 # generate the description
149 descr <- 'GNU R package "'
150 if ('Title' %in% colnames(pkg$description)) {
151 descr <- paste(descr,pkg$description[1,'Title'],sep='')
153 descr <- paste(descr,pkg$name,sep='')
155 long_descr <- pkg$description[1,'Description']
157 if (length(long_descr) < 1 || long_descr == "") {
158 # bypass lintian extended-description-is-empty for which we care not.
159 long_descr <- paste('The author/maintainer of this package'
160 ,'did not care to enter a longer description.')
163 # using \n\n.\n\n is not very nice, but is necessary to make sure
164 # the longer description does not begin on the synopsis line --- R's
165 # write.dcf does not appear to have a nicer way of doing this.
166 descr <- paste(descr,'"\n\n', long_descr, sep='')
167 # add some extra nice info about the original R package
168 for (r_info in c('Author','Maintainer')) {
169 if (r_info %in% colnames(pkg$description)) {
170 descr <- paste(descr,'\n\n',r_info,': ',pkg$description[1,r_info],sep='')
173 if (Encoding(descr) == "unknown")
174 Encoding(descr) <- "latin1" # or should it be UTF-8
176 control[2,'Description'] <- descr
178 # Debian policy says 72 char width; indent minimally
179 write.dcf(control,file=pkg$debfile('control.in'),indent=1,width=72)
180 write.dcf(control,indent=1,width=72)