File: configureApp.R

package info (click to toggle)
r-cran-rsconnect 1.3.4-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,044 kB
  • sloc: python: 185; sh: 13; makefile: 5
file content (191 lines) | stat: -rw-r--r-- 5,937 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
#' Configure an Application
#'
#' Configure an application running on a remote server.
#'
#' @inheritParams deployApp
#'
#' @param appName Name of application to configure
#' @param appDir Directory containing application. Defaults to
#'   current working directory.
#' @inheritParams deployApp
#' @param redeploy Re-deploy application after its been configured.
#' @param size Configure application instance size
#' @param instances Configure number of application instances
#' @examples
#' \dontrun{
#'
#' # set instance size for an application
#' configureApp("myapp", size="xlarge")
#' }
#' @seealso [applications()], [deployApp()]
#' @note This function works only for ShinyApps servers.
#' @export
configureApp <- function(appName, appDir = getwd(), account = NULL, server = NULL,
                         redeploy = TRUE, size = NULL,
                         instances = NULL, logLevel = c("normal", "quiet", "verbose")) {

  accountDetails <- accountInfo(account, server)
  checkShinyappsServer(accountDetails$server)

  if (is.null(appName))
    appName <- basename(appDir)
  application <- resolveApplication(accountDetails, appName)

  displayStatus <- displayStatus(identical(logLevel, "quiet"))

  # some properties may required a rebuild to take effect
  rebuildRequired <- FALSE

  # get a list of properties to set
  properties <- list()
  if (! is.null(size)) {
    properties[["application.instances.template"]] <- size
  }
  if (! is.null(instances)) {
    properties[["application.instances.count"]] <- instances
  }

  # set application properties
  client <- clientForAccount(accountDetails)
  for (i in names(properties)) {
    propertyName <- i
    propertyValue <- properties[[i]]

    # dispatch to the appropriate client implementation
    if (is.function(client$configureApplication))
      client$configureApplication(application$id, propertyName, propertyValue)
    else if (is.function(client$setApplicationProperty))
      client$setApplicationProperty(application$id, propertyName, propertyValue)
    else
      stop("Server ", accountDetails$server, " has no appropriate configuration method.")
  }

  # redeploy application if requested
  if (redeploy) {
    if (length(properties) > 0) {
      deployApp(appDir = appDir, appName = appName, account = account, logLevel = logLevel, upload = rebuildRequired)
    }
    else
    {
      displayStatus("No configuration changes to deploy")
    }
  }
}

#' Set Application property
#'
#' Set a property on currently deployed ShinyApps application.
#'
#' @param propertyName Name of property
#' @param propertyValue Property value
#' @param appName Name of application
#' @param appPath Directory or file that was deployed. Defaults to current
#'   working directory.
#' @inheritParams deployApp
#' @param force Forcibly set the property
#'
#' @note This function only works for ShinyApps servers.
#'
#' @examples
#' \dontrun{
#'
#' # set instance size for an application
#' setProperty("application.instances.count", 1)
#'
#' # disable application package cache
#' setProperty("application.package.cache", FALSE)
#'
#' }
#' @export
setProperty <- function(propertyName, propertyValue, appPath = getwd(),
                        appName = NULL, account = NULL, server = NULL, force = FALSE) {

  deployment <- findDeployment(
    appPath = appPath,
    appName = appName,
    server = server,
    account = account
  )
  accountDetails <- accountInfo(deployment$account, deployment$server)
  checkShinyappsServer(accountDetails$server)

  client <- clientForAccount(accountDetails)
  application <- getAppByName(client, accountDetails, deployment$name)

  invisible(client$setApplicationProperty(application$id,
                                         propertyName,
                                         propertyValue,
                                         force))
}

#' Unset Application property
#'
#' Unset a property on currently deployed ShinyApps application (restoring to
#' its default value)
#'
#' @inheritParams setProperty
#' @param force Forcibly unset the property
#'
#' @note This function only works for ShinyApps servers.
#'
#' @examples
#' \dontrun{
#'
#' # unset application package cache property to revert to default
#' unsetProperty("application.package.cache")
#'
#' }
#' @export
unsetProperty <- function(propertyName, appPath = getwd(), appName = NULL,
                          account = NULL, server = NULL, force = FALSE) {

  deployment <- findDeployment(
    appPath = appPath,
    appName = appName,
    server = server,
    account = account
  )
  accountDetails <- accountInfo(deployment$account, deployment$server)
  checkShinyappsServer(accountDetails$server)

  client <- clientForAccount(accountDetails)
  application <- getAppByName(client, accountInfo, deployment$name)

  invisible(client$unsetApplicationProperty(application$id,
                                           propertyName,
                                           force))
}


#' Show Application property
#'
#' Show properties of an application deployed to ShinyApps.
#'
#' @param appName Name of application
#' @param appPath Directory or file that was deployed. Defaults to current
#'   working directory.
#' @inheritParams deployApp
#'
#' @note This function works only for ShinyApps servers.
#'
#' @export
showProperties <- function(appPath = getwd(), appName = NULL, account = NULL, server = NULL) {

  deployment <- findDeployment(
    appPath = appPath,
    appName = appName,
    account = account,
    server = server
  )
  accountDetails <- accountInfo(deployment$account, deployment$server)
  checkShinyappsServer(accountDetails$server)

  client <- clientForAccount(accountDetails)
  application <- getAppByName(client, accountDetails, deployment$name)

  # convert to data frame
  res <- do.call(rbind, application$deployment$properties)
  df <- as.data.frame(res, stringsAsFactors = FALSE)
  names(df) <- c("value")
  return(df)
}