Browse code

Missing argument added

WilliamMc authored on 22/12/2020 19:27:07
Showing 2 changed files

... ...
@@ -1,7 +1,7 @@
1 1
 Package: idpr
2 2
 Type: Package
3 3
 Title: Profiling and Analyzing Intrinsically Disordered Proteins in R
4
-Version: 1.0.003
4
+Version: 1.0.005
5 5
 Authors@R: c(person(c("William", "M."), "McFadden", 
6 6
                 email = "wmm27@pitt.edu", 
7 7
                 role = c("cre", "aut")),
... ...
@@ -29,6 +29,12 @@
29 29
 #'   \code{\link{netCharge}} for additional details
30 30
 #' @param pH numeric value, 7.0 by default.
31 31
 #'   The environmental pH is used to calculate residue charge.
32
+#' @param plotResults logical value, TRUE by default.
33
+#'   This determines what is returned. If \code{plotResults = FALSE}, a
34
+#'   data frame is returned with the Sequence(s), Average Scaled Hydropathy,
35
+#'   and Average Net Charge. 
36
+#'   If  \code{plotResults = TRUE}, a graphical output is returned (ggplot)
37
+#'   showing the Charge Hydropathy Plot (recommended).
32 38
 #' @param ... additional arguments to be passed to
33 39
 #'   \link[idpr:netCharge]{idpr::netCharge()},
34 40
 #'   \link[idpr:meanScaledHydropathy]{idpr::meanScaledHydropathy()} or
... ...
@@ -108,6 +114,7 @@ chargeHydropathyPlot <- function(
108 114
     customPlotTitle = NA,
109 115
     pH = 7.0,
110 116
     pKaSet = "IPC_protein",
117
+    plotResults = TRUE,
111 118
     ...) {
112 119
 
113 120
     if (nchar(sequence[1]) == 1) {
... ...
@@ -131,6 +138,10 @@ chargeHydropathyPlot <- function(
131 138
     dataCollected$sequence <- do.call(rbind, sequenceList)
132 139
     dataCollected$avg_scaled_hydropathy <- do.call(rbind, hydropathyList)
133 140
     dataCollected$avg_net_charge <- do.call(rbind, chargeList)
141
+    
142
+    if (!plotResults) {
143
+        return(dataCollected)
144
+    }
134 145
 
135 146
     # ---- Math for plotting lines
136 147
     #The equations for the lines are: