gene.graph {exonmap}R Documentation

Use the X:MAP database to find annotated gene structure and generate a plot

Description

Draws a variety of line graphs mapping expression data to a given gene

Usage

gene.graph(gene,data,gps,gp.cols,gp.lty,gp.pch,scale.to.gene = FALSE,type=c("mean-int","median-int","mean-fc","median-fc","splicing-index"), use.symbol = TRUE,use.mt=FALSE,probes.min=4,main="gene",xlab,ylab,xlim,ylim,exon.y=0,exon.height=1,by.order=FALSE,show.introns,exon.bg.col="#eeeeee",exon.bg.border.col="#dddddd")

Arguments

gene The gene to plot
data matrix or ExpressionSet object containg expression data
gps List of groups by which to collect the expression data when calculating, for example, fold change or mean intensities. Each group is a vector of column indices into data
gp.cols Vector of colours to colour each group's line by. If generating a fold or splicing index plot, only the first element is used.
gp.lty Vector of line types for each group's line. If generating a fold change or splicing index plot, only the first element is used.
gp.pch For 'by.order' plots, a vector of plot character types for each group's line. If generating a fold change or splicing index plot, only the first element is used.
scale.to.gene If TRUE, then mean-center each plot around zero.
type The type of calculatin used to create the data for the plot. See details.
use.symbol If TRUE then label by the gene symbol, if FALSE, the gene name.
use.mt If TRUE then include multitarget probesets. See select.probewise and exclude.probewise for details on how the filtering is done.
probes.min Show probesets with at least this many probes hitting the gene.
main Plot title.
xlab X axis label. Overrides use.symbol.
ylab Y axis label.
xlim Range of values to plot on the x axis.
ylim Range of values to plot on the y axis.
exon.y y position to draw exons
exon.height Height to draw exons.
by.order If TRUE then the x axis position corresponds to the nucleotide position of the probeset match against the genome (see details), including introns. If FALSE, then sort probesets by chromosomal location, and plot them in numerical order.
show.introns Only has an effect when by.order is TRUE. If FALSE then don't include intronic probesets in the plot.
exon.bg.col Background colour used to draw exons in by.order plots. Setting the colour to NA suppresses them.
exon.bg.border.col Border colour used to draw exons. Setting the colour to NA suppresses them.

Details

At its simplest, takes an Ensembl gene id and plots the intron-exon structure of the gene along with one or more line plots calculated from the expression data. The method used to calculate the plotted data is specified by type, and can be used to define plots based on average intensities, fold changes, or the splicing index.

The function divides the expression data into one or more groups, defined by the parameter gps which expects a list, each element of which is a vector of indices into the columns (i.e. arrays) of data.

For example, gps=list(1:6) would define one group containing the first 6 arrays in data, while gps=list(1:3,4:6) would define two groups, of three arrays each, and gps=list(1,2,3,4,5,6) would define six groups with one array in each. When the type of the plot is 'mean-int' or 'median-int' then the mean (or median) intensity for each group is plotted as a separate line in the plot. If the type is 'mean-fc', 'median-fc' or 'splicing-index', then gps is expected to contain two elements and a single line is plotted, representing the average fold change or splicing index (as appropriate).

The x position of each probeset is taken to be half way between the 5'-most and 3'-most probe for that probeset. If by.order is TRUE, then probesets are sorted by x position and plotted in numeric order. For these (by.order=TRUE plots), if show.introns is FALSE, then only exon-targeting probesets are plotted.

Value

none

Author(s)

Crispin Miller

References

http://bioinformatics.picr.man.ac.uk/

See Also

gene.strip plot.gene

Examples

 
## Not run: 
   xmapDatabase("Human")
   data(exonmap)
   par(mfrow=c(3,2))
   gene.graph("ENSG00000141510",x.rma,gps=list(1:3,4:6),type="mean-fc",gp.col="red")
   gene.graph("ENSG00000141510",x.rma,gps=list(1:3,4:6),type="mean-int",gp.col=c("red","orange"))
   gene.graph("ENSG00000141510",x.rma,gps=list(1,2,3,4,5,6),type="mean-int",gp.col=1:6)
   gene.graph("ENSG00000141510",x.rma,gps=list(1,2,3,4,5,6),type="mean-int",gp.col=1:6,by.order=TRUE)
   gene.graph("ENSG00000141510",x.rma,gps=list(1,2,3,4,5,6),type="mean-int",gp.col=1:6,by.order=TRUE,show.introns=TRUE)
   gene.graph("ENSG00000141510",x.rma,gps=list(1,2,3,4,5,6),type="mean-int",gp.col=c(rep("red",3),rep("orange",3)),gp.pch=c(1,1,1,2,2,2),by.order=TRUE,show.introns=TRUE,exon.bg.col=NA)
## End(Not run)

[Package exonmap version 1.4.3 Index]