Skip to content

Commit

Permalink
fix: update to fetch USCS cytoband info, closes #19
Browse files Browse the repository at this point in the history
  • Loading branch information
m-jahn committed May 13, 2024
1 parent 3984adf commit 5234de3
Show file tree
Hide file tree
Showing 3 changed files with 8 additions and 23 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ importFrom(Biostrings,readAAStringSet)
importFrom(Biostrings,readDNAStringSet)
importFrom(Biostrings,translate)
importFrom(GenomeInfoDb,"seqlengths<-")
importFrom(GenomeInfoDb,genome)
importFrom(GenomeInfoDb,seqlengths)
importFrom(GenomeInfoDb,seqnames)
importFrom(GenomicAlignments,alphabetFrequencyFromBam)
Expand Down
20 changes: 2 additions & 18 deletions R/geom_ideogram.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@
#' @importFrom utils menu
#' @importFrom rtracklayer ucscGenomes ucscTableQuery tableName getTable
#' GRangesForUCSCGenome browserSession
#' @importFrom GenomeInfoDb seqlengths seqlengths<- seqnames
#' @importFrom GenomeInfoDb seqlengths genome seqlengths<- seqnames
#' @export
#'
#' @examples
Expand Down Expand Up @@ -95,22 +95,6 @@ geom_ideogram <- function(genome = "hg19", mark.color = "red", mark.alpha = 0.7,

#' @export
ggplot_add.ideogram <- function(object, plot, object_name) {
# if (length(plot$layers) == 0) {
# # geom_base
# # get plot data
# plot.data <- plot[[1]]$layers[[1]]$data
# # prepare plot range
# plot.chr <- as.character(plot.data[1, "seqnames"])
# plot.region.start <- plot.data[1, "start"]
# plot.region.end <- plot.data[nrow(plot.data), "end"]
# } else {
# # get plot data
# plot.data <- plot$layers[[1]]$data
# # prepare plot range
# plot.chr <- as.character(plot.data[1, "seqnames"])
# plot.region.start <- plot$coordinates$limits$x[1]
# plot.region.end <- plot$coordinates$limits$x[2]
# }
# get plot data, plot data should contain bins
if ("patchwork" %in% class(plot)) {
plot.data <- plot[[1]]$layers[[1]]$data
Expand Down Expand Up @@ -146,7 +130,7 @@ ggplot_add.ideogram <- function(object, plot, object_name) {
plot.height <- object$plot.height

# get genome and chr ideogram
genome.info <- suppressWarnings(getIdeogram(genome = genome, subchr = plot.chr, cytobands = TRUE))
genome.info <- suppressWarnings(getIdeogram(genomes = genome, subchr = plot.chr, cytobands = TRUE))
genome.info.df <- genome.info %>% as.data.frame()
# get genome length
genome.length <- genome.info.df[nrow(genome.info.df), "end"]
Expand Down
10 changes: 5 additions & 5 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -242,9 +242,8 @@ SplitTxExonUTR <- function(exon.df, utr.df) {
# From: https://github.com/jorainer/biovizBase/blob/master/R/ideogram.R
# Fix bug: the names on the supplied 'seqlengths' vector must be
# identical to the seqnames
getIdeogram <- function(genome, subchr = NULL, cytobands = TRUE) {
.gnm <- genome
lst <- lapply(.gnm, function(genome) {
getIdeogram <- function(genomes, subchr = NULL, cytobands = TRUE) {
lst <- lapply(genomes, function(genome) {
if (!(exists("session") && extends(class(session), "BrowserSession"))) {
session <- rtracklayer::browserSession()
}
Expand All @@ -255,8 +254,9 @@ getIdeogram <- function(genome, subchr = NULL, cytobands = TRUE) {
}
if (cytobands) {
message("Loading ideogram...")
GenomeInfoDb::genome(session) <- genome
tryres <- try(query <-
rtracklayer::ucscTableQuery(session, "cytoBand", genome))
rtracklayer::ucscTableQuery(session, table = "cytoBand", genome = genome))
if (!inherits(tryres, "try-error")) {
rtracklayer::tableName(query) <- "cytoBand"
df <- rtracklayer::getTable(query)
Expand Down Expand Up @@ -292,7 +292,7 @@ getIdeogram <- function(genome, subchr = NULL, cytobands = TRUE) {
gr <- sort(gr)
gr
})
names(lst) <- .gnm
names(lst) <- genomes
if (length(lst) == 1) {
res <- lst[[1]]
} else {
Expand Down

0 comments on commit 5234de3

Please sign in to comment.