... | ... |
@@ -602,6 +602,9 @@ setMethod("setStacks", "AnnotationTrack", function(GdObject, recomputeRanges = T |
602 | 602 |
bins <- rep(1, length(GdObject)) |
603 | 603 |
} else { |
604 | 604 |
gp <- group(GdObject) |
605 |
+ if (!is.factor(gp)) { |
|
606 |
+ gp <- factor(gp, levels=unique(gp)) |
|
607 |
+ } |
|
605 | 608 |
needsGrp <- any(duplicated(gp)) |
606 | 609 |
lranges <- .dpOrDefault(GdObject, ".__groupRanges") |
607 | 610 |
gpt <- if (needsGrp) table(gp) else rep(1, length(GdObject)) |
... | ... |
@@ -1919,6 +1922,9 @@ setMethod("drawGD", signature("OverlayTrack"), function(GdObject, ...) { |
1919 | 1922 |
stacks <- max(bins) |
1920 | 1923 |
res <- .pxResolution(coord = "x") |
1921 | 1924 |
gp <- group(GdObject) |
1925 |
+ if (!is.factor(gp)) { |
|
1926 |
+ gp <- factor(gp, levels=unique(gp)) |
|
1927 |
+ } |
|
1922 | 1928 |
grpSplit <- split(range(GdObject), gp) |
1923 | 1929 |
grpRanges <- unlist(range(grpSplit)) |
1924 | 1930 |
needBar <- vapply(grpSplit, length, FUN.VALUE = numeric(1L)) > 1 & width(grpRanges) > res |
... | ... |
@@ -2835,6 +2835,9 @@ availableDefaultMapping <- function(file, trackType) { |
2835 | 2835 |
} |
2836 | 2836 |
if (length(GdObject) > 0) { |
2837 | 2837 |
gp <- group(GdObject) |
2838 |
+ if (!is.factor(gp)) { |
|
2839 |
+ gp <- factor(gp, levels=unique(gp)) |
|
2840 |
+ } |
|
2838 | 2841 |
needsGrp <- any(duplicated(gp)) |
2839 | 2842 |
finalRanges <- if (needsGrp) { |
2840 | 2843 |
groups <- split(range(GdObject), gp) |