Skip to content

Commit

Permalink
1.0.1 release cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
pfh committed Feb 4, 2018
1 parent e88ad7d commit 43cd006
Show file tree
Hide file tree
Showing 13 changed files with 96 additions and 234 deletions.
4 changes: 2 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
Package: topconfects
Title: Top Results by Confident Effect Size
Version: 0.0.1
Version: 1.0.1
Authors@R: person("Paul", "Harrison", email = "pfh@logarithmic.net", role = c("aut", "cre"))
Description: Uses limma's treat or edgeR's glmTreat to rank genes (or other
features) by effect size.
features) by confident log2 fold change.
Depends:
R (>= 3.3.0)
Imports:
Expand Down
14 changes: 0 additions & 14 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -5,25 +5,11 @@ export(confects_plot_me)
export(edger_confects)
export(edger_group_confects)
export(effect_contrast)
export(effect_contrast_ratio)
export(effect_gamma)
export(effect_link_log2)
export(effect_rss)
export(effect_rssm)
export(effect_sd)
export(effect_shift)
export(effect_shift_log2)
export(effect_shift_stepdown)
export(effect_shift_stepdown_log2)
export(effect_shift_stepup)
export(effect_shift_stepup_log2)
export(group_effect_rssm)
export(group_effect_shift)
export(group_effect_shift_log2)
export(group_effect_shift_stepdown)
export(group_effect_shift_stepdown_log2)
export(group_effect_shift_stepup)
export(group_effect_shift_stepup_log2)
export(limma_confects)
export(limma_group_confects)
export(limma_nonlinear_confects)
Expand Down
114 changes: 57 additions & 57 deletions R/fit.R
Original file line number Diff line number Diff line change
Expand Up @@ -156,21 +156,21 @@ effect_contrast <- function(contrast) {
}


#' Ratio of contrasts effect.
#'
#' Ratio of two contrasts, i.e. \code{sum(contrast1*beta)/sum(contrast2*beta)}.
#'
#' @param contrast1 First contrast weights, a vector with the same length as the number of columns in the design matrix.
#'
#' @param contrast2 Second contrast weights, a vector with the same length as the number of columns in the design matrix.
#'
#' \code{sum(contrast2*beta)} should always produce a positive value.
#'
#' @return
#'
#' An object defining how to calculate an effect size.
#'
#' @export
# Ratio of contrasts effect.
#
# Ratio of two contrasts, i.e. \code{sum(contrast1*beta)/sum(contrast2*beta)}.
#
# @param contrast1 First contrast weights, a vector with the same length as the number of columns in the design matrix.
#
# @param contrast2 Second contrast weights, a vector with the same length as the number of columns in the design matrix.
#
# \code{sum(contrast2*beta)} should always produce a positive value.
#
# @return
#
# An object defining how to calculate an effect size.
#
# @export
effect_contrast_ratio <- function(contrast1, contrast2) {
list(
signed = TRUE,
Expand All @@ -190,19 +190,19 @@ effect_contrast_ratio <- function(contrast1, contrast2) {
}


#' Standard-deviation of a set of coefficients as effect size
#'
#' This is intended as the effect size version of an ANOVA. For effect_sd, the effect size is the standard deviation of some coefficients about their mean. For effect_rssm, it is the root sum of squared differences from the mean. For effect_rss, it is simply the square root of the sum of squared coefficients.
#'
#' \code{effect_rssm} may be better suited to comparing effect sizes from designs with differing numbers of coefficients, such as differential exon usage.
#'
#' @param coef The column numbers of the design matrix for the relevant coefficients.
#'
#' @return
#'
#' An object defining how to calculate an effect size.
#'
#' @export
# Standard-deviation of a set of coefficients as effect size
#
# This is intended as the effect size version of an ANOVA. For effect_sd, the effect size is the standard deviation of some coefficients about their mean. For effect_rssm, it is the root sum of squared differences from the mean. For effect_rss, it is simply the square root of the sum of squared coefficients.
#
# \code{effect_rssm} may be better suited to comparing effect sizes from designs with differing numbers of coefficients, such as differential exon usage.
#
# @param coef The column numbers of the design matrix for the relevant coefficients.
#
# @return
#
# An object defining how to calculate an effect size.
#
# @export
effect_sd <- function(coef) {
n <- length(coef)
assert_that(n > 1) #n=2 case may be problematic
Expand Down Expand Up @@ -230,8 +230,8 @@ effect_sd <- function(coef) {
}


#' @rdname effect_sd
#' @export
# @rdname effect_sd
# @export
effect_rssm <- function(coef) {
n <- length(coef)
assert_that(n > 1) #n=2 case may be problematic
Expand Down Expand Up @@ -259,8 +259,8 @@ effect_rssm <- function(coef) {
}


#' @rdname effect_sd
#' @export
# @rdname effect_sd
# @export
effect_rss <- function(coef) {
list(
signed = FALSE,
Expand Down Expand Up @@ -294,8 +294,8 @@ effect_rss <- function(coef) {
#'
#' Note that this effect size is not symmetric: \code{effect_shift_log2(c(1,2),c(3,4))} and \code{effect_shift_log2(c(1,3),c(2,4))} will give different results.
#'
#' The _stepdown and _stepup versions are for cumulative distributions. These are most useful in group effect form, where they can be used to examine shifts in start or end of transcriptions from RNA-seq or microarray data.
#'
# The _stepdown and _stepup versions are for cumulative distributions. These are most useful in group effect form, where they can be used to examine shifts in start or end of transcriptions from RNA-seq or microarray data.
#
#' @param coef1 Column numbers in the design matrix for the first condition, in some meaningful order.
#'
#' @param coef2 Corresponding column numbers for the second condition.
Expand All @@ -313,8 +313,8 @@ effect_shift <- function(coef1, coef2) {
effect_shift_inner(n, sign_mat, coef1, coef2, c(-1,1))
}

#' @rdname effect_shift
#' @export
# @rdname effect_shift
# @export
effect_shift_stepdown <- function(coef1, coef2) {
assert_that(length(coef1) == length(coef2))
n <- length(coef1)
Expand All @@ -331,8 +331,8 @@ effect_shift_stepdown <- function(coef1, coef2) {
effect_shift_inner(n, mat, coef1, coef2, NULL)
}

#' @rdname effect_shift
#' @export
# @rdname effect_shift
# @export
effect_shift_stepup <- function(coef1, coef2) {
effect_shift_stepdown(rev(coef2), rev(coef1))
}
Expand Down Expand Up @@ -375,33 +375,33 @@ effect_shift_inner <- function(n, mat, coef1, coef2, limits=NULL) {
effect_shift_log2 <- function(coef1, coef2)
effect_link_log2(effect_shift(coef1, coef2))

#' @rdname effect_shift
#' @export
# @rdname effect_shift
# @export
effect_shift_stepdown_log2 <- function(coef1, coef2)
effect_link_log2(effect_shift_stepdown(coef1, coef2))

#' @rdname effect_shift
#' @export
# @rdname effect_shift
# @export
effect_shift_stepup_log2 <- function(coef1, coef2)
effect_link_log2(effect_shift_stepup(coef1, coef2))



#' Goodman and Kruskall's gamma, Yule's Q
#'
#' Goodman and Kruskall's gamma as an effect size. Yule's Q is a special case where coef1 and coef2 both have two coefficients, and is a symmetric effect size for the interaction of two experimental factors.
#'
#' \code{effect_gamma_log2} is adapted to work with log2 scaled coefficients. This is almost certainly the version you want.
#'
#' @param coef1 Column numbers in the design matrix for the first condition, in some meaningful order.
#'
#' @param coef2 Corresponding column numbers for the second condition.
#'
#' @return
#'
#' An object defining how to calculate an effect size.
#'
#' @export
# Goodman and Kruskall's gamma, Yule's Q
#
# Goodman and Kruskall's gamma as an effect size. Yule's Q is a special case where coef1 and coef2 both have two coefficients, and is a symmetric effect size for the interaction of two experimental factors.
#
# \code{effect_gamma_log2} is adapted to work with log2 scaled coefficients. This is almost certainly the version you want.
#
# @param coef1 Column numbers in the design matrix for the first condition, in some meaningful order.
#
# @param coef2 Corresponding column numbers for the second condition.
#
# @return
#
# An object defining how to calculate an effect size.
#
# @export
effect_gamma <- function(coef1, coef2) {
assert_that(length(coef1) == length(coef2))
n <- length(coef1)
Expand Down
62 changes: 31 additions & 31 deletions R/group_confects.R
Original file line number Diff line number Diff line change
Expand Up @@ -20,27 +20,27 @@ group_effect_1 <- function(design, coef, effect_func, design_common=NULL) {
get_effect = get_effect)
}

#' Group effect for differential splicing
#'
#' Create a group effect object to detect differential splicing (or similar). The effect size is the root sum of squared differences of the coefficient from the mean.
#'
#' The coefficient should represent a difference between two conditions.
#'
#' The idea is to detect differences in differential expression between features in a group (ie exons in a gene).
#'
#' @param design Design matrix.
#'
#' @param coef Column number in design matrix of the coefficient to be tested.
#'
#' @param design_common Experimental! Optional sample-level design matrix. For example, this can be used to account for a batch effect or matched samples.
#'
#' @return
#'
#' A group effect object.
#'
#' @seealso \code{\link{effect_rssm}}
#'
#' @export
# Group effect for differential splicing
#
# Create a group effect object to detect differential splicing (or similar). The effect size is the root sum of squared differences of the coefficient from the mean.
#
# The coefficient should represent a difference between two conditions.
#
# The idea is to detect differences in differential expression between features in a group (ie exons in a gene).
#
# @param design Design matrix.
#
# @param coef Column number in design matrix of the coefficient to be tested.
#
# @param design_common Experimental! Optional sample-level design matrix. For example, this can be used to account for a batch effect or matched samples.
#
# @return
#
# A group effect object.
#
# @seealso \code{\link{effect_rssm}}
#
# @export
group_effect_rssm <- function(design, coef, design_common=NULL)
group_effect_1(design, coef, effect_rssm, design_common=design_common)

Expand Down Expand Up @@ -73,7 +73,7 @@ group_effect_2 <- function(design, coef1, coef2, effect_func, design_common=NULL
#'
#' The coefficients should represent the expression levels in two different conditions.
#'
#' The _stepup and _stepdown versions may be used to look for shifts in start or end of transcription from RNA-seq or microarray data, where the observed levels are expected to be cumulative or reverse cumulative.
# The _stepup and _stepdown versions may be used to look for shifts in start or end of transcription from RNA-seq or microarray data, where the observed levels are expected to be cumulative or reverse cumulative.
#'
#' @param design Design matrix.
#'
Expand All @@ -93,13 +93,13 @@ group_effect_2 <- function(design, coef1, coef2, effect_func, design_common=NULL
group_effect_shift <- function(design, coef1, coef2, design_common=NULL)
group_effect_2(design, coef1, coef2, effect_shift, design_common=design_common)

#' @rdname group_effect_shift
#' @export
# @rdname group_effect_shift
# @export
group_effect_shift_stepup <- function(design, coef1, coef2, design_common=NULL)
group_effect_2(design, coef1, coef2, effect_shift_stepup, design_common=design_common)

#' @rdname group_effect_shift
#' @export
# @rdname group_effect_shift
# @export
group_effect_shift_stepdown <- function(design, coef1, coef2, design_common=NULL)
group_effect_2(design, coef1, coef2, effect_shift_stepdown, design_common=design_common)

Expand All @@ -108,13 +108,13 @@ group_effect_shift_stepdown <- function(design, coef1, coef2, design_common=NULL
group_effect_shift_log2 <- function(design, coef1, coef2, design_common=NULL)
group_effect_2(design, coef1, coef2, effect_shift_log2, design_common=design_common)

#' @rdname group_effect_shift
#' @export
# @rdname group_effect_shift
# @export
group_effect_shift_stepup_log2 <- function(design, coef1, coef2, design_common=NULL)
group_effect_2(design, coef1, coef2, effect_shift_stepup_log2, design_common=design_common)

#' @rdname group_effect_shift
#' @export
# @rdname group_effect_shift
# @export
group_effect_shift_stepdown_log2 <- function(design, coef1, coef2, design_common=NULL)
group_effect_2(design, coef1, coef2, effect_shift_stepdown_log2, design_common=design_common)

Expand Down Expand Up @@ -154,7 +154,7 @@ group_design_maker <- function(design, design_common=NULL) {
memoise(group_design)
}

#' Group confects (differential exon usage, etc)
#' Group confects (differential 5' or 3' end usage, etc)
#'
#' Find differential exon usage, etc.
#'
Expand Down
4 changes: 3 additions & 1 deletion index.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
# | -●- Topconfects

TOP results by CONfident efFECT Size. Topconfects is an R package intended for RNA-seq or microarray Differntial Expression analysis and similar, where we are interested in placing confidence bounds on many effect sizes--one per gene--from few samples.
TOP results by CONfident efFECT Size. Topconfects is an R package intended for RNA-seq or microarray Differntial Expression analysis and similar, where we are interested in placing confidence bounds on many effect sizes---one per gene---from few samples.

Topconfects builds on [TREAT](http://bioinformatics.oxfordjournals.org/content/25/6/765.long) p-values offered by the limma and edgeR packages. It tries a range of fold changes, and uses this to rank genes by effect size while maintaining a given FDR. This also produces confidence bounds on the fold changes, with adjustment for multiple testing. See [nest_confects](reference/nest_confects.html) for details.

Expand Down Expand Up @@ -42,11 +42,13 @@ Topconfects is developed by Paul Harrison [@paulfharrison](https://twitter.com/p

<br/>

<!--
## Future work
Gene-set enrichment tests. Here also the smallest p-value does not necessarily imply the greatest interest.
<br/>
-->

## References

Expand Down
2 changes: 1 addition & 1 deletion man/edger_group_confects.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

21 changes: 0 additions & 21 deletions man/effect_contrast_ratio.Rd

This file was deleted.

22 changes: 0 additions & 22 deletions man/effect_gamma.Rd

This file was deleted.

Loading

0 comments on commit 43cd006

Please sign in to comment.