Browse code

Code cleanup.

Robert Ivánek authored on 10/01/2022 09:18:58
Showing 6 changed files

... ...
@@ -6,10 +6,11 @@
6 6
 ^\.Rproj\.user$
7 7
 ^\.Rbuildignore$
8 8
 ^\.gitignore$
9
+^\.git$
9 10
 ^\.github$
10 11
 ^\.travis\.yml$
11 12
 ^\.codecov\.yml$
12 13
 ^Dockerfile$
13 14
 ^LICENSE$
14 15
 ^Rplots\.pdf$
15
-^vignettes\/Gviz-logo\.pdf$
16 16
\ No newline at end of file
17
+^vignettes\/Gviz-logo\.pdf$
... ...
@@ -660,16 +660,14 @@ setMethod("initialize", "AnnotationTrack", function(.Object, ...) {
660 660
     if (is.null(list(...)$range) && is.null(list(...)$genome) && is.null(list(...)$chromosome)) {
661 661
         return(.Object)
662 662
     }
663
-    ## the diplay parameter defaults
663
+    ## the display parameter defaults
664 664
     .makeParMapping()
665 665
     .Object <- .updatePars(.Object, "AnnotationTrack")
666 666
     range <- list(...)$range
667 667
     if (!is.null(range) && length(.Object)) {
668 668
         if (!all(.Object@columns %in% colnames(values(range)))) {
669
-            stop(paste(
670
-                "Problem initializing AnnotationTrack need the following columns:",
671
-                paste(.Object@columns, collpase = ", ")
672
-            ), "\n")
669
+            stop("Problem initializing AnnotationTrack, need the following columns:",
670
+                toString(.Object@columns, collapse = ", "))
673 671
         }
674 672
         grp <- if (is(.Object, "GeneRegionTrack")) values(range)$transcript else values(range)$group
675 673
         if (any(vapply(split(as.character(strand(range)), grp), function(x) length(unique(x)), numeric(1)) != 1)) {
... ...
@@ -35,7 +35,7 @@ setMethod("seqnames", "SequenceBSgenomeTrack", function(x) as.character(seqnames
35 35
 setMethod("seqlevels", "RangeTrack", function(x) unique(seqnames(x)))
36 36
 setMethod("seqlevels", "SequenceDNAStringSetTrack", function(x) seqnames(x)[width(x@sequence) > 0])
37 37
 setMethod("seqlevels", "SequenceRNAStringSetTrack", function(x) seqnames(x)[width(x@sequence) > 0])
38
-setMethod("seqlevels", "SequenceBSgenomeTrack", function(x) seqnames(x)[bsapply(new("BSParams", X = x@sequence, FUN = length, simplify = T)) > 0]) # maybe seqnames only to speed-up
38
+setMethod("seqlevels", "SequenceBSgenomeTrack", function(x) seqnames(x)[bsapply(new("BSParams", X = x@sequence, FUN = length, simplify = TRUE)) > 0]) # maybe seqnames only, to speed-up
39 39
 setMethod("seqinfo", "RangeTrack", function(x) table(seqnames(x)))
40 40
 
41 41
 ## Min and max ranges
... ...
@@ -205,7 +205,7 @@ setMethod("subseq", "ReferenceSequenceTrack", function(x, start = NA, end = NA,
205 205
     if (!is.na(start[1] + end[1] + width[1])) {
206 206
         warning("All 'start', 'stop' and 'width' are provided, ignoring 'width'")
207 207
         width <- NA
208
-    } 
208
+    }
209 209
     ## We want start and end to be set if width is provided
210 210
     if (!is.na(width[1])) {
211 211
         if (is.na(start) && is.na(end)) {
... ...
@@ -1015,9 +1015,9 @@ setMethod(
1015 1015
         switch(agFun,
1016 1016
                "mean" = runmean,
1017 1017
                "sum" = runsum,
1018
-               "median" = runmed2 <-  function(x, k, na.rm=FALSE, ...) { 
1018
+               "median" = runmed2 <-  function(x, k, na.rm=FALSE, ...) {
1019 1019
                    na.action <- if (na.rm) { "na.omit" } else { "+Big_alternate" }
1020
-                       runmed(x=as.numeric(x), k=k, na.action=na.action) 
1020
+                       runmed(x=as.numeric(x), k=k, na.action=na.action)
1021 1021
                    },
1022 1022
                "min" = runqmin <- function(x, k, i=1, ...) { runq(x=x, k=k, i=i, ...) },
1023 1023
                "max" = runqmax <- function(x, k, i=k, ...) { runq(x=x, k=k, i=i, ...) },
... ...
@@ -1026,7 +1026,7 @@ setMethod(
1026 1026
     } else {
1027 1027
         if (is.function(agFun)) {
1028 1028
             function(x, k, na.rm=FALSE, endrule="constant") {
1029
-                ans <- vapply(0:(length(x)-k), function(offset) agFun(x[1:k + offset], na.rm=na.rm), FUN.VALUE = numeric(1))
1029
+                ans <- vapply(0:(length(x)-k), function(offset) agFun(x[seq_len(k) + offset], na.rm=na.rm), FUN.VALUE = numeric(1))
1030 1030
                 ans <- Rle(ans)
1031 1031
                 if (endrule == "constant") {
1032 1032
                     j <- (k + 1L)%/%2L
... ...
@@ -2752,11 +2752,7 @@ setMethod("drawGD", signature("GenomeAxisTrack"), function(GdObject, minBase, ma
2752 2752
     if (!is.null(scaleLen)) {
2753 2753
         len <- (maxBase - minBase + 1)
2754 2754
         if (scaleLen > len) {
2755
-            warning(paste("scale (", scaleLen,
2756
-                ") cannot be larger than plotted region",
2757
-                len, " - setting to ~5%\n",
2758
-                sep = ""
2759
-            ))
2755
+            warning(sprintf("scale (%d) cannot be larger than plotted region %d - setting to ~5%\n", scaleLen, len))
2760 2756
             scaleLen <- 0.05
2761 2757
         }
2762 2758
         xoff <- len * 0.03 + minBase
... ...
@@ -3624,21 +3620,21 @@ setMethod("drawGD", signature("DataTrack"), function(GdObject, minBase, maxBase,
3624 3620
             na_idx <- which(is.na(upper))
3625 3621
             ## case 1. there are no error bars to plot at all
3626 3622
             if (length(na_idx) == length(upper)) {
3627
-                if (debugMode) cat("\t Case 1: all empty. returning\n")
3623
+                if (debugMode) message("\t Case 1: all empty. returning")
3628 3624
                 return(TRUE)
3629 3625
                 ## case 2. no missing points
3630 3626
             } else if (length(na_idx) < 1) {
3631
-                if (debugMode) cat("\t Case 2: one continuous polygon\n")
3627
+                if (debugMode) message("\t Case 2: one continuous polygon")
3632 3628
                 panel.polygon(c(x, rev(x)), c(upper, rev(lower)),
3633 3629
                     border = col, col = fill, alpha = alpha, ...
3634 3630
                 )
3635 3631
                 ## case 3. have complete data with some or no missing points
3636 3632
             } else {
3637 3633
                 curr_start <- min(which(!is.na(upper)))
3638
-                if (debugMode) cat(sprintf("\t Case 3: %i of %i NA\n", length(na_idx), length(upper)))
3634
+                if (debugMode) message(sprintf("\t Case 3: %i of %i NA", length(na_idx), length(upper)))
3639 3635
                 curr_na_pos <- 1
3640 3636
                 while (curr_na_pos <= length(na_idx)) {
3641
-                    if (debugMode) cat(sprintf("\t\tcurr_na_pos = %i, na_idx length= %i\n", curr_na_pos, length(na_idx)))
3637
+                    if (debugMode) message(sprintf("\t\tcurr_na_pos = %i, na_idx length= %i", curr_na_pos, length(na_idx)))
3642 3638
                     ## complete the current poly
3643 3639
                     idx <- curr_start:(na_idx[curr_na_pos] - 1)
3644 3640
                     panel.polygon(c(x[idx], rev(x[idx])), c(upper[idx], rev(lower[idx])),
... ...
@@ -3646,7 +3642,7 @@ setMethod("drawGD", signature("DataTrack"), function(GdObject, minBase, maxBase,
3646 3642
                     )
3647 3643
                     ## contiguous empty spots - skip
3648 3644
                     while ((na_idx[curr_na_pos + 1] == na_idx[curr_na_pos] + 1) && (curr_na_pos < length(na_idx))) {
3649
-                        if (debugMode) cat(sprintf("\t\ttight-loop:curr_na_pos = %i\n", curr_na_pos))
3645
+                        if (debugMode) message(sprintf("\t\ttight-loop:curr_na_pos = %i", curr_na_pos))
3650 3646
                         curr_na_pos <- curr_na_pos + 1
3651 3647
                     }
3652 3648
                     ## at this point, either we've finished NA spots or the next one is far away.
... ...
@@ -3656,7 +3652,7 @@ setMethod("drawGD", signature("DataTrack"), function(GdObject, minBase, maxBase,
3656 3652
                 }
3657 3653
                 ## there is one last polygon at the end of the view range
3658 3654
                 if (na_idx[length(na_idx)] < length(upper)) {
3659
-                    if (debugMode) cat("\tWrapping last polygon\n")
3655
+                    if (debugMode) message("\tWrapping last polygon")
3660 3656
                     idx <- curr_start:length(upper)
3661 3657
                     panel.polygon(c(x[idx], rev(x[idx])), c(upper[idx], rev(lower[idx])),
3662 3658
                         col = fill, border = col, alpha = alpha, ...
... ...
@@ -3699,7 +3695,7 @@ setMethod("drawGD", signature("DataTrack"), function(GdObject, minBase, maxBase,
3699 3695
             names(fill) <- NULL
3700 3696
             for (j in seq_along(by)) {
3701 3697
                 g <- names(by)[j]
3702
-                if (debugMode) print(g)
3698
+                if (debugMode) message(g)
3703 3699
                 df <- data.frame(
3704 3700
                     x = position(GdObject), y = mu[[j]],
3705 3701
                     low = mu[[j]] - confint[[j]], high = mu[[j]] + confint[[j]],
... ...
@@ -4781,8 +4777,8 @@ setMethod("show", signature(object = "OverlayTrack"), function(object) {
4781 4777
 
4782 4778
 ## A helper function to plot general information about a ReferenceTrack
4783 4779
 .referenceTrackInfo <- function(object, type) {
4784
-    cat(sprintf(
4785
-        "%s '%s'\n| genome: %s\n| active chromosome: %s\n| referenced file: %s\n",
4780
+    message(sprintf(
4781
+        "%s '%s'\n| genome: %s\n| active chromosome: %s\n| referenced file: %s",
4786 4782
         type,
4787 4783
         names(object),
4788 4784
         genome(object),
... ...
@@ -4790,7 +4786,7 @@ setMethod("show", signature(object = "OverlayTrack"), function(object) {
4790 4786
         object@reference
4791 4787
     ))
4792 4788
     if (length(object@mapping) && type != "ReferenceDataTrack") {
4793
-          cat(sprintf("| mapping: %s\n", paste(names(object@mapping), as.character(object@mapping), sep = "=", collapse = ", ")))
4789
+          message(sprintf("| mapping: %s\n", paste(names(object@mapping), as.character(object@mapping), sep = "=", collapse = ", ")))
4794 4790
       }
4795 4791
 }
4796 4792
 
... ...
@@ -55,11 +55,11 @@
55 55
 
56 56
 ## We want to deal with chromosomes in a reasonable way. This coerces likely inputs to a unified
57 57
 ## chromosome name as understood by UCSC. Accepted inputs are:
58
-##    - a single integer or a character coercable to one or integer-character combinations
58
+##    - a single integer or a character coercible to one or integer-character combinations
59 59
 ##    - a character, starting with 'chr' (case insensitive)
60 60
 ## Arguments:
61 61
 ##    o x: a character string to be converted to a valid UCSC chromosome name
62
-##    o force: a logical flag, force prepending of 'chr' if missing
62
+##    o force: a logical flag, force pre-pending of 'chr' if missing
63 63
 ## Value: the UCSC character name
64 64
 .chrName <- function(x, force = FALSE) {
65 65
     if (!getOption("ucscChromosomeNames") || length(x) == 0) {
... ...
@@ -86,10 +86,9 @@
86 86
             head <- TRUE
87 87
         }
88 88
         if (!head) {
89
-            stop(sprintf(paste(
90
-                "Invalid chromosome identifier '%s'\nPlease consider setting options(ucscChromosomeNames=FALSE)",
91
-                "to allow for arbitrary chromosome identifiers."
92
-            ), y))
89
+            stop(sprintf("Invalid chromosome identifier '%s'\n", y),
90
+                 "Please consider setting options(ucscChromosomeNames=FALSE) ",
91
+                 "to allow for arbitrary chromosome identifiers.")
93 92
         }
94 93
         substring(y, 1, 3) <- tolower(substring(y, 1, 3))
95 94
         y
... ...
@@ -113,7 +112,7 @@
113 112
 ## unimplemented types...
114 113
 ## Arguments:
115 114
 ##    o GdObject: an object inheriting from class GdObject
116
-## Value: a logical skalar indicating whether stacking is needed or not
115
+## Value: a logical scalar indicating whether stacking is needed or not
117 116
 .needsStacking <- function(GdObject) stacking(GdObject) %in% c("squish", "pack", "full")
118 117
 
119 118
 
... ...
@@ -1434,38 +1433,25 @@ addScheme <- function(scheme, name) {
1434 1433
         ds <- listDatasets(bm)
1435 1434
         mt <- ds[match(map$dataset, ds$dataset), "version"]
1436 1435
         if (is.na(mt)) {
1437
-            stop(sprintf(paste(
1438
-                "Gviz thinks that the UCSC genome identifier '%s' should map to the Biomart data set '%s' which is not correct.",
1439
-                "\nPlease manually provide biomaRt object"
1440
-            ), genome, map$dataset))
1436
+            stop(sprintf("Gviz thinks that the UCSC genome identifier '%s' should map to the Biomart data set '%s' which is not correct.",
1437
+                         genome, map$dataset), "\nPlease manually provide biomaRt object")
1441 1438
         }
1442 1439
         if (mt != map$value) {
1443
-            stop(sprintf(
1444
-                paste(
1445
-                    "Gviz thinks that the UCSC genome identifier '%s' should map to the current Biomart head as '%s',",
1446
-                    "but its current version is '%s'.\nPlease manually provide biomaRt object"
1447
-                ),
1448
-                genome, map$value, mt
1449
-            ))
1440
+            stop(sprintf("Gviz thinks that the UCSC genome identifier '%s' should map to the current Biomart head as '%s', ",
1441
+                         genome, map$value, mt), "but its current version is '%s'.\nPlease manually provide biomaRt object.")
1450 1442
         }
1451 1443
     } else {
1452 1444
         bm <- useEnsembl(biomart = "ENSEMBL_MART_ENSEMBL", dataset = map$dataset, host = sprintf("%s.archive.ensembl.org", tolower(sub(".", "", map$date, fixed = TRUE))))
1453 1445
         ds <- listDatasets(bm)
1454 1446
         mt <- ds[match(map$dataset, ds$dataset), "version"]
1455 1447
         if (is.na(mt)) {
1456
-            stop(sprintf(paste(
1457
-                "Gviz thinks that the UCSC genome identifier '%s' should map to the Biomart data set '%s' which is not correct.",
1458
-                "\nPlease manually provide biomaRt object"
1459
-            ), genome, map$dataset))
1448
+            stop(sprintf("Gviz thinks that the UCSC genome identifier '%s' should map to the Biomart data set '%s' which is not correct.",
1449
+                         genome, map$dataset), "\nPlease manually provide biomaRt object")
1460 1450
         }
1461 1451
         if (mt != map$value) {
1462
-            stop(sprintf(
1463
-                paste(
1464
-                    "Gviz thinks that the UCSC genome identifier '%s' should map to Biomart archive %s (version %s) as '%s',",
1465
-                    "but its version is '%s'.\nPlease manually provide biomaRt object"
1466
-                ),
1467
-                genome, sub(".", " ", map$date, fixed = TRUE), map$version, map$value, mt
1468
-            ))
1452
+            stop(sprintf("Gviz thinks that the UCSC genome identifier '%s' should map to Biomart archive %s (version %s) as '%s',",
1453
+                         genome, sub(".", " ", map$date, fixed = TRUE), map$version, map$value, mt),
1454
+                 "but its version is '%s'.\nPlease manually provide biomaRt object")
1469 1455
         }
1470 1456
     }
1471 1457
     return(bm)
... ...
@@ -2216,7 +2202,7 @@ availableDisplayPars <- function(class) {
2216 2202
       }
2217 2203
     class <- match.arg(class, c(
2218 2204
         "GdObject", "GenomeAxisTrack", "RangeTrack", "NumericTrack", "DataTrack", "IdeogramTrack", "StackedTrack",
2219
-        "AnnotationTrack", "DetailsAnnotationTrack", "GeneRegionTrack", "BiomartGeneRegionTrack", 
2205
+        "AnnotationTrack", "DetailsAnnotationTrack", "GeneRegionTrack", "BiomartGeneRegionTrack",
2220 2206
         "AlignmentsTrack", "SequenceTrack", "SequenceBSgenomeTrack", "SequenceDNAStringSetTrack", "SequenceRNAStringSetTrack"
2221 2207
     ))
2222 2208
     parents <- names(getClassDef(class)@contains)
... ...
@@ -2372,10 +2358,8 @@ availableDisplayPars <- function(class) {
2372 2358
         dat
2373 2359
     })
2374 2360
     if (is(res, "try-error")) {
2375
-        warning(sprintf(paste(
2376
-            "File '%s' is not valid according to the GFF3 standard and can not be properly parsed.",
2377
-            "Results may not be what you expected!"
2378
-        ), file))
2361
+        warning(sprintf("File '%s' is not valid according to the GFF3 standard and can not be properly parsed.",
2362
+                        file), "\nResults may not be what you expected!")
2379 2363
         res <- dat
2380 2364
     }
2381 2365
     return(res)
... ...
@@ -2804,13 +2788,8 @@ availableDefaultMapping <- function(file, trackType) {
2804 2788
         vm[[inputType]] <- setNames(list(list(".stream" = stream)), trackType)
2805 2789
     } else {
2806 2790
         if (is.null(vm[[inputType]]) || is.null(vm[[inputType]][[trackType]])) {
2807
-            warning(sprintf(
2808
-                paste(
2809
-                    "There are no default mappings from %s files to %s. Please provide a manual mapping",
2810
-                    "in the track constructor if you haven't already done so."
2811
-                ),
2812
-                inputType, trackType
2813
-            ))
2791
+            warning(sprintf("There are no default mappings from %s files to %s. Please provide a manual mapping",
2792
+                            inputType, trackType), " in the track constructor if you haven't already done so.")
2814 2793
             vm[[inputType]] <- setNames(list(list(".stream" = stream)), trackType)
2815 2794
         }
2816 2795
     }
... ...
@@ -821,7 +821,7 @@ updateDocumentation <- function(outdir="~/Rpacks/Gviz/man")
821 821
 ## run
822 822
 ##       compareDtContent(<className>, <documentationDir>, details)
823 823
 ## and check the results. This should show you what is different between the current man page file and the central definitions
824
-## It will also find things that may have been added/edited manually in the man page file, and might need backporting into the
824
+## It will also find things that may have been added/edited manually in the man page file, and might need back-porting into the
825 825
 ## central definition list.
826 826
 ## When you are happy with the results, run
827 827
 ##       updateRdFile(<className>, <documentationDir>)
... ...
@@ -2357,223 +2357,6 @@ getScheme(name=getOption("Gviz.scheme"))
2357 2357
 
2358 2358
     } 
2359 2359
 
2360
-    \item{AlignedReadTrack}{: 
2361
-
2362
-      \describe{ 
2363
-
2364
-        \item{}{\code{detail="coverage"}: the amount of detail to plot
2365
-          the data. Either \code{coverage} to show the coverage only,
2366
-          or \code{reads} to show individual reads. For large data sets
2367
-          the latter can be very inefficient. Please note that \code{reads}
2368
-          is only available when the object has been created with option
2369
-          \code{coverageOnly=FALSE}.} 
2370
-
2371
-        \item{}{\code{type="histogram"}: the plot type, one or several
2372
-          in \code{c("p","l", "b", "a", "s", "g", "r", "S", "smooth",
2373
-          "histogram", "mountain", "polygon", "h", "boxplot", "gradient",
2374
-          "heatmap", "horizon")}. See the 'Details' section in
2375
-          \code{\linkS4class{DataTrack}} for more information on the
2376
-          individual plotting types.} 
2377
-
2378
-        \item{}{\code{fill="#0080ff"}: the fill color for the coverage
2379
-          indicator.} 
2380
-
2381
-        \item{}{\code{size=NULL}: the relative size of the track.
2382
-          Defaults to size selection based on the underlying data. Can
2383
-          be overridden in the \code{\link{plotTracks}} function.} 
2384
-
2385
-        \item{}{\code{collapse=FALSE}: collapse overlapping ranges and
2386
-          aggregate the underlying data.} 
2387
-
2388
-      } 
2389
-
2390
-      \bold{\emph{Inherited from class StackedTrack:}} 
2391
-
2392
-      \describe{ 
2393
-
2394
-        \item{}{\code{stackHeight=0.75}: Numeric between 0 and 1.
2395
-          Controls the vertical size and spacing between stacked
2396
-          elements. The number defines the proportion of the total
2397
-          available space for the stack that is used to draw the glyphs.
2398
-          E.g., a value of 0.5 means that half of the available vertical
2399
-          drawing space (for each stacking line) is used for the glyphs,
2400
-          and thus one quarter of the available space each is used for
2401
-          spacing above and below the glyph. Defaults to 0.75.} 
2402
-
2403
-        \item{}{\code{reverseStacking=FALSE}: Logical flag. Reverse
2404
-          the y-ordering of stacked items. I.e., features that are
2405
-          plotted on the bottom-most stacks will be moved to the top-most
2406
-          stack and vice versa.} 
2407
-
2408
-      } 
2409
-
2410
-      \bold{\emph{Inherited from class GdObject:}} 
2411
-
2412
-      \describe{ 
2413
-
2414
-        \item{}{\code{alpha=1}: Numeric scalar. The transparency for
2415
-          all track items.} 
2416
-
2417
-        \item{}{\code{alpha.title=NULL}: Numeric scalar. The transparency
2418
-          for the title panel.} 
2419
-
2420
-        \item{}{\code{background.panel="transparent"}: Integer or
2421
-          character scalar. The background color of the content panel.} 
2422
-
2423
-        \item{}{\code{background.title="lightgray"}: Integer or character
2424
-          scalar. The background color for the title panel.} 
2425
-
2426
-        \item{}{\code{background.legend="transparent"}: Integer or
2427
-          character scalar. The background color for the legend.} 
2428
-
2429
-        \item{}{\code{cex.axis=NULL}: Numeric scalar. The expansion
2430
-          factor for the axis annotation. Defaults to \code{NULL}, in
2431
-          which case it is automatically determined based on the
2432
-          available space.} 
2433
-
2434
-        \item{}{\code{cex.title=NULL}: Numeric scalar. The expansion
2435
-          factor for the title panel. This effects the fontsize of both
2436
-          the title and the axis, if any. Defaults to \code{NULL},
2437
-          which means that the text size is automatically adjusted to
2438
-          the available space.} 
2439
-
2440
-        \item{}{\code{cex=1}: Numeric scalar. The overall font expansion
2441
-          factor for all text and glyphs, unless a more specific
2442
-          definition exists.} 
2443
-
2444
-        \item{}{\code{col.axis="white"}: Integer or character scalar.
2445
-          The font and line color for the y axis, if any.} 
2446
-
2447
-        \item{}{\code{col.border.title="white"}: Integer or character
2448
-          scalar. The border color for the title panels.} 
2449
-
2450
-        \item{}{\code{col.frame="lightgray"}: Integer or character
2451
-          scalar. The line color used for the panel frame, if
2452
-          \code{frame==TRUE}} 
2453
-
2454
-        \item{}{\code{col.grid="#808080"}: Integer or character scalar.
2455
-          Default line color for grid lines, both when \code{type=="g"}
2456
-          in \code{\link{DataTrack}}s and when display parameter
2457
-          \code{grid==TRUE}.} 
2458
-
2459
-        \item{}{\code{col.line=NULL}: Integer or character scalar.
2460
-          Default colors for plot lines. Usually the same as the global
2461
-          \code{col} parameter.} 
2462
-
2463
-        \item{}{\code{col.symbol=NULL}: Integer or character scalar.
2464
-          Default colors for plot symbols. Usually the same as the
2465
-          global \code{col} parameter.} 
2466
-
2467
-        \item{}{\code{col.title="white"}: Integer or character scalar.
2468
-          The border color for the title panels} 
2469
-
2470
-        \item{}{\code{col="#0080FF"}: Integer or character scalar.
2471
-          Default line color setting for all plotting elements, unless
2472
-          there is a more specific control defined elsewhere.} 
2473
-
2474
-        \item{}{\code{fontcolor="black"}: Integer or character scalar.
2475
-          The font color for all text, unless a more specific definition
2476
-          exists.} 
2477
-
2478
-        \item{}{\code{fontface.title=2}: Integer or character scalar.
2479
-          The font face for the title panels.} 
2480
-
2481
-        \item{}{\code{fontface=1}: Integer or character scalar. The
2482
-          font face for all text, unless a more specific definition exists.} 
2483
-
2484
-        \item{}{\code{fontfamily.title="sans"}: Integer or character
2485
-          scalar. The font family for the title panels.} 
2486
-
2487
-        \item{}{\code{fontfamily="sans"}: Integer or character scalar.
2488
-          The font family for all text, unless a more specific definition
2489
-          exists.} 
2490
-
2491
-        \item{}{\code{fontsize=12}: Numeric scalar. The font size for
2492
-          all text, unless a more specific definition exists.} 
2493
-
2494
-        \item{}{\code{frame=FALSE}: Boolean. Draw a frame around the
2495
-          track when plotting.} 
2496
-
2497
-        \item{}{\code{grid=FALSE}: Boolean, switching on/off the plotting
2498
-          of a grid.} 
2499
-
2500
-        \item{}{\code{h=-1}: Integer scalar. Parameter controlling the
2501
-          number of horizontal grid lines, see \code{\link{panel.grid}}
2502
-          for details.} 
2503
-
2504
-        \item{}{\code{lineheight=1}: Numeric scalar. The font line
2505
-          height for all text, unless a more specific definition exists.} 
2506
-
2507
-        \item{}{\code{lty.grid="solid"}: Integer or character scalar.
2508
-          Default line type for grid lines, both when \code{type=="g"}
2509
-          in \code{\link{DataTrack}}s and when display parameter
2510
-          \code{grid==TRUE}.} 
2511
-
2512
-        \item{}{\code{lty="solid"}: Numeric scalar. Default line type
2513
-          setting for all plotting elements, unless there is a more
2514
-          specific control defined elsewhere.} 
2515
-
2516
-        \item{}{\code{lwd.border.title=1}: Integer scalar. The border
2517
-          width for the title panels.} 
2518
-
2519
-        \item{}{\code{lwd.title=1}: Integer scalar. The border width
2520
-          for the title panels} 
2521
-
2522
-        \item{}{\code{lwd.grid=1}: Numeric scalar. Default line width
2523
-          for grid lines, both when \code{type=="g"} in \code{\link{DataTrack}}s
2524
-          and when display parameter \code{grid==TRUE}.} 
2525
-
2526
-        \item{}{\code{lwd=1}: Numeric scalar. Default line width setting
2527
-          for all plotting elements, unless there is a more specific
2528
-          control defined elsewhere.} 
2529
-
2530
-        \item{}{\code{min.distance=1}: Numeric scalar. The minimum
2531
-          pixel distance before collapsing range items, only if
2532
-          \code{collapse==TRUE}. See \code{\link{collapsing}} for details.} 
2533
-
2534
-        \item{}{\code{min.height=3}: Numeric scalar. The minimum range
2535
-          height in pixels to display. All ranges are expanded to this
2536
-          size in order to avoid rendering issues. See \code{\link{collapsing}}
2537
-          for details.} 
2538
-
2539
-        \item{}{\code{min.width=1}: Numeric scalar. The minimum range
2540
-          width in pixels to display. All ranges are expanded to this
2541
-          size in order to avoid rendering issues. See \code{\link{collapsing}}
2542
-          for details.} 
2543
-
2544
-        \item{}{\code{reverseStrand=FALSE}: Logical scalar. Set up the
2545
-          plotting coordinates in 3' -> 5' direction if \code{TRUE}.
2546
-          This will effectively mirror the plot on the vertical axis.} 
2547
-
2548
-        \item{}{\code{rotation.title=90}: The rotation angle for the
2549
-          text in the title panel. Even though this can be adjusted,
2550
-          the automatic resizing of the title panel will currently not
2551
-          work, so use at own risk.} 
2552
-
2553
-        \item{}{\code{rotation=0}: The rotation angle for all text
2554
-          unless a more specific definiton exists.} 
2555
-
2556
-        \item{}{\code{showAxis=TRUE}: Boolean controlling whether to
2557
-          plot a y axis (only applies to track types where axes are
2558
-          implemented).} 
2559
-
2560
-        \item{}{\code{showTitle=TRUE}: Boolean controlling whether to
2561
-          plot a title panel. Although this can be set individually
2562
-          for each track, in multi-track plots as created by
2563
-          \code{\link{plotTracks}} there will still be an empty
2564
-          placeholder in case any of the other tracks include a title.
2565
-          The same holds true for axes. Note that the the title panel
2566
-          background color could be set to transparent in order to
2567
-          completely hide it.} 
2568
-
2569
-        \item{}{\code{v=-1}: Integer scalar. Parameter controlling the
2570
-          number of vertical grid lines, see \code{\link{panel.grid}}
2571
-          for details.} 
2572
-
2573
-      } 
2574
-
2575
-    } 
2576
-
2577 2360
   } 
2578 2361
 
2579 2362
 }