Hi Jean-Louis,
jean-louis.ruelle at gskbio.com wrote:
> Dear all,
>
> I'd like to combine hgu133a and hgu133a2 chips in a single data
analysis
> (gcrma, ...).
> I used combine.AffyBatch to get both the combined affybatch and the
hybrid
> CDF, and all worked smoothly.
> However, I get into trouble when running rma, it looks like the new
CDF
> environment is not known to R; that is further confirmed in using
> getCdfEnvAffy, as can be seen below.
> Indeed, I'd like to background correct the raw data with gcrma, but
that
> can be done separately on both data sets (is it correct ?), which
will
> then be combined after for normalisation and summarization with rma.
> However, the problem remains.
> Has anybody been successful at combining hgu133a and hgu133a2 ?
>
> I'm running R 2.3.1 and BioC 1.8 , on Win XP.
> rawdata.p6p12 and rawdata.p15 are plain affybatches;
>
>
>>library(matchprobes)
>>
>
> combined=combineAffyBatch(list(rawdata.p6p12,rawdata.p15),c("hgu133a
probe","hgu133a2probe"),newcdf="hgu133aa2")
> package:hgu133aprobe hgu133aprobe
> package:hgu133a2probe hgu133a2probe
> 241837 unique probes in common
>
>>rawdata.p6p15=combined$dat
>>hgu133aa2cdf=combined$cdf
>>
>>str(rawdata.p6p15)
>
> Formal class 'AffyBatch' [package "affy"] with 10 slots
> ..@ cdfName : chr "hgu133aa2"
> ..@ nrow : num 0
> ..@ ncol : num 0
> ..@ exprs : num [1:483674, 1:21] 662 1078 1631 4645 6793
...
> lot of stuff deleted
>
>
>>eset=rma(rawdata.p6p15)
>
> Error in getCdfInfo(object) : Could not obtain CDF environment,
problems
> encountered:
> Specified environment does not contain hgu133aa2
> Library - package hgu133aa2cdf not installed
> Data for package affy did not contain hgu133aa2cdf
> Bioconductor - hgu133aa2cdf not available
I think the problem here is that you have named your cdf hgu133aa2cdf,
but the cdfname of your AffyBatch is hgu133aa2. Try
cdfName(rawdata.p6p15) <- "hgu133aa2cdf"
and see if it works.
HTH,
Jim
>
>>library(altcdfenvs)
>
> Loading required package: makecdfenv
>
>>getCdfEnvAffy(rawdata.p6p15)
>
> Error in getCdfInfo(abatch) : Could not obtain CDF environment,
problems
> encountered:
> Specified environment does not contain hgu133aa2
> Library - package hgu133aa2cdf not installed
> Data for package affy did not contain hgu133aa2cdf
> Bioconductor - hgu133aa2cdf not available
>
>
> Thanks for your help.
> Jean-Louis
>
> ====================================================
> Jean-Louis Ruelle
> GlaxoSmithKline Biologicals, R&D
> Rue de l'Institut, 89
> 1330 Rixensart
> Belgium
>
> Phone : + 32-2-6568451
> Fax : +32-2-6568436
> email : jean-louis.ruelle at gskbio.com
>
>
>
> The information contained in this message is confidential
an...{{dropped}}
>
> _______________________________________________
> Bioconductor mailing list
> Bioconductor at stat.math.ethz.ch
> https://stat.ethz.ch/mailman/listinfo/bioconductor
> Search the archives:
http://news.gmane.org/gmane.science.biology.informatics.conductor
--
James W. MacDonald, M.S.
Biostatistician
Affymetrix and cDNA Microarray Core
University of Michigan Cancer Center
1500 E. Medical Center Drive
7410 CCGC
Ann Arbor MI 48109
734-647-5623
**********************************************************
Electronic Mail is not secure, may not be read every day, and should
not be used for urgent or sensitive issues.
>
> Now, for everybody, it seems (at least on my side) that cdfName()
can only
> get the name of environment associated with the affybatch, and
cannot set
> it.
That will be the case whenever the accessor function doing the
assignment
has not been defined.
cdfName() does return something because the function that 'gets' the
value
has been defined (and for this particular class), while the function
that
'sets' a value has not.
I suspect that this was done to prevent beginners from accidentally
changing this (but as you note it, it can cause trouble to people that
do want to change it as well).
> I've set it with :
> rawdata.p6p15 at cdfName <- "hgu133aa2cdf"
>
This way, you are accessing directly the attribute (or slot) called
cdfName
(using the "@" operator, that could also be done by calling the
function "@":
"@"(rawdata.p6p15, "cdfName", "hgu133aa2cdf")
"@"(rawdata.p6p15, "cdfName")
), and since the function "@" can 'get' and 'set'
you are free to assign a value to the slot.
L.
lgautier at altern.org writes:
>>
>> Now, for everybody, it seems (at least on my side) that cdfName()
can only
>> get the name of environment associated with the affybatch, and
cannot set
>> it.
>
> That will be the case whenever the accessor function doing the
assignment
> has not been defined.
> cdfName() does return something because the function that 'gets' the
value
> has been defined (and for this particular class), while the function
that
> 'sets' a value has not.
>
> I suspect that this was done to prevent beginners from accidentally
> changing this (but as you note it, it can cause trouble to people
that
> do want to change it as well).
>
>> I've set it with :
>> rawdata.p6p15 at cdfName <- "hgu133aa2cdf"
>>
>
> This way, you are accessing directly the attribute (or slot) called
cdfName
> (using the "@" operator, that could also be done by calling the
function "@":
> "@"(rawdata.p6p15, "cdfName", "hgu133aa2cdf")
> "@"(rawdata.p6p15, "cdfName")
> ), and since the function "@" can 'get' and 'set'
> you are free to assign a value to the slot.
If there is a reasonable use-case for setting the CDF name, let's
add a cdfName<- method and discourage use of '@'.
+ seth