moduleConfig.R 62.8 KB
Newer Older
1
2
# DQAgui - A graphical user interface (GUI) to the functions implemented in the
# R package 'DQAstats'.
3
# Copyright (C) 2019-2022 Universitätsklinikum Erlangen
Lorenz Kapsner's avatar
Lorenz Kapsner committed
4
5
6
7
8
9
10
11
12
13
14
15
16
17
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 3 of the License, or
# (at your option) any later version.
#
# This program is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
# GNU General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program.  If not, see <http://www.gnu.org/licenses/>.

18

19
#' @title module_config_server
kapsner's avatar
kapsner committed
20
21
22
23
24
#'
#' @param input Shiny server input object
#' @param output Shiny server output object
#' @param session Shiny session object
#' @param rv The global 'reactiveValues()' object, defined in server.R
25
26
#' @param input_re The Shiny server input object, wrapped into a reactive
#'   expression: input_re = reactive({input})
kapsner's avatar
kapsner committed
27
#'
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
#' @return The function returns a shiny server module.
#'
#' @seealso \url{https://shiny.rstudio.com/articles/modules.html}
#'
#' @examples
#' if (interactive()) {
#' rv <- list()
#' shiny::callModule(
#'   module_config_server,
#'   "moduleConfig",
#'   rv = rv,
#'   input_re = reactive(input)
#' )
#' }
#'
kapsner's avatar
kapsner committed
43
44
#' @export
#'
45
# module_config_server
46
47
48
module_config_server <-
  function(input, output, session, rv, input_re) {
    # filepath roots dir
49
50
51
    roots <- c(
      # home = "/home/",
      home = "~",
52
53
      source = Sys.getenv("CSV_SOURCE_BASEPATH"),
      target = Sys.getenv("CSV_TARGET_BASEPATH")
54
55
    )

56

57
58
59
60
61
62
    ## Mapping between system_type and tab_name:
    system_types_mapping <-
      list("postgres" = "PostgreSQL",
           "csv" = "CSV",
           "oracle" = "Oracle")

63
64
65
66
    # If source-csv-path-button is clicked, read the path and save it:
    # root-folder of shinyFiles::shinyDirChoose
    shinyFiles::shinyDirChoose(
      input = input,
67
68
      id = "config_sourcedir_in",
      roots = roots,
69
70
      defaultRoot = ifelse(roots[["source"]] == "", "home", "source"),
      allowDirCreate = FALSE,
71
      session = session
72
    )
73
74
75

    shinyFiles::shinyDirChoose(
      input = input,
76
77
      id = "config_targetdir_in",
      roots = roots,
78
79
      defaultRoot = ifelse(roots[["target"]] == "", "home", "target"),
      allowDirCreate = FALSE,
80
      session = session
81
    )
82
83

    # observe click button event
84
    observeEvent(
85
      eventExpr = input$config_sourcedir_in,
86
87
      ignoreInit = TRUE,
      ignoreNULL = TRUE,
88
      handlerExpr = {
89
        rv$csv_dir_src_clicked <- FALSE
Lorenz Kapsner's avatar
Lorenz Kapsner committed
90
        rv$csv_dir_src <- as.character(
91
          DIZtools::clean_path_name(
Lorenz Kapsner's avatar
Lorenz Kapsner committed
92
93
94
95
            shinyFiles::parseDirPath(
              roots = roots,
              selection = input$config_sourcedir_in
            )))
96

97
        rv$source$settings$path <- rv$csv_dir_src
98

99
100
101
        if (!identical(rv$source$settings$path, character(0)) &&
            !is.null(rv$source$settings$path) &&
            rv$source$settings$path != "") {
102
103
          # workaround to tell ui, that it is there
          output$source_csv_dir <- reactive({
104
            DIZtools::feedback(
105
              paste0("Source file dir: ",
106
                     rv$source$settings$path),
107
108
109
110
              findme = "ad440c9fcb",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )
111
            paste(rv$source$settings$path)
112
113
          })
          outputOptions(output, "source_csv_dir", suspendWhenHidden = FALSE)
114
115
          rv$source$system_name <-
            input_re()[["moduleConfig-source_csv_presettings_list"]]
116
          rv$source$system_type <- "csv"
117

118
          ## Fixes #42 (GitLab):
119
120
          env_var_name <-
            paste0(toupper(rv$source$system_name), "_PATH")
121
          DIZtools::feedback(
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
            print_this = paste0(
              "CSV path '",
              rv$source$settings$path,
              "' was assigned in the GUI.",
              " Assigning it to the environment variable '",
              env_var_name,
              "' now."
            ),
            findme = "272f922ab2",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
          ## Setting the path as environment variable (this must be done via
          ## `do.call` because otherwise the name `env_var_name` will
          ## become the name of the env-var and not its value.
          ## Sys.setenv(env_var_name = rv$source$settings$path) leads to
          ## `env_var_name = "path"` be created and not
          ## `example_name = "path"`):
140
          DIZtools::setenv2(key = env_var_name, val = rv$source$settings$path)
141
142
          rm(env_var_name)

143
          DIZtools::feedback(
144
145
146
            paste0("rv$source$system_type = ",
                   rv$source$system_type),
            findme = "91ebdd5a1d")
147
148
149
150
151
          output$source_system_feedback_txt <-
            renderText({
              feedback_txt(system = "CSV", type = "source")
            })
        }
152
        check_load_data_button(rv, session)
153
      }
154
155
156
    )
    observeEvent(
      eventExpr = input$config_targetdir_in,
157
158
      ignoreInit = TRUE,
      ignoreNULL = TRUE,
159
      handlerExpr = {
160
        rv$csv_dir_tar_clicked <- FALSE
Lorenz Kapsner's avatar
Lorenz Kapsner committed
161
        rv$csv_dir_tar <- as.character(
162
          DIZtools::clean_path_name(
Lorenz Kapsner's avatar
Lorenz Kapsner committed
163
164
165
166
            shinyFiles::parseDirPath(
              roots = roots,
              selection = input$config_targetdir_in
            )))
167
        rv$target$settings$path <- rv$csv_dir_tar
168

169
170
171
        if (!identical(rv$target$settings$path, character(0)) &&
            !is.null(rv$target$settings$path) &&
            rv$target$settings$path != "") {
172
173
          # workaround to tell ui, that it is there
          output$target_csv_dir <- reactive({
174
            DIZtools::feedback(
175
              paste0("Target file dir: ",
176
                     rv$target$settings$path),
177
178
179
180
              findme = "6f18c181e5",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )
181
            paste(rv$target$settings$path)
182
183
          })
          outputOptions(output, "target_csv_dir", suspendWhenHidden = FALSE)
184
185
          rv$target$system_name <-
            input_re()[["moduleConfig-target_csv_presettings_list"]]
186
          rv$target$system_type <- "csv"
187

188
          ## Fixes #42 (GitLab):
189
190
          env_var_name <-
            paste0(toupper(rv$target$system_name), "_PATH")
191
          DIZtools::feedback(
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
            print_this = paste0(
              "CSV path '",
              rv$target$settings$path,
              "' was assigned in the GUI.",
              " Assigning it to the environment variable '",
              env_var_name,
              "' now."
            ),
            findme = "fe2b85dc3c",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
          ## Setting the path as environment variable (this must be done via
          ## `do.call` because otherwise the name `env_var_name` will
          ## become the name of the env-var and not its value.
          ## Sys.setenv(env_var_name = rv$target$settings$path) leads to
          ## `env_var_name = "path"` be created and not
          ## `example_name = "path"`):
210
          DIZtools::setenv2(key = env_var_name, val = rv$target$settings$path)
211
212
          rm(env_var_name)

213
          DIZtools::feedback(
214
215
216
            paste0("rv$target$system_type = ",
                   rv$target$system_type),
            findme = "4690c52739")
217
218
219
220
221
          output$target_system_feedback_txt <-
            renderText({
              feedback_txt(system = "CSV", type = "target")
            })
        }
222
        check_load_data_button(rv, session)
223
      }
224
    )
225

226
227
228
229
230
    # load mdr
    observeEvent(
      eventExpr = input_re()[["moduleConfig-config_load_mdr"]],
      handlerExpr = {
        if (is.null(rv$mdr)) {
231
          DIZtools::feedback(
232
233
234
235
236
            print_this = "Reading MDR ...",
            findme = "f877fee7d2",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
237
          DIZtools::feedback(
238
239
            print_this = paste0("MDR-Filename:",
                                rv$mdr_filename),
240
241
242
243
            findme = "582d6a39c6",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
244
          DIZtools::feedback(
245
246
            print_this = paste0("rv$utilspath:",
                                rv$utilspath),
247
248
249
250
            findme = "b5c71849f9",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
251

Lorenz Kapsner's avatar
Lorenz Kapsner committed
252
253
254
255
256
257
          rv$mdr <- button_mdr(
            utils_path = rv$utilspath,
            mdr_filename = rv$mdr_filename,
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
258
259
          stopifnot(data.table::is.data.table(rv$mdr))

260
261
262
          ## Read in the settings
          # - Determine the different systems from mdr:
          vec <-
263
            c("source_system_name",
264
              "source_system_type")
Lorenz Kapsner's avatar
Lorenz Kapsner committed
265
          rv$systems <- unique(rv$mdr[, vec, with = FALSE])
266
          rv$systems <- rv$systems[!is.na(get("source_system_name"))]
267
          DIZtools::feedback(
268
269
270
271
272
            print_this = paste0(
              "Different systems found in the MDR: ",
              paste(unique(rv$systems[["source_system_name"]]),
                    collapse = ", ")
            ),
273
274
275
276
            findme = "4451da82ad",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
277

278
279
280
281
          # - Read the settings for all these systems:
          unique_systems <-
            rv$systems[!is.na(get("source_system_name")),
                       unique(get("source_system_name"))]
282

283
          # FIXME remove settings reading in the future
284
          rv$settings <-
285
            sapply(unique_systems, function(x) {
286
287
              DIZutils::get_config_env(
                system_name = x,
288
289
290
                logfile_dir = rv$log$logfile_dir,
                headless = rv$headless
              )
Lorenz Kapsner's avatar
Lorenz Kapsner committed
291
292
293
294
            },
            USE.NAMES = TRUE,
            simplify = FALSE
          )
295

296
297
298
          ## Create mapping for display names:
          tmp <- names(rv$settings)
          names(tmp) <- names(rv$settings)
299
300
301
302
303
304
305
          rv$displaynames <- lapply(tmp, function(x) {
            ret <- get_display_name_from_settings(settings = rv$settings,
                                                  prefilter = x)
            return(ret)
          }) %>%
            data.table::as.data.table() %>%
            data.table::transpose(keep.names = "displayname")
306
307
          rm(tmp)
          data.table::setnames(x = rv$displaynames,
308
                               old = "V1",
309
310
                               new = "source_system_name")

311
312
313
314
          # - Different system-types:
          rv$system_types <-
            rv$systems[!is.na(get("source_system_type")),
                       unique(get("source_system_type"))]
315

316
          DIZtools::feedback(
317
            print_this = rv$system_types,
318
            prefix = "System types:  ",
319
320
321
322
            findme = "9aec84fcca",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
323
324
          if (!("csv" %in% tolower(rv$system_types))) {
            # Remove CSV-Tabs:
325
            DIZtools::feedback(
326
              "Removing csv-tab from source ...",
327
328
329
330
              findme = "3c2f368001",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )
Jonathan Mang's avatar
Jonathan Mang committed
331
332
            shiny::removeTab(inputId = "source_tabs",
                             target = system_types_mapping[["csv"]])
333

334
            DIZtools::feedback(
335
              "Removing csv-tab from target ...",
336
337
338
339
              findme = "337b20a126",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )
Jonathan Mang's avatar
Jonathan Mang committed
340
341
            shiny::removeTab(inputId = "target_tabs",
                             target = system_types_mapping[["csv"]])
342
343
344
345
346
          } else {
            csv_system_names <-
              rv$systems[get("source_system_type") == "csv" &
                           !is.na(get("source_system_name")),
                         unique(get("source_system_name"))]
347
            DIZtools::feedback(
348
349
350
351
352
353
              csv_system_names,
              prefix = "csv_system_names: ",
              findme = "5a083a3d53",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )
354

355
356
357
358
            csv_system_names <-
              rv$displaynames[get("source_system_name") %in%
                                csv_system_names, get("displayname")]

359
360
361
            if (length(csv_system_names) > 0) {
              # Show buttons to prefill diff. systems presettings:
              # - Add a button/choice/etc. for each system:
362
              shiny::updateSelectInput(session = session,
363
364
                                inputId = "source_csv_presettings_list",
                                choices = csv_system_names)
365
              shiny::updateSelectInput(session = session,
366
367
                                inputId = "target_csv_presettings_list",
                                choices = csv_system_names)
368
369
370
371
            }
          }
          if (!("postgres" %in% tolower(rv$system_types))) {
            # Remove Postgres-Tabs:
372
            DIZtools::feedback(
373
374
375
376
              "Removing postgres-tab from source ...",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )
Jonathan Mang's avatar
Jonathan Mang committed
377
378
            shiny::removeTab(inputId = "source_tabs",
                             target = system_types_mapping[["postgres"]])
379

380
            DIZtools::feedback(
381
382
383
384
              "Removing postgres-tab from target ...",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )
Jonathan Mang's avatar
Jonathan Mang committed
385
386
            shiny::removeTab(inputId = "target_tabs",
                             target = system_types_mapping[["postgres"]])
387
388
389
390
391
392
393
394
395
396
397
          } else{
            # Fill the tab with presettings
            # - filter for all system_names with
            #% system_type == postgres
            #% select source_system_name from
            #% rv$systems where source_system_type == postgres
            #% GROUP BY source_system_name
            postgres_system_names <-
              rv$systems[get("source_system_type") == "postgres" &
                           !is.na(get("source_system_name")),
                         unique(get("source_system_name"))]
398
            DIZtools::feedback(
399
400
401
402
403
404
              postgres_system_names,
              prefix = "postgres_system_names: ",
              findme = "be136f5ab6",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )
405

406
407
408
409
            postgres_system_names <-
              rv$displaynames[get("source_system_name") %in%
                                postgres_system_names, get("displayname")]

410
411
412
            if (length(postgres_system_names) > 0) {
              # Show buttons to prefill diff. systems presettings:
              # - Add a button/choice/etc. for each system:
413
              shiny::updateSelectInput(session = session,
414
                                inputId = "source_postgres_presettings_list",
415
                                choices = postgres_system_names)
416
              shiny::updateSelectInput(session = session,
417
                                inputId = "target_postgres_presettings_list",
418
                                choices = postgres_system_names)
419
420
            }
          }
Jonathan Mang's avatar
Jonathan Mang committed
421
422
          if (!("oracle" %in% tolower(rv$system_types))) {
            # Remove Oracle-Tabs:
423
            DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
424
425
426
427
428
              "Removing oracle-tab from source ...",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless,
              findme = "8e93367dec"
            )
Jonathan Mang's avatar
Jonathan Mang committed
429
430
            shiny::removeTab(inputId = "source_tabs",
                             target = system_types_mapping[["oracle"]])
Jonathan Mang's avatar
Jonathan Mang committed
431

432
            DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
433
434
435
436
437
              "Removing oracle-tab from target ...",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless,
              findme = "1c2023da56"
            )
Jonathan Mang's avatar
Jonathan Mang committed
438
439
            shiny::removeTab(inputId = "target_tabs",
                             target = system_types_mapping[["oracle"]])
Jonathan Mang's avatar
Jonathan Mang committed
440
441
442
443
444
445
446
447
448
449
450
          } else{
            # Fill the tab with presettings
            # - filter for all system_names with
            #% system_type == oracle
            #% select source_system_name from
            #% rv$systems where source_system_type == oracle
            #% GROUP BY source_system_name
            oracle_system_names <-
              rv$systems[get("source_system_type") == "oracle" &
                           !is.na(get("source_system_name")),
                         unique(get("source_system_name"))]
451
            DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
452
453
454
455
456
457
458
              oracle_system_names,
              prefix = "oracle_system_names: ",
              findme = "bea2cd91a1",
              logfile_dir = rv$log$logfile_dir,
              headless = rv$headless
            )

459
460
461
462
            oracle_system_names <-
              rv$displaynames[get("source_system_name") %in%
                                oracle_system_names, get("displayname")]

Jonathan Mang's avatar
Jonathan Mang committed
463
464
465
466
467
468
469
470
471
472
473
            if (length(oracle_system_names) > 0) {
              # Show buttons to prefill diff. systems presettings:
              # - Add a button/choice/etc. for each system:
              updateSelectInput(session = session,
                                inputId = "source_oracle_presettings_list",
                                choices = oracle_system_names)
              updateSelectInput(session = session,
                                inputId = "target_oracle_presettings_list",
                                choices = oracle_system_names)
            }
          }
474
475

          first_system <- tolower(rv$system_types)[[1]]
476
          DIZtools::feedback(
477
478
            print_this = paste0("Setting tab '",
                                first_system,
Jonathan Mang's avatar
Jonathan Mang committed
479
480
                                "' as active tab for source",
                                " and target on config page."),
481
482
483
            findme = "46c03705a8",
            logfile_dir = rv$log$logfile_dir
          )
Jonathan Mang's avatar
Jonathan Mang committed
484
485
486
487
488
489
490
491
          shiny::updateTabsetPanel(
            session = session,
            inputId = "source_tabs",
            selected = system_types_mapping[[first_system]])
          shiny::updateTabsetPanel(
            session = session,
            inputId = "target_tabs",
            selected = system_types_mapping[[first_system]])
Jonathan Mang's avatar
Jonathan Mang committed
492

493
494
495
496
497
498
499
500
501

          # Store the system-types in output-variable to only
          # show these tabs on the config page:
          output$system_types <- reactive({
            rv$system_types
          })
          outputOptions(output,
                        "system_types",
                        suspendWhenHidden = FALSE)
502
503

          # workaround to tell ui, that mdr is there
504
505
506
          output$mdr_present <- reactive({
            return(TRUE)
          })
507
508
509
510
511
512
513
514
515
516
517
518
          outputOptions(output,
                        "mdr_present",
                        suspendWhenHidden = FALSE)

          # workaround to tell ui, that mdr is there
          output$source_system_type <- reactive({
            return(input_re()
                   [["moduleConfig-config_source_system_type"]])
          })
          outputOptions(output,
                        "source_system_type",
                        suspendWhenHidden = FALSE)
519
520
521
522
          output$source_system_feedback_txt <-
            renderText({
              "\U26A0 Please select a source system to load the data."
            })
523
        }
524
        check_load_data_button(rv, session)
525
      })
kapsner's avatar
kapsner committed
526
527


528
529
    # If the "load presets"-button was pressed, startload & show the presets:
    # observeEvent(input$source_pg_presettings_btn, {
530
    observeEvent(input$source_postgres_presettings_list, {
531
      DIZtools::feedback(
532
533
        print_this =
          paste0(
534
            "Input-preset '",
535
            input$source_postgres_presettings_list,
536
            "' was chosen as SOURCE.",
537
538
            " Loading presets ..."
          ),
539
540
541
        findme = "e9832b3092",
        logfile_dir = rv$log$logfile_dir,
        headless = rv$headless
kapsner's avatar
kapsner committed
542
      )
543
544
545
546
547
548
549
      config_stuff <-
        rv$settings[[tolower(input$source_postgres_presettings_list)]]
      config_stuff <-
        get_settings_from_displayname(
          displayname = input$source_postgres_presettings_list,
          settings = rv$settings
        )
550

551
      DIZtools::feedback(
552
553
554
555
        print_this = paste(
          "Loaded successfully.",
          "Filling presets to global rv-object and UI ..."
        ),
556
557
558
        findme = "3c9136d49f",
        logfile_dir = rv$log$logfile_dir,
        headless = rv$headless
559
      )
560
561
      if (length(config_stuff) != 0) {
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
                        inputId = "config_source_postgres_dbname",
                        value = config_stuff[["dbname"]])
        updateTextInput(session = session,
                        inputId = "config_source_postgres_host",
                        value = config_stuff[["host"]])
        updateTextInput(session = session,
                        inputId = "config_source_postgres_port",
                        value = config_stuff[["port"]])
        updateTextInput(session = session,
                        inputId = "config_source_postgres_user",
                        value = config_stuff[["user"]])
        updateTextInput(session = session,
                        inputId = "config_source_postgres_password",
                        value = config_stuff[["password"]])
      } else{
        updateTextInput(session = session,
                        inputId = "config_source_postgres_dbname",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_source_postgres_host",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_source_postgres_port",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_source_postgres_user",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_source_postgres_password",
                        value = "")
      }
      updateActionButton(
        session = session,
        inputId = "source_postgres_test_connection",
        label = "Test & Save connection",
        icon = icon("database")
      )
      shinyjs::enable("source_postgres_test_connection")
    })

    observeEvent(input$source_oracle_presettings_list, {
603
      DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
604
605
606
607
608
609
610
611
612
613
614
        print_this =
          paste0(
            "Input-preset ",
            input$source_oracle_presettings_list,
            " was chosen as SOURCE.",
            " Loading presets ..."
          ),
        findme = "44179e7b1f",
        logfile_dir = rv$log$logfile_dir,
        headless = rv$headless
      )
615
616
617
618
619
      config_stuff <-
        get_settings_from_displayname(
          displayname = input$source_oracle_presettings_list,
          settings = rv$settings
        )
Jonathan Mang's avatar
Jonathan Mang committed
620

621
      DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
622
623
624
625
626
627
628
629
630
631
632
        print_this = paste(
          "Loaded successfully.",
          "Filling presets to global rv-object and UI ..."
        ),
        findme = "ff874cb58d",
        logfile_dir = rv$log$logfile_dir,
        headless = rv$headless
      )
      if (length(config_stuff) != 0) {
        updateTextInput(session = session,
                        inputId = "config_source_oracle_dbname",
633
634
                        value = config_stuff[["dbname"]])
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
635
                        inputId = "config_source_oracle_host",
636
637
                        value = config_stuff[["host"]])
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
638
                        inputId = "config_source_oracle_port",
639
640
                        value = config_stuff[["port"]])
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
641
                        inputId = "config_source_oracle_user",
642
643
                        value = config_stuff[["user"]])
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
644
                        inputId = "config_source_oracle_password",
645
                        value = config_stuff[["password"]])
Jonathan Mang's avatar
Jonathan Mang committed
646
647
648
        updateTextInput(session = session,
                        inputId = "config_source_oracle_sid",
                        value = config_stuff[["sid"]])
649
650
      } else{
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
651
652
653
654
                        inputId = "config_source_oracle_dbname",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_source_oracle_host",
655
656
                        value = "")
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
657
                        inputId = "config_source_oracle_port",
658
659
                        value = "")
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
660
                        inputId = "config_source_oracle_user",
661
662
                        value = "")
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
663
                        inputId = "config_source_oracle_password",
664
665
                        value = "")
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
666
                        inputId = "config_source_oracle_sid",
667
668
                        value = "")
      }
669
670
      updateActionButton(
        session = session,
Jonathan Mang's avatar
Jonathan Mang committed
671
        inputId = "source_oracle_test_connection",
672
673
674
        label = "Test & Save connection",
        icon = icon("database")
      )
Jonathan Mang's avatar
Jonathan Mang committed
675
      shinyjs::enable("source_oracle_test_connection")
676
677
    })

Jonathan Mang's avatar
Jonathan Mang committed
678

679
    #observeEvent(input$target_pg_presettings_btn, {
680
    observeEvent(input$target_postgres_presettings_list, {
681
      DIZtools::feedback(
682
683
        paste0(
          "Input-preset ",
684
          input$target_postgres_presettings_list,
Jonathan Mang's avatar
Jonathan Mang committed
685
          " was chosen as TARGET.",
686
          " Loading presets ..."
687
688
689
690
        ),
        findme = "d603f8127a",
        logfile_dir = rv$log$logfile_dir,
        headless = rv$headless
691
      )
692
693
694
695
696
697
      # config_stuff <-
      config_stuff <-
        get_settings_from_displayname(
          displayname = input$target_postgres_presettings_list,
          settings = rv$settings
        )
698

699
      DIZtools::feedback(
700
701
702
703
704
705
706
707
        paste(
          "Loaded successfully.",
          "Filling presets to global rv-object and UI ..."
        ),
        findme = "fa908f0035",
        logfile_dir = rv$log$logfile_dir,
        headless = rv$headless
      )
708
709
      if (length(config_stuff) != 0) {
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
710
                        inputId = "config_target_postgres_dbname",
711
712
                        value = config_stuff[["dbname"]])
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
713
                        inputId = "config_target_postgres_host",
714
715
                        value = config_stuff[["host"]])
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
716
                        inputId = "config_target_postgres_port",
717
718
                        value = config_stuff[["port"]])
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
719
                        inputId = "config_target_postgres_user",
720
721
                        value = config_stuff[["user"]])
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
722
                        inputId = "config_target_postgres_password",
723
724
725
                        value = config_stuff[["password"]])
      } else{
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
726
                        inputId = "config_target_postgres_dbname",
727
728
                        value = "")
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
729
                        inputId = "config_target_postgres_host",
730
731
                        value = "")
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
732
                        inputId = "config_target_postgres_port",
733
734
                        value = "")
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
735
                        inputId = "config_target_postgres_user",
736
737
                        value = "")
        updateTextInput(session = session,
Jonathan Mang's avatar
Jonathan Mang committed
738
                        inputId = "config_target_postgres_password",
739
740
                        value = "")
      }
741
742
      updateActionButton(
        session = session,
Jonathan Mang's avatar
Jonathan Mang committed
743
        inputId = "target_postgres_test_connection",
744
745
746
        label = "Test & Save connection",
        icon = icon("database")
      )
Jonathan Mang's avatar
Jonathan Mang committed
747
      shinyjs::enable("target_postgres_test_connection")
748
    })
kapsner's avatar
kapsner committed
749

Jonathan Mang's avatar
Jonathan Mang committed
750
    observeEvent(input$target_oracle_presettings_list, {
751
      DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
752
753
754
755
756
757
758
759
760
761
        paste0(
          "Input-preset ",
          input$target_oracle_presettings_list,
          " was chosen as TARGET.",
          " Loading presets ..."
        ),
        findme = "1156504e13",
        logfile_dir = rv$log$logfile_dir,
        headless = rv$headless
      )
762
763
764
765
766
767
       # config_stuff <-
      config_stuff <-
        get_settings_from_displayname(
          displayname = input$target_oracle_presettings_list,
          settings = rv$settings
        )
kapsner's avatar
kapsner committed
768

769
      DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
        paste(
          "Loaded successfully.",
          "Filling presets to global rv-object and UI ..."
        ),
        findme = "3d39553c3c",
        logfile_dir = rv$log$logfile_dir,
        headless = rv$headless
      )
      if (length(config_stuff) != 0) {
        updateTextInput(session = session,
                        inputId = "config_target_oracle_dbname",
                        value = config_stuff[["dbname"]])
        updateTextInput(session = session,
                        inputId = "config_target_oracle_host",
                        value = config_stuff[["host"]])
        updateTextInput(session = session,
                        inputId = "config_target_oracle_port",
                        value = config_stuff[["port"]])
        updateTextInput(session = session,
                        inputId = "config_target_oracle_user",
                        value = config_stuff[["user"]])
        updateTextInput(session = session,
                        inputId = "config_target_oracle_password",
                        value = config_stuff[["password"]])
        updateTextInput(session = session,
                        inputId = "config_target_oracle_sid",
                        value = config_stuff[["sid"]])
      } else{
        updateTextInput(session = session,
                        inputId = "config_target_oracle_dbname",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_target_oracle_host",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_target_oracle_port",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_target_oracle_user",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_target_oracle_password",
                        value = "")
        updateTextInput(session = session,
                        inputId = "config_target_oracle_sid",
                        value = "")
816
      }
Jonathan Mang's avatar
Jonathan Mang committed
817
818
819
820
821
822
823
      updateActionButton(
        session = session,
        inputId = "target_oracle_test_connection",
        label = "Test & Save connection",
        icon = icon("database")
      )
      shinyjs::enable("target_oracle_test_connection")
824
    })
kapsner's avatar
kapsner committed
825

826

Jonathan Mang's avatar
Jonathan Mang committed
827
828
829
830
831
832
833
834
835
836
    observeEvent(input$source_postgres_test_connection, {
      test_connection_button_clicked(
        rv = rv,
        source_target = "source",
        db_type = "postgres",
        input = input,
        output = output,
        session = session
      )
    })
837

Jonathan Mang's avatar
Jonathan Mang committed
838
839
840
841
842
843
844
845
846
    observeEvent(input$source_oracle_test_connection, {
      test_connection_button_clicked(
        rv = rv,
        source_target = "source",
        db_type = "oracle",
        input = input,
        output = output,
        session = session
      )
847
848
    })

Jonathan Mang's avatar
Jonathan Mang committed
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
    observeEvent(input$target_postgres_test_connection, {
      test_connection_button_clicked(
        rv = rv,
        source_target = "target",
        db_type = "postgres",
        input = input,
        output = output,
        session = session
      )
    })

    observeEvent(input$target_oracle_test_connection, {
      test_connection_button_clicked(
        rv = rv,
        source_target = "target",
        db_type = "oracle",
        input = input,
        output = output,
        session = session
      )
    })


872
    observeEvent(input$target_system_to_source_system_btn, {
Jonathan Mang's avatar
Jonathan Mang committed
873
874
      if (isTRUE(input$target_system_to_source_system_btn)) {
        ## Target was != source and should become equal:
875
876
877
        # Hide target-setting-tabs:
        hideTab(inputId = "target_tabs", target = "CSV")
        hideTab(inputId = "target_tabs", target = "PostgreSQL")
Jonathan Mang's avatar
Jonathan Mang committed
878
        hideTab(inputId = "target_tabs", target = "Oracle")
879
880
881
        # Assign source-values to target:
        rv <- set_target_equal_to_source(rv)
        # Set internal flag that target == source:
Lorenz Kapsner's avatar
Lorenz Kapsner committed
882
        rv$target_is_source <- TRUE
883
884
885
886
887
888
        # Show feedback-box in the UI:
        output$target_system_feedback_txt <-
          renderText({
            feedback_txt(system = "The source system", type = "target")
          })
        # Feedback to the console:
889
        DIZtools::feedback(
890
891
892
893
894
          "Target == source now.",
          findme = "94d3a2090c",
          logfile_dir = rv$log$logfile_dir,
          headless = rv$headless
        )
Jonathan Mang's avatar
Jonathan Mang committed
895
896
897
898
899
900
901
902
      } else if (isFALSE(input$target_system_to_source_system_btn)) {
        ## Target was == source but should become different now:
        rv$target_is_source <- F
        rv$target <- NULL
        output$target_system_feedback_txt <- NULL
        # Show target-settings-tabs again:
        showTab(inputId = "target_tabs", target = "CSV")
        showTab(inputId = "target_tabs", target = "PostgreSQL")
Jonathan Mang's avatar
Jonathan Mang committed
903
        showTab(inputId = "target_tabs", target = "Oracle")
Jonathan Mang's avatar
Jonathan Mang committed
904
        # Feedback to the console:
905
        DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
906
907
908
909
910
          "Target != source now.",
          findme = "ec51b122ee",
          logfile_dir = rv$log$logfile_dir,
          headless = rv$headless
        )
911
      }
912
      check_load_data_button(rv, session)
913
    })
914
915
916
917
918
919

    observe({
      if (is.null(rv$sitenames)) {
        # check, if user has provided custom site names
        rv$sitenames <- tryCatch({
          outlist <- jsonlite::fromJSON(
920
            paste0(rv$utilspath, "/MISC/sitenames.JSON")
921
922
923
          )
          outlist
        }, error = function(e) {
924
          outlist <- list("undefined" = "undefined")
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
          outlist
          # TODO instead of dropdown menu, render text input field in the
          # case, users have not provided sitenames. This allows them
          # to specify a name of the DQA session (which will be included
          # into the report's title)
        }, finally = function(f) {
          return(outlist)
        })

        updateSelectInput(
          session,
          "config_sitename",
          choices = rv$sitenames,
          selected = ifelse(!is.null(rv$sitename),
                            rv$sitename,
                            character(0))
        )
      }
    })
944

945
946
947
948
    observeEvent(input_re()[["moduleConfig-dash_load_btn"]], {
      tryCatch({
        ## For runtime calculation:
        start_time <- Sys.time()
949

950
        DIZtools::feedback(
Lorenz Kapsner's avatar
Lorenz Kapsner committed
951
952
953
954
955
956
957
958
959
960
961
          paste0(
            "Restricting date slider state: ",
            input$date_restriction_slider
          ),
          type = "Info",
          findme = "1dcsdfg37b8",
          logfile_dir = rv$log$logfile_dir,
          headless = rv$headless
        )
        rv$restricting_date$use_it <- input$date_restriction_slider

962
963
964
965
966
        # The button is on "moduleConfig".
        # This tab here will be set active below if all inputs are valid.

        # Error flag: If an error occurs, the flag will be set to true
        # and the main calculation won't start:
Lorenz Kapsner's avatar
Lorenz Kapsner committed
967
        error_tmp <- FALSE
968
969
970
971

        # check, if mdr is present. without mdr, we cannot perform any
        # further operations
        if (is.null(rv$mdr)) {
972
          DIZtools::feedback(
973
974
            "No MDR found. Please provide a metadata repository (MDR).",
            type = "Warning",
975
976
977
            findme = "1dc68937b8",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
978
          )
Lorenz Kapsner's avatar
Lorenz Kapsner committed
979
          error_tmp <- TRUE
980
981
982
983
984
985
          # mdr is present:
        } else {
          # check if sitename is present
          if (nchar(input_re()[["moduleConfig-config_sitename"]]) < 2 ||
              any(grepl("\\s", input_re()[["moduleConfig-config_sitename"]]))) {
            # site name is missing:
986
987
988
989
990
991
992
993
            shiny::showModal(shiny::modalDialog(
              title = "The sitename is missing",
              paste0(
                "There are no empty strings or spaces allowed in",
                " the site name configuration.",
                " Please select your site name."
              )
            ))
Lorenz Kapsner's avatar
Lorenz Kapsner committed
994
            error_tmp <- TRUE
995
996
          } else {
            # site name is present:
997
998
            rv$sitename <-
              input_re()[["moduleConfig-config_sitename"]]
999
1000
          }

1001
1002
1003
          # Check if at least one data element was selected for analyzation:
          if (length(input_re()[[paste0("moduleConfig-select_dqa_assessment",
                                        "_variables")]]) <= 0) {
1004
            DIZtools::feedback(
1005
1006
1007
1008
1009
1010
              print_this = paste0(
                "You didn't specify a data element to",
                " analyze. Please select at least one data element",
                " and try again."
              ),
              type = "UI",
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1011
              ui = TRUE,
Jonathan Mang's avatar
Jonathan Mang committed
1012
1013
              findme = "57562a3092",
              logfile_dir = rv$log$logfile_dir
1014
            )
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1015
            error_tmp <- TRUE
1016
1017
          }

1018
1019
1020
          # If target should be identical to source, set it here again:
          if (isTRUE(rv$target_is_source)) {
            rv <- set_target_equal_to_source(rv)
1021
            DIZtools::feedback(print_this = "Source == Target",
Jonathan Mang's avatar
Jonathan Mang committed
1022
1023
1024
1025
1026
                               findme = "c14c17bf15",
                               logfile_dir = rv$log$logfile_dir,
                               headless = rv$headless
            )
          } else {
1027
            DIZtools::feedback(print_this = "Source != Target",
Jonathan Mang's avatar
Jonathan Mang committed
1028
1029
1030
1031
                               findme = "54fe9a5717",
                               logfile_dir = rv$log$logfile_dir,
                               headless = rv$headless
            )
1032
1033
          }

1034
          DIZtools::feedback(
1035
1036
1037
1038
1039
            paste0("Source system is ", rv$source$system_name),
            findme = "1d61685355",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
1040
          DIZtools::feedback(
1041
1042
1043
1044
1045
            paste0("Target system is ", rv$target$system_name),
            findme = "eaf72ed747",
            logfile_dir = rv$log$logfile_dir,
            headless = rv$headless
          )
1046
1047
        }

1048
1049
1050
1051
1052
        if (validate_inputs(rv,
                            input = input,
                            output = output,
                            session = session) &&
            !error_tmp) {
1053
1054
1055
1056
          # set flags to inactivate config-widgets and start loading of
          # data
          rv$getdata_target <- TRUE
          rv$getdata_source <- TRUE
1057
          rv$start <- TRUE
1058
1059
1060
1061
1062
1063
1064
1065
1066
1067
1068
1069
1070

          if (!dir.exists(paste0(tempdir(), "/_settings/"))) {
            dir.create(paste0(tempdir(), "/_settings/"))
          }

          # save user settings
          writeLines(
            jsonlite::toJSON(
              list(
                "source_system" = rv$source$settings,
                "target_system" = rv$target$settings,
                "site_name" = rv$sitename
              ),
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1071
1072
              pretty = TRUE,
              auto_unbox = FALSE
1073
1074
1075
1076
            ),
            paste0(tempdir(), "/_settings/global_settings.JSON")
          )
        }
1077
      }, error = function(cond) {
1078
        DIZtools::feedback(
1079
1080
1081
          print_this = paste0(cond),
          findme = "05c96798f8",
          type = "Error",
1082
1083
          logfile_dir = rv$log$logfile_dir
        )
1084
        ## Trigger the modal for the user/UI:
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1085
        rv$error <- TRUE
1086
1087
1088
1089
1090
1091
        show_failure_alert(
          paste0(
            "Executing the script to pre-check the",
            " input parameters before data-loading failed"
          )
        )
1092
      })
1093
1094
1095
1096
1097
1098
      print_runtime(
        start_time = start_time,
        name = "moduleConfig-dash_load_btn",
        logfile_dir = rv$log$logfile_dir
      )
    })
1099

Jonathan Mang's avatar
Jonathan Mang committed
1100
    observeEvent(input$select_all_assessment_variables, {
1101
1102
      updateCheckboxGroupInput(
        session = session,
Jonathan Mang's avatar
Jonathan Mang committed
1103
        inputId = "select_dqa_assessment_variables",
1104
        choices = sort(rv$dqa_assessment[["designation"]]),
1105
1106
1107
1108
        selected = rv$dqa_assessment[["designation"]]
      )
    })

Jonathan Mang's avatar
Jonathan Mang committed
1109
    observeEvent(input$select_no_assessment_variables, {
1110
1111
      updateCheckboxGroupInput(
        session = session,
Jonathan Mang's avatar
Jonathan Mang committed
1112
        inputId = "select_dqa_assessment_variables",
1113
        choices = sort(rv$dqa_assessment[["designation"]]),
1114
1115
1116
        selected = NULL
      )
    })
1117

1118
1119
    shiny::observeEvent(eventExpr = input$date_restriction_slider,
                        handlerExpr = {
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1120
                          if (isTRUE(input$date_restriction_slider)) {
1121
                            DIZtools::feedback(
1122
1123
1124
1125
1126
1127
1128
1129
1130
1131
1132
1133
                              print_this = "Date restriction will be applied",
                              findme = "4736de090c",
                              logfile_dir = rv$log$logfile_dir
                            )
                            shinyjs::show(id = "datetime_picker")
                            shinyjs::enable(id = "datetime_picker")
                            rv$restricting_date$use_it <- TRUE
                            rv$restricting_date$start <-
                              as.Date(input$datetime_picker[[1]])
                            rv$restricting_date$end <-
                              as.Date(input$datetime_picker[[2]])
                          } else {
1134
                            DIZtools::feedback(
Jonathan Mang's avatar
Jonathan Mang committed
1135
1136
                              print_this = paste0("Date restriction will",
                                                  " NOT be applied"),
1137
1138
1139
1140
1141
1142
1143
1144
1145
1146
                              findme = "508c7f34f9",
                              logfile_dir = rv$log$logfile_dir
                            )
                            shinyjs::disable(id = "datetime_picker")
                            shinyjs::hide(id = "datetime_picker")
                            rv$restricting_date$use_it <- FALSE
                            rv$restricting_date$start <- NULL
                            rv$restricting_date$end <- NULL
                          }
                        }
1147
                        , ignoreInit = TRUE
1148
1149
                        )

1150
1151
1152
    ## Date-time picker for date restriction:
    shiny::observeEvent(eventExpr = input$datetime_picker,
                        handlerExpr = {
1153
1154
1155
1156
1157
1158
1159
1160
1161
1162
1163
1164
1165
1166
                          rv$restricting_date$use_it <- TRUE
                          rv$restricting_date$start <-
                            as.Date(input$datetime_picker[[1]])
                          rv$restricting_date$end <-
                            as.Date(input$datetime_picker[[2]])

                          output$datetime_picker_info_start <-
                            shiny::renderText({
                              paste0(
                                "Start timestamp: ",
                                input$datetime_picker[[1]]
                              )
                            })
                          output$datetime_picker_info_end <-
1167
1168
                            shiny::renderText({
                              paste0(
1169
                                "End timestamp: ",
1170
1171
1172
                                input$datetime_picker[[2]]
                              )
                            })
1173
                          DIZtools::feedback(
1174
1175
1176
1177
1178
1179
1180
1181
1182
1183
1184
                            print_this = paste0(
                              "Using ",
                              rv$restricting_date$start,
                              " as start and ",
                              rv$restricting_date$end,
                              " as end timestamp for filtering the data."
                            ),
                            findme = "04bf478581",
                            logfile_dir = rv$log$logfile_dir,
                            headless = rv$headless
                          )
1185
                        })
1186

Jonathan Mang's avatar
Jonathan Mang committed
1187

1188
  }
kapsner's avatar
kapsner committed
1189

1190
#' @title module_config_ui
kapsner's avatar
kapsner committed
1191
1192
1193
#'
#' @param id A character. The identifier of the shiny object
#'
1194
1195
1196
1197
1198
1199
1200
1201
1202
1203
1204
1205
1206
1207
1208
1209
#' @return The function returns a shiny ui module.
#'
#' @seealso \url{https://shiny.rstudio.com/articles/modules.html}
#'
#' @examples
#' if (interactive()) {
#' shinydashboard::tabItems(
#'   shinydashboard::tabItem(
#'     tabName = "config",
#'     module_config_ui(
#'       "moduleConfig"
#'     )
#'   )
#' )
#' }
#'
kapsner's avatar
kapsner committed
1210
1211
#' @export
#'
1212
1213
# module_config_ui
module_config_ui <- function(id) {
kapsner's avatar
kapsner committed
1214
1215
  ns <- NS(id)

1216
1217
  tagList(
    fluidRow(
1218
1219
1220
1221
1222
1223
      column(
        9,
        ## This will be displayed after the MDR is loaded successfully:
        conditionalPanel(
          condition =
            "typeof output['moduleConfig-system_types'] !== 'undefined'",
1224
          box(
1225
1226
            title =  "SOURCE settings",
            width = 6,
1227
            #solidHeader = TRUE,
Jonathan Mang's avatar
Jonathan Mang committed
1228
            tabsetPanel(
1229
1230
1231
              # The id lets us use input$source_tabs
              # on the server to find the current tab
              id = ns("source_tabs"),
1232
              # selected = "PostgreSQL",
1233
              tabPanel(
1234
1235
1236
1237
1238
                # ATTENTION: If you change the title, you also have to change
                # the
                # corresponding part above for the "source == source" button
                # reaction. Otherwise the tabs won't hide/show up anymore.
                # >> ATTENTION <<
1239
                title = "CSV",
1240
1241
                # >> ATTENTION << for title. See above.
                id = ns("source_tab_csv"),
1242
1243
1244
1245
1246
1247
1248
1249
1250
1251
1252
1253
1254
1255
                h4("Source CSV Upload"),
                box(
                  title = "Available CSV-Systems",
                  # background = "blue",
                  # solidHeader = TRUE,
                  width = 12,
                  selectInput(
                    # This will be filled in the server part.
                    inputId = ns("source_csv_presettings_list"),
                    label = NULL,
                    choices = NULL,
                    selected = NULL
                  ),
                  style = "text-align:center;"
1256
                ),
1257
1258
1259
                div(
                  paste(
                    "Please choose the directory of your",
1260
                    " source data in csv format (default: '/home/input')."
1261
1262
1263
1264
1265
1266
1267
1268
1269
1270
1271
                  )
                ),
                br(),
                # If the path is already set, display it
                conditionalPanel(
                  condition = paste0(
                    "typeof ",
                    "output['moduleConfig-source_csv_dir']",
                    " !== 'undefined'"
                  ),
                  verbatimTextOutput(ns("source_csv_dir")),
1272
                  style = "text-align:center;"
1273
                ),
1274
1275
1276
                br(),

                # If there is no path set yet: Display the button to choose it
1277
1278
1279
1280
1281
1282
1283
                shinyFiles::shinyDirButton(
                  id = ns("config_sourcedir_in"),
                  label = "Source Dir",
                  title = "Please select the source directory",
                  buttonType = "default",
                  icon = icon("folder"),
                  class = NULL,
1284
1285
                  style = "text-align:center;"
                )
1286
              ),
1287
              tabPanel(
1288
1289
1290
1291
1292
                # ATTENTION: If you change the title, you also have to change
                # the
                # corresponding part above for the "source == source" button
                # reaction. Otherwise the tabs won't hide/show up anymore.
                # >> ATTENTION <<
1293
                title = "PostgreSQL",
1294
1295
                # >> ATTENTION << for title. See above.
                id = ns("source_tab_pg"),
1296
1297
1298
1299
1300
1301
1302
1303
                h4("Source Database Connection"),
                box(
                  title = "Preloadings",
                  # background = "blue",
                  #solidHeader = TRUE,
                  width = 12,
                  selectInput(
                    # This will be filled in the server part.
1304
                    inputId = ns("source_postgres_presettings_list"),
1305
1306
1307
1308
                    label = NULL,
                    choices = NULL,
                    selected = NULL
                  ),
1309
1310
                  style = "text-align:center;"
                ),
1311
                textInput(
Jonathan Mang's avatar
Jonathan Mang committed
1312
                  inputId = ns("config_source_postgres_dbname"),
1313
1314
                  label = "DB Name",
                  placeholder = "Enter the name of the database ..."
1315
                ),
1316
                textInput(
Jonathan Mang's avatar
Jonathan Mang committed
1317
                  inputId = ns("config_source_postgres_host"),
1318
1319
1320
1321
                  label = "IP",
                  placeholder = "Enter the IP here in format '192.168.1.1' ..."
                ),
                textInput(
Jonathan Mang's avatar
Jonathan Mang committed
1322
                  inputId = ns("config_source_postgres_port"),
1323
1324
1325
1326
                  label = "Port",
                  placeholder = "Enter the Port of the database connection ..."
                ),
                textInput(
Jonathan Mang's avatar
Jonathan Mang committed
1327
                  inputId = ns("config_source_postgres_user"),
1328
1329
1330
1331
1332
                  label = "Username",
                  placeholder =
                    "Enter the Username for the database connection ..."
                ),
                passwordInput(
Jonathan Mang's avatar
Jonathan Mang committed
1333
                  inputId = ns("config_source_postgres_password"),
1334
1335
1336
1337
1338
                  label = "Password",
                  placeholder = "Enter the database password ..."
                ),
                br(),
                actionButton(
Jonathan Mang's avatar
Jonathan Mang committed
1339
1340
1341
1342
1343
1344
1345
1346
1347
1348
1349
1350
1351
1352
1353
1354
1355
1356
1357
1358
1359
1360
1361
1362
1363
1364
1365
1366
1367
1368
1369
1370
1371
1372
1373
1374
1375
1376
1377
1378
1379
1380
1381
1382
1383
1384
1385
1386
1387
1388
1389
1390
1391
1392
1393
1394
1395
1396
1397
1398
1399
1400
1401
1402
1403
                  inputId = ns("source_postgres_test_connection"),
                  label = "Test & Save connection",
                  icon = icon("database"),
                  style = "text-align:center;"
                )
              ),
              tabPanel(
                # ATTENTION: If you change the title, you also have to change
                # the
                # corresponding part above for the "target == source" button
                # reaction. Otherwise the tabs won't hide/show up anymore.
                # >> ATTENTION <<
                title = "Oracle",
                # >> ATTENTION << for title. See above.
                id = ns("source_tab_oracle"),
                h4("Source Database Connection"),
                box(
                  title = "Preloadings",
                  # background = "blue",
                  #solidHeader = TRUE,
                  width = 12,
                  selectInput(
                    # This will be filled in the server part.
                    inputId = ns("source_oracle_presettings_list"),
                    label = NULL,
                    choices = NULL,
                    selected = NULL
                  ),
                  style = "text-align:center;"
                ),
                textInput(
                  inputId = ns("config_source_oracle_dbname"),
                  label = "DB Name",
                  placeholder = "Enter the name of the database ..."
                ),
                textInput(
                  inputId = ns("config_source_oracle_host"),
                  label = "IP",
                  placeholder = "Enter the IP here in format '192.168.1.1' ..."
                ),
                textInput(
                  inputId = ns("config_source_oracle_port"),
                  label = "Port",
                  placeholder = "Enter the Port of the database connection ..."
                ),
                textInput(
                  inputId = ns("config_source_oracle_user"),
                  label = "Username",
                  placeholder =
                    "Enter the Username for the database connection ..."
                ),
                passwordInput(
                  inputId = ns("config_source_oracle_password"),
                  label = "Password",
                  placeholder = "Enter the database password ..."
                ),
                textInput(
                  inputId = ns("config_source_oracle_sid"),
                  label = "SID",
                  placeholder =
                    "Enter the SID for the database connection ..."
                ),
                br(),
                actionButton(
                  inputId = ns("source_oracle_test_connection"),
1404
1405
1406
1407
                  label = "Test & Save connection",
                  icon = icon("database"),
                  style = "text-align:center;"
                )
1408
              )
1409
1410
            )
          ),
1411
1412
1413
          box(
            title =  "TARGET settings",
            width = 6,
1414
            #solidHeader = TRUE,
Jonathan Mang's avatar
Jonathan Mang committed
1415
            tabsetPanel(
1416
1417
1418
1419
1420
              # The id lets us use input$target_tabs
              # on the server to find the current tab
              id = ns("target_tabs"),
              # selected = "PostgreSQL",
              tabPanel(
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1421
1422
                # ATTENTION: If you change the title, you also have to change
                # the
1423
1424
1425
1426
1427
1428
1429
1430
1431
1432
1433
1434
1435
1436
1437
1438
1439
1440
1441
1442
                # corresponding part above for the "target == source" button
                # reaction. Otherwise the tabs won't hide/show up anymore.
                # >> ATTENTION <<
                title = "CSV",
                # >> ATTENTION << for title. See above.
                id = ns("target_tab_csv"),
                h4("Target CSV Upload"),
                box(
                  title = "Available CSV-Systems",
                  # background = "blue",
                  # solidHeader = TRUE,
                  width = 12,
                  selectInput(
                    # This will be filled in the server part.
                    inputId = ns("target_csv_presettings_list"),
                    label = NULL,
                    choices = NULL,
                    selected = NULL
                  ),
                  style = "text-align:center;"
1443
                ),
1444
1445
1446
                div(
                  paste(
                    "Please choose the directory of your",
1447
                    " target data in csv format (default: '/home/input')."
1448
1449
1450
1451
1452
1453
1454
1455
1456
1457
1458
                  )
                ),
                br(),
                # If the path is already set, display it
                conditionalPanel(
                  condition = paste0(
                    "typeof ",
                    "output['moduleConfig-target_csv_dir']",
                    " !== 'undefined'"
                  ),
                  verbatimTextOutput(ns("target_csv_dir")),
1459
                  style = "text-align:center;"
1460
                ),
1461
1462
1463
                br(),

                # If there is no path set yet: Display the button to choose it
1464
1465
1466
1467
1468
1469
1470
                shinyFiles::shinyDirButton(
                  id = ns("config_targetdir_in"),
                  label = "Target Dir",
                  title = "Please select the target directory",
                  buttonType = "default",
                  icon = icon("folder"),
                  class = NULL,
1471
1472
                  style = "text-align:center;"
                )
1473
              ),
1474
              tabPanel(
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1475
1476
                # ATTENTION: If you change the title, you also have to change
                # the
1477
1478
1479
1480
1481
1482
1483
1484
1485
1486
1487
1488
1489
1490
                # corresponding part above for the "target == source" button
                # reaction. Otherwise the tabs won't hide/show up anymore.
                # >> ATTENTION <<
                title = "PostgreSQL",
                # >> ATTENTION << for title. See above.
                id = ns("target_tab_pg"),
                h4("Target Database Connection"),
                box(
                  title = "Preloadings",
                  # background = "blue",
                  #solidHeader = TRUE,
                  width = 12,
                  selectInput(
                    # This will be filled in the server part.
1491
                    inputId = ns("target_postgres_presettings_list"),
1492
1493
1494
1495
                    label = NULL,
                    choices = NULL,
                    selected = NULL
                  ),
1496
1497
                  style = "text-align:center;"
                ),
1498
                textInput(
Jonathan Mang's avatar
Jonathan Mang committed
1499
1500
1501
1502
1503
1504
1505
1506
1507
1508
1509
1510
1511
1512
1513
1514
1515
1516
1517
1518
1519
1520
1521
1522
1523
1524
1525
1526
1527
1528
1529
1530
1531
1532
1533
1534
1535
1536
1537
1538
1539
1540
1541
1542
1543
1544
1545
1546
1547
1548
1549
1550
1551
1552
1553
1554
1555
1556
1557
                  inputId = ns("config_target_postgres_dbname"),
                  label = "DB Name",
                  placeholder = "Enter the name of the database ..."
                ),
                textInput(
                  inputId = ns("config_target_postgres_host"),
                  label = "IP",
                  placeholder = "Enter the IP here in format '192.168.1.1' ..."
                ),
                textInput(
                  inputId = ns("config_target_postgres_port"),
                  label = "Port",
                  placeholder = "Enter the Port of the database connection ..."
                ),
                textInput(
                  inputId = ns("config_target_postgres_user"),
                  label = "Username",
                  placeholder =
                    "Enter the Username for the database connection ..."
                ),
                passwordInput(
                  inputId = ns("config_target_postgres_password"),
                  label = "Password",
                  placeholder = "Enter the database password ..."
                ),
                br(),
                actionButton(
                  inputId = ns("target_postgres_test_connection"),
                  label = "Test & Save connection",
                  icon = icon("database"),
                  style = "text-align:center;"
                )
              ),
              tabPanel(
                # ATTENTION: If you change the title, you also have to change
                # the
                # corresponding part above for the "target == source" button
                # reaction. Otherwise the tabs won't hide/show up anymore.
                # >> ATTENTION <<
                title = "Oracle",
                # >> ATTENTION << for title. See above.
                id = ns("target_tab_oracle"),
                h4("Target Database Connection"),
                box(
                  title = "Preloadings",
                  # background = "blue",
                  #solidHeader = TRUE,
                  width = 12,
                  selectInput(
                    # This will be filled in the server part.
                    inputId = ns("target_oracle_presettings_list"),
                    label = NULL,
                    choices = NULL,
                    selected = NULL
                  ),
                  style = "text-align:center;"
                ),
                textInput(
                  inputId = ns("config_target_oracle_dbname"),
1558
1559
                  label = "DB Name",
                  placeholder = "Enter the name of the database ..."
1560
                ),
1561
                textInput(
Jonathan Mang's avatar
Jonathan Mang committed
1562
                  inputId = ns("config_target_oracle_host"),
1563
1564
1565
1566
                  label = "IP",
                  placeholder = "Enter the IP here in format '192.168.1.1' ..."
                ),
                textInput(
Jonathan Mang's avatar
Jonathan Mang committed
1567
                  inputId = ns("config_target_oracle_port"),
1568
1569
1570
1571
                  label = "Port",
                  placeholder = "Enter the Port of the database connection ..."
                ),
                textInput(
Jonathan Mang's avatar
Jonathan Mang committed
1572
                  inputId = ns("config_target_oracle_user"),
1573
1574
1575
1576
1577
                  label = "Username",
                  placeholder =
                    "Enter the Username for the database connection ..."
                ),
                passwordInput(
Jonathan Mang's avatar
Jonathan Mang committed
1578
                  inputId = ns("config_target_oracle_password"),
1579
1580
1581
                  label = "Password",
                  placeholder = "Enter the database password ..."
                ),
Jonathan Mang's avatar
Jonathan Mang committed
1582
1583
1584
1585
1586
1587
                textInput(
                  inputId = ns("config_target_oracle_sid"),
                  label = "SID",
                  placeholder =
                    "Enter the SID for the database connection ..."
                ),
1588
1589
                br(),
                actionButton(
Jonathan Mang's avatar
Jonathan Mang committed
1590
                  inputId = ns("target_oracle_test_connection"),
1591
1592
1593
1594
                  label = "Test & Save connection",
                  icon = icon("database"),
                  style = "text-align:center;"
                )
1595
              )
Jonathan Mang's avatar
Jonathan Mang committed
1596
            ),
Jonathan Mang's avatar
Jonathan Mang committed
1597
            tags$hr(),
Jonathan Mang's avatar
Jonathan Mang committed
1598
1599
            checkboxInput(
              inputId = ns("target_system_to_source_system_btn"),
Jonathan Mang's avatar
Jonathan Mang committed
1600
              # inputId = ns("randomstringhere"),
Jonathan Mang's avatar
Jonathan Mang committed
1601
1602
1603
1604
              label = paste0(" Use SOURCE also as TARGET",
                             " (Compare source with itself)"),
              value = FALSE
            ),
Jonathan Mang's avatar
Jonathan Mang committed
1605
            tags$hr()
1606
          )
1607
        )
1608
1609
1610
1611
      ),
      column(
        3,
        conditionalPanel(
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1612
1613
          condition =
            "typeof output['moduleConfig-mdr_present'] == 'undefined'",
1614
1615
1616
1617
1618
1619
1620
1621
1622
1623
1624
          box(
            title = "Load Metadata Repository",
            actionButton(
              inputId = ns("config_load_mdr"),
              label = "Load MDR",
              icon = icon("table")
            ),
            width = 12
          )
        ),
        conditionalPanel(
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1625
          condition =
1626
            "typeof output['moduleConfig-mdr_present'] !== 'undefined'",
1627
          box(
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1628
            title = "Load the data",
1629
            h4(htmlOutput(ns("source_system_feedback_txt"))),
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1630
            br(),
1631
            h4(htmlOutput(ns("target_system_feedback_txt"))),
1632
1633
1634
1635
            hr(),
            selectInput(
              ns("config_sitename"),
              "Please enter the name of your site",
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1636
              selected = FALSE,
1637
              choices = NULL,
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1638
              multiple = FALSE
1639
1640
            ),
            hr(),
1641
1642
            actionButton(ns("dash_load_btn"),
                         "Load data",
1643
1644
1645
1646
1647
                         icon = icon("file-upload"),
                         style = paste0("color: #fff;",
                                        "background-color: #337ab7;",
                                        "border-color: #2e6da4;",
                                        "display:center-align;")),
1648
            width = 12
1649
          ),
1650
1651
          box(
            id = ns("config_select_datetime_picker_box"),
1652
            title = "Do you want to time-filter the input data?",
1653
1654
            shinyWidgets::switchInput(inputId = ns("date_restriction_slider"),
                                      label = "Apply time-filtering",
1655
                                      labelWidth = 150,
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1656
                                      value = NULL,
1657
                                      disabled = TRUE
1658
1659
                                      # , labelWidth = "80px"
                                      ),
1660
1661
            daterangepicker::daterangepicker(
              inputId = ns("datetime_picker"),
1662
1663
1664
1665
              label = "Click to change the date range:",
              start = as.Date("1970-01-01"),
              end = Sys.Date(),
              # style = "width:100%; border-radius:4px",
1666
1667
1668
              ranges = datepicker_get_list_of_ranges(),
              options = list(
                showDropdowns = TRUE,
1669
1670
1671
                # timePicker = TRUE,
                # timePicker24Hour = TRUE,
                autoApply = TRUE,
Jonathan Mang's avatar
Jonathan Mang committed
1672
1673
1674
                locale = list(separator = " <-> ",
                              format = "DD.MM.Y",
                              firstDay = 1)
1675
              )
1676
              # ,icon = shiny::icon("datetime")
1677
1678
1679
            ),
            width = 12
          ),
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1680
          box(
1681
1682
1683
            id = ns("config_select_dqa_assessment_box"),
            title = "Analyse the following data elements",
            hr(),
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1684
            actionButton(
Jonathan Mang's avatar
Jonathan Mang committed
1685
              inputId = ns("select_all_assessment_variables"),
1686
              label = "Select all"
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1687
            ),
1688
            actionButton(
Jonathan Mang's avatar
Jonathan Mang committed
1689
              inputId = ns("select_no_assessment_variables"),
1690
1691
1692
1693
              label = "Unselect all"
            ),
            hr(),
            checkboxGroupInput(
Jonathan Mang's avatar
Jonathan Mang committed
1694
              inputId = ns("select_dqa_assessment_variables"),
1695
1696
              label = NULL,
              choices = NULL),
1697
            width = 12
Lorenz Kapsner's avatar
Lorenz Kapsner committed
1698
          )
1699
        )
1700
1701
1702
      )
    )
  )
kapsner's avatar
kapsner committed
1703
}