5970a6c3 |
tibble::tribble(
~names, ~types, ~transform, ~flag, ~tag,
"ProjectID", "char", NULL, "required", "project_id",
"FUSIONID", "char", NULL, "optional", "fusion_id",
"PoolID", "char", NULL, "required", "pool_id",
"TagSequence", "char", NULL, "required", "tag_seq",
"SubjectID", "char", NULL, "required", "subject",
"VectorType", "char", NULL, "optional", NA_character_,
"VectorID", "char", NULL, "required", "vector_id",
"ExperimentID", "char", NULL, "optional", NA_character_,
"Tissue", "char", NULL, "required", "tissue",
"TimePoint", "char", ~ stringr::str_pad(.x, 4, side = "left", pad = "0"),
"required", "tp_days",
"DNAFragmentation", "char", NULL, "optional", NA_character_,
"PCRMethod", "char", NULL, "required", "pcr_method",
"TagIDextended", "char", NULL, "optional", NA_character_,
"Keywords", "char", NULL, "optional", NA_character_,
"CellMarker", "char", NULL, "required", "cell_marker",
"TagID", "char", NULL, "required", "tag_id",
"NGSProvider", "char", NULL, "optional", NA_character_,
"NGSTechnology", "char", NULL, "required", "ngs_tech",
"ConverrtedFilesDir", "char", NULL, "optional", NA_character_,
"ConverrtedFilesName", "char", NULL, "optional", NA_character_,
"SourceFileFolder", "char", NULL, "optional", NA_character_,
"SourceFileNameR1", "char", NULL, "optional", NA_character_,
"SourceFileNameR2", "char", NULL, "optional", NA_character_,
"DNAnumber", "char", NULL, "required", "dna_num",
"ReplicateNumber", "int", NULL, "required", "pcr_replicate",
"DNAextractionDate", "date", NULL, "optional", NA_character_,
"DNAngUsed", "numeric", NULL, "required", NA_character_,
"LinearPCRID", "char", NULL, "optional", NA_character_,
"LinearPCRDate", "date", NULL, "optional", NA_character_,
"SonicationDate", "date", NULL, "optional", NA_character_,
"LigationDate", "date", NULL, "optional", NA_character_,
"1stExpoPCRID", "char", NULL, "optional", NA_character_,
"1stExpoPCRDate", "date", NULL, "optional", NA_character_,
"2ndExpoID", "char", NULL, "optional", NA_character_,
"2ndExpoDate", "date", NULL, "optional", NA_character_,
"FusionPrimerPCRID", "char", NULL, "optional", NA_character_,
"FusionPrimerPCRDate", "date", NULL, "optional", NA_character_,
"PoolDate", "date", NULL, "optional", NA_character_,
"SequencingDate", "date", NULL, "required", NA_character_,
"VCN", "numeric", NULL, "required", "vcn",
"Genome", "char", NULL, "required", "genome",
"SequencingRound", "int", NULL, "optional", NA_character_,
"Genotype", "char", NULL, "optional", NA_character_,
"TestGroup", "char", NULL, "optional", NA_character_,
"MOI", "char", NULL, "optional", NA_character_,
"Engraftment", "numeric", NULL, "optional", NA_character_,
"Transduction", "numeric", NULL, "optional", NA_character_,
"Notes", "char", NULL, "optional", NA_character_,
"AddedField1", "char", NULL, "optional", NA_character_,
"AddedField2", "char", NULL, "optional", NA_character_,
"AddedField3", "char", NULL, "optional", NA_character_,
"AddedField4", "char", NULL, "optional", NA_character_,
"concatenatePoolIDSeqRun", "char", NULL, "required",
"vispa_concatenate",
"AddedField6_RelativeBloodPercentage", "char", NULL, "optional",
NA_character_,
"AddedField7_PurityTestFeasibility", "char", NULL, "optional",
NA_character_,
"AddedField8_FacsSeparationPurity", "char", NULL, "optional",
NA_character_,
"Kapa", "numeric", NULL, "required", NA_character_,
"ulForPool", "numeric", NULL, "required", NA_character_,
"CompleteAmplificationID", "char", NULL, "required", "pcr_repl_id",
"UniqueID", "char", NULL, "required", NA_character_,
"StudyTestID", "char", NULL, "optional", NA_character_,
"StudyTestGroup", "char", NULL, "optional", NA_character_,
"MouseID", "char", NULL, "optional", NA_character_,
"Tigroup", "char", NULL, "optional", NA_character_,
"Tisource", "char", NULL, "optional", NA_character_,
"PathToFolderProjectID", "char", NULL, "required", "proj_folder",
"SamplesNameCheck", "char", NULL, "optional", NA_character_,
"TimepointDays", "char", NULL, "optional", NA_character_,
"TimepointMonths", "char", NULL, "optional", NA_character_,
"TimepointYears", "char", NULL, "optional", NA_character_,
"ng DNA corrected", "numeric", NULL, "optional", NA_character_
)
|
5970a6c3 |
tibble::tribble(
~names, ~types, ~transform, ~flag, ~tag,
"RUN_NAME", "char", NULL, "required", NA_character_,
"POOL", "char", NULL, "required", "vispa_concatenate",
"TAG", "char", ~ stringr::str_replace_all(.x,
pattern = "\\.",
replacement = ""
), "required",
"tag_seq",
"RAW_READS", "int", NULL, "optional", NA_character_,
"QUALITY_PASSED", "int", NULL, "optional", NA_character_,
"PHIX_MAPPING", "int", NULL, "optional", NA_character_,
"PLASMID_MAPPED_BYPOOL", "int", NULL, "optional", NA_character_,
"BARCODE_MUX", "int", NULL, "required", NA_character_,
"LTR_IDENTIFIED", "int", NULL, "optional", NA_character_,
"TRIMMING_FINAL_LTRLC", "int", NULL, "optional", NA_character_,
"LV_MAPPED", "int", NULL, "optional", NA_character_,
"BWA_MAPPED_OVERALL", "int", NULL, "optional", NA_character_,
"ISS_MAPPED_OVERALL", "int", NULL, "optional", NA_character_,
"ISS_MAPPED_PP", "int", NULL, "optional", NA_character_
)
|
5970a6c3 |
tibble::tribble(
~types, ~mapping, ~fread,
"char", "c", "character",
"int", "i", "integer",
"logi", "l", "logical",
"numeric", "d", "numeric",
"factor", "f", "factor",
"date", "c", "charcter",
"ymd", "c", "character",
"ydm", "c", "character",
"mdy", "c", "character",
"myd", "c", "character",
"dmy", "c", "character",
"yq", "c", "character",
"ym", "c", "character",
"my", "c", "character",
"ymd_hms", "c", "character",
"ymd_hm", "c", "character",
"ymd_h", "c", "character",
"dmy_hms", "c", "character",
"dmy_hm", "c", "character",
"dmy_h", "c", "character",
"mdy_hms", "c", "character",
"mdy_hm", "c", "character",
"mdy_h", "c", "character",
"ydm_hms", "c", "character",
"ydm_hm", "c", "character",
"ydm_h", "c", "character"
)
|
5970a6c3 |
"vispa_concatenate", "tag_seq"
),
needed_in = list(
c(
"top_targeted_genes",
"CIS_grubbs",
"compute_near_integrations"
),
c(
"top_targeted_genes",
"CIS_grubbs",
"compute_near_integrations"
),
c(
"CIS_grubbs",
"compute_near_integrations"
),
c(
"top_targeted_genes",
"CIS_grubbs",
"compute_near_integrations",
"CIS_volcano_plot"
),
c(
"top_targeted_genes",
"CIS_grubbs"
),
c(
"generate_default_folder_structure",
"import_Vispa2_stats", "remove_collisions",
"generate_Vispa2_launch_AF", "import_association_file",
"import_parallel_Vispa2Matrices"
),
c(
"generate_Vispa2_launch_AF", "remove_collisions",
"import_association_file"
),
c("generate_Vispa2_launch_AF"),
c(
"generate_default_folder_structure",
"import_association_file", "import_Vispa2_stats"
),
c(
"import_association_file",
"HSC_population_size_estimate"
),
c("generate_Vispa2_launch_AF"),
c(
"generate_Vispa2_launch_AF", "import_association_file",
"HSC_population_size_estimate"
),
c("generate_Vispa2_launch_AF", "import_association_file"),
c(),
c(
"generate_Vispa2_launch_AF", "import_association_file",
"HSC_population_size_estimate"
),
c("generate_Vispa2_launch_AF"),
c(),
c(),
c("import_association_file", "remove_collisions"),
c(),
c(
"import_association_file", "generate_Vispa2_launch_AF",
"generate_default_folder_structure",
"import_Vispa2_stats", "import_parallel_Vispa2Matrices"
),
c(
"pcr_id_column", "generate_Vispa2_launch_AF",
"import_association_file", "import_Vispa2_stats"
),
c("import_association_file"),
c(),
c(
"import_association_file", "generate_Vispa2_launch_AF",
"generate_default_folder_structure",
"import_Vispa2_stats", "import_parallel_Vispa2Matrices"
),
c(
"generate_default_folder_structure",
"import_association_file", "import_Vispa2_stats"
)
),
description = c(
paste("Number of the chromosome"),
paste("The locus at which the integration occurs"),
paste("The DNA strand in which the integration occurs"),
paste("The symbol of the gene"),
paste("The strand of the gene"),
paste("Unique identifier of a project"),
paste("Unique identifier of a sequencing pool"),
paste(
"Identification code/number of the",
"barcoded (SLiM-)PCR product included in the",
"sequencing library"
),
paste("The barcode tag sequence"),
paste(
"Unique identifier of a study subject",
"(usually a patient)"
),
paste("Unique identifier of the vector used"),
paste("The biological tissue the sample belongs to"),
paste("The time point expressed in days"),
paste("The PCR method used"),
paste(
"Cell marker associated with isolated",
"cells carrying the IS"
),
paste(
"Unique identifier of the barcode tag, as specified",
"in VISPA2 requirements"
),
paste("Technology used for next generation sequencing"),
paste(
"Identification code/number of the DNA extraction",
"from a specific biological sample"
),
paste("Number of the PCR replicate"),
paste("Vector copy number"),
paste("Unique identifier of a pool as specified in VISPA2"),
paste(
"Unique identifier of the pcr replicate, used as",
"key to join data and metadata"
),
paste(
"Path on disk containing the standard VISPA2 folder",
"structure of the project"
),
paste("The reference genome (e.g. 'hg19')"),
paste("Unique identifier of a pool as specified in VISPA2"),
paste("The barcode tag sequence")
),
dyn_vars_tbl = c(
"mand_vars", "mand_vars", "mand_vars",
"annot_vars", "annot_vars",
"af_vars", "af_vars", "af_vars", "af_vars", "af_vars",
"af_vars", "af_vars", "af_vars", "af_vars", "af_vars",
"af_vars", "af_vars", "af_vars", "af_vars", "af_vars",
"af_vars", "af_vars", "af_vars", "af_vars",
"iss_vars", "iss_vars"
)
)
|