From: jnpaulson <nosson@gmail.com>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@116424 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,6 +1,7 @@ |
1 | 1 |
version 1.13.xx (2015) |
2 | 2 |
+ Upgrade support for biom-format vs. 2.0 |
3 | 3 |
+ Fixed issue - "MRtable, etc will report NA rows when user requests more features than available" |
4 |
+ + Fixed s2 miscalculation in calcZeroComponent |
|
4 | 5 |
version 1.11.xx (2015) |
5 | 6 |
+ Adding fitFeatureModel - a feature based zero-inflated log-normal model. |
6 | 7 |
+ Added MRcoefs,MRtable,MRfulltable support for fitFeatureModel output. |
... | ... |
@@ -148,7 +148,8 @@ calcZeroComponent<-function(mat,mod,weights){ |
148 | 148 |
fit <- glm.fit(mod, weights[i,], family=binomial()) |
149 | 149 |
cf = coefficients(fit) |
150 | 150 |
df = fit$df.residual |
151 |
- s2 = sum( (weights[i,] - t(mod %*% (exp(cf)/(1+exp(cf)))))^2 )/df |
|
151 |
+ mc = exp(mod %*% cf) |
|
152 |
+ s2 = sum((weights[i, ] - t(mc/(1 + mc)))^2)/df |
|
152 | 153 |
# s2 = sum(residuals(fit)^2)/df |
153 | 154 |
c(beta= cf, s2 = s2, df = df) |
154 | 155 |
}) |