... | ... |
@@ -22,17 +22,22 @@ nonLinearWorkflow <- function(input, output, session, parent, |
22 | 22 |
ns <- session$ns |
23 | 23 |
|
24 | 24 |
output$ui <- renderUI({ |
25 |
- bsCollapsePanel(tagList(icon("chevron-circle-down"), "Downstream Analysis"), |
|
26 |
- uiOutput(ns("de")), |
|
27 |
- uiOutput(ns("pa")), |
|
28 |
- uiOutput(ns("qcf")), |
|
29 |
- uiOutput(ns("nbc")), |
|
30 |
- uiOutput(ns("cw")), |
|
31 |
- uiOutput(ns("dr")), |
|
32 |
- uiOutput(ns("fs")), |
|
33 |
- uiOutput(ns("cl")), |
|
34 |
- uiOutput(ns("cv")), |
|
35 |
- style = "success") |
|
25 |
+ bsCollapse( |
|
26 |
+ open = "Next Steps", |
|
27 |
+ bsCollapsePanel("Next Steps", |
|
28 |
+ uiOutput(ns("de")), |
|
29 |
+ uiOutput(ns("pa")), |
|
30 |
+ uiOutput(ns("qcf")), |
|
31 |
+ uiOutput(ns("nbc")), |
|
32 |
+ uiOutput(ns("cw")), |
|
33 |
+ uiOutput(ns("dr")), |
|
34 |
+ uiOutput(ns("fs")), |
|
35 |
+ uiOutput(ns("cl")), |
|
36 |
+ uiOutput(ns("cv")), |
|
37 |
+ style = "success" |
|
38 |
+ ) |
|
39 |
+ ) |
|
40 |
+ |
|
36 | 41 |
}) |
37 | 42 |
|
38 | 43 |
if(de){ |
... | ... |
@@ -145,11 +145,32 @@ shinyServer(function(input, output, session) { |
145 | 145 |
} |
146 | 146 |
|
147 | 147 |
updateFeatureAnnots <- function(){ |
148 |
+ |
|
148 | 149 |
selectRowData <- colnames(rowData(vals$counts)) |
150 |
+ my_list <- data.frame() |
|
151 |
+ for(i in selectRowData) { |
|
152 |
+ my_list[i,1] <- paste0(i, " (e.g. ", paste(head(rowData(vals$counts)[,i], n = 3), collapse = ","), ")") |
|
153 |
+ } |
|
154 |
+ selectRowDataWithExamples <- as.character(my_list[,1]) |
|
155 |
+ |
|
156 |
+ |
|
157 |
+ selectNonNARowData <- names(apply(rowData(vals$counts), 2, anyNA)[apply(rowData(vals$counts), 2, anyNA) == FALSE]) |
|
158 |
+ my_list2 <- data.frame() |
|
159 |
+ for(j in selectNonNARowData) { |
|
160 |
+ my_list2[j,1] <- paste0(j, " (e.g. ", paste(head(rowData(vals$counts)[,j], n = 3), collapse = ","), ")") |
|
161 |
+ } |
|
162 |
+ selectNonNARowDataWithExamples <- as.character(my_list2[,1]) |
|
163 |
+ |
|
164 |
+ Default <- paste0("Default (e.g. ", paste(head(rownames(vals$counts), n = 3), collapse = ","), ")") |
|
165 |
+ |
|
149 | 166 |
updateSelectInput(session, "gsByParam", |
150 | 167 |
choices = c("rownames", selectRowData)) |
151 | 168 |
updateSelectInput(session, "importFeatureDispOpt", |
152 |
- choices = c("Rownames (Default)", selectRowData)) |
|
169 |
+ choices = c(Default, |
|
170 |
+ selectRowDataWithExamples)) |
|
171 |
+ updateSelectInput(session, "importFeatureNamesOpt", |
|
172 |
+ choices = c(Default, |
|
173 |
+ selectNonNARowDataWithExamples)) |
|
153 | 174 |
updateSelectInput(session, "filteredFeature", |
154 | 175 |
choices = c("none", selectRowData)) |
155 | 176 |
updateSelectInput(session, "hvgPlotFeatureDisplay", |
... | ... |
@@ -435,7 +456,7 @@ shinyServer(function(input, output, session) { |
435 | 456 |
count <- 0 |
436 | 457 |
if (!is.na(path)) { |
437 | 458 |
# Add Reference selection for cellRangerV2 |
438 |
- if (input$algoChoice == "cellRanger2") { |
|
459 |
+ if (input$uploadChoice == "cellRanger2") { |
|
439 | 460 |
## Identify available reference |
440 | 461 |
firstSampleDir <- list.dirs(path, recursive = FALSE)[1] |
441 | 462 |
refPath <- file.path(firstSampleDir, "outs/filtered_gene_bc_matrices") |
... | ... |
@@ -492,7 +513,7 @@ shinyServer(function(input, output, session) { |
492 | 513 |
collapse = .Platform$file.sep)) |
493 | 514 |
path <- dirPaths$sDirectory |
494 | 515 |
if (!is.na(path)) { |
495 |
- if (input$algoChoice == "cellRanger2") { |
|
516 |
+ if (input$uploadChoice == "cellRanger2") { |
|
496 | 517 |
## Identify available reference |
497 | 518 |
refPath <- file.path(path, "outs/filtered_gene_bc_matrices") |
498 | 519 |
refList <- basename(list.dirs(refPath, recursive = FALSE)) |
... | ... |
@@ -582,7 +603,7 @@ shinyServer(function(input, output, session) { |
582 | 603 |
} else { |
583 | 604 |
allDirs <- list.dirs(basePath, recursive = FALSE) |
584 | 605 |
# if we are adding a new CellRangerV2 sample |
585 |
- if (input$algoChoice == "cellRanger2") { |
|
606 |
+ if (input$uploadChoice == "cellRanger2") { |
|
586 | 607 |
allUI <- vector() |
587 | 608 |
allIDs <- vector() |
588 | 609 |
count <- 0 |
... | ... |
@@ -671,6 +692,7 @@ shinyServer(function(input, output, session) { |
671 | 692 |
) |
672 | 693 |
removeModal() |
673 | 694 |
} |
695 |
+ updateCollapse(session = session, "importUI", style = list("1. Add sample to import:" = "success")) |
|
674 | 696 |
}) |
675 | 697 |
|
676 | 698 |
# event listeners for Cell Ranger import modals' OK buttons |
... | ... |
@@ -682,7 +704,7 @@ shinyServer(function(input, output, session) { |
682 | 704 |
showModal(importCRSDir(failed = TRUE)) |
683 | 705 |
} else { |
684 | 706 |
# add the files to the appropriate reactiveValues |
685 |
- if (input$algoChoice == "cellRanger2") { |
|
707 |
+ if (input$uploadChoice == "cellRanger2") { |
|
686 | 708 |
id <- paste0("snewSampleCR2", allImportEntries$id_count) |
687 | 709 |
entry <- list(type="cellRanger2", id=id, |
688 | 710 |
params=list(cellRangerDirs = dirname(samplePath), |
... | ... |
@@ -698,7 +720,7 @@ shinyServer(function(input, output, session) { |
698 | 720 |
allImportEntries$id_count <- allImportEntries$id_count + 1 |
699 | 721 |
} |
700 | 722 |
# add new row to table |
701 |
- addToGeneralSampleTable(input$algoChoice, id, samplePath, input$sSampleID) |
|
723 |
+ addToGeneralSampleTable(input$uploadChoice, id, samplePath, input$sSampleID) |
|
702 | 724 |
# handler to remove the sample that was just added |
703 | 725 |
observeEvent(input[[paste0("remove", id)]],{ |
704 | 726 |
removeUI( |
... | ... |
@@ -716,6 +738,8 @@ shinyServer(function(input, output, session) { |
716 | 738 |
}) |
717 | 739 |
removeModal() |
718 | 740 |
} |
741 |
+ updateCollapse(session = session, "importUI", style = list("1. Add sample to import:" = "success")) |
|
742 |
+ |
|
719 | 743 |
}) |
720 | 744 |
|
721 | 745 |
# data directory |
... | ... |
@@ -724,7 +748,7 @@ shinyServer(function(input, output, session) { |
724 | 748 |
if ((!nzchar(input$dSampleID)) || (identical(dataPath, character(0)))) { |
725 | 749 |
showModal(importCRDDir(failed = TRUE)) |
726 | 750 |
} else { |
727 |
- if (input$algoChoice == "cellRanger2") { |
|
751 |
+ if (input$uploadChoice == "cellRanger2") { |
|
728 | 752 |
id <- paste0("dnewSampleCR2", allImportEntries$id_count) |
729 | 753 |
entry <- list(type="cellRanger2", id=id, |
730 | 754 |
params=list(dataDir = dataPath, |
... | ... |
@@ -738,7 +762,7 @@ shinyServer(function(input, output, session) { |
738 | 762 |
allImportEntries$id_count <- allImportEntries$id_count + 1 |
739 | 763 |
} |
740 | 764 |
# add new row to table |
741 |
- addToGeneralSampleTable(input$algoChoice, id, dataPath, input$dSampleID) |
|
765 |
+ addToGeneralSampleTable(input$uploadChoice, id, dataPath, input$dSampleID) |
|
742 | 766 |
observeEvent(input[[paste0("remove", id)]],{ |
743 | 767 |
removeUI( |
744 | 768 |
selector = paste0("#", id) |
... | ... |
@@ -755,6 +779,8 @@ shinyServer(function(input, output, session) { |
755 | 779 |
}) |
756 | 780 |
removeModal() |
757 | 781 |
} |
782 |
+ updateCollapse(session = session, "importUI", style = list("1. Add sample to import:" = "success")) |
|
783 |
+ |
|
758 | 784 |
}) |
759 | 785 |
|
760 | 786 |
# event handler for pressing OK on the import modal |
... | ... |
@@ -765,29 +791,29 @@ shinyServer(function(input, output, session) { |
765 | 791 |
showModal(importModal(failed = TRUE)) |
766 | 792 |
} else { |
767 | 793 |
entry <- list() |
768 |
- if (input$algoChoice == "starSolo") { |
|
794 |
+ if (input$uploadChoice == "starSolo") { |
|
769 | 795 |
id <- paste0("newSampleSS", allImportEntries$id_count) |
770 | 796 |
entry <- list(type="starSolo", id = id, params=list(STARsoloDirs = basePath, samples = input$sampleName)) |
771 | 797 |
allImportEntries$samples <- c(allImportEntries$samples, list(entry)) |
772 | 798 |
allImportEntries$id_count <- allImportEntries$id_count+1 |
773 |
- } else if (input$algoChoice == "busTools") { |
|
799 |
+ } else if (input$uploadChoice == "busTools") { |
|
774 | 800 |
id <- paste0("newSampleBUS", allImportEntries$id_count) |
775 | 801 |
entry <- list(type="busTools", id = id, params=list(BUStoolsDirs = basePath, samples = input$sampleName)) |
776 | 802 |
allImportEntries$samples <- c(allImportEntries$samples, list(entry)) |
777 | 803 |
allImportEntries$id_count <- allImportEntries$id_count+1 |
778 |
- } else if (input$algoChoice == "seqc") { |
|
804 |
+ } else if (input$uploadChoice == "seqc") { |
|
779 | 805 |
id <- paste0("newSampleSEQ", allImportEntries$id_count) |
780 | 806 |
entry <- list(type="seqc", id = id, params=list(seqcDirs = basePath, prefix = input$sampleID, samples = input$sampleName)) |
781 | 807 |
updateTextInput(session, "sampleID", value = "") |
782 | 808 |
allImportEntries$samples <- c(allImportEntries$samples, list(entry)) |
783 | 809 |
allImportEntries$id_count <- allImportEntries$id_count+1 |
784 |
- } else if (input$algoChoice == "optimus") { |
|
810 |
+ } else if (input$uploadChoice == "optimus") { |
|
785 | 811 |
id <- paste0("newSampleOpt", allImportEntries$id_count) |
786 | 812 |
entry <- list(type="optimus", id = id, params=list(OptimusDirs = basePath, samples = input$sampleName)) |
787 | 813 |
allImportEntries$samples <- c(allImportEntries$samples, list(entry)) |
788 | 814 |
allImportEntries$id_count <- allImportEntries$id_count+1 |
789 | 815 |
} |
790 |
- addToGeneralSampleTable(input$algoChoice, id, basePath, input$sampleName) |
|
816 |
+ addToGeneralSampleTable(input$uploadChoice, id, basePath, input$sampleName) |
|
791 | 817 |
observeEvent(input[[paste0("remove", id)]],{ |
792 | 818 |
removeUI( |
793 | 819 |
selector = paste0("#", id) |
... | ... |
@@ -804,6 +830,8 @@ shinyServer(function(input, output, session) { |
804 | 830 |
}) |
805 | 831 |
removeModal() |
806 | 832 |
} |
833 |
+ updateCollapse(session = session, "importUI", style = list("1. Add sample to import:" = "success")) |
|
834 |
+ |
|
807 | 835 |
}) |
808 | 836 |
|
809 | 837 |
# Event handler to import a file input |
... | ... |
@@ -844,6 +872,8 @@ shinyServer(function(input, output, session) { |
844 | 872 |
} |
845 | 873 |
allImportEntries$samples <- allImportEntries$samples[toRemove] |
846 | 874 |
}) |
875 |
+ updateCollapse(session = session, "importUI", style = list("1. Add sample to import:" = "success")) |
|
876 |
+ |
|
847 | 877 |
}) |
848 | 878 |
|
849 | 879 |
# Event handler to import an example input |
... | ... |
@@ -879,6 +909,8 @@ shinyServer(function(input, output, session) { |
879 | 909 |
} |
880 | 910 |
allImportEntries$samples <- allImportEntries$samples[toRemove] |
881 | 911 |
}) |
912 |
+ updateCollapse(session = session, "importUI", style = list("1. Add sample to import:" = "success")) |
|
913 |
+ |
|
882 | 914 |
}) |
883 | 915 |
|
884 | 916 |
# Event handler to import an RDS input |
... | ... |
@@ -904,6 +936,8 @@ shinyServer(function(input, output, session) { |
904 | 936 |
} |
905 | 937 |
allImportEntries$samples <- allImportEntries$samples[toRemove] |
906 | 938 |
}) |
939 |
+ updateCollapse(session = session, "importUI", style = list("1. Add sample to import:" = "success")) |
|
940 |
+ |
|
907 | 941 |
}) |
908 | 942 |
|
909 | 943 |
# Event handler for "Upload" button on import page |
... | ... |
@@ -1006,6 +1040,8 @@ shinyServer(function(input, output, session) { |
1006 | 1040 |
# datasets. Otherwise, errors may pop out when Shiny listens to the new |
1007 | 1041 |
# object but cannot find the old result. |
1008 | 1042 |
}) |
1043 |
+ updateCollapse(session = session, "importUI", style = list("2. Create dataset:" = "success")) |
|
1044 |
+ |
|
1009 | 1045 |
callModule(module = nonLinearWorkflow, id = "nlw-import", parent = session, qcf = TRUE) |
1010 | 1046 |
|
1011 | 1047 |
.loadClose() # close the notification spinner and console log |
... | ... |
@@ -1332,13 +1368,20 @@ shinyServer(function(input, output, session) { |
1332 | 1368 |
if (!is.null(vals$counts)) { |
1333 | 1369 |
withBusyIndicatorServer("importFeatureDipSet", { |
1334 | 1370 |
selected <- NULL |
1335 |
- if (!input$importFeatureDispOpt == "Rownames (Default)") { |
|
1336 |
- selected <- input$importFeatureDispOpt |
|
1371 |
+ |
|
1372 |
+ if (!stringr::word(input$importFeatureDispOpt, 1) == "Default") { |
|
1373 |
+ featureName <- word(input$importFeatureDispOpt, 1) |
|
1374 |
+ selected <- featureName |
|
1375 |
+ } |
|
1376 |
+ if (!stringr::word(input$importFeatureNamesOpt, 1) == "Default") { |
|
1377 |
+ featureID <- word(input$importFeatureNamesOpt, 1) |
|
1378 |
+ rownames(vals$counts) <- rowData(vals$counts)[[featureID]] |
|
1337 | 1379 |
} |
1338 | 1380 |
vals$counts <- setSCTKDisplayRow(vals$counts, selected) |
1339 | 1381 |
updateFeatureDisplaySelect(selected = selected) |
1340 | 1382 |
}) |
1341 | 1383 |
} |
1384 |
+ updateCollapse(session = session, "importUI", style = list("3. Data summary:" = "success")) |
|
1342 | 1385 |
}) |
1343 | 1386 |
updateFeatureDisplaySelect <- function(selected = NULL, updateOptions = FALSE) |
1344 | 1387 |
{ |
... | ... |
@@ -2125,7 +2168,7 @@ shinyServer(function(input, output, session) { |
2125 | 2168 |
}, striped = TRUE, border = TRUE, align = "c", spacing = "l") |
2126 | 2169 |
|
2127 | 2170 |
#Render summary table |
2128 |
- output$summarycontents <- renderTable({ |
|
2171 |
+ output$summarycontents <- DT::renderDataTable({ |
|
2129 | 2172 |
req(vals$counts) |
2130 | 2173 |
if ("Sample" %in% names(colData(vals$counts))) { |
2131 | 2174 |
sampleVar <- "Sample" |
... | ... |
@@ -2138,7 +2181,7 @@ shinyServer(function(input, output, session) { |
2138 | 2181 |
singleCellTK::summarizeSCE(inSCE = vals$counts, |
2139 | 2182 |
useAssay = NULL, |
2140 | 2183 |
sampleVariableName = sampleVar) |
2141 |
- }, striped = TRUE, border = TRUE, align = "c", spacing = "l") |
|
2184 |
+ }) |
|
2142 | 2185 |
|
2143 | 2186 |
|
2144 | 2187 |
#Reset the data to the original uploaded dataset |
... | ... |
@@ -16,6 +16,7 @@ if ("scRNAseq" %in% rownames(installed.packages())){ |
16 | 16 |
"NestorowaHSC (Nestorowa et al, 2016)" = "NestorowaHSCData") |
17 | 17 |
} |
18 | 18 |
|
19 |
+# User Interface for import Workflow --- |
|
19 | 20 |
shinyPanelImport <- fluidPage( |
20 | 21 |
useShinyjs(), |
21 | 22 |
tags$style(appCSS), |
... | ... |
@@ -33,26 +34,36 @@ shinyPanelImport <- fluidPage( |
33 | 34 |
) |
34 | 35 |
), |
35 | 36 |
tags$br(), |
36 |
- tags$div( |
|
37 |
- class = "container", |
|
38 |
- h1("Import"), |
|
39 |
- h5(tags$a(href = paste0(docs.artPath, "import_data.html"), |
|
40 |
- "(help)", target = "_blank")), |
|
41 |
- tags$hr(), |
|
42 |
- h3("1. Choose data source:"), |
|
43 |
- radioButtons("uploadChoice", label = NULL, c("Import from a preprocessing tool" = 'directory', |
|
44 |
- "Import from flat files (.csv, .txt, .mtx)" = "files", |
|
45 |
- "Upload SingleCellExperiment or Seurat object stored in an RDS File" = "rds", |
|
46 |
- "Import example datasets" = "example") |
|
47 |
- ), |
|
48 |
- tags$hr(), |
|
49 |
- conditionalPanel(condition = sprintf("input['%s'] == 'files'", "uploadChoice"), |
|
50 |
- h3("2. Upload data in tab separated text format:"), |
|
51 |
- fluidRow( |
|
52 |
- column(width = 4, |
|
53 |
- wellPanel( |
|
54 |
- h4("Example count file:"), |
|
55 |
- HTML('<table class="table"><thead><tr class="header"><th>Gene</th> |
|
37 |
+ |
|
38 |
+ h1("Import"), |
|
39 |
+ h5(tags$a(href = paste0(docs.artPath, "import_data.html"), |
|
40 |
+ "(help)", target = "_blank")), |
|
41 |
+ tags$hr(), |
|
42 |
+ |
|
43 |
+ bsCollapse( |
|
44 |
+ id = "importUI", |
|
45 |
+ open = "1. Add sample to import:", |
|
46 |
+ bsCollapsePanel( |
|
47 |
+ "1. Add sample to import:", |
|
48 |
+ radioButtons("uploadChoice", label = NULL, c("Cell Ranger (Version 3 or above)" = "cellRanger3", |
|
49 |
+ "Cell Ranger (Version 2)" = "cellRanger2", |
|
50 |
+ "STARsolo" = "starSolo", |
|
51 |
+ "BUStools" = "busTools", |
|
52 |
+ "SEQC" = "seqc", |
|
53 |
+ "Optimus" = "optimus", |
|
54 |
+ #"Import from a preprocessing tool" = 'directory', |
|
55 |
+ "Import from flat files (.csv, .txt, .mtx)" = "files", |
|
56 |
+ "Upload SingleCellExperiment or Seurat object stored in an RDS File" = "rds", |
|
57 |
+ "Import example datasets" = "example") |
|
58 |
+ ), |
|
59 |
+ tags$hr(), |
|
60 |
+ conditionalPanel(condition = sprintf("input['%s'] == 'files'", "uploadChoice"), |
|
61 |
+ h3("Upload data in tab separated text format:"), |
|
62 |
+ fluidRow( |
|
63 |
+ column(width = 4, |
|
64 |
+ wellPanel( |
|
65 |
+ h4("Example count file:"), |
|
66 |
+ HTML('<table class="table"><thead><tr class="header"><th>Gene</th> |
|
56 | 67 |
<th>Cell1</th><th>Cell2</th><th>…</th><th>CellN</th> |
57 | 68 |
</tr></thead><tbody><tr class="odd"><td>Gene1</td><td>0</td> |
58 | 69 |
<td>0</td><td>…</td><td>0</td></tr><tr class="even"> |
... | ... |
@@ -63,257 +74,264 @@ shinyPanelImport <- fluidPage( |
63 | 74 |
<td>…</td><td>…</td></tr><tr class="odd"> |
64 | 75 |
<td>GeneM</td><td>10</td><td>10</td><td>…</td><td>10</td> |
65 | 76 |
</tr></tbody></table>'), |
66 |
- tags$a(href = "https://drive.google.com/open?id=1n0CtM6phfkWX0O6xRtgPPg6QuPFP6pY8", |
|
67 |
- "Download an example count file here.", target = "_blank"), |
|
68 |
- tags$br(), |
|
69 |
- tags$br(), |
|
70 |
- fileInput( |
|
71 |
- "countsfile", |
|
72 |
- HTML( |
|
73 |
- paste("Input assay (eg. counts, required):", |
|
74 |
- tags$span(style = "color:red", "*", sep = "")) |
|
75 |
- ), |
|
76 |
- accept = c( |
|
77 |
- "text/csv", "text/comma-separated-values", "mtx", |
|
78 |
- "text/tab-separated-values", "text/plain", ".csv", ".tsv" |
|
79 |
- ) |
|
80 |
- ) |
|
81 |
- ), |
|
82 |
- h4("Input Assay Type:"), |
|
83 |
- selectInput("inputAssayType", label = NULL, |
|
84 |
- c("counts", "normcounts", "logcounts", "cpm", |
|
85 |
- "logcpm", "tpm", "logtpm") |
|
86 |
- ) |
|
87 |
- ), |
|
88 |
- column(width = 4, |
|
89 |
- wellPanel( |
|
90 |
- h4("Example cell annotation file:"), |
|
91 |
- HTML('<table class="table"><thead><tr class="header"><th>Cell</th> |
|
77 |
+ tags$a(href = "https://drive.google.com/open?id=1n0CtM6phfkWX0O6xRtgPPg6QuPFP6pY8", |
|
78 |
+ "Download an example count file here.", target = "_blank"), |
|
79 |
+ tags$br(), |
|
80 |
+ tags$br(), |
|
81 |
+ fileInput( |
|
82 |
+ "countsfile", |
|
83 |
+ HTML( |
|
84 |
+ paste("Input assay (eg. counts, required):", |
|
85 |
+ tags$span(style = "color:red", "*", sep = "")) |
|
86 |
+ ), |
|
87 |
+ accept = c( |
|
88 |
+ "text/csv", "text/comma-separated-values", "mtx", |
|
89 |
+ "text/tab-separated-values", "text/plain", ".csv", ".tsv" |
|
90 |
+ ) |
|
91 |
+ ) |
|
92 |
+ ), |
|
93 |
+ h4("Input Assay Type:"), |
|
94 |
+ selectInput("inputAssayType", label = NULL, |
|
95 |
+ c("counts", "normcounts", "logcounts", "cpm", |
|
96 |
+ "logcpm", "tpm", "logtpm") |
|
97 |
+ ) |
|
98 |
+ ), |
|
99 |
+ column(width = 4, |
|
100 |
+ wellPanel( |
|
101 |
+ h4("Example cell annotation file:"), |
|
102 |
+ HTML('<table class="table"><thead><tr class="header"><th>Cell</th> |
|
92 | 103 |
<th>Annot1</th><th>…</th></tr></thead><tbody><tr class="odd"> |
93 | 104 |
<td>Cell1</td><td>a</td><td>…</td></tr><tr class="even"> |
94 | 105 |
<td>Cell2</td><td>a</td><td>…</td></tr><tr class="odd"> |
95 | 106 |
<td>Cell3</td><td>b</td><td>…</td></tr><tr class="even"> |
96 | 107 |
<td>…</td><td>…</td><td>…</td></tr><tr class="odd"><td>CellN</td> |
97 | 108 |
<td>b</td><td>…</td></tr></tbody></table>'), |
98 |
- tags$a(href = "https://drive.google.com/open?id=10IDmZQUiASN4wnzO4-WRJQopKvxCNu6J", |
|
99 |
- "Download an example annotation file here.", target = "_blank"), |
|
100 |
- tags$br(), |
|
101 |
- tags$br(), |
|
102 |
- fileInput( |
|
103 |
- "annotFile", "Cell annotations (optional):", |
|
104 |
- accept = c( |
|
105 |
- "text/csv", "text/comma-separated-values", |
|
106 |
- "text/tab-separated-values", "text/plain", ".csv", ".tsv" |
|
109 |
+ tags$a(href = "https://drive.google.com/open?id=10IDmZQUiASN4wnzO4-WRJQopKvxCNu6J", |
|
110 |
+ "Download an example annotation file here.", target = "_blank"), |
|
111 |
+ tags$br(), |
|
112 |
+ tags$br(), |
|
113 |
+ fileInput( |
|
114 |
+ "annotFile", "Cell annotations (optional):", |
|
115 |
+ accept = c( |
|
116 |
+ "text/csv", "text/comma-separated-values", |
|
117 |
+ "text/tab-separated-values", "text/plain", ".csv", ".tsv" |
|
118 |
+ ) |
|
107 | 119 |
) |
108 | 120 |
) |
109 |
- ) |
|
110 |
- ), |
|
111 |
- column(width = 4, |
|
112 |
- wellPanel( |
|
113 |
- h4("Example feature file:"), |
|
114 |
- HTML('<table class="table"><thead><tr class="header"><th>Gene</th> |
|
121 |
+ ), |
|
122 |
+ column(width = 4, |
|
123 |
+ wellPanel( |
|
124 |
+ h4("Example feature file:"), |
|
125 |
+ HTML('<table class="table"><thead><tr class="header"><th>Gene</th> |
|
115 | 126 |
<th>Annot2</th><th>…</th></tr></thead><tbody><tr class="odd"> |
116 | 127 |
<td>Gene1</td><td>a</td><td>…</td></tr><tr class="even"> |
117 | 128 |
<td>Gene2</td><td>a</td><td>…</td></tr><tr class="odd"> |
118 | 129 |
<td>Gene3</td><td>b</td><td>…</td></tr><tr class="even"> |
119 | 130 |
<td>…</td><td>…</td><td>…</td></tr><tr class="odd"><td>GeneM</td> |
120 | 131 |
<td>b</td><td>…</td></tr></tbody></table>'), |
121 |
- tags$a(href = "https://drive.google.com/open?id=1gxXaZPq5Wrn2lNHacEVaCN2a_FHNvs4O", |
|
122 |
- "Download an example feature file here.", target = "_blank"), |
|
123 |
- tags$br(), |
|
124 |
- tags$br(), |
|
125 |
- fileInput( |
|
126 |
- "featureFile", "Feature annotations (optional):", |
|
127 |
- accept = c( |
|
128 |
- "text/csv", "text/comma-separated-values", |
|
129 |
- "text/tab-separated-values", "text/plain", ".csv", ".tsv" |
|
132 |
+ tags$a(href = "https://drive.google.com/open?id=1gxXaZPq5Wrn2lNHacEVaCN2a_FHNvs4O", |
|
133 |
+ "Download an example feature file here.", target = "_blank"), |
|
134 |
+ tags$br(), |
|
135 |
+ tags$br(), |
|
136 |
+ fileInput( |
|
137 |
+ "featureFile", "Feature annotations (optional):", |
|
138 |
+ accept = c( |
|
139 |
+ "text/csv", "text/comma-separated-values", |
|
140 |
+ "text/tab-separated-values", "text/plain", ".csv", ".tsv" |
|
141 |
+ ) |
|
130 | 142 |
) |
131 | 143 |
) |
132 |
- ) |
|
133 |
- ) |
|
134 |
- ), |
|
135 |
- actionButton("addFilesImport", "Add To Sample List") |
|
136 |
- ), |
|
137 |
- conditionalPanel( |
|
138 |
- condition = sprintf("input['%s'] == 'example'", "uploadChoice"), |
|
139 |
- h3("2. Choose Example Dataset:"), |
|
140 |
- selectInput("selectExampleData", label = NULL, exampleDatasets), |
|
141 |
- conditionalPanel( |
|
142 |
- condition = sprintf("input['%s'] == 'fluidigm_pollen'", "selectExampleData"), |
|
143 |
- h3(tags$a(href = "http://dx.doi.org/10.1038/nbt.2967", "130 cells from (Pollen et al. 2014), 65 at high coverage and 65 at low coverage", target = "_blank")), |
|
144 |
- "Transcriptomes of cell populations in both of low-coverage (~0.27 million reads per cell) and high-coverage (~5 million reads per cell) to identify cell-type-specific biomarkers, and to compare gene expression across samples specifically for cells of a given type as well as to reconstruct developmental lineages of related cell types. Data was loaded from the 'scRNASeq' package.", |
|
145 |
- tags$br(), |
|
146 |
- tags$br() |
|
147 |
- ), |
|
148 |
- conditionalPanel( |
|
149 |
- condition = sprintf("input['%s'] == 'allen_tasic'", "selectExampleData"), |
|
150 |
- h3(tags$a(href = "http://dx.doi.org/10.1038/nn.4216", "Mouse visual cortex cells from (Tasic et al. 2016)", target = "_blank")), |
|
151 |
- "Subset of 379 cells from the mouse visual cortex. Data was loaded from the 'scRNASeq' package.", |
|
152 |
- tags$br(), |
|
153 |
- tags$br() |
|
154 |
- ), |
|
155 |
- conditionalPanel( |
|
156 |
- condition = sprintf("input['%s'] == 'NestorowaHSCData'", "selectExampleData"), |
|
157 |
- h3(tags$a(href = "https://www.nature.com/articles/nbt.2967", "1920 Mouse haematopoietic stem cells from (Nestorowa et al. 2015).", target= "_blank")), |
|
158 |
- "Data was loaded from the 'scRNASeq' package.", |
|
159 |
- tags$br(), |
|
160 |
- tags$br() |
|
161 |
- ), |
|
162 |
- conditionalPanel( |
|
163 |
- condition = sprintf("input['%s'] == 'pbmc3k'", "selectExampleData"), |
|
164 |
- h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "2,700 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
165 |
- "Data was loaded with the 'TENxPBMCData' package.", |
|
166 |
- tags$br(), |
|
167 |
- tags$br() |
|
168 |
- ), |
|
169 |
- conditionalPanel( |
|
170 |
- condition = sprintf("input['%s'] == 'pbmc4k'", "selectExampleData"), |
|
171 |
- h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "4,430 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
172 |
- "Data was loaded with the 'TENxPBMCData' package.", |
|
173 |
- tags$br(), |
|
174 |
- tags$br() |
|
175 |
- ), |
|
176 |
- conditionalPanel( |
|
177 |
- condition = sprintf("input['%s'] == 'pbmc6k'", "selectExampleData"), |
|
178 |
- h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "5,419 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
179 |
- "Data was loaded with the 'TENxPBMCData' package.", |
|
180 |
- tags$br(), |
|
181 |
- tags$br() |
|
182 |
- ), |
|
183 |
- conditionalPanel( |
|
184 |
- condition = sprintf("input['%s'] == 'pbmc8k'", "selectExampleData"), |
|
185 |
- h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "8,381 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
186 |
- "Data was loaded with the 'TENxPBMCData' package.", |
|
187 |
- tags$br(), |
|
188 |
- tags$br() |
|
144 |
+ ) |
|
145 |
+ ), |
|
146 |
+ actionButton("addFilesImport", "Add To Dataset List") |
|
189 | 147 |
), |
190 | 148 |
conditionalPanel( |
191 |
- condition = sprintf("input['%s'] == 'pbmc33k'", "selectExampleData"), |
|
192 |
- h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "33,148 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
193 |
- "Data was loaded with the 'TENxPBMCData' package.", |
|
194 |
- tags$br(), |
|
195 |
- tags$br() |
|
149 |
+ condition = sprintf("input['%s'] == 'example'", "uploadChoice"), |
|
150 |
+ h3("Choose Example Dataset:"), |
|
151 |
+ selectInput("selectExampleData", label = NULL, exampleDatasets), |
|
152 |
+ conditionalPanel( |
|
153 |
+ condition = sprintf("input['%s'] == 'fluidigm_pollen'", "selectExampleData"), |
|
154 |
+ h3(tags$a(href = "http://dx.doi.org/10.1038/nbt.2967", "130 cells from (Pollen et al. 2014), 65 at high coverage and 65 at low coverage", target = "_blank")), |
|
155 |
+ "Transcriptomes of cell populations in both of low-coverage (~0.27 million reads per cell) and high-coverage (~5 million reads per cell) to identify cell-type-specific biomarkers, and to compare gene expression across samples specifically for cells of a given type as well as to reconstruct developmental lineages of related cell types. Data was loaded from the 'scRNASeq' package.", |
|
156 |
+ tags$br(), |
|
157 |
+ tags$br() |
|
158 |
+ ), |
|
159 |
+ conditionalPanel( |
|
160 |
+ condition = sprintf("input['%s'] == 'allen_tasic'", "selectExampleData"), |
|
161 |
+ h3(tags$a(href = "http://dx.doi.org/10.1038/nn.4216", "Mouse visual cortex cells from (Tasic et al. 2016)", target = "_blank")), |
|
162 |
+ "Subset of 379 cells from the mouse visual cortex. Data was loaded from the 'scRNASeq' package.", |
|
163 |
+ tags$br(), |
|
164 |
+ tags$br() |
|
165 |
+ ), |
|
166 |
+ conditionalPanel( |
|
167 |
+ condition = sprintf("input['%s'] == 'NestorowaHSCData'", "selectExampleData"), |
|
168 |
+ h3(tags$a(href = "https://www.nature.com/articles/nbt.2967", "1920 Mouse haematopoietic stem cells from (Nestorowa et al. 2015).", target= "_blank")), |
|
169 |
+ "Data was loaded from the 'scRNASeq' package.", |
|
170 |
+ tags$br(), |
|
171 |
+ tags$br() |
|
172 |
+ ), |
|
173 |
+ conditionalPanel( |
|
174 |
+ condition = sprintf("input['%s'] == 'pbmc3k'", "selectExampleData"), |
|
175 |
+ h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "2,700 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
176 |
+ "Data was loaded with the 'TENxPBMCData' package.", |
|
177 |
+ tags$br(), |
|
178 |
+ tags$br() |
|
179 |
+ ), |
|
180 |
+ conditionalPanel( |
|
181 |
+ condition = sprintf("input['%s'] == 'pbmc4k'", "selectExampleData"), |
|
182 |
+ h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "4,430 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
183 |
+ "Data was loaded with the 'TENxPBMCData' package.", |
|
184 |
+ tags$br(), |
|
185 |
+ tags$br() |
|
186 |
+ ), |
|
187 |
+ conditionalPanel( |
|
188 |
+ condition = sprintf("input['%s'] == 'pbmc6k'", "selectExampleData"), |
|
189 |
+ h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "5,419 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
190 |
+ "Data was loaded with the 'TENxPBMCData' package.", |
|
191 |
+ tags$br(), |
|
192 |
+ tags$br() |
|
193 |
+ ), |
|
194 |
+ conditionalPanel( |
|
195 |
+ condition = sprintf("input['%s'] == 'pbmc8k'", "selectExampleData"), |
|
196 |
+ h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "8,381 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
197 |
+ "Data was loaded with the 'TENxPBMCData' package.", |
|
198 |
+ tags$br(), |
|
199 |
+ tags$br() |
|
200 |
+ ), |
|
201 |
+ conditionalPanel( |
|
202 |
+ condition = sprintf("input['%s'] == 'pbmc33k'", "selectExampleData"), |
|
203 |
+ h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "33,148 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
204 |
+ "Data was loaded with the 'TENxPBMCData' package.", |
|
205 |
+ tags$br(), |
|
206 |
+ tags$br() |
|
207 |
+ ), |
|
208 |
+ conditionalPanel( |
|
209 |
+ condition = sprintf("input['%s'] == 'pbmc68k'", "selectExampleData"), |
|
210 |
+ h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "68,579 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
211 |
+ "Data was loaded with the 'TENxPBMCData' package.", |
|
212 |
+ tags$br(), |
|
213 |
+ tags$br() |
|
214 |
+ ), |
|
215 |
+ actionButton("addExampleImport", "Add To Sample List") |
|
196 | 216 |
), |
197 | 217 |
conditionalPanel( |
198 |
- condition = sprintf("input['%s'] == 'pbmc68k'", "selectExampleData"), |
|
199 |
- h3(tags$a(href = "https://doi.org/10.1038/ncomms14049", "68,579 peripheral blood mononuclear cells (PBMCs) from 10X Genomics", target = "_blank")), |
|
200 |
- "Data was loaded with the 'TENxPBMCData' package.", |
|
201 |
- tags$br(), |
|
202 |
- tags$br() |
|
203 |
- ), |
|
204 |
- actionButton("addExampleImport", "Add To Sample List") |
|
205 |
- ), |
|
206 |
- conditionalPanel( |
|
207 |
- condition = sprintf("input['%s'] == 'rds'", "uploadChoice"), |
|
208 |
- h3("2. Choose an RDS file that contains a SingleCellExperiment or Seurat object:"), |
|
209 |
- fileInput( |
|
210 |
- "rdsFile", "SingleCellExperiment or Seurat RDS file:", accept = c(".rds", ".RDS") |
|
211 |
- ), |
|
212 |
- actionButton("addRDSImport", "Add To Sample List") |
|
213 |
- ), |
|
214 |
- conditionalPanel( |
|
215 |
- condition = sprintf("input['%s'] == 'directory'", "uploadChoice"), |
|
216 |
- tags$style(HTML(" |
|
217 |
- div { |
|
218 |
- word-wrap: break-word; |
|
219 |
- } |
|
220 |
- ")), |
|
221 |
- h3("2. Choose a Preprocessing Tool:"), |
|
222 |
- radioButtons("algoChoice", label = NULL, c("Cell Ranger v2" = "cellRanger2", |
|
223 |
- "Cell Ranger v3" = "cellRanger3", |
|
224 |
- "STARsolo" = "starSolo", |
|
225 |
- "BUStools" = "busTools", |
|
226 |
- "SEQC" = "seqc", |
|
227 |
- "Optimus" = "optimus") |
|
218 |
+ condition = sprintf("input['%s'] == 'rds'", "uploadChoice"), |
|
219 |
+ h3("Choose an RDS file that contains a SingleCellExperiment or Seurat object:"), |
|
220 |
+ fileInput( |
|
221 |
+ "rdsFile", "SingleCellExperiment or Seurat RDS file:", accept = c(".rds", ".RDS") |
|
222 |
+ ), |
|
223 |
+ actionButton("addRDSImport", "Add To Sample List") |
|
228 | 224 |
), |
229 |
- tags$br(), |
|
225 |
+ #conditionalPanel( |
|
226 |
+ #condition = sprintf("input['%s'] == 'directory'", "uploadChoice"), |
|
227 |
+ #tags$style(HTML(" |
|
228 |
+ #div { |
|
229 |
+ # word-wrap: break-word; |
|
230 |
+ #} |
|
231 |
+ #")), |
|
232 |
+ #h3("2. Choose a Preprocessing Tool:"), |
|
233 |
+ #radioButtons("algoChoice", label = NULL, c("Cell Ranger v2" = "cellRanger2", |
|
234 |
+ # "Cell Ranger v3" = "cellRanger3", |
|
235 |
+ # "STARsolo" = "starSolo", |
|
236 |
+ # "BUStools" = "busTools", |
|
237 |
+ # "SEQC" = "seqc", |
|
238 |
+ # "Optimus" = "optimus") |
|
239 |
+ #), |
|
240 |
+ #tags$br(), |
|
230 | 241 |
conditionalPanel( |
231 |
- condition = sprintf("input['%s'] == 'cellRanger2'", "algoChoice"), |
|
242 |
+ condition = sprintf("input['%s'] == 'cellRanger2'", "uploadChoice"), |
|
232 | 243 |
actionButton("addCR2Sample", "Add a Sample"), |
233 | 244 |
), |
234 | 245 |
conditionalPanel( |
235 |
- condition = sprintf("input['%s'] == 'cellRanger3'", "algoChoice"), |
|
246 |
+ condition = sprintf("input['%s'] == 'cellRanger3'", "uploadChoice"), |
|
236 | 247 |
actionButton("addCR3Sample", "Add a Sample"), |
237 | 248 |
), |
238 | 249 |
conditionalPanel( |
239 |
- condition = sprintf("input['%s'] == 'starSolo'", "algoChoice"), |
|
250 |
+ condition = sprintf("input['%s'] == 'starSolo'", "uploadChoice"), |
|
240 | 251 |
wellPanel( |
241 | 252 |
h5("Please select the directory that contains your /Gene directory as your base directory. ") |
242 | 253 |
), |
243 | 254 |
actionButton("addSSSample", "Add a Sample"), |
244 | 255 |
), |
245 | 256 |
conditionalPanel( |
246 |
- condition = sprintf("input['%s'] == 'busTools'", "algoChoice"), |
|
257 |
+ condition = sprintf("input['%s'] == 'busTools'", "uploadChoice"), |
|
247 | 258 |
wellPanel( |
248 | 259 |
h5("Please select your /genecount directory as your base directory.") |
249 | 260 |
), |
250 | 261 |
actionButton("addBUSSample", "Add a Sample"), |
251 | 262 |
), |
252 | 263 |
conditionalPanel( |
253 |
- condition = sprintf("input['%s'] == 'seqc'", "algoChoice"), |
|
264 |
+ condition = sprintf("input['%s'] == 'seqc'", "uploadChoice"), |
|
254 | 265 |
wellPanel( |
255 | 266 |
h5("Please select the directory that contains your sample files as your base directory.") |
256 | 267 |
), |
257 | 268 |
actionButton("addSEQSample", "Add a Sample"), |
258 | 269 |
), |
259 | 270 |
conditionalPanel( |
260 |
- condition = sprintf("input['%s'] == 'optimus'", "algoChoice"), |
|
271 |
+ condition = sprintf("input['%s'] == 'optimus'", "uploadChoice"), |
|
261 | 272 |
wellPanel( |
262 | 273 |
h5("Please select the directory that contains the following four directories - call-MergeCountFiles, call-MergeCellMetrics, call-MergeGeneMetrics, call-RunEmptyDrops - as your base directory.") |
263 | 274 |
), |
264 | 275 |
actionButton("addOptSample", "Add a Sample"), |
265 | 276 |
), |
277 |
+ style = "primary" |
|
266 | 278 |
), |
267 |
- tags$hr(), |
|
268 |
- h3("3. Import:"), |
|
269 |
- wellPanel( |
|
270 |
- h4("Samples to Import:"), |
|
271 |
- fluidRow( |
|
272 |
- column(3, tags$b("Type")), |
|
273 |
- column(3, tags$b("Location")), |
|
274 |
- column(3, tags$b("Sample Name")), |
|
275 |
- column(3, tags$b("Remove")) |
|
279 |
+ |
|
280 |
+ bsCollapsePanel( |
|
281 |
+ "2. Create dataset:", |
|
282 |
+ wellPanel( |
|
283 |
+ h4("Samples to Import:"), |
|
284 |
+ fluidRow( |
|
285 |
+ column(3, tags$b("Type")), |
|
286 |
+ column(3, tags$b("Location")), |
|
287 |
+ column(3, tags$b("Sample Name")), |
|
288 |
+ column(3, tags$b("Remove")) |
|
289 |
+ ), |
|
290 |
+ tags$div(id = "newSampleImport"), |
|
291 |
+ tags$br(), |
|
292 |
+ tags$br(), |
|
293 |
+ actionButton("clearAllImport", "Clear Samples") |
|
294 |
+ ), |
|
295 |
+ shinyjs::hidden( |
|
296 |
+ tags$div( |
|
297 |
+ id = "combineOptions", |
|
298 |
+ radioButtons("combineSCEChoice", label = NULL, c("Add to existing dataset" = 'addToExistingSCE', |
|
299 |
+ "Overwrite existing dataset" = "overwriteSCE") |
|
300 |
+ ) |
|
301 |
+ ) |
|
276 | 302 |
), |
277 |
- tags$div(id = "newSampleImport"), |
|
303 |
+ actionButton("uploadData", "Create"), |
|
304 |
+ |
|
278 | 305 |
tags$br(), |
279 | 306 |
tags$br(), |
280 |
- actionButton("clearAllImport", "Clear Samples") |
|
307 |
+ style = "primary" |
|
281 | 308 |
), |
282 |
- shinyjs::hidden( |
|
283 |
- tags$div( |
|
284 |
- id = "combineOptions", |
|
285 |
- radioButtons("combineSCEChoice", label = NULL, c("Add to existing SCE object" = 'addToExistingSCE', |
|
286 |
- "Overwrite existing SCE object" = "overwriteSCE") |
|
309 |
+ |
|
310 |
+ bsCollapsePanel( |
|
311 |
+ "3. Data summary:", |
|
312 |
+ hidden( |
|
313 |
+ wellPanel( |
|
314 |
+ id = "annotationData", |
|
315 |
+ h3("Data summary"), |
|
316 |
+ DT::dataTableOutput("summarycontents"), |
|
317 |
+ |
|
318 |
+ tags$hr(), |
|
319 |
+ |
|
320 |
+ h3("Dataset options:"), |
|
321 |
+ selectInput("importFeatureNamesOpt", |
|
322 |
+ "Set feature ID (only showing annotations without the NAs)", |
|
323 |
+ c("Default", featureChoice)), |
|
324 |
+ selectInput("importFeatureDispOpt", |
|
325 |
+ "Set feature names to be displayed in downstream visualization", |
|
326 |
+ c("Default", featureChoice)), |
|
327 |
+ |
|
328 |
+ withBusyIndicatorUI(actionButton("importFeatureDipSet", "Set")), |
|
287 | 329 |
) |
288 |
- ) |
|
289 |
- ), |
|
290 |
- actionButton("uploadData", "Import"), |
|
291 |
- |
|
292 |
- tags$br(), |
|
293 |
- tags$br(), |
|
294 |
- hidden( |
|
295 |
- wellPanel( |
|
296 |
- id = "annotationData", |
|
297 |
- h3("Data summary"), |
|
298 |
- tableOutput("summarycontents"), |
|
299 |
- |
|
300 |
- tags$hr(), |
|
301 |
- |
|
302 |
- h3("Set Feature for Display:"), |
|
303 |
- selectInput("importFeatureDispOpt", |
|
304 |
- "Select the feature ID type that should be displayed in downstream visualization", |
|
305 |
- c("Rownames (Default)", featureChoice)), |
|
306 |
- withBusyIndicatorUI(actionButton("importFeatureDipSet", "Set")), |
|
307 |
- ) |
|
308 |
- ), |
|
309 |
- |
|
310 |
- tags$div( |
|
311 |
- class = "container", |
|
312 |
- p("") |
|
313 |
- ), |
|
314 |
- |
|
315 |
- nonLinearWorkflowUI(id = "nlw-import") |
|
316 |
- ) |
|
317 |
- #includeHTML("www/footer.html") |
|
330 |
+ ), |
|
331 |
+ |
|
332 |
+ style = "primary" |
|
333 |
+ ) |
|
334 |
+ ), |
|
335 |
+ nonLinearWorkflowUI(id = "nlw-import") |
|
318 | 336 |
) |
319 | 337 |
|