[BioC] package structure

Robert M. Flight rflight79 at gmail.com
Sat Feb 26 16:42:36 CET 2011


Thank you both very much for the suggestions, I'm sure one or the
other will definitely help me solve this. This should definitely make
the overall package development easier.

-Robert

On Fri, Feb 25, 2011 at 20:26, Vincent Carey <stvjc at channing.harvard.edu> wrote:
> In addition to Valerie's suggestions, you might consider an
> interesting approach to dynamic response to package loading in the
> oligoClasses/oligo stack.  The packageEvent and setHook functions of
> base R are used quite effectively there -- see oligoClasses/R/zzz.R
>
> On Fri, Feb 25, 2011 at 5:43 PM, Valerie Obenchain <vobencha at fhcrc.org> wrote:
>> Hi Robert,
>>
>> I don't think you need to create two packages. You can put Rgraphviz and
>> Cairo in the Suggests field of your package DESCRIPTION file.
>> Using the .onLoad function in a zzz.R file you can include a check if
>> the user has the packages loaded and set a global varaiable.
>> The global variable can be used to dictate if code dependent on
>> Rgarphviz and Ciaro is run.
>>
>> For example,
>>
>> In a zzz.R file, define a global variable
>>
>>    .options <- new.env(parent = emptyenv())
>>
>> Use the .onLoad function to set the global variable,
>>
>>    .onLoad <- function(...) {
>>        .options[["foo.available"]] <- require(foo, quietly = TRUE)
>>    }
>>
>> In your package code, check the value of the global variable to execute
>> code dependent on the graph packages,
>>
>> if(.options[["foo.available"]]) do something ... else do something else ....
>>
>>
>> Valerie
>>
>>
>>
>> On 02/25/2011 12:15 PM, Robert M. Flight wrote:
>>> Hi All,
>>>
>>> I'm looking for some advice on package structure and dependencies.
>>>
>>> I'm working on a package that allows for different types of
>>> meta-analyses between different datasets. As part of the original
>>> development leading up to creating a package, I also generated a
>>> series of functions that do a lot of work to generate navigable
>>> results using HTML imagemaps.
>>>
>>> However, the visualizations depend currently on Rgraphviz (layouts)
>>> and Cairo (PNG figure generation). The results can be summarized in
>>> different ways than the visualizations I have developed (potentially
>>> using Cytoscape, or just as a table), and I want to make the package
>>> as easy to install and use as possible. Therefore, if I can make the
>>> analysis package not require Rgraphviz and Cairo, I think that would
>>> be good.
>>>
>>> Would it be advisable to create a second package containing the
>>> functions necessary for creating the visualizations? Otherwise I
>>> introduce dependencies that may not even be used by the users of the
>>> package. And I don't know of any other proper way (i.e. besides
>>> "require", which I believe is to be avoided in packages) to call other
>>> packages than having them in the DESCRIPTION and NAMESPACE files, and
>>> I believe anything in NAMESPACE requires that the package be
>>> installed.
>>>
>>> I would appreciate others thoughts on this.
>>>
>>> Thanks,
>>>
>>> -Robert
>>>
>>> Robert M. Flight, Ph.D.
>>> University of Louisville Bioinformatics Laboratory
>>> University of Louisville
>>> Louisville, KY
>>>
>>> PH 502-852-1809 (HSC)
>>> PH 502-852-0467 (Belknap)
>>> EM robert.flight at louisville.edu
>>> EM rflight79 at gmail.com
>>>
>>> Williams and Holland's Law:
>>>        If enough data is collected, anything may be proven by
>>> statistical methods.
>>>
>>> _______________________________________________
>>> Bioconductor mailing list
>>> Bioconductor at r-project.org
>>> https://stat.ethz.ch/mailman/listinfo/bioconductor
>>> Search the archives: http://news.gmane.org/gmane.science.biology.informatics.conductor
>>>
>>
>>
>>        [[alternative HTML version deleted]]
>>
>> _______________________________________________
>> Bioconductor mailing list
>> Bioconductor at r-project.org
>> https://stat.ethz.ch/mailman/listinfo/bioconductor
>> Search the archives: http://news.gmane.org/gmane.science.biology.informatics.conductor
>>
>



More information about the Bioconductor mailing list