[R] closest match in R to c-like struct?
(Ted Harding)
Ted.Harding at manchester.ac.uk
Sat May 1 22:19:02 CEST 2010
See below.
On 01-May-10 19:14:08, steven mosher wrote:
> maybe I can illustrate the problem by showing how a c programmer
> might think about the problem and the kinds of mistakes 'we' (I)
> make when trying to do this in R
>
> cstruct<-function(int, bool){
> +
> + myint<- int*2;
> +
> + mybool<-!bool;
> + myvec<-rep(mybool,10)
> + mymat<-matrix(myint*10,nrow=3,ncol=3)
> + myframe<-data.frame(rep(myint,5),rep(bool,5))
> + returnlist<-list(myint,mybool,myvec,mymat,myframe)
> + return(returnlist)
> +
> +
> +
> + }
>
># so I have a function that returns a list of hetergenous variables.
># an int, a bool, a vector of bools, a matrix of ints, a dataframe of
># ints and bools
>
>> test<-cstruct(3,T)
>
>
>> test
> [[1]]
> [1] 6
>
> [[2]]
> [1] FALSE
>
> [[3]]
> [1] FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE
>
> [[4]]
> [,1] [,2] [,3]
> [1,] 60 60 60
> [2,] 60 60 60
> [3,] 60 60 60
>
> [[5]]
> rep.myint..5. rep.bool..5.
> 1 6 TRUE
> 2 6 TRUE
> 3 6 TRUE
> 4 6 TRUE
> 5 6 TRUE
>
># Now I want to access the first element of my list which is an
># "an int"
># first mistake I always make is I just revert to thinking in the
># 'dot' structure of a c struct.
>
>> test.myint
> Error: object 'test.myint' not found
>
># Then I think its stored like a var in a dataframe, accessed by
># the $
>> test$myint
> NULL
>
># then I try to access the first element of the list
>> test[1]
> [[1]]
> [1] 6
>
># That works.. but the [[1]] confuses me when I eval test[1] I want 6
># back
># again thinking in C.
># so I try the third element
>
>> test[3]
> [[1]]
> [1] FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE
>
># ok I get my vect of bools back. Now I want the first element
># of that thing
># well test[3] is that thing.. and I want element 1 of test[3]
>
>> test[3][1]
> [[1]]
> [1] FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE
>
>#hmm thats not what I expect. I wanted F back.
># frustrated I try this which i know is wrong
>
>> test[3,1]
> Error in test[3, 1] : incorrect number of dimensions
>
># crap.. maybe the $ is supposed to be used
>> test$V3
> NULL
>
># arrg.. how about 'dot"
>> test.myvec
> Error: object 'test.myvec' not found
>
>
> Anyways, That's the kind of frustration. I have a list, third element
> is a matrix how do I referernce the 2 row 2 colum of the matrix in my
> list.. for example.
> and so forth..
When you constructed your return-list, you simply entered the list
components using the R-names of the objects, as used in the code:
returnlist<-list(myint,mybool,myvec,mymat,myframe)
To use the "$" extractor, you need to give them "external" names,
so you could modify the above to:
returnlist<-list(Myint=myint,Mybool=mybool,
Myvec=myvec,Mymat=mymat,Myframe=myframe)
Then, after
test<-cstruct(3,T)
you can access test$Myint, test$mybool, etc.; and, in particular,
test$Mymat will be the matrix mymat you put in there, so you
can extract elements of this using
test$Mymat[2,2]
for the element in row 2, column 2, and so on. Without making
the return-list a named list, its components have no names,
so then test$mymat (as you did) will not work because there
is no component with name "mymat" (there is no component with
any name). The name "mymat" was used by R to identify the
object whose contents were to be placed in the list; that
internal object-name does not get placed in the list.
Note: In my modification above I used "Myint=myint" etc. instead
of "myint=myint" to highlight the distinction between the
component-name and the object-name. But you can just as well
use exactly the same name for component-name as for object-name:
R will recognise them as distinct and do the right thing.
So you could just as well do:
returnlist<-list(myint=myint,mybool=mybool,
myvec=myvec,mymat=mymat,myframe=myframe)
and then, after
test<-cstruct(3,T)
do
test$Mymat[2,2]
You can also use positional references if the list components have
no names. Since your "mymat" is in position 4,
test[[4]]
would return the whole matrix. Then
test[[4]][2,2]
would return the element in row 2, column 2.
As a standard example, try for instance
X <- 0.1*((-10):10)
Y <- 0.5*X + 0.2*rnorm(length(X))
LM <- lm(Y ~ X)
summary(LM)
# Call:
# lm(formula = Y ~ X)
# Residuals:
# Min 1Q Median 3Q Max
# -0.373283 -0.083458 0.009206 0.139763 0.278242
# Coefficients:
# Estimate Std. Error t value Pr(>|t|)
# (Intercept) -0.06018 0.04448 -1.353 0.192
# X 0.46270 0.07345 6.299 4.78e-06 ***
# ---
# Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
# Residual standard error: 0.2038 on 19 degrees of freedom
# Multiple R-squared: 0.6762, Adjusted R-squared: 0.6592
# F-statistic: 39.68 on 1 and 19 DF, p-value: 4.784e-06
Suppose you just wanted the Estimates and P-values. Then
summary(LM)$coef[,c(1,4)]
# Estimate Pr(>|t|)
# (Intercept) -0.06018002 1.919241e-01
# X 0.46269824 4.783990e-06
The component $coef of summary(LM) is a matrix, so the above
extracts its first and fourth columns.
Alternatively, similarly to the positional extraction shown
for your "test" list:
summary(LM)[[4]][,c(2,4)]
# Std. Error Pr(>|t|)
# (Intercept) 0.04447759 1.919241e-01
# X 0.07345233 4.783990e-06
Since LM is of class lm ("linear model"), summary(LM) sees this and
calls the method summary.lm; this returns a list, and to find out
what's in it have a look at
?summary.lm
under "Value:"
"The function 'summary.lm' computes and returns a list of summary
statistics of the fitted linear model given in ?object?, using the
components (list elements) '"call"' and '"terms"' from its
argument, plus
[...]
coefficients: a p x 4 matrix with columns for the estimated
coefficient, its standard error, t-statistic and corresponding
(two-sided) p-value. Aliased coefficients are omitted.
[...]"
And so on. ("coefficients" is, by implication from '?summary.lm',
in position 4 in the list -- just like your "mymat", as it happens!)
Ted.
> On Sat, May 1, 2010 at 10:56 AM, Ted Harding
> <Ted.Harding at manchester.ac.uk>wrote:
>
>> On 01-May-10 16:58:49, Giovanni Azua wrote:
>> >
>> > On May 1, 2010, at 6:48 PM, steven mosher wrote:
>> >> I was talking with another guy on the list about this very topic.
>> >>
>> >> A simple example would help.
>> >>
>> >> first a sample C struct, and then how one would do the equivalent
>> >> in
>> >> R.
>> >>
>> >> In the end i suppose one want to do a an 'array' of these structs,
>> >> or
>> >> list
>> >> of the structs.
>> >
>> > Or like in my use-case ... I needed a c-like struct to define the
>> > type
>> > for aggregating the data to return from a function.
>> >
>> > Best regards,
>> > Giovanni
>>
>> Assuming that I understand what you want, this is straightforward
>> and can be found throughout the many functions available in R.
>> The general form is:
>>
>> myfunction <- function(...){
>> <code to compute objects A1, A2, ... , An>
>> list(valA1=A1, valA2=A2, ... , valAn=An)
>> }
>>
>> and then a call like
>>
>> myresults <- myfunction(...)
>>
>> will create a list "myresults" with compnents "valA1", ... ,"valAn"
>> which you can access as desired on the lines of
>>
>> myresults$valA5
>>
>> As a simple example, the following is a function which explores
>> by simulation the power of the Fisher Exact Test for comparing
>> two proportions in a 2x2 table:
>>
>> power.fisher.test <- function(p1,p2,n1,n2,alpha=0.05,nsim=100){
>> y1 <- rbinom(nsim,size=n1,prob=p1)
>> y2 <- rbinom(nsim,size=n2,prob=p2)
>> y <- cbind(y1,n1-y1,y2,n2-y2)
>> p.value <- rep(0,nsim)
>> for (i in 1:nsim)
>> p.value[i] <- fisher.test(matrix(y[i,],2,2))$p.value
>> list(Pwr=mean(p.value < alpha),SE.Pwr=sd(p.value <
>> alpha)/sqrt(nsim))
>> }
>>
>> So, given two binomials B(n1,p1) and B(n2,p2), what would be the
>> power of the Fisher test to detect that p1 was different from p2,
>> at given significance level alpha? This is investigated by repeating,
>> nsim times:
>> sample from Bin(n1,p1), sample from Bin(n2.p2)
>> do a Fisher test and get its P-value; store it
>> in a vector p.value of length nsim
>> and then finally:
>> estimate the power as the proportion Pwr of the nsim cases
>> in which the P-value was less than alpha
>> get the SE of this estimate
>> return these two values as components Pwr and SE.Pwr of a list
>>
>> As it happens, here each component of the resulting list is of
>> the same type (a single number); but in a different computation
>> each component (and of course there could be more than two)
>> could be anything -- even another list. So you can have lists
>> of lists ... !
>>
>> Thus, instead of the simple returned list above:
>>
>> list(Pwr=mean(p.value < alpha),
>> SE.Pwr=sd(p.value < alpha)/sqrt(nsim))
>>
>> you could have
>>
>> list(Binoms=list(Bin1=list(size=n1,prob=p1),
>> Bin2=list(size=n2,prob=p2))
>> Pwr=mean(p.value < alpha),
>> SE.Pwr=sd(p.value < alpha)/sqrt(nsim))
>>
>> thus also returning the details of the Binomials for which the
>> simulation was carried out. You could access these all together as:
>>
>> power.fisher.test(...)$Binoms
>>
>> or separately as
>>
>> power.fisher.test(...)$Binoms$Bin1
>> or
>> power.fisher.test(...)$Binoms$Bin2
>>
>> or even
>> power.fisher.test(...)$Binoms$Bin1$size
>> power.fisher.test(...)$Binoms$Bin1$prob
>> etc.
>>
>> Ted.
>>
>> --------------------------------------------------------------------
>> E-Mail: (Ted Harding) <Ted.Harding at manchester.ac.uk>
>> Fax-to-email: +44 (0)870 094 0861
>> Date: 01-May-10 Time: 18:56:50
>> ------------------------------ XFMail ------------------------------
>>
>> ______________________________________________
>> R-help at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-help
>> PLEASE do read the posting guide
>> http://www.R-project.org/posting-guide.html
>> and provide commented, minimal, self-contained, reproducible code.
>>
>
> [[alternative HTML version deleted]]
>
> ______________________________________________
> R-help at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide
> http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.
--------------------------------------------------------------------
E-Mail: (Ted Harding) <Ted.Harding at manchester.ac.uk>
Fax-to-email: +44 (0)870 094 0861
Date: 01-May-10 Time: 21:18:59
------------------------------ XFMail ------------------------------
More information about the R-help
mailing list