]> git.donarmstrong.com Git - cran2deb.git/blob - pkg/trunk/R/debcontrol.R
sysreq: remove depth 2 nesting of brackets in comments.
[cran2deb.git] / pkg / trunk / R / debcontrol.R
1 get_dependencies <- function(pkg,extra_deps) {
2     # determine dependencies
3     dependencies <- r_dependencies_of(description=pkg$description)
4     depends <- list()
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
9                                 ,repopref=pkg$repo
10                                 ,build=build))
11     }
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'])
20         depends$bin = c(sysreq,depends$bin)
21         depends$build = c(sysreq,depends$build)
22     }
23
24     # make sure we depend upon R in some way...
25     if (!length(grep('^r-base',depends$build))) {
26         depends$build = c(depends$build,pkgname_as_debian('R',version='>= 2.7.0',build=T))
27         depends$bin   = c(depends$bin,  pkgname_as_debian('R',version='>= 2.7.0',build=F))
28     }
29     # also include stuff to allow tcltk to build (suggested by Dirk)
30     depends$build = c(depends$build,'xvfb','xauth','xfonts-base')
31
32     # remove duplicates
33     depends <- lapply(depends,unique)
34
35     # append the Debian dependencies
36     depends$build=c(depends$build,'debhelper (>> 4.1.0)','cdbs')
37     if (pkg$archdep) {
38         depends$bin=c(depends$bin,'${shlibs:Depends}')
39     }
40
41     # the names of dependent source packages (to find the .changes file to
42     # upload via dput). these can be found recursively.
43     depends$r = r_dependency_closure(dependencies)
44     # append command line dependencies
45     depends$r = c(extra_deps$r, depends$r)
46     return(depends)
47 }
48
49 sysreqs_as_debian <- function(sysreq_text) {
50     # form of this field is unspecified (ugh) but most people seem to stick
51     # with this
52     debs <- c()
53     for (sysreq in strsplit(sysreq_text,'[[:space:]]*,[[:space:]]*')[[1]]) {
54         startreq = sysreq
55         # constant case
56         sysreq = tolower(sysreq)
57         # drop version information/comments for now
58         sysreq = gsub('[[][^])]*[]]','',sysreq)
59         sysreq = gsub('\\([^)]*\\)','',sysreq)
60         sysreq = gsub('[[][^])]*[]]','',sysreq)
61         sysreq = gsub('version','',sysreq)
62         sysreq = gsub('from','',sysreq)
63         sysreq = gsub('[<>=]*[[:space:]]*[[:digit:]]+[[:digit:].+:~-]*','',sysreq)
64         # byebye URLs
65         sysreq = gsub('(ht|f)tps?://[[:alnum:]!?*"\'(),%$_@.&+/=-]*','',sysreq)
66         # squish out space
67         sysreq = chomp(gsub('[[:space:]]+',' ',sysreq))
68         deb <- db_sysreq_override(sysreq)
69         if (is.na(deb)) {
70             message(paste('E: do not know what to do with SystemRequirement:',sysreq))
71             message(paste('E: original SystemRequirement:',startreq))
72             stop('unmet system requirement')
73         }
74         message(paste('N: mapped SystemRequirement',startreq,'onto',deb,'via',sysreq))
75         if (deb == 'build-essential') {
76             # already in any build environment so no explicit depend.
77             message(paste('N: SystemRequirement',startreq,'dropped'))
78         } else {
79             debs = c(debs,deb)
80         }
81     }
82     return(debs)
83 }
84
85 generate_control <- function(pkg) {
86     # construct control file
87     control = data.frame()
88     control[1,'Source'] = pkg$srcname
89     control[1,'Section'] = 'math'
90     control[1,'Priority'] = 'optional'
91     control[1,'Maintainer'] = maintainer
92     control[1,'Build-Depends'] = paste(pkg$depends$build,collapse=', ')
93     control[1,'Standards-Version'] = '3.8.0'
94
95     control[2,'Package'] = pkg$debname
96     control[2,'Architecture'] = 'all'
97     if (pkg$archdep) {
98         control[2,'Architecture'] = 'any'
99     }
100     control[2,'Depends'] = paste(pkg$depends$bin,collapse=', ')
101
102     # bundles provide virtual packages of their contents
103     if (pkg$is_bundle) {
104         control[2,'Provides'] = paste(
105                     lapply(r_bundle_contains(pkg$name)
106                           ,function(name) return(pkgname_as_debian(paste(name)
107                                                                   ,repopref=pkg$repo)))
108                           ,collapse=', ')
109     }
110
111     # generate the description
112     descr = 'GNU R package "'
113     if ('Title' %in% colnames(pkg$description)) {
114         descr = paste(descr,pkg$description[1,'Title'],sep='')
115     } else {
116         descr = paste(descr,pkg$name,sep='')
117     }
118     if (pkg$is_bundle) {
119         long_descr <- pkg$description[1,'BundleDescription']
120     } else {
121         long_descr <- pkg$description[1,'Description']
122     }
123     # using \n\n.\n\n is not very nice, but is necessary to make sure
124     # the longer description does not begin on the synopsis line --- R's
125     # write.dcf does not appear to have a nicer way of doing this.
126     descr = paste(descr,'"\n\n', long_descr, sep='')
127     if ('URL' %in% colnames(pkg$description)) {
128         descr = paste(descr,'\n\nURL: ',pkg$description[1,'URL'],sep='')
129     }
130     control[2,'Description'] = descr
131
132     # Debian policy says 72 char width; indent minimally
133     write.dcf(control,file=pkg$debfile('control.in'),indent=1,width=72)
134     write.dcf(control,indent=1,width=72)
135 }
136