diff --git a/NAMESPACE b/NAMESPACE index 07871f65..84e65a2c 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -44,6 +44,7 @@ export(data_curator_app_subpage) export(delete_provenance) export(dsp_dataset_mapping) export(find_child) +export(find_child_type) export(find_data_root) export(find_in) export(find_nf_asset) @@ -61,6 +62,7 @@ export(make_folder) export(make_public) export(make_public_viewable) export(manifest_generate) +export(manifest_passed) export(manifest_validate) export(map_sample_input_ss) export(map_sample_io) @@ -75,9 +77,11 @@ export(nf_cnv_dataset) export(nf_sarek_datasets) export(nf_star_salmon_datasets) export(nf_workflow_version) +export(precheck_manifest) export(processing_flowchart) export(register_study) export(register_study_files) +export(remanifest) export(remove_button) export(remove_wiki_subpage) export(summarize_attribute) diff --git a/R/annotation_qc.R b/R/annotation_qc.R index 8aae41ec..6d6589d0 100644 --- a/R/annotation_qc.R +++ b/R/annotation_qc.R @@ -133,7 +133,7 @@ tersely <- function(error) { #' @param result Result list data from schematic service. #' @returns Boolean for whether passed. #' @returns List of structure `list(result = result, notes = notes)`, where `result` indicates whether the dataset passed. -#' @keywords internal +#' @export manifest_passed <- function(result) { errors <- length(result$errors) @@ -280,26 +280,104 @@ meta_qc_project <- function(project_id, result_file = NULL, ...) { } + #' List datasets in project #' -#' Return a list of dataset folders if they are in expected location in project, otherwise NULL w/ explanatory message. +#' Return a list of datasets. Datasets can be folders in the expected location in the project or actual dataset entities. +#' Note that dataset-folders will always be what exists first in the project, as sort of the dataset precursor. +#' The files in dataset-folders can be translated to dataset entities later. +#' When not found, will return NULL w/ explanatory message. #' #' @inheritParams find_data_root +#' @param type Whether to list datasets as immediate folders under "Raw Data" root (default, see details) or actual dataset entities in the project. #' @export -list_project_datasets <- function(project_id) { +list_project_datasets <- function(project_id, + type = c("folder", "dataset")) { - data_root <- find_data_root(project_id) - if(is.null(data_root)) { + type <- match.arg(type) + if(type == "folder") { + data_root <- find_data_root(project_id) + if(is.null(data_root)) { - warning("Data root could not be located.") - return() + warning("Data root could not be located.") + return() - } else { + } else { - in_data <- .syn$getChildren(data_root) - in_data <- reticulate::iterate(in_data) - datasets <- Filter(function(x) x$type == "org.sagebionetworks.repo.model.Folder", in_data) - if(!length(datasets)) warning("No datasets found under data root.") + in_data <- .syn$getChildren(data_root) + in_data <- reticulate::iterate(in_data) + datasets <- Filter(function(x) x$type == "org.sagebionetworks.repo.model.Folder", in_data) + if(!length(datasets)) warning("No datasets found under data root.") + datasets + } + } else { + children <- .syn$getChildren(project_id) + datasets <- reticulate::iterate(children) + datasets <- Filter(function(x) x$type == "org.sagebionetworks.repo.model.table.Dataset", datasets) + if(!length(datasets)) warning("No dataset entities found in project.") datasets } } + +#' Precheck a manifest +#' +#' Precheck before sending manifest off to schematic validation service. +#' Provides additional context and helpful recommendations. +#' +#' @param manifest_csv Path to manifest_csv. +#' @param official_props (Optional) Doc listing official model attributes. Currently this requires the LinkML format. +#' @export +precheck_manifest <- function(manifest_csv, + official_props = "https://raw.githubusercontent.com/nf-osi/nf-metadata-dictionary/main/modules/props.yaml") { + + manifest <- fread(manifest_csv) + attributes <- names(manifest) + + #-- ERRORS --# + if(!"Component" %in% attributes) { + message(glue::glue()) + } else { + unique_components <- unique(manifest$Component) + if(length(unique_components) > 1) { + which_components <- glue::glue_collapse(shQuote(unique_components), ", ") + message(glue::glue("{emoji::emoji('x')} Multiple components detected in a single manifest: {which_components}. This can happen when files were annotated at different eras. + Suggestions: 1) Split up the manifest because schematic can only validate one type at a type. 2) Harmonize the components if this is sensible. + For example, RNASeqTemplate is an alias for GenomicsAssayTemplate")) + } + + if("" %in% unique_components) { + message(glue::glue("{emoji::emoji('x')} Blank value '' for Component detected. This can happen because files were annotated before 2022, when Component was introduced for most DCCs.")) + } + + } + + # Duplicate columns like age..1 etc. + likely_dups <- grep("[.][0-9]+", attributes, value = TRUE) + if(length(likely_dups)) { + likely_dups <- glue::glue_collapse(shQuote(likely_dups), ", ") + message(glue::glue("{emoji::emoji('x')} The pattern of these attribute names suggest duplicates: {likely_dups}. This may happen when metadata is supplemented programmatically with a data-type mismatch")) + } + + #-- WARNINGS --# + # These technically don't break present-day schematic revalidation but should be cleaned up; many are from earlier schematic issues. + + # See https://sagebionetworks.slack.com/archives/C01ANC02U59/p1681418154850589 + if("Uuid" %in% attributes) { + message(crayon::yellow(glue::glue("{emoji::emoji('warning')} An attribute `Uuid` is present and should preferably be removed."))) + } + + # See https://github.com/Sage-Bionetworks/schematic/issues/476#issuecomment-848853193 + if("eTag" %in% attributes) { + message(crayon::yellow(glue::glue("{emoji::emoji('warning')} An attribute `eTag` is present and preferably be removed."))) + } + + #-- INFO only --# + if(!is.null(official_props)) props <- names(yaml::read_yaml(official_props)$slots) + custom_attributes <- setdiff(attributes, props) + if(length(custom_attributes)) { + custom_attributes <- glue::glue_collapse(shQuote(custom_attributes), ", ") + message(crayon::blue(glue::glue("{emoji::emoji('information')} Custom attributes (not documented in data model) were found: {custom_attributes}. In general, custom attributes added by the researcher to help with data management are fine. + Just check that they are not PHI or added by mistake. If they are deemed generally useful or important enough, they can also be documented officially in the data model for others to reference."))) + } + +} diff --git a/R/find.R b/R/find.R index c9a928db..6cd91eb8 100644 --- a/R/find.R +++ b/R/find.R @@ -1,15 +1,15 @@ # Utils to help overcome nested folders #' Find in path -#' +#' #' Get the Synapse id of an entity nested several folder layers deep without #' having to click through the UI or create a fileview as long as the structure/path is known. -#' +#' #' @param scope Id of the container (project or folder) to begin search. #' @param path Path string in format "subdir1/subdir2/file.txt", where the last-level element will be the id returned. #' @export find_in <- function(scope, path) { - + path_list <- strsplit(path, split = "/", fixed = TRUE)[[1]] here <- scope id <- NULL @@ -28,11 +28,11 @@ find_in <- function(scope, path) { #' @param child_name Name of child entity. #' @export find_child <- function(child_name, parent) { - + q <- .syn$getChildren(parent) child_id <- NULL repeat { - x <- reticulate::iter_next(q) + x <- reticulate::iter_next(q) if(is.null(x) || x$name == child_name) { child_id <- x$id break @@ -41,18 +41,37 @@ find_child <- function(child_name, parent) { child_id } + +#' Find children of type +#' +#' Small utility like`find_child` but retrieves files by type rather than by specific name. +#' Returns a vector of ids, with entity names set as names. +#' +#' @inheritParams find_child +#' @param child_type Type(s) as a list, even for only one type. Defaults to "file". +#' @export +find_child_type <- function(parent, child_type = list("file")) { + + x <- .syn$getChildren(parent, includeTypes = child_type) + y <- reticulate::iterate(x) + if(!length(y)) return() + z <- setNames(sapply(y, `[[`, "id"), sapply(y, `[[`, "name")) + return(z) +} + + #' Find data folder -#' +#' #' Convenience function to find data folder, which can have slight name variations, in a project. -#' +#' #' @param project_id Synapse project id. #' @export find_data_root <- function(project_id) { - + data_root <- find_child("Data", parent = project_id) if(is.null(data_root)) data_root <- find_child("Raw Data", parent = project_id) data_root -} +} # Find nextflow assets --------------------------------------------------------- # @@ -60,21 +79,21 @@ find_data_root <- function(project_id) { # Convenience functions for getting Synapse ids of nextflow assets #' Find a standard nextflow workflow output asset -#' +#' #' Note that samplesheets became part of the output only for newer versions of nf-core/rna-seq; -#' older runs may not find samplesheets. -#' Paths default to known working paths corresponding to the latest major workflow version, -#' but this may change and may need to be updated as part of util maintenance. -#' +#' older runs may not find samplesheets. +#' Paths default to known working paths corresponding to the latest major workflow version, +#' but this may change and may need to be updated as part of util maintenance. +#' #' @param syn_out Id of top-level folder that corresponds to `publishDir` in a nextflow workflow. #' @param asset Name of asset to find. #' @param workflow Specify workflow, "rna-seq" or "sarek"; defaults to "rna-seq" -#' @returns Id of samplesheet. +#' @returns Id of samplesheet. #' @export -find_nf_asset <- function(syn_out, +find_nf_asset <- function(syn_out, asset = c("software_versions", "multiqc_report", "samplesheet", "samtools_stats"), workflow = "rna-seq") { - + asset <- match.arg(asset) # Assets and paths can differ slightly depending on workflow, except for `software_versions.yml`, get workflow first if(workflow == "rna-seq") { @@ -93,7 +112,7 @@ find_nf_asset <- function(syn_out, } else { stop("Unrecognized workflow.") } - + id <- find_in(syn_out, path) if(is.null(id)) stop("File not found. Is this the right output directory/path?") id @@ -101,12 +120,12 @@ find_nf_asset <- function(syn_out, #' Return workflow version according to workflow meta -#' +#' #' @inheritParams find_nf_asset -#' @returns Version string. +#' @returns Version string. #' @export nf_workflow_version <- function(syn_out) { - + version_meta <- find_nf_asset(syn_out, asset = "software_versions") file <- .syn$get(version_meta, downloadFile = TRUE) yml <- yaml::read_yaml(file$path) diff --git a/R/remanifest.R b/R/remanifest.R new file mode 100644 index 00000000..9391ec2d --- /dev/null +++ b/R/remanifest.R @@ -0,0 +1,108 @@ +#' Reconstitute a manifest +#' +#' Quickly "reconstitute" a manifest for files with existing annotations. +#' This is a *power-user* alternative to schematic's `manifest_generate` with option `useAnnotations = TRUE` for certain scenarios: +#' +#' - Meant to be faster and more convenient for workflows focused on scalable/programmatic annotation/revalidation. +#' Convenience and speed mainly comes from bypassing the schematic API layer and using the Synapse API directly, +#' so manifest is reconstituted directly as R `data.table` **instead of having to download a Googlesheets or Excel intermediate**. +#' **The result `.csv` is still intended to be schematic-compatible for validation via `manifest_validate`**. +#' +#' - Works with both a Synapse dataset entity as well as a folder; +#' schematic currently only handles the latter (the folder concept predates Synapse datasets). +#' +#' - If folder-scoped, can choose between generating manifest with just immediate files *or*, like schematic, nested files. +#' This is useful, for example, if the main scope folder is "RNA-seq" and the main files are fastqs, but there is a child folder called "md5" with md5 files, +#' and the manifest is really meant for the fastqs. +#' +#' - Does not try to download `synapse_manifest.csv`, which can be useful to regenerate a manifest when ARs have been set. +#' +#' - Does not require an asset view. +#' +#' Other developer notes: +#' See also `gather_annotations` for the under-the-hood workhorse. +#' Intended for further development to be used as part of advanced annotation utils. +#' +#' @param scope Synapse id of something representing one or more datasets. Can be a folder *or* Synapse dataset entity. +#' @param file Name of file to be written. Use `NULL` to return the `data.table` instead of writing to file. +#' @param recurse Include everything nested within folder scope, default `TRUE`, or only the immediate files. +#' Not used if dataset is Synapse dataset entity. +#' @param mf Intermediate manifest to build upon; used when recursive. +#' @import data.table +#' @export +remanifest <- function(scope, + file = "manifest.csv", + recurse = TRUE, + mf = data.table()) { + + dataset <- .syn$get(scope[1]) + if(dataset$properties$concreteType == "org.sagebionetworks.repo.model.table.Dataset") { + + dataset_items <- sapply(dataset$properties$datasetItems, `[[`, "entityId") + if(!length(dataset_items)) { + + return(data.table()) + + } else { + + manifest <- gather_annotations(dataset_items) + if(!is.null(file)) save_manifest(manifest, file) else manifest + + } + + } else if(dataset$properties$concreteType == "org.sagebionetworks.repo.model.Folder") { + + files <- find_child_type(scope[1]) + if(length(files)) { + ids <- files + manifest <- gather_annotations(ids) + } else { + manifest <- data.table() + } + + if(recurse) { + more <- find_child_type(scope[1], list("folder")) + scope <- c(scope[-1], more) + if(!length(scope)) { + manifest <- rbind(mf, manifest, fill = T) + if(!is.null(file)) save_manifest(manifest, file) else manifest + } else { + remanifest(scope = scope, + recurse = recurse, + mf = rbind(mf, manifest, fill = T)) + } + } else { + if(!is.null(file)) save_manifest(manifest, file) else manifest + } + + } else { + + "Dataset is only accepted as a folder or dataset entity. Please check the id used." + + } +} + +#' Internal helper for gathering annotations into a table using the REST API +#' +#' This is an internal implementation that works directly with the platform service JSON +#' to afford more low-level control and avoid Python-R object conversion differences between reticulate versions. +#' +#' @param ids One or more ids. +#' @param list_sep List separator for list annotations. +#' @keywords internal +gather_annotations <- function(ids, list_sep = ", ") { + results <- lapply(ids, function(id) .syn$restGET(glue::glue("https://repo-prod.prod.sagebase.org/repo/v1/entity/{id}/annotations2"))) + annotations <- lapply(results, function(x) c(list(entityId = list(value = x$id)), x$annotations)) + annotations <- lapply(annotations, function(x) lapply(x, function(col) paste(col$value, collapse = list_sep))) + manifest <- data.table::rbindlist(annotations, fill = TRUE) + manifest +} + + +#' Save manifest +#' +#' @keywords internal +save_manifest <- function(manifest, file) { + fwrite(manifest, file = file) + checked_message(glue::glue("Saved manifest as {file}")) +} diff --git a/_pkgdown.yml b/_pkgdown.yml index fc12b754..5b37ee74 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -40,6 +40,9 @@ reference: - meta_qc_project - manifest_generate - manifest_validate + - manifest_passed + - precheck_manifest + - remanifest - infer_data_type - subtitle: Special annotation of nextflow processed data desc: Special annotation of nextflow processed data diff --git a/man/find_child_type.Rd b/man/find_child_type.Rd new file mode 100644 index 00000000..b4088381 --- /dev/null +++ b/man/find_child_type.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/find.R +\name{find_child_type} +\alias{find_child_type} +\title{Find children of type} +\usage{ +find_child_type(parent, child_type = list("file")) +} +\arguments{ +\item{parent}{Parent container (project or folder).} + +\item{child_type}{Type(s) as a list, even for only one type. Defaults to "file".} +} +\description{ +Small utility like\code{find_child} but retrieves files by type rather than by specific name. +Returns a vector of ids, with entity names set as names. +} diff --git a/man/gather_annotations.Rd b/man/gather_annotations.Rd new file mode 100644 index 00000000..780af711 --- /dev/null +++ b/man/gather_annotations.Rd @@ -0,0 +1,18 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/remanifest.R +\name{gather_annotations} +\alias{gather_annotations} +\title{Internal helper for gathering annotations into a table using the REST API} +\usage{ +gather_annotations(ids, list_sep = ", ") +} +\arguments{ +\item{ids}{One or more ids.} + +\item{list_sep}{List separator for list annotations.} +} +\description{ +This is an internal implementation that works directly with the platform service JSON +to afford more low-level control and avoid Python-R object conversion differences between reticulate versions. +} +\keyword{internal} diff --git a/man/list_project_datasets.Rd b/man/list_project_datasets.Rd index c0c7e374..6bcc4f2c 100644 --- a/man/list_project_datasets.Rd +++ b/man/list_project_datasets.Rd @@ -4,11 +4,16 @@ \alias{list_project_datasets} \title{List datasets in project} \usage{ -list_project_datasets(project_id) +list_project_datasets(project_id, type = c("folder", "dataset")) } \arguments{ \item{project_id}{Synapse project id.} + +\item{type}{Whether to list datasets as immediate folders under "Raw Data" root (default, see details) or actual dataset entities in the project.} } \description{ -Return a list of dataset folders if they are in expected location in project, otherwise NULL w/ explanatory message. +Return a list of datasets. Datasets can be folders in the expected location in the project or actual dataset entities. +Note that dataset-folders will always be what exists first in the project, as sort of the dataset precursor. +The files in dataset-folders can be translated to dataset entities later. +When not found, will return NULL w/ explanatory message. } diff --git a/man/manifest_passed.Rd b/man/manifest_passed.Rd index 05ed526b..faf05ab0 100644 --- a/man/manifest_passed.Rd +++ b/man/manifest_passed.Rd @@ -17,4 +17,3 @@ List of structure \code{list(result = result, notes = notes)}, where \code{resul \description{ Provide a pass/fail summary result } -\keyword{internal} diff --git a/man/precheck_manifest.Rd b/man/precheck_manifest.Rd new file mode 100644 index 00000000..71c319f2 --- /dev/null +++ b/man/precheck_manifest.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/annotation_qc.R +\name{precheck_manifest} +\alias{precheck_manifest} +\title{Precheck a manifest} +\usage{ +precheck_manifest( + manifest_csv, + official_props = + "https://raw.githubusercontent.com/nf-osi/nf-metadata-dictionary/main/modules/props.yaml" +) +} +\arguments{ +\item{manifest_csv}{Path to manifest_csv.} + +\item{official_props}{(Optional) Doc listing official model attributes. Currently this requires the LinkML format.} +} +\description{ +Precheck before sending manifest off to schematic validation service. +Provides additional context and helpful recommendations. +} diff --git a/man/remanifest.Rd b/man/remanifest.Rd new file mode 100644 index 00000000..9d7c84cf --- /dev/null +++ b/man/remanifest.Rd @@ -0,0 +1,41 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/remanifest.R +\name{remanifest} +\alias{remanifest} +\title{Reconstitute a manifest} +\usage{ +remanifest(scope, file = "manifest.csv", recurse = TRUE, mf = data.table()) +} +\arguments{ +\item{scope}{Synapse id of something representing one or more datasets. Can be a folder \emph{or} Synapse dataset entity.} + +\item{file}{Name of file to be written. Use \code{NULL} to return the \code{data.table} instead of writing to file.} + +\item{recurse}{Include everything nested within folder scope, default \code{TRUE}, or only the immediate files. +Not used if dataset is Synapse dataset entity.} + +\item{mf}{Intermediate manifest to build upon; used when recursive.} +} +\description{ +Quickly "reconstitute" a manifest for files with existing annotations. +This is a \emph{power-user} alternative to schematic's \code{manifest_generate} with option \code{useAnnotations = TRUE} for certain scenarios: +} +\details{ +\itemize{ +\item Meant to be faster and more convenient for workflows focused on scalable/programmatic annotation/revalidation. +Convenience and speed mainly comes from bypassing the schematic API layer and using the Synapse API directly, +so manifest is reconstituted directly as R \code{data.table} \strong{instead of having to download a Googlesheets or Excel intermediate}. +\strong{The result \code{.csv} is still intended to be schematic-compatible for validation via \code{manifest_validate}}. +\item Works with both a Synapse dataset entity as well as a folder; +schematic currently only handles the latter (the folder concept predates Synapse datasets). +\item If folder-scoped, can choose between generating manifest with just immediate files \emph{or}, like schematic, nested files. +This is useful, for example, if the main scope folder is "RNA-seq" and the main files are fastqs, but there is a child folder called "md5" with md5 files, +and the manifest is really meant for the fastqs. +\item Does not try to download \code{synapse_manifest.csv}, which can be useful to regenerate a manifest when ARs have been set. +\item Does not require an asset view. +} + +Other developer notes: +See also \code{gather_annotations} for the under-the-hood workhorse. +Intended for further development to be used as part of advanced annotation utils. +} diff --git a/man/save_manifest.Rd b/man/save_manifest.Rd new file mode 100644 index 00000000..9d233491 --- /dev/null +++ b/man/save_manifest.Rd @@ -0,0 +1,12 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/remanifest.R +\name{save_manifest} +\alias{save_manifest} +\title{Save manifest} +\usage{ +save_manifest(manifest, file) +} +\description{ +Save manifest +} +\keyword{internal} diff --git a/vignettes/.gitignore b/vignettes/.gitignore index 097b2416..5f844791 100644 --- a/vignettes/.gitignore +++ b/vignettes/.gitignore @@ -1,2 +1,3 @@ *.html *.R +*cache diff --git a/vignettes/manifest_rd1.csv b/vignettes/manifest_rd1.csv new file mode 100644 index 00000000..abce6a04 --- /dev/null +++ b/vignettes/manifest_rd1.csv @@ -0,0 +1,581 @@ +entityId,age,sex,...1,Uuid,assay,DNA_ID,RNA_ID,tissue,ageUnit,runType,species,studyId,bodyPart,dataType,entityId,readPair,Component,aliquotID,diagnosis,studyName,tumorType,fileFormat,initiative,isCellLine,isStranded,readLength,specimenID,dataSubtype,libraryPrep,individualID,resourceType,fundingAgency,parentSpecimenID,parentSpecimenId,nucleicAcidSource,progressReportNumber,experimentalCondition,specimenPreparationMethod,eTag,organ,cellType,comments,platform,readDepth,nf1Genotype,nf2Genotype,isPrimaryCell,modelSystemName,readStrandOrigin,dissociationMethod,readPairOrientation,genePerturbationType,libraryPreparationMethod,transplantationRecipientSpecies,...44,...46,accessTeam,accessType,sciDataRelease,isMultiSpecimen,specimenIdSource,isMultiIndividual,individualIdSource,timePointUnit,transplantationType,transplantationDonorTissue,transplantationDonorSpecies,transplantationRecipientTissue +syn47905003,24.0,Male,49,0fc6df60-dfd2-4087-8b78-d6998b578dcb,RNA-seq,146_D13,146_R13,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left flank,raw counts,syn47905003,1,RNASeqTemplate,7464G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-E79BF,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_DifNF_PT_left_flank,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47996391,37.0,Male,75,7b63e3cf-af31-4eed-bdc1-fdccc401373b,RNA-seq,038_D18,038_R18,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right lateral shoulder,raw counts,syn47996391,1,RNASeqTemplate,E6D5A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-9AHHB,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_lateral_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47899382,55.0,Female,40,9199eacb-bc7b-47ec-ac8e-05688a445e94,RNA-seq,117_D23,117_R23,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right back,raw counts,syn47899382,2,RNASeqTemplate,C4H9E,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-117-D3BH9,raw,rRNAdepletion,JH-2-117,experimentalData,NTAP,JH-2-117_MPNST_PT_right_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47908215,24.0,Male,56,3aa46ea4-6f45-4ee3-9754-34527fcdf685,RNA-seq,146_D33,146_R33,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,head,raw counts,syn47908215,2,RNASeqTemplate,747GF,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-9GAD9,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_head,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47907864,24.0,Male,55,32d130c2-a8ae-4c21-b2c6-46f7a139fc97,RNA-seq,146_D33,146_R33,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,head,raw counts,syn47907864,1,RNASeqTemplate,747GF,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-9GAD9,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_head,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569880,33.0,Female,,5d7a85eb-6efe-4e32-bb57-a1845791bc9d,RNA-seq,,,cell line,years,pairedEnd,Homo sapiens,syn4939902,Left Thigh,geneExpression,syn23569880,2,GenomicsAssayTemplate,8GCFH,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,Yes,Yes,151,JH-2-077-4H749,raw,polyAselection,JH-2-077,experimentalData,NTAP,JH-2-077_PN_PT,"",bulk cell,"",WU_batch1,Viably frozen,e4f446d1-0c47-4030-90d2-2c3a0d74fd56,"","",Left Thigh,Illumina NovaSeq 6000,36M_read pairs,-/-,"",No,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47887173,24.0,Male,21,2b63989e-b6cd-47b4-afd2-be12d303ac33,RNA-seq,146_D34,146_R34,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,abdomen,raw counts,syn47887173,1,RNASeqTemplate,9FFF3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-D6FBB,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_abdomen,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn43707239,12.0,Male,3,2c98783d-8ee1-43e3-93cf-e7ed54ebc975,RNA-seq,,,primary tumor,,pairedEnd,Homo sapiens,syn4939902,Retroperitoneal,raw counts,syn43707239,2,RNASeqTemplate,DG6C8,,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,,Open Proposal Program,No,Yes,,JH-2-031-BFF3F,,rRNAdepletion,JH-2-031,experimentalData,NTAP,JH-2-031_MPNST_PT,"",,,WU_PDX_batch1,Flash frozen,,,,,,,,,No,,,,fr-firststrand,,TruSeq standard total RNA library kit,,3,3,,,,,,,,,,,, +syn47907611,24.0,Male,54,9968461c-7bab-491c-a17a-a26200de4ca5,RNA-seq,146_D33,146_R33,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,head,raw counts,syn47907611,2,RNASeqTemplate,747GF,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-9GAD9,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_head,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47906435,24.0,Male,53,d350df55-8515-4129-8831-26842bb18641,RNA-seq,146_D33,146_R33,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,head,raw counts,syn47906435,1,RNASeqTemplate,747GF,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-9GAD9,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_head,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569870,9.0,Female,,7d43bd5c-c1a1-46c8-8e3b-729447a6c5e7,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Groin,geneExpression,syn23569870,1,GenomicsAssayTemplate,AB35D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-061-1H66H,raw,polyAselection,JH-2-061,experimentalData,NTAP,JH-2-061_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,35de98e8-457d-4922-870e-8722502da370,"","",Right Groin,Illumina NovaSeq 6000,38M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47897283,17.0,Female,36,487a578b-f36d-47c4-a533-9423b979ad93,RNA-seq,125_D30,125_R30,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn47897283,2,RNASeqTemplate,DCE65,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-125-ADE77,raw,rRNAdepletion,JH-2-125,experimentalData,NTAP,JH-2-125_PN_PT_right_flank,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569881,20.0,Male,,50f910a4-19cf-41d9-906b-2af4a6bfcd9e,RNA-seq,,,cell line,years,pairedEnd,Homo sapiens,syn4939902,From 2-060-7,geneExpression,syn23569881,1,GenomicsAssayTemplate,GG71G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-060-99B2D,raw,polyAselection,JH-2-060,experimentalData,NTAP,JH-2-060_PN_CL,"",bulk cell,"",WU_batch1,Flash frozen,d6f33ead-6310-4915-a034-193df850181b,"","",From 2-060-7,Illumina NovaSeq 6000,31M_read pairs,-/-,"",No,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47908536,24.0,Male,57,b8e9de78-b556-422b-a972-ee9cecc12e56,RNA-seq,146_D14,146_R14,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,forehead,raw counts,syn47908536,1,RNASeqTemplate,935AE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-38B3A,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_forehead,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47888593,24.0,Male,24,91726c86-c322-4b31-8506-8d747a0ce4ac,RNA-seq,146_D34,146_R34,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,abdomen,raw counts,syn47888593,2,RNASeqTemplate,9FFF3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-D6FBB,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_abdomen,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47997020,37.0,Male,77,05e29389-e185-420e-9cf5-469e40a58508,RNA-seq,038_D19,038_R19,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right center shoulder,raw counts,syn47997020,1,RNASeqTemplate,2AFB3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-G3H41,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_center_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47877362,37.0,Male,3,d9d284d6-794c-45a5-895b-f08b52752afb,RNA-seq,038_D1,038_R1,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right medial shoulder,raw counts,syn47877362,1,RNASeqTemplate,7AC45,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-EF4H5,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_medial_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47909658,24.0,Male,59,34839e39-2935-4ac9-975b-73774258dd26,RNA-seq,146_D14,146_R14,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,forehead,raw counts,syn47909658,1,RNASeqTemplate,935AE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-38B3A,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_forehead,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47999352,37.0,Male,80,19c1c8dd-9528-4efa-835b-9d81f27e7614,RNA-seq,038_D19,038_R19,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right center shoulder,raw counts,syn47999352,2,RNASeqTemplate,2AFB3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-G3H41,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_center_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn43706239,24.0,Male,7,695afcce-7e3d-4b41-b517-e8c3d4f84c32,RNA-seq,,,primary tumor,,pairedEnd,Homo sapiens,syn4939902,left paraspinal Tumor,raw counts,syn43706239,2,RNASeqTemplate,622H1,,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,,Open Proposal Program,No,Yes,,JH-2-023-876HC,,rRNAdepletion,JH-2-023,experimentalData,NTAP,JH-2-023_MPNST_PT,"",,,WU_PDX_batch1,Flash frozen,,,,,,,,,No,,,,fr-firststrand,,TruSeq standard total RNA library kit,,7,7,,,,,,,,,,,, +syn15269094,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15269094,2,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47903630,19.0,Female,48,58f6f8e4-cd95-4ee2-b6b4-3fe4d8e0da8d,RNA-seq,079_D20,079_R20,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,left leg below knee,raw counts,syn47903630,2,RNASeqTemplate,22CC8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-079-HBHGH,raw,rRNAdepletion,JH-2-079,experimentalData,NTAP,JH-2-079-d_MPNST_RT_left_leg_below_knee,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47895183,17.0,Female,34,7fbe35f5-88e2-4cfe-80db-70b4491bd136,RNA-seq,125_D30,125_R30,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn47895183,2,RNASeqTemplate,DCE65,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-125-ADE77,raw,rRNAdepletion,JH-2-125,experimentalData,NTAP,JH-2-125_PN_PT_right_flank,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569860,5.0,Male,,c2a26330-6c49-4c06-afc5-62b92685abf1,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Leg Above Knee,geneExpression,syn23569860,1,GenomicsAssayTemplate,EG55A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,Yes,151,JH-2-082-G8357,raw,polyAselection,JH-2-082,experimentalData,NTAP,JH-2-082_MPNST_PT,"",bulk cell,"",WU_batch1,Flash frozen,2d918984-8b1e-4965-bc78-960a64de298b,"","",Leg Above Knee,Illumina NovaSeq 6000,40M_read pairs,-/-,"",No,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn23569871,9.0,Female,,386ae4e7-940f-4b92-92ed-06e18459011a,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Groin,geneExpression,syn23569871,2,GenomicsAssayTemplate,AB35D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-061-1H66H,raw,polyAselection,JH-2-061,experimentalData,NTAP,JH-2-061_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,5ac3d6ee-a38a-4ebc-ac78-858e419e162a,"","",Right Groin,Illumina NovaSeq 6000,38M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47885184,40.0,Male,17,5dd5aaf4-c0d7-445d-85e4-20dc1de8d755,RNA-seq,119_D7,119_R7,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left brachial plexus,raw counts,syn47885184,1,RNASeqTemplate,C4D86,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-119-A3F2H,raw,rRNAdepletion,JH-2-119,experimentalData,NTAP,JH-2-119_MPNST_PT_left_brachial_plexus,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569882,20.0,Male,,2a3cbda1-55fe-48f3-ae49-5f7e40a19acc,RNA-seq,,,cell line,years,pairedEnd,Homo sapiens,syn4939902,From 2-060-7,geneExpression,syn23569882,2,GenomicsAssayTemplate,GG71G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-060-99B2D,raw,polyAselection,JH-2-060,experimentalData,NTAP,JH-2-060_PN_CL,"",bulk cell,"",WU_batch1,Flash frozen,d297ed81-ddef-4d04-a20a-4d81c2fb1e77,"","",From 2-060-7,Illumina NovaSeq 6000,31M_read pairs,-/-,"",No,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn43706526,24.0,Male,8,9bce904b-5afa-415b-a666-6216cd847ad5,RNA-seq,,,primary tumor,,pairedEnd,Homo sapiens,syn4939902,left paraspinal Tumor,raw counts,syn43706526,2,RNASeqTemplate,622H1,,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,,Open Proposal Program,No,Yes,,JH-2-023-876HC,,rRNAdepletion,JH-2-023,experimentalData,NTAP,JH-2-023_MPNST_PT,"",,,WU_PDX_batch1,Flash frozen,,,,,,,,,No,,,,fr-firststrand,,TruSeq standard total RNA library kit,,8,8,,,,,,,,,,,, +syn47910088,46.0,Male,61,b8bfdfae-28ac-4da1-83d6-7a5f47e08b9a,RNA-seq,012_D16,012_R16,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,L5 Paravertebral Mass,raw counts,syn47910088,1,RNASeqTemplate,4H93H,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-012-2325A,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,JH-2-012-b_MPNST_RT_L5_Paravertebral_Mass,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47909935,24.0,Male,60,f5ba50fc-aaf8-4950-b96b-27a8818bb2da,RNA-seq,146_D14,146_R14,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,forehead,raw counts,syn47909935,2,RNASeqTemplate,935AE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-38B3A,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_forehead,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569861,5.0,Male,,1d470b4d-d59c-48a3-be69-80926d4152bd,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Leg Above Knee,geneExpression,syn23569861,2,GenomicsAssayTemplate,EG55A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,Yes,151,JH-2-082-G8357,raw,polyAselection,JH-2-082,experimentalData,NTAP,JH-2-082_MPNST_PT,"",bulk cell,"",WU_batch1,Flash frozen,467b965e-2d9c-4e5f-9426-cb49ec905d01,"","",Leg Above Knee,Illumina NovaSeq 6000,40M_read pairs,-/-,"",No,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn23569872,10.0,Female,,e55b6944-9c49-4cb1-947e-dd4383771419,RNA-seq,,,xenograft passage,years,pairedEnd,Homo sapiens,syn4939902,Scalp,geneExpression,syn23569872,1,GenomicsAssayTemplate,6G883,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,Yes,151,JH-2-055-9F5F3,raw,polyAselection,JH-2-055,experimentalData,NTAP,JH-2-055-b_MPNST_Xeno,"",bulk cell,"",WU_batch1,Viably frozen,1ace1f28-7c24-4d0a-8955-37484b2d174f,"","",Scalp,Illumina NovaSeq 6000,41M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn15264091,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15264091,2,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47902763,19.0,Female,46,55c59f04-04a8-4814-9a64-d593567815cb,RNA-seq,079_D20,079_R20,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,left leg below knee,raw counts,syn47902763,2,RNASeqTemplate,22CC8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-079-HBHGH,raw,rRNAdepletion,JH-2-079,experimentalData,NTAP,JH-2-079-d_MPNST_RT_left_leg_below_knee,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47902389,21.0,Male,44,ee4a9788-1849-411f-8249-042eb5778bf0,RNA-seq,138_D10,138_R10,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left sciatic nerve,raw counts,syn47902389,2,RNASeqTemplate,CG64A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Atypical Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-138-A225B,raw,rRNAdepletion,JH-2-138,experimentalData,NTAP,JH-2-138_AtyNF_PT_left_sciatic_nerve,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47886242,40.0,Male,20,30479f78-f761-4844-b3a1-bf209bd1a59c,RNA-seq,119_D7,119_R7,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left brachial plexus,raw counts,syn47886242,2,RNASeqTemplate,C4D86,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-119-A3F2H,raw,rRNAdepletion,JH-2-119,experimentalData,NTAP,JH-2-119_MPNST_PT_left_brachial_plexus,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47997331,37.0,Male,78,dadfdcaf-f049-4d89-8a28-c1fd9cda6b38,RNA-seq,038_D19,038_R19,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right center shoulder,raw counts,syn47997331,2,RNASeqTemplate,2AFB3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-G3H41,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_center_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569862,35.0,Female,,64bde58e-fc1a-40d3-b658-fa19b077c3ce,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Thigh,geneExpression,syn23569862,1,GenomicsAssayTemplate,GA258,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-044-83F15,raw,polyAselection,JH-2-044,experimentalData,NTAP,JH-2-044_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,8b4cdbbd-b422-4907-aab4-2d15c97250f8,"","",Left Thigh,Illumina NovaSeq 6000,36M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn23569873,10.0,Female,,3927a75c-9aae-430a-91a0-3e43a148a917,RNA-seq,,,xenograft passage,years,pairedEnd,Homo sapiens,syn4939902,Scalp,geneExpression,syn23569873,2,GenomicsAssayTemplate,6G883,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,Yes,151,JH-2-055-9F5F3,raw,polyAselection,JH-2-055,experimentalData,NTAP,JH-2-055-b_MPNST_Xeno,"",bulk cell,"",WU_batch1,Viably frozen,941b6e9b-d821-416d-a60f-610cf2d484f5,"","",Scalp,Illumina NovaSeq 6000,41M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn23569884,16.0,Male,,46ef1b6b-9aa3-4584-a82b-14ffdca56e2d,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Liver,geneExpression,syn23569884,1,GenomicsAssayTemplate,B6471,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-084-AE169,raw,polyAselection,JH-2-084,experimentalData,NTAP,JH-2-084_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,f21c9ee1-84fd-46d3-8de1-c3b9a7acda34,"","",Right Liver,Illumina NovaSeq 6000,40M_read pairs,+/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn43705989,10.0,Male,2,6b6bfd9a-3839-4cdd-aea3-0ca719d1f57d,RNA-seq,,,primary tumor,,pairedEnd,Homo sapiens,syn4939902,Left Pelvic Mass,raw counts,syn43705989,2,RNASeqTemplate,19DGB,,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,,Open Proposal Program,No,Yes,,JH-2-002-94FAA,,rRNAdepletion,JH-2-002,experimentalData,NTAP,JH-2-002_MPNST_PT,"",,,WU_PDX_batch1,Flash frozen,,,,,,,,,No,,,,fr-firststrand,,TruSeq standard total RNA library kit,,2,2,,,,,,,,,,,, +syn15269592,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15269592,1,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47998993,37.0,Male,79,00530548-9c46-4d0c-a09c-6f705e9e1506,RNA-seq,038_D19,038_R19,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right center shoulder,raw counts,syn47998993,1,RNASeqTemplate,2AFB3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-G3H41,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_center_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569863,35.0,Female,,15a5c35a-3ca7-4cef-abdd-981c71441ae4,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Thigh,geneExpression,syn23569863,2,GenomicsAssayTemplate,GA258,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-044-83F15,raw,polyAselection,JH-2-044,experimentalData,NTAP,JH-2-044_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,88a48c5f-3cc0-4f39-b13d-3779dda4246d,"","",Left Thigh,Illumina NovaSeq 6000,36M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn15268790,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15268790,1,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47899102,55.0,Female,39,f6cd890f-3330-45e2-ae47-fa53fc536cc6,RNA-seq,117_D23,117_R23,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right back,raw counts,syn47899102,1,RNASeqTemplate,C4H9E,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-117-D3BH9,raw,rRNAdepletion,JH-2-117,experimentalData,NTAP,JH-2-117_MPNST_PT_right_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15267591,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15267591,1,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn23569885,16.0,Male,,4864d982-4acf-44dd-9071-8d928fddcef4,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Liver,geneExpression,syn23569885,2,GenomicsAssayTemplate,B6471,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-084-AE169,raw,polyAselection,JH-2-084,experimentalData,NTAP,JH-2-084_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,d5c859c1-58bf-48e8-9d2c-34bb5611c54e,"","",Right Liver,Illumina NovaSeq 6000,40M_read pairs,+/-,"",Yes,"",forward,mechanical,fr-firststrand,Not Applicable,TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn15266271,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15266271,1,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn47876387,37.0,Male,2,799a98a0-4763-4af0-9f34-3d60c5e452a0,RNA-seq,038_D1,038_R1,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right medial shoulder,raw counts,syn47876387,2,RNASeqTemplate,7AC45,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-EF4H5,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_medial_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15268020,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15268020,1,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47905977,24.0,Male,52,b76df595-f0a0-437f-be9e-8809210f5119,RNA-seq,146_D13,146_R13,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left flank,raw counts,syn47905977,2,RNASeqTemplate,7464G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-E79BF,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_DifNF_PT_left_flank,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569864,44.0,Female,,91975b58-342f-420f-93c9-341de9ede6e8,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Leg,geneExpression,syn23569864,1,GenomicsAssayTemplate,D2C35,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-045-GH3AA,raw,polyAselection,JH-2-045,experimentalData,NTAP,JH-2-045_cNF_PT,"",bulk cell,"",WU_batch1,Flash frozen,e86f79ab-d11a-46a7-b302-4bab16cb7cd0,"","",Right Leg,Illumina NovaSeq 6000,39M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn15269880,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15269880,1,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267020,18.0,Female,,1c33950c-3573-4eda-b435-fd5433c85f20,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15267020,1,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15268241,23.0,Male,,99e48bbd-ce05-4e41-90ae-d235ebdc174e,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15268241,1,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15269374,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15269374,2,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15269165,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15269165,1,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590090,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590090,2,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47905209,24.0,Male,50,d96e8a15-2cfe-4e59-8f55-55261e2c7443,RNA-seq,146_D13,146_R13,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left flank,raw counts,syn47905209,2,RNASeqTemplate,7464G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-E79BF,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_DifNF_PT_left_flank,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47885387,40.0,Male,18,15f60bc2-32ef-47a8-a85a-1f6307a65046,RNA-seq,119_D7,119_R7,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left brachial plexus,raw counts,syn47885387,2,RNASeqTemplate,C4D86,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-119-A3F2H,raw,rRNAdepletion,JH-2-119,experimentalData,NTAP,JH-2-119_MPNST_PT_left_brachial_plexus,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47995024,37.0,Male,73,1bb7124f-7e17-4e7d-aba8-6430d912197d,RNA-seq,038_D18,038_R18,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right lateral shoulder,raw counts,syn47995024,1,RNASeqTemplate,E6D5A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-9AHHB,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_lateral_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569854,37.0,Female,,2fab416b-e98c-4c26-91e2-bb42fcccd2a2,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn23569854,1,GenomicsAssayTemplate,7FGE5,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-076-41G1H,raw,polyAselection,JH-2-076,experimentalData,NTAP,JH-2-076_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,93b5fc9e-0258-4066-a90b-6ec87234e507,"","",Left Leg,Illumina NovaSeq 6000,41M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn23569865,44.0,Female,,069349fa-cece-4d53-b31c-5fa285701b55,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Leg,geneExpression,syn23569865,2,GenomicsAssayTemplate,D2C35,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-045-GH3AA,raw,polyAselection,JH-2-045,experimentalData,NTAP,JH-2-045_cNF_PT,"",bulk cell,"",WU_batch1,Flash frozen,1dc6a791-476c-4e63-86c1-05aa4c5f444d,"","",Right Leg,Illumina NovaSeq 6000,39M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn23569876,20.0,Male,,012a6e94-92d0-4423-bf04-bbf16e112e2a,RNA-seq,,,cell line,years,pairedEnd,Homo sapiens,syn4939902,From 2-060-7,geneExpression,syn23569876,1,GenomicsAssayTemplate,HD38A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-060-9G31E,raw,polyAselection,JH-2-060,experimentalData,NTAP,JH-2-060_PN_CL,"",bulk cell,"",WU_batch1,Viably frozen,bfe2c2ad-e067-4866-9051-57907f640e33,"","",From 2-060-7,Illumina NovaSeq 6000,41M_read pairs,-/-,"",No,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47899489,21.0,Male,41,06d31b48-d943-4483-a647-a1a1ae609407,RNA-seq,138_D10,138_R10,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left sciatic nerve,raw counts,syn47899489,1,RNASeqTemplate,CG64A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Atypical Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-138-A225B,raw,rRNAdepletion,JH-2-138,experimentalData,NTAP,JH-2-138_AtyNF_PT_left_sciatic_nerve,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47893791,55.0,Female,31,030c6e46-fec8-4c6d-9d09-d724335eb69f,RNA-seq,124_D29,124_R29,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,peroneal nerve tumor,raw counts,syn47893791,1,RNASeqTemplate,5G98D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-124-7GG3C,raw,rRNAdepletion,JH-2-124,experimentalData,NTAP,JH-2-124_DifNF_PT_peroneal_nerve_tumor,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590190,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590190,1,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590080,10.0,Male,,e936a34b-259e-4994-8721-311f5ae4407d,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590080,1,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590091,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590091,1,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47888897,48.0,Male,25,c98b460b-fd95-4b88-8f34-0a446951d939,RNA-seq,120_D27,120_R27,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn47888897,1,RNASeqTemplate,GGF19,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-120-F91H4,raw,rRNAdepletion,JH-2-120,experimentalData,NTAP,JH-2-120_PN_PT_right_flank_T1,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15264162,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15264162,1,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn23569855,37.0,Female,,cff552e5-bb5d-416a-b7c6-46f01b80e3dd,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn23569855,2,GenomicsAssayTemplate,7FGE5,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-076-41G1H,raw,polyAselection,JH-2-076,experimentalData,NTAP,JH-2-076_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,fe00e2ac-5eb4-4cbe-b489-134e2bed36ef,"","",Left Leg,Illumina NovaSeq 6000,41M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn23569866,24.0,Male,,03084987-97f7-4fcb-a0b9-1f99a519c726,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn23569866,1,GenomicsAssayTemplate,5F9FC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-068-2BHHG,raw,polyAselection,JH-2-068,experimentalData,NTAP,JH-2-068_DifNF_PT_4,"",bulk cell,"",WU_batch1,Flash frozen,58db8a68-a724-401f-87eb-ada9865d8398,"","",Sciatic Nerve,Illumina NovaSeq 6000,38M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn23569877,20.0,Male,,dbb93109-cc9a-48e9-b92e-09228416fedf,RNA-seq,,,cell line,years,pairedEnd,Homo sapiens,syn4939902,From 2-060-7,geneExpression,syn23569877,2,GenomicsAssayTemplate,HD38A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-060-9G31E,raw,polyAselection,JH-2-060,experimentalData,NTAP,JH-2-060_PN_CL,"",bulk cell,"",WU_batch1,Viably frozen,663d84a9-9580-4f86-b2cb-bca04974c821,"","",From 2-060-7,Illumina NovaSeq 6000,41M_read pairs,-/-,"",No,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47910501,46.0,Male,62,e05c6a92-3d6e-43a1-bbd5-a8e9185b8280,RNA-seq,012_D16,012_R16,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,L5 Paravertebral Mass,raw counts,syn47910501,2,RNASeqTemplate,4H93H,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-012-2325A,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,JH-2-012-b_MPNST_RT_L5_Paravertebral_Mass,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15269442,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15269442,1,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15268474,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15268474,1,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47888039,24.0,Male,23,13156bb2-17e7-4515-af76-71d421e3fbdb,RNA-seq,146_D34,146_R34,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,abdomen,raw counts,syn47888039,1,RNASeqTemplate,9FFF3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-D6FBB,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_abdomen,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47879448,37.0,Male,7,26c2556a-ee06-49b9-bd7e-47ce054b11e5,RNA-seq,038_D2,038_R2,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Scalp,raw counts,syn47879448,1,RNASeqTemplate,2HBA1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-1D23G,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_cNF_PT_Scalp,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15267077,18.0,Female,,9fae9549-bf1c-4691-ab2f-632cbbb7350a,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15267077,2,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590290,10.0,Male,,4be70396-67e9-4fcc-8615-ab8d093206fe,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590290,1,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn47875873,37.0,Male,1,2b7fa879-1603-41a1-bee1-6c427faa5524,RNA-seq,038_D1,038_R1,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right medial shoulder,raw counts,syn47875873,1,RNASeqTemplate,7AC45,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-EF4H5,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_medial_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590070,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590070,2,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470280,9.0,Male,,30df1849-a746-4a67-b9e7-e9d3ffc2ed4f,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Bladder,geneExpression,syn26470280,2,GenomicsAssayTemplate,F783D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-085-F2983,raw,polyAselection,JH-2-085,experimentalData,NTAP,JH-2-085-b_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590081,10.0,Male,,9b6ad8a1-d7bd-4cca-97c4-e1276786581e,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590081,2,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470291,55.0,Male,,f6da5bf1-d601-4469-b780-217f7f6f5c99,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Lower Extremity,geneExpression,syn26470291,2,GenomicsAssayTemplate,494GE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-086-5EA11,raw,polyAselection,JH-2-086,experimentalData,NTAP,JH-2-086_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590092,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590092,2,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264492,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15264492,1,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn47882099,68.0,Female,11,f4041020-a588-49ff-8770-82295e882a3d,RNA-seq,051_D3,051_R3,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left leg above knee,raw counts,syn47882099,1,RNASeqTemplate,C8D4G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-051-E5FDC,raw,rRNAdepletion,JH-2-051,experimentalData,NTAP,JH-2-051-b_DifNF_PT_left_leg_above_knee,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15266462,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15266462,2,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264042,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15264042,1,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn23569867,24.0,Male,,399c15c5-4f9d-4260-accd-432fa2a1c780,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn23569867,2,GenomicsAssayTemplate,5F9FC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-068-2BHHG,raw,polyAselection,JH-2-068,experimentalData,NTAP,JH-2-068_DifNF_PT_4,"",bulk cell,"",WU_batch1,Flash frozen,5692388b-72ce-44fb-801f-b3eeb364e094,"","",Sciatic Nerve,Illumina NovaSeq 6000,38M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47989966,46.0,Male,63,9b151128-354d-458d-a84a-790929bb0fb0,RNA-seq,012_D16,012_R16,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,L5 Paravertebral Mass,raw counts,syn47989966,1,RNASeqTemplate,4H93H,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-012-2325A,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,JH-2-012-b_MPNST_RT_L5_Paravertebral_Mass,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn23569878,33.0,Female,,2624c42d-f70d-4d09-96b5-738d49672641,RNA-seq,,,cell line,years,pairedEnd,Homo sapiens,syn4939902,Left Thigh,geneExpression,syn23569878,1,GenomicsAssayTemplate,8GCFH,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,Yes,Yes,151,JH-2-077-4H749,raw,polyAselection,JH-2-077,experimentalData,NTAP,JH-2-077_PN_PT,"",bulk cell,"",WU_batch1,Viably frozen,3083dbb6-2d76-4346-aa22-b98feb749dc9,"","",Left Thigh,Illumina NovaSeq 6000,36M_read pairs,-/-,"",No,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47996049,37.0,Male,74,5ea8c8cd-78ed-4853-9f9d-59427d8ea969,RNA-seq,038_D18,038_R18,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right lateral shoulder,raw counts,syn47996049,2,RNASeqTemplate,E6D5A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-9AHHB,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_lateral_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15268112,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15268112,1,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15266077,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15266077,2,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47900525,21.0,Male,43,4211b3d8-c6f2-4543-ad0e-a8690448247b,RNA-seq,138_D10,138_R10,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left sciatic nerve,raw counts,syn47900525,1,RNASeqTemplate,CG64A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Atypical Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-138-A225B,raw,rRNAdepletion,JH-2-138,experimentalData,NTAP,JH-2-138_AtyNF_PT_left_sciatic_nerve,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15268189,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15268189,2,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590390,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590390,1,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590280,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590280,1,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590291,10.0,Male,,39147335-1699-442f-9bf5-7ae06e8695b4,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590291,2,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590060,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590060,2,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15591391,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15591391,1,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47885686,40.0,Male,19,0e6831da-81ca-4338-b607-8dd4a0ebb868,RNA-seq,119_D7,119_R7,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left brachial plexus,raw counts,syn47885686,1,RNASeqTemplate,C4D86,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-119-A3F2H,raw,rRNAdepletion,JH-2-119,experimentalData,NTAP,JH-2-119_MPNST_PT_left_brachial_plexus,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47894156,55.0,Female,32,408ef1da-36ca-41d4-8718-a3b1e5af2543,RNA-seq,124_D29,124_R29,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,peroneal nerve tumor,raw counts,syn47894156,2,RNASeqTemplate,5G98D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-124-7GG3C,raw,rRNAdepletion,JH-2-124,experimentalData,NTAP,JH-2-124_DifNF_PT_peroneal_nerve_tumor,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590071,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590071,1,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590192,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590192,2,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470281,55.0,Male,,da52d998-af08-417f-9d03-fb20d65abecb,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Lower Extremity,geneExpression,syn26470281,1,GenomicsAssayTemplate,494GE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-086-5EA11,raw,polyAselection,JH-2-086,experimentalData,NTAP,JH-2-086_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590082,18.0,Female,,a737fe63-958c-4ba6-8416-1e72ccabbbae,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590082,1,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590093,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590093,1,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15263196,10.0,Male,,24f075b5-ef0d-4b4a-95ae-f8a25d746533,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15263196,2,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn23569868,42.0,Male,,5dc3c358-db4b-4967-8d98-6a149cefc71e,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right 4th Finger with Skin,geneExpression,syn23569868,1,GenomicsAssayTemplate,C61FE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-075-3HE68,raw,polyAselection,JH-2-075,experimentalData,NTAP,JH-2-075_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,277757ac-65f0-417f-8dc7-70b722681df2,"","",Right 4th Finger with Skin,Illumina NovaSeq 6000,43M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn47999537,17.0,Female,81,73a27aff-2eb2-48c1-afe4-e474ac73b93e,RNA-seq,125_D31,125_R31,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left back,raw counts,syn47999537,1,RNASeqTemplate,G9D8E,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-125-EBFHA,raw,rRNAdepletion,JH-2-125,experimentalData,NTAP,JH-2-125_PN_PT_left_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15270390,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15270390,2,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47882365,68.0,Female,12,36c4f4df-ea54-49f9-a907-086d7c344823,RNA-seq,051_D3,051_R3,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left leg above knee,raw counts,syn47882365,2,RNASeqTemplate,C8D4G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-051-E5FDC,raw,rRNAdepletion,JH-2-051,experimentalData,NTAP,JH-2-051-b_DifNF_PT_left_leg_above_knee,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590270,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590270,2,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590391,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590391,2,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15262492,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15262492,2,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15591370,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15591370,1,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590281,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590281,2,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47897523,55.0,Female,37,faf74c19-ed49-4738-987e-91e79c72c885,RNA-seq,117_D23,117_R23,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right back,raw counts,syn47897523,1,RNASeqTemplate,C4H9E,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-117-D3BH9,raw,rRNAdepletion,JH-2-117,experimentalData,NTAP,JH-2-117_MPNST_PT_right_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn26470370,13.0,Male,,62915f5d-27e9-4987-8a66-2d22e5187beb,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Tibial Nerve,geneExpression,syn26470370,1,GenomicsAssayTemplate,1CH62,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-107-AGD39,raw,polyAselection,JH-2-107,experimentalData,NTAP,JH-2-107_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590292,18.0,Female,,2c0c103a-c8b4-4e11-895e-8e1cb89d8851,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590292,1,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590061,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590061,1,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590072,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590072,2,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470282,55.0,Male,,e15c1b39-1fee-4c99-b913-b57ee8887252,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Lower Extremity,geneExpression,syn26470282,2,GenomicsAssayTemplate,494GE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-086-5EA11,raw,polyAselection,JH-2-086,experimentalData,NTAP,JH-2-086_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15266650,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15266650,2,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590083,18.0,Female,,7d57bb77-e511-479f-9865-5372dbfb48ba,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590083,2,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590094,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590094,2,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267530,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15267530,2,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn43705908,10.0,Male,1,1efd08aa-4bda-4b12-8945-77fcd5050eff,RNA-seq,,,primary tumor,,pairedEnd,Homo sapiens,syn4939902,Left Pelvic Mass,raw counts,syn43705908,2,RNASeqTemplate,19DGB,,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,,Open Proposal Program,No,Yes,,JH-2-002-94FAA,,rRNAdepletion,JH-2-002,experimentalData,NTAP,JH-2-002_MPNST_PT,"",,,WU_PDX_batch1,Flash frozen,,,,,,,,,No,,,,fr-firststrand,,TruSeq standard total RNA library kit,,1,1,,,,,,,,,,,, +syn23569858,5.0,Male,,c9fc8c5e-d0e3-4125-9827-493f5ff2a789,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Leg Above Knee,geneExpression,syn23569858,1,GenomicsAssayTemplate,A92CA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-082-B5148,raw,polyAselection,JH-2-082,experimentalData,NTAP,JH-2-082_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,11760b40-2799-4b69-bcd9-b319c0d077bc,"","",Leg Above Knee,Illumina NovaSeq 6000,42M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn15269753,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15269753,1,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267696,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15267696,1,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn23569869,42.0,Male,,ded92c6c-e76c-4aeb-ac4f-c2a09c8b2c3a,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right 4th Finger with Skin,geneExpression,syn23569869,2,GenomicsAssayTemplate,C61FE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-075-3HE68,raw,polyAselection,JH-2-075,experimentalData,NTAP,JH-2-075_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,0ca60f8e-b828-4dc2-a75d-4b2c5c1edc08,"","",Right 4th Finger with Skin,Illumina NovaSeq 6000,43M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn15267355,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15267355,1,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15270083,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15270083,2,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590370,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590370,2,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590260,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590260,1,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47992124,22.0,Male,67,3c584c17-d5ca-460f-a5bc-deccdc0ec7fc,RNA-seq,115_D22,115_R22,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left buttocks,raw counts,syn47992124,1,RNASeqTemplate,4C392,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-115-6A3FB,raw,rRNAdepletion,JH-2-115,experimentalData,NTAP,JH-2-115_DifNF_PT_left_buttocks,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590150,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590150,2,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590271,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590271,1,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590392,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590392,1,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470360,65.0,Female,,5bf2666f-d55a-4593-9965-0c70f698877b,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Buttocks,geneExpression,syn26470360,1,GenomicsAssayTemplate,94G2C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-100-19H33,raw,polyAselection,JH-2-100,experimentalData,NTAP,JH-2-100_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590040,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590040,2,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590161,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590161,1,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590282,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590282,1,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470371,13.0,Male,,cbbdb947-fe74-4595-b253-677d487ba4d2,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Tibial Nerve,geneExpression,syn26470371,2,GenomicsAssayTemplate,1CH62,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-107-AGD39,raw,polyAselection,JH-2-107,experimentalData,NTAP,JH-2-107_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590051,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590051,1,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15591382,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15591382,2,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590293,18.0,Female,,c80470ff-5a2f-43de-9137-8350e3a0a9ec,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590293,2,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590062,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590062,2,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590073,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590073,1,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590194,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590194,1,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47883037,33.0,Male,15,5c63ba3f-64b0-4d8a-b719-3b3c386abf6a,RNA-seq,118_D24,118_R24,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,back,raw counts,syn47883037,1,RNASeqTemplate,F1GHC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-118-DFAFC,raw,rRNAdepletion,JH-2-118,experimentalData,NTAP,JH-2-118_PN_PT_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn26470283,55.0,Male,,dc8f0155-81fa-4398-881b-5cbeb1e9cc0b,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Lower Extremity,geneExpression,syn26470283,1,GenomicsAssayTemplate,494GE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-086-5EA11,raw,polyAselection,JH-2-086,experimentalData,NTAP,JH-2-086_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590095,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590095,1,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265232,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15265232,1,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn23569859,5.0,Male,,28445f52-19a4-487e-b41e-8d17198af0fc,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Leg Above Knee,geneExpression,syn23569859,2,GenomicsAssayTemplate,A92CA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-082-B5148,raw,polyAselection,JH-2-082,experimentalData,NTAP,JH-2-082_PN_PT,"",bulk cell,"",WU_batch1,Flash frozen,6225745f-f68a-4087-b5ee-cecea855491f,"","",Leg Above Knee,Illumina NovaSeq 6000,42M_read pairs,-/-,"",Yes,"",forward,mechanical,fr-firststrand,"",TruSeq standard total RNA library kit,"",,,,,,,,,,,,,, +syn15267466,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15267466,1,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264199,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15264199,2,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267246,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15267246,1,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15268049,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15268049,2,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47880585,37.0,Male,8,b992b092-b865-4b3e-9e52-797236566869,RNA-seq,038_D2,038_R2,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Scalp,raw counts,syn47880585,2,RNASeqTemplate,2HBA1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-1D23G,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_cNF_PT_Scalp,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15269039,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15269039,1,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15263990,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15263990,2,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264980,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15264980,2,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590360,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590360,2,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590371,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590371,1,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590382,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590382,1,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470350,63.0,Male,,6e43b04c-f44f-4236-a646-cd6e725379c6,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Upper Back,geneExpression,syn26470350,1,GenomicsAssayTemplate,H5A8H,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-093-214AE,raw,polyAselection,JH-2-093,experimentalData,NTAP,JH-2-093_cNF_PT_2,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590030,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590030,2,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590393,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590393,2,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470361,65.0,Female,,04ea0cab-4ab6-40a7-b35d-ef616c4f2de8,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Buttocks,geneExpression,syn26470361,2,GenomicsAssayTemplate,94G2C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-100-19H33,raw,polyAselection,JH-2-100,experimentalData,NTAP,JH-2-100_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590041,23.0,Male,,5616ec55-5ff7-41c2-8461-7fb6591e0f19,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590041,1,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590283,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590283,2,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470372,13.0,Male,,0ec9e823-a703-41b3-a838-25feea1e7b30,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Tibial Nerve,geneExpression,syn26470372,1,GenomicsAssayTemplate,1CH62,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-107-AGD39,raw,polyAselection,JH-2-107,experimentalData,NTAP,JH-2-107_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590052,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590052,2,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590063,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590063,1,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590184,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590184,1,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590195,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590195,2,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47877835,37.0,Male,5,3f180a0d-57e9-4f8c-8da9-1e1222e2594d,RNA-seq,038_D2,038_R2,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Scalp,raw counts,syn47877835,1,RNASeqTemplate,2HBA1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-1D23G,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_cNF_PT_Scalp,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47899747,21.0,Male,42,478e78e9-1cfc-430a-93f2-6747aab4354d,RNA-seq,138_D10,138_R10,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left sciatic nerve,raw counts,syn47899747,2,RNASeqTemplate,CG64A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Atypical Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-138-A225B,raw,rRNAdepletion,JH-2-138,experimentalData,NTAP,JH-2-138_AtyNF_PT_left_sciatic_nerve,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590096,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590096,2,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265574,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15265574,1,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15268984,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15268984,2,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265278,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15265278,2,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn48003313,48.0,Male,88,2b70ddad-896f-48a3-9b12-a58e716f099b,RNA-seq,120_D28,120_R28,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn48003313,2,RNASeqTemplate,2HG48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-120-C4924,raw,rRNAdepletion,JH-2-120,experimentalData,NTAP,JH-2-120_PN_PT_right_flank_T2,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15269667,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15269667,2,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15261791,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15261791,1,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47992522,22.0,Male,68,c2ef6114-b8a0-4d76-bb53-326add8235f7,RNA-seq,115_D22,115_R22,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left buttocks,raw counts,syn47992522,2,RNASeqTemplate,4C392,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-115-6A3FB,raw,rRNAdepletion,JH-2-115,experimentalData,NTAP,JH-2-115_DifNF_PT_left_buttocks,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47991477,22.0,Male,65,03bfadc1-2a14-41f7-9672-df714ea56509,RNA-seq,115_D22,115_R22,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left buttocks,raw counts,syn47991477,1,RNASeqTemplate,4C392,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-115-6A3FB,raw,rRNAdepletion,JH-2-115,experimentalData,NTAP,JH-2-115_DifNF_PT_left_buttocks,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590240,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590240,1,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590361,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590361,1,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590130,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590130,1,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590372,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590372,2,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47882489,33.0,Male,13,75599a32-29b2-458f-8c67-f5f29646c88a,RNA-seq,118_D24,118_R24,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,back,raw counts,syn47882489,1,RNASeqTemplate,F1GHC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-118-DFAFC,raw,rRNAdepletion,JH-2-118,experimentalData,NTAP,JH-2-118_PN_PT_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590020,18.0,Female,,addb407e-2a42-4caa-92f9-e0feb2323a5e,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590020,2,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590262,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590262,2,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590383,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590383,2,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47996724,37.0,Male,76,28e01cc5-68b6-479e-a797-0de7368de35f,RNA-seq,038_D18,038_R18,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right lateral shoulder,raw counts,syn47996724,2,RNASeqTemplate,E6D5A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-9AHHB,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_lateral_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn26470351,63.0,Male,,bdfde769-8779-4862-81f1-772f8d977bff,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Upper Back,geneExpression,syn26470351,2,GenomicsAssayTemplate,H5A8H,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-093-214AE,raw,polyAselection,JH-2-093,experimentalData,NTAP,JH-2-093_cNF_PT_2,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590031,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590031,1,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590152,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590152,1,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590273,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590273,2,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590394,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590394,1,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470362,29.0,Male,,7d3e6a21-e36c-4a5e-9336-8033043aabbf,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Neck,geneExpression,syn26470362,1,GenomicsAssayTemplate,1G93A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-104-51E2H,raw,polyAselection,JH-2-104,experimentalData,NTAP,JH-2-104_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590042,23.0,Male,,2fa8fa28-ed8f-416c-8b9e-4d0ed88b7086,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590042,2,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590163,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590163,2,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590284,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590284,1,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470373,13.0,Male,,4d1e434f-ae20-40d0-b043-414ca5fdf66f,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Tibial Nerve,geneExpression,syn26470373,2,GenomicsAssayTemplate,1CH62,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-107-AGD39,raw,polyAselection,JH-2-107,experimentalData,NTAP,JH-2-107_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590053,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590053,1,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590174,10.0,Male,,8764f32e-ea71-4991-9d65-aad5f78eeb6a,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590174,1,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15262033,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15262033,2,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15266510,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15266510,1,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590064,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590064,2,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590185,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590185,2,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590075,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590075,2,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267742,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15267742,2,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590097,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590097,1,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267303,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15267303,2,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15268524,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15268524,2,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15266357,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15266357,2,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15269525,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15269525,2,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15266137,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15266137,1,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15262760,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15262760,2,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47891367,48.0,Male,27,2d646383-9abe-4279-902a-f9600c9497f4,RNA-seq,120_D27,120_R27,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn47891367,1,RNASeqTemplate,GGF19,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-120-F91H4,raw,rRNAdepletion,JH-2-120,experimentalData,NTAP,JH-2-120_PN_PT_right_flank_T1,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47896944,17.0,Female,35,8c2be5ab-0859-4760-93a5-c31cf43425fc,RNA-seq,125_D30,125_R30,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn47896944,1,RNASeqTemplate,DCE65,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-125-ADE77,raw,rRNAdepletion,JH-2-125,experimentalData,NTAP,JH-2-125_PN_PT_right_flank,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590340,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590340,2,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15262441,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15262441,1,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590230,23.0,Male,,73901bc3-1b71-432b-be5e-018a042b70af,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590230,1,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590362,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590362,2,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470330,34.0,Male,,70476d55-b8b9-4a50-b5a6-df7cfa5af6b5,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Sciatic Nerve,geneExpression,syn26470330,1,GenomicsAssayTemplate,GDFG1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-091-CAA8H,raw,polyAselection,JH-2-091,experimentalData,NTAP,JH-2-091_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590010,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590010,1,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590373,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590373,1,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590142,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590142,1,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47897747,55.0,Female,38,65db07f8-b344-4db1-a452-fcfdee1f7f69,RNA-seq,117_D23,117_R23,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right back,raw counts,syn47897747,2,RNASeqTemplate,C4H9E,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-117-D3BH9,raw,rRNAdepletion,JH-2-117,experimentalData,NTAP,JH-2-117_MPNST_PT_right_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn26470352,63.0,Male,,26192d26-1889-4479-bc7b-2fd471c3accc,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Upper Back,geneExpression,syn26470352,1,GenomicsAssayTemplate,H5A8H,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-093-214AE,raw,polyAselection,JH-2-093,experimentalData,NTAP,JH-2-093_cNF_PT_2,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590032,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590032,2,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590153,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590153,2,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590274,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590274,1,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590395,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590395,2,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470363,29.0,Male,,d1374e4f-d0f3-45ac-a241-f091bca88403,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Neck,geneExpression,syn26470363,2,GenomicsAssayTemplate,1G93A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-104-51E2H,raw,polyAselection,JH-2-104,experimentalData,NTAP,JH-2-104_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15267941,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15267941,1,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590164,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590164,1,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590285,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590285,2,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264685,23.0,Male,,870e72b1-0f8a-4c36-af46-8699388c2eb9,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15264685,1,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470374,52.0,Male,,26bff576-b798-4a8f-b2ba-2d579e7cd830,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Ankle,geneExpression,syn26470374,1,GenomicsAssayTemplate,6C5FF,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-111-G645D,raw,polyAselection,JH-2-111,experimentalData,NTAP,JH-2-111_DifNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590054,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590054,2,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590296,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590296,1,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590065,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590065,1,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590197,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590197,1,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590087,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590087,1,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265686,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15265686,1,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590098,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590098,2,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47887429,24.0,Male,22,45836662-2e40-4d0c-ab74-80b1a6897440,RNA-seq,146_D34,146_R34,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,abdomen,raw counts,syn47887429,2,RNASeqTemplate,9FFF3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-D6FBB,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_abdomen,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15263751,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15263751,2,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590330,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590330,2,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590341,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590341,1,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590110,23.0,Male,,7d42b77c-4153-43da-b3ec-a751a4a0e922,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590110,2,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590231,23.0,Male,,1c0844c4-ea57-491f-b7a5-57bfe156ad32,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590231,2,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590363,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590363,1,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470331,34.0,Male,,6d215b05-cc39-4d3b-ad49-25ee2d37a337,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Sciatic Nerve,geneExpression,syn26470331,2,GenomicsAssayTemplate,GDFG1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-091-CAA8H,raw,polyAselection,JH-2-091,experimentalData,NTAP,JH-2-091_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590011,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590011,2,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590132,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590132,2,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590253,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590253,1,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590374,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590374,2,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590264,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590264,1,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470353,63.0,Male,,83d20066-15f1-4d7c-842f-61c1dae49ad0,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Upper Back,geneExpression,syn26470353,2,GenomicsAssayTemplate,H5A8H,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-093-214AE,raw,polyAselection,JH-2-093,experimentalData,NTAP,JH-2-093_cNF_PT_2,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590033,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590033,1,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590275,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590275,2,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590396,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590396,1,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264554,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15264554,2,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15265885,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15265885,2,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470364,29.0,Male,,6a8351da-0e5d-4341-9875-1f794362db56,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Neck,geneExpression,syn26470364,1,GenomicsAssayTemplate,1G93A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-104-51E2H,raw,polyAselection,JH-2-104,experimentalData,NTAP,JH-2-104_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn26470254,26.0,Male,,e8c12dc4-c2d7-4e7e-b70c-72ae4d62c774,RNA-seq,,,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,Left paraspinal recurrence,geneExpression,syn26470254,1,GenomicsAssayTemplate,2G2E2,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,Yes,151,JH-2-023-91HBD,raw,polyAselection,JH-2-023,experimentalData,NTAP,JH-2-023-d_MPNST_RT,"",bulk cell,Not Applicable,WU_batch1&WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn26470375,52.0,Male,,4ff31fdf-ad0a-4009-931c-1c994b7591ea,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Ankle,geneExpression,syn26470375,2,GenomicsAssayTemplate,6C5FF,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-111-G645D,raw,polyAselection,JH-2-111,experimentalData,NTAP,JH-2-111_DifNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590055,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590055,1,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590176,10.0,Male,,6c5606ff-d972-4458-955c-f95e3b39e967,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590176,2,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590297,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590297,2,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590066,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590066,2,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590187,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590187,1,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590198,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590198,2,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590088,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590088,2,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590099,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590099,1,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267645,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15267645,2,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265467,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15265467,1,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267414,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15267414,2,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn48000588,17.0,Female,83,64f62394-f162-4c6d-934d-f31811fd5031,RNA-seq,125_D31,125_R31,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left back,raw counts,syn48000588,1,RNASeqTemplate,G9D8E,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-125-EBFHA,raw,rRNAdepletion,JH-2-125,experimentalData,NTAP,JH-2-125_PN_PT_left_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47882624,33.0,Male,14,94314141-618f-445a-bec2-fc7d9ca340b1,RNA-seq,118_D24,118_R24,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,back,raw counts,syn47882624,2,RNASeqTemplate,F1GHC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-118-DFAFC,raw,rRNAdepletion,JH-2-118,experimentalData,NTAP,JH-2-118_PN_PT_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590430,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590430,2,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590441,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590441,2,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15263620,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15263620,2,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15270154,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15270154,1,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47892227,55.0,Female,29,6d185e97-5105-4aea-bb05-b185cad831ad,RNA-seq,124_D29,124_R29,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,peroneal nerve tumor,raw counts,syn47892227,1,RNASeqTemplate,5G98D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-124-7GG3C,raw,rRNAdepletion,JH-2-124,experimentalData,NTAP,JH-2-124_DifNF_PT_peroneal_nerve_tumor,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590320,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590320,2,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590452,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590452,1,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590331,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590331,1,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15262311,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15262311,1,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590342,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590342,2,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590353,10.0,Male,,c5888e9f-4480-4912-9e87-2c06ce81770f,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590353,1,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590364,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590364,2,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470332,36.0,Female,,9c0a9f11-fee9-4d49-ae05-49049f215ca6,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Flank,geneExpression,syn26470332,1,GenomicsAssayTemplate,2H1C1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-092-B4F11,raw,polyAselection,JH-2-092,experimentalData,NTAP,JH-2-092_cNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15262597,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15262597,2,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470343,36.0,Female,,fa2d98df-50af-4169-a916-23ada11a743f,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Flank,geneExpression,syn26470343,1,GenomicsAssayTemplate,2H1C1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-092-B4F11,raw,polyAselection,JH-2-092,experimentalData,NTAP,JH-2-092_cNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590023,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590023,1,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590144,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590144,2,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590265,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590265,2,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265622,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15265622,2,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47884318,33.0,Male,16,185d4ae4-dd53-4d84-b2fa-3afb6d71add9,RNA-seq,118_D24,118_R24,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,back,raw counts,syn47884318,2,RNASeqTemplate,F1GHC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-118-DFAFC,raw,rRNAdepletion,JH-2-118,experimentalData,NTAP,JH-2-118_PN_PT_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn26470354,30.0,Female,,2941b583-0c12-4828-becf-7489bc4a1b46,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Ankle Superficial,geneExpression,syn26470354,1,GenomicsAssayTemplate,CC3H4,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-094-5HA24,raw,polyAselection,JH-2-094,experimentalData,NTAP,JH-2-094_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590034,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590034,2,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590155,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590155,1,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590276,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590276,1,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590397,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590397,2,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470365,29.0,Male,,1e2cfd94-33ef-4006-8897-1e6563e25faa,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Neck,geneExpression,syn26470365,2,GenomicsAssayTemplate,1G93A,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-104-51E2H,raw,polyAselection,JH-2-104,experimentalData,NTAP,JH-2-104_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590045,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590045,1,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265402,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15265402,2,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590166,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590166,2,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15266975,10.0,Male,,101e6a3e-2cd5-406c-8e7e-b2a6f1cd8713,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15266975,2,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470255,26.0,Male,,e0ad2a3e-706e-44b8-917e-b326ed945ead,RNA-seq,,,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,Left paraspinal recurrence,geneExpression,syn26470255,2,GenomicsAssayTemplate,2G2E2,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,Yes,151,JH-2-023-91HBD,raw,polyAselection,JH-2-023,experimentalData,NTAP,JH-2-023-d_MPNST_RT,"",bulk cell,Not Applicable,WU_batch1&WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn26470376,52.0,Male,,64f1755d-6605-487d-9128-7da089fb52ed,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Ankle,geneExpression,syn26470376,1,GenomicsAssayTemplate,6C5FF,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-111-G645D,raw,polyAselection,JH-2-111,experimentalData,NTAP,JH-2-111_DifNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590056,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590056,2,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590177,18.0,Female,,32ac071b-2995-45d7-8f34-7fffa79111fc,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590177,1,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590298,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590298,1,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15262157,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15262157,1,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47994219,23.0,Male,71,0bc6e8f9-0261-412d-b818-e59d0fca973a,RNA-seq,028_D17,028_R17,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,cervical spine,raw counts,syn47994219,1,RNASeqTemplate,E4D24,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-028-3686C,raw,rRNAdepletion,JH-2-028,experimentalData,NTAP,JH-2-028-b_PN_PT_cervical_spine,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590067,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590067,1,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15263136,10.0,Male,,aad905bc-eaf7-4064-9c46-65447cc6eba1,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15263136,1,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn48001754,48.0,Male,85,7b802e7f-e98b-4893-bfe4-285d4785df9a,RNA-seq,120_D28,120_R28,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn48001754,1,RNASeqTemplate,2HG48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-120-C4924,raw,rRNAdepletion,JH-2-120,experimentalData,NTAP,JH-2-120_PN_PT_right_flank_T2,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590089,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590089,1,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264357,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15264357,1,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15269813,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15269813,2,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264247,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15264247,1,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn48002338,48.0,Male,87,9fe9fc4f-7aaa-4e98-81d1-96c97a503255,RNA-seq,120_D28,120_R28,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn48002338,1,RNASeqTemplate,2HG48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-120-C4924,raw,rRNAdepletion,JH-2-120,experimentalData,NTAP,JH-2-120_PN_PT_right_flank_T2,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47880733,68.0,Female,9,769d7409-16d8-4269-8830-e500aca375f2,RNA-seq,051_D3,051_R3,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left leg above knee,raw counts,syn47880733,1,RNASeqTemplate,C8D4G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-051-E5FDC,raw,rRNAdepletion,JH-2-051,experimentalData,NTAP,JH-2-051-b_DifNF_PT_left_leg_above_knee,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590420,18.0,Female,,88c37bca-4a85-4a33-a892-9614948fd840,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590420,2,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590431,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590431,1,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590310,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590310,2,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590442,23.0,Male,,d128786b-18a0-4979-ab6b-aa43bdfa3e41,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590442,1,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590453,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590453,2,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15270287,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15270287,1,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590211,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590211,1,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590332,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590332,2,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15263401,18.0,Female,,b57eb610-4c6f-4a23-847e-463ee6cf7386,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15263401,2,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470300,13.0,Male,,71fad54f-0c94-4110-a08e-9dd873515334,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Sciatic Nerve,geneExpression,syn26470300,1,GenomicsAssayTemplate,HH51C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-089-H8EBA,raw,polyAselection,JH-2-089,experimentalData,NTAP,JH-2-089_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590101,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590101,2,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590222,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590222,2,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15266910,10.0,Male,,82306ef9-3906-447a-9559-6e62f22e4114,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15266910,1,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590343,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590343,1,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470311,13.0,Male,,16171979-af17-47d8-ba87-bb370fb55097,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Sciatic Nerve,geneExpression,syn26470311,2,GenomicsAssayTemplate,HH51C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-089-H8EBA,raw,polyAselection,JH-2-089,experimentalData,NTAP,JH-2-089_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590354,10.0,Male,,a61c5ba5-30c3-41f6-bedf-38a3d521d0c4,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590354,2,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470322,13.0,Male,,d964480d-7659-4251-9f3f-178c0f5526dd,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Sciatic Nerve,geneExpression,syn26470322,1,GenomicsAssayTemplate,HH51C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-089-H8EBA,raw,polyAselection,JH-2-089,experimentalData,NTAP,JH-2-089_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590244,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590244,2,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590365,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590365,1,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264402,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15264402,2,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470333,36.0,Female,,2b8abbba-8428-4a7e-9ffe-c6aae5f3631a,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Flank,geneExpression,syn26470333,2,GenomicsAssayTemplate,2H1C1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-092-B4F11,raw,polyAselection,JH-2-092,experimentalData,NTAP,JH-2-092_cNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590134,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590134,1,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590255,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590255,2,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590376,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590376,1,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15263687,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15263687,1,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470344,36.0,Female,,ddc96af1-26e7-4ad6-a029-bd9c4147bbe4,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Flank,geneExpression,syn26470344,2,GenomicsAssayTemplate,2H1C1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-092-B4F11,raw,polyAselection,JH-2-092,experimentalData,NTAP,JH-2-092_cNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590024,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590024,2,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590145,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590145,1,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15262367,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15262367,2,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470355,30.0,Female,,64b5fa68-7f31-4f91-abc7-cc37940254be,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Ankle Superficial,geneExpression,syn26470355,2,GenomicsAssayTemplate,CC3H4,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-094-5HA24,raw,polyAselection,JH-2-094,experimentalData,NTAP,JH-2-094_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15267812,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15267812,1,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590035,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590035,1,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590156,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590156,2,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590277,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590277,2,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590398,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590398,1,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470366,44.0,,,,RNA-seq,,,primary tumor,,,,syn4939902,,,,,,,,The Johns Hopkins NF1 biospecimen repository,,,Open Proposal Program,,,,,,,JH-2-105,,NTAP,,"",,,JH_batch1,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590046,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590046,2,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470256,26.0,Male,,698cb30a-372a-47bb-a7dc-27052aa1b99f,RNA-seq,,,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,Left paraspinal recurrence,geneExpression,syn26470256,1,GenomicsAssayTemplate,2G2E2,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,Yes,151,JH-2-023-91HBD,raw,polyAselection,JH-2-023,experimentalData,NTAP,JH-2-023-d_MPNST_RT,"",bulk cell,Not Applicable,WU_batch1&WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn26470377,52.0,Male,,9ccbbb6f-877b-42e2-abf6-8563bb20c825,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Ankle,geneExpression,syn26470377,2,GenomicsAssayTemplate,6C5FF,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-111-G645D,raw,polyAselection,JH-2-111,experimentalData,NTAP,JH-2-111_DifNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590057,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590057,1,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590299,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590299,2,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470267,9.0,Male,,ae35094d-a98c-4bef-8828-996fbbf4141e,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Bladder,geneExpression,syn26470267,1,GenomicsAssayTemplate,F783D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-085-F2983,raw,polyAselection,JH-2-085,experimentalData,NTAP,JH-2-085-b_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590068,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590068,2,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590189,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590189,2,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47877708,37.0,Male,4,136efb96-bcd4-44c9-9b26-b63d0d3b64c0,RNA-seq,038_D1,038_R1,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right medial shoulder,raw counts,syn47877708,2,RNASeqTemplate,7AC45,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-EF4H5,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_DifNF_PT_right_medial_shoulder,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15266558,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15266558,2,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15266206,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15266206,2,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47890513,48.0,Male,26,3c27d054-f194-4615-85ac-ded2e7cb3489,RNA-seq,120_D27,120_R27,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn47890513,2,RNASeqTemplate,GGF19,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-120-F91H4,raw,rRNAdepletion,JH-2-120,experimentalData,NTAP,JH-2-120_PN_PT_right_flank_T1,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15268308,23.0,Male,,1e1aada5-efa0-4f72-996e-84fb3f26ecf2,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15268308,2,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15262852,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15262852,2,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590410,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590410,1,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590300,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590300,1,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590432,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590432,2,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590311,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590311,1,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590443,23.0,Male,,f736c66c-b7b2-415d-a917-8176e7716ea0,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590443,2,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590454,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590454,1,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590333,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590333,1,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590102,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590102,1,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590344,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590344,2,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265954,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15265954,1,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47994628,23.0,Male,72,e4f11839-621f-46fa-ab1e-27b550bf7f92,RNA-seq,028_D17,028_R17,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,cervical spine,raw counts,syn47994628,2,RNASeqTemplate,E4D24,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-028-3686C,raw,rRNAdepletion,JH-2-028,experimentalData,NTAP,JH-2-028-b_PN_PT_cervical_spine,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590355,18.0,Female,,3c92ec3e-4bc1-4bb4-8878-02be93e4b6ea,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590355,1,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470323,13.0,Male,,23ec31aa-d0d0-469e-8424-9371e54db712,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Sciatic Nerve,geneExpression,syn26470323,2,GenomicsAssayTemplate,HH51C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-089-H8EBA,raw,polyAselection,JH-2-089,experimentalData,NTAP,JH-2-089_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590366,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590366,2,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590256,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590256,1,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590377,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590377,2,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590025,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590025,1,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590267,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590267,1,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590388,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590388,1,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470356,30.0,Female,,db6e2148-6a2a-42e9-ae14-5c53b196678c,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Ankle Superficial,geneExpression,syn26470356,1,GenomicsAssayTemplate,CC3H4,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-094-5HA24,raw,polyAselection,JH-2-094,experimentalData,NTAP,JH-2-094_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590036,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590036,2,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590278,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590278,1,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15264304,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15264304,2,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590399,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590399,2,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470367,44.0,,,,RNA-seq,,,primary tumor,,,,syn4939902,,,,,,,,The Johns Hopkins NF1 biospecimen repository,,,Open Proposal Program,,,,,,,JH-2-105,,NTAP,,"",,,JH_batch1,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn48001602,17.0,Female,84,d821db88-25c2-4737-be02-104602d6d044,RNA-seq,125_D31,125_R31,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left back,raw counts,syn48001602,2,RNASeqTemplate,G9D8E,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-125-EBFHA,raw,rRNAdepletion,JH-2-125,experimentalData,NTAP,JH-2-125_PN_PT_left_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn26470257,26.0,Male,,3570a1b9-bb51-4b2b-a916-606c97fe60bb,RNA-seq,,,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,Left paraspinal recurrence,geneExpression,syn26470257,2,GenomicsAssayTemplate,2G2E2,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,Yes,151,JH-2-023-91HBD,raw,polyAselection,JH-2-023,experimentalData,NTAP,JH-2-023-d_MPNST_RT,"",bulk cell,Not Applicable,WU_batch1&WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590058,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590058,2,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590179,18.0,Female,,31ec1117-f79d-4670-b617-e1fe6ebdce92,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590179,2,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn47999908,17.0,Female,82,5d7b827f-eb05-4a26-90ab-ba0aa2b276ce,RNA-seq,125_D31,125_R31,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left back,raw counts,syn47999908,2,RNASeqTemplate,G9D8E,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-125-EBFHA,raw,rRNAdepletion,JH-2-125,experimentalData,NTAP,JH-2-125_PN_PT_left_back,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590069,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590069,1,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15266416,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15266416,1,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267989,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15267989,2,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15268847,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15268847,2,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15267879,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15267879,2,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265349,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15265349,1,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47891823,48.0,Male,28,d068e827-68f3-4cfa-87db-38a40e2a1a4f,RNA-seq,120_D27,120_R27,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn47891823,2,RNASeqTemplate,GGF19,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-120-F91H4,raw,rRNAdepletion,JH-2-120,experimentalData,NTAP,JH-2-120_PN_PT_right_flank_T1,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47880999,68.0,Female,10,00a4a687-11c5-4297-bd76-79793a354e22,RNA-seq,051_D3,051_R3,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left leg above knee,raw counts,syn47880999,2,RNASeqTemplate,C8D4G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-051-E5FDC,raw,rRNAdepletion,JH-2-051,experimentalData,NTAP,JH-2-051-b_DifNF_PT_left_leg_above_knee,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47992847,23.0,Male,69,bbdfb8a4-d075-45cb-a71e-10cf810109c4,RNA-seq,028_D17,028_R17,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,cervical spine,raw counts,syn47992847,1,RNASeqTemplate,E4D24,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-028-3686C,raw,rRNAdepletion,JH-2-028,experimentalData,NTAP,JH-2-028-b_PN_PT_cervical_spine,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590400,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590400,1,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590411,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590411,2,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47894617,17.0,Female,33,aecab835-698a-4040-9404-fcd255efb4ad,RNA-seq,125_D30,125_R30,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn47894617,1,RNASeqTemplate,DCE65,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-125-ADE77,raw,rRNAdepletion,JH-2-125,experimentalData,NTAP,JH-2-125_PN_PT_right_flank,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47893418,55.0,Female,30,687cbda6-430f-49b8-9dc4-d3120b776475,RNA-seq,124_D29,124_R29,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,peroneal nerve tumor,raw counts,syn47893418,2,RNASeqTemplate,5G98D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-124-7GG3C,raw,rRNAdepletion,JH-2-124,experimentalData,NTAP,JH-2-124_DifNF_PT_peroneal_nerve_tumor,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590301,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590301,2,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590433,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590433,1,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590312,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590312,2,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15263865,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15263865,2,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590455,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590455,2,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15262545,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15262545,1,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590334,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590334,2,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590103,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590103,2,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590345,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590345,1,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264745,23.0,Male,,fd3f5913-4bb1-4254-be24-bfd9a266d669,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15264745,2,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590356,18.0,Female,,5e6c05fe-0e89-4539-a52e-55a66a08317d,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590356,2,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470324,32.0,Male,,b85d7c9b-4291-4d21-aa8b-8261cf501069,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Brachial Plexus,geneExpression,syn26470324,1,GenomicsAssayTemplate,G36F6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-090-19D3F,raw,polyAselection,JH-2-090,experimentalData,NTAP,JH-2-090_DifNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590367,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590367,1,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590136,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590136,2,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590378,23.0,Male,,bc541d33-c486-4943-a844-ab49ea0e35ec,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590378,1,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15265746,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15265746,2,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470346,36.0,Female,,b6e5fecb-1c1f-48f5-bb0c-d47746e9f31d,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Flank,geneExpression,syn26470346,1,GenomicsAssayTemplate,BFCBA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-092-B52E5,raw,polyAselection,JH-2-092,experimentalData,NTAP,JH-2-092_cNF_PT_2,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590026,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590026,2,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590147,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590147,2,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590389,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590389,2,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470357,30.0,Female,,6a2ad3ba-0a6c-4700-85f5-9e4ccc2699d4,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Ankle Superficial,geneExpression,syn26470357,2,GenomicsAssayTemplate,CC3H4,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-094-5HA24,raw,polyAselection,JH-2-094,experimentalData,NTAP,JH-2-094_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15268903,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15268903,1,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15266604,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15266604,1,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590037,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590037,1,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590158,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590158,1,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590279,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590279,2,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn26470368,44.0,,,,RNA-seq,,,primary tumor,,,,syn4939902,,,,,,,,The Johns Hopkins NF1 biospecimen repository,,,Open Proposal Program,,,,,,,JH-2-105,,NTAP,,"",,,JH_batch1,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn26470258,9.0,Male,,152d6d84-ce49-4100-ab1c-0db350c5c2e7,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Bladder,geneExpression,syn26470258,1,GenomicsAssayTemplate,F783D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-085-F2983,raw,polyAselection,JH-2-085,experimentalData,NTAP,JH-2-085-b_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590059,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15590059,1,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15269948,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15269948,2,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15261974,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15261974,1,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590401,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590401,2,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15264922,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15264922,1,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590423,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590423,1,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590302,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590302,1,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590434,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590434,2,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15591402,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15591402,2,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590313,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590313,1,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590203,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590203,1,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590214,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590214,2,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590335,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590335,1,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590104,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590104,1,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590346,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590346,2,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590115,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590115,1,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15262216,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15262216,2,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470325,32.0,Male,,eaabc99f-f8eb-4a8f-95cd-59cc3b3e4471,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Brachial Plexus,geneExpression,syn26470325,2,GenomicsAssayTemplate,G36F6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-090-19D3F,raw,polyAselection,JH-2-090,experimentalData,NTAP,JH-2-090_DifNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590126,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590126,1,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590368,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590368,2,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15263316,18.0,Female,,3746594f-a70b-4811-b537-def6753e3bf2,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15263316,1,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590137,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590137,1,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590258,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590258,2,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590379,23.0,Male,,0b228fd5-8c82-432b-bd6a-2d5476cb44fe,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590379,2,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470347,36.0,Female,,6ecd701f-fe2c-4b03-a892-0c5df2814145,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Flank,geneExpression,syn26470347,2,GenomicsAssayTemplate,BFCBA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-092-B52E5,raw,polyAselection,JH-2-092,experimentalData,NTAP,JH-2-092_cNF_PT_2,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590027,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590027,1,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590148,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590148,1,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470358,65.0,Female,,e25b6abe-5424-4285-93dd-582de89965df,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Buttocks,geneExpression,syn26470358,1,GenomicsAssayTemplate,94G2C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-100-19H33,raw,polyAselection,JH-2-100,experimentalData,NTAP,JH-2-100_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590038,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590038,2,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590159,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590159,2,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470369,44.0,,,,RNA-seq,,,primary tumor,,,,syn4939902,,,,,,,,The Johns Hopkins NF1 biospecimen repository,,,Open Proposal Program,,,,,,,JH-2-105,,NTAP,,"",,,JH_batch1,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn26470259,9.0,Male,,6eb695ff-ae17-44c7-b768-dd19332452f4,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Bladder,geneExpression,syn26470259,2,GenomicsAssayTemplate,F783D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-085-F2983,raw,polyAselection,JH-2-085,experimentalData,NTAP,JH-2-085-b_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15262701,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15262701,1,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15270214,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15270214,2,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47990418,46.0,Male,64,3b1d6c2c-9313-4400-b1b6-67e1f637cc82,RNA-seq,012_D16,012_R16,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,L5 Paravertebral Mass,raw counts,syn47990418,2,RNASeqTemplate,4H93H,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-012-2325A,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,JH-2-012-b_MPNST_RT_L5_Paravertebral_Mass,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590402,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590402,1,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590424,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590424,2,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590303,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590303,2,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590435,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590435,1,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590314,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590314,2,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590446,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590446,1,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590325,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590325,1,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590336,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15590336,2,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590105,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590105,2,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590226,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590226,1,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590347,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590347,1,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470326,32.0,Male,,c851407d-47c7-4a18-becf-a7228cbb1449,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Brachial Plexus,geneExpression,syn26470326,1,GenomicsAssayTemplate,G36F6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-090-19D3F,raw,polyAselection,JH-2-090,experimentalData,NTAP,JH-2-090_DifNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590369,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590369,1,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590017,10.0,Male,,313611b6-5c77-4c2a-a2db-4001491a6395,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590017,1,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470348,36.0,Female,,532be130-3433-4dea-981d-b4fbed748646,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Flank,geneExpression,syn26470348,1,GenomicsAssayTemplate,BFCBA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-092-B52E5,raw,polyAselection,JH-2-092,experimentalData,NTAP,JH-2-092_cNF_PT_2,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590028,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590028,2,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470359,65.0,Female,,efe63471-f9cf-450c-abb1-e52c631a2695,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Buttocks,geneExpression,syn26470359,2,GenomicsAssayTemplate,94G2C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-100-19H33,raw,polyAselection,JH-2-100,experimentalData,NTAP,JH-2-100_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590039,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590039,1,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15265528,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15265528,2,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47991816,22.0,Male,66,421e3c4f-2712-4f0d-aa4f-15492764f7c8,RNA-seq,115_D22,115_R22,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left buttocks,raw counts,syn47991816,2,RNASeqTemplate,4C392,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-115-6A3FB,raw,rRNAdepletion,JH-2-115,experimentalData,NTAP,JH-2-115_DifNF_PT_left_buttocks,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47993917,23.0,Male,70,943708ab-8def-4c6b-a6f3-f539baa50816,RNA-seq,028_D17,028_R17,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,cervical spine,raw counts,syn47993917,2,RNASeqTemplate,E4D24,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-028-3686C,raw,rRNAdepletion,JH-2-028,experimentalData,NTAP,JH-2-028-b_PN_PT_cervical_spine,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590403,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590403,2,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590425,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590425,1,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590304,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590304,1,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590436,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590436,2,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590315,23.0,Male,,ec2a3157-84ec-4b9a-a15e-6c0453d6d5d4,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590315,1,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590447,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590447,2,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590326,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590326,2,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590337,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590337,1,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590348,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590348,2,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn48001903,48.0,Male,86,702ee2fe-6660-4097-a0c5-803a99821e12,RNA-seq,120_D28,120_R28,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,right flank,raw counts,syn48001903,2,RNASeqTemplate,2HG48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-120-C4924,raw,rRNAdepletion,JH-2-120,experimentalData,NTAP,JH-2-120_PN_PT_right_flank_T2,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590117,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590117,2,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590359,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15590359,1,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470327,32.0,Male,,70053097-46cc-498a-9f51-e8e15413aa6f,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Brachial Plexus,geneExpression,syn26470327,2,GenomicsAssayTemplate,G36F6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-090-19D3F,raw,polyAselection,JH-2-090,experimentalData,NTAP,JH-2-090_DifNF_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590128,24.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,left paraspinal Tumor,geneExpression,syn15590128,2,,82G48,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-023-1G2BC,raw,rRNAdepletion,JH-2-023,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590018,10.0,Male,,d7291fc3-bb1a-46a8-b64f-6988c7b0b56e,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590018,2,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590139,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Scalp,geneExpression,syn15590139,2,,BAEBD,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-006-D6BA4,raw,rRNAdepletion,JH-2-006,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470349,36.0,Female,,6ad31109-13c4-46f8-8456-6daa524d8191,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Flank,geneExpression,syn26470349,2,GenomicsAssayTemplate,BFCBA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-092-B52E5,raw,polyAselection,JH-2-092,experimentalData,NTAP,JH-2-092_cNF_PT_2,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","same patient, different anatomical sites",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590029,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590029,1,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15261900,25.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"posterior cervical spine, C5-7",geneExpression,syn15261900,2,,C461C,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-019-DB5EH,raw,rRNAdepletion,JH-2-019,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15263803,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15263803,1,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590404,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590404,1,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590426,2.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Mid Upper Back,geneExpression,syn15590426,2,,G36A1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-032-AE88A,raw,rRNAdepletion,JH-2-032,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15270018,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15270018,1,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590305,12.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Retroperitoneal Tumor,geneExpression,syn15590305,2,,78GAB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-031-9GEA9,raw,rRNAdepletion,JH-2-031,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590437,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590437,1,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590316,23.0,Male,,d63e01e6-783f-4351-b0d8-b126c522dd05,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590316,2,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590327,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590327,1,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590338,44.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590338,2,,77BH3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-009-518B9,raw,rRNAdepletion,JH-2-009,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590228,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590228,2,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15263539,35.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left C2 cervical spine,geneExpression,syn15263539,1,,96B78,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-014-AH466,raw,rRNAdepletion,JH-2-014,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn26470328,34.0,Male,,b0f3ff22-2794-4078-8e15-80b64e529d24,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Sciatic Nerve,geneExpression,syn26470328,1,GenomicsAssayTemplate,GDFG1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-091-CAA8H,raw,polyAselection,JH-2-091,experimentalData,NTAP,JH-2-091_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590019,18.0,Female,,385a04df-df28-4fe0-942c-699812c0f6be,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590019,1,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15262803,10.0,Male,,,RNA-seq,,,cell line,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15262803,1,,2E57B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,Yes,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,FALSE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590405,29.0,Female,,,RNA-seq,,,primary tumor,,,Human,syn4939902,Tumor From Right Flank,geneExpression,syn15590405,2,,7B15A,,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-001-8A1B1,raw,rRNAdepletion,JH-2-001,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,,,,,, +syn15590427,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590427,1,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590306,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590306,1,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590438,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590438,2,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590207,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590207,2,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590328,10.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Pelvic Mass,geneExpression,syn15590328,2,,A71AA,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590218,13.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Supraclavicular,geneExpression,syn15590218,1,,HF616,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-026-9FD64,raw,rRNAdepletion,JH-2-026,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590339,31.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Femoral Nerve,geneExpression,syn15590339,1,,7HBG6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Nodular Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-021-6GFE7,raw,rRNAdepletion,JH-2-021,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590108,23.0,Male,,a63591a1-df67-4b6c-a0aa-b79a498d0763,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Sciatic Nerve,geneExpression,syn15590108,1,GenomicsAssayTemplate,2B9EB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-015-55B8D,raw,polyAselection,JH-2-015,experimentalData,NTAP,JH-2-015_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","","","",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn26470329,34.0,Male,,7778ffd1-7c12-4535-9a75-7ba5cb74be35,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Right Sciatic Nerve,geneExpression,syn26470329,2,GenomicsAssayTemplate,GDFG1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,Yes,151,JH-2-091-CAA8H,raw,polyAselection,JH-2-091,experimentalData,NTAP,JH-2-091_PN_PT,"",bulk cell,Not Applicable,WU_batch2,Flash frozen,,nerves,"","",Illumina NovaSeq 6000,No_report,-/-,"",Yes,"",forward,mechanical,fr-firststrand,,TruSeq standard total RNA library kit,,,,,,,,,,,"",,,, +syn15590406,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590406,1,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590417,10.0,Male,,37f5c2e0-7d56-4616-b49f-83727ca5ca7a,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590417,1,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590428,44.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Calf Mass,geneExpression,syn15590428,2,,7EC36,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-004-9D9D7,raw,rRNAdepletion,JH-2-004,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590307,8.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Sciatic Notch,geneExpression,syn15590307,2,,HC8GG,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-003-H3G1H,raw,rRNAdepletion,JH-2-003,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590439,10.0,Male,,,RNA-seq,,,xenograft passage,,,Homo sapiens,syn4939902,From sample 2-002-20,geneExpression,syn15590439,1,,3BAGC,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151,JH-2-002-GAF53,raw,rRNAdepletion,JH-2-002,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,xenograft,Primary Tumor,Mouse,Primary Tumor +syn15590329,18.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Lesion,geneExpression,syn15590329,1,,93DE8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-017-9FH8F,raw,rRNAdepletion,JH-2-017,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590407,41.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Chest Wall,geneExpression,syn15590407,2,,37B26,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-012-HE58H,raw,rRNAdepletion,JH-2-012,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590418,10.0,Male,,f474bc36-df16-487d-92e0-aedc782027d9,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Leg,geneExpression,syn15590418,2,GenomicsAssayTemplate,C5E25,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151bp,JH-2-002-FF824,raw,polyAselection,JH-2-002,experimentalData,NTAP,JH-2-002-b_PN_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590429,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15590429,1,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590319,18.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Right Thigh,geneExpression,syn15590319,1,,818HB,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-016-6H516,raw,rRNAdepletion,JH-2-016,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn43707288,12.0,Male,4,8a7796d8-5ac9-4370-b39a-885c4415300b,RNA-seq,,,primary tumor,,pairedEnd,Homo sapiens,syn4939902,Retroperitoneal,raw counts,syn43707288,2,RNASeqTemplate,DG6C8,,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,,Open Proposal Program,No,Yes,,JH-2-031-BFF3F,,rRNAdepletion,JH-2-031,experimentalData,NTAP,JH-2-031_MPNST_PT,"",,,WU_PDX_batch1,Flash frozen,,,,,,,,,No,,,,fr-firststrand,,TruSeq standard total RNA library kit,,4,4,,,,,,,,,,,, +syn47905483,24.0,Male,51,0ed486d4-273f-4736-b217-94eb32864c8d,RNA-seq,146_D13,146_R13,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,left flank,raw counts,syn47905483,1,RNASeqTemplate,7464G,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Diffuse Infiltrating Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-E79BF,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_DifNF_PT_left_flank,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15590408,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590408,1,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590419,18.0,Female,,4a302c21-e75c-413a-b235-69bc0a6aa98d,RNA-seq,,,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Left Superior Mediastinum,geneExpression,syn15590419,1,GenomicsAssayTemplate,15C1D,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,151bp,JH-2-016-4H597,raw,polyAselection,JH-2-016,experimentalData,NTAP,JH-2-016_MPNST_PT,"",bulk cell,"",JH_batch1,Flash frozen,,"","",JH_batch1,Illumina HiSeq 2500,50M,-/-,+/+,Yes,"","",mechanical,"",,TruSeq standard total RNA library kit,,,,,PRIVATE,FALSE,No,Biobank,No,NTAP Biobank,,,,, +syn15590309,38.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Left Femoral Nerve,geneExpression,syn15590309,1,,BB99B,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-010-H915D,raw,rRNAdepletion,JH-2-010,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15265809,32.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Arm,geneExpression,syn15265809,1,,AG2A6,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-007-B14BB,raw,rRNAdepletion,JH-2-007,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47908960,24.0,Male,58,8de1722f-2c79-4ffb-9bb7-57817980f221,RNA-seq,146_D14,146_R14,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,forehead,raw counts,syn47908960,2,RNASeqTemplate,935AE,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-146-38B3A,raw,rRNAdepletion,JH-2-146,experimentalData,NTAP,JH-2-146_PN_PT_forehead,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn15263929,15.0,Female,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,"Skin, superficial",geneExpression,syn15263929,1,,AA816,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Plexiform Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-013-7886G,raw,rRNAdepletion,JH-2-013,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn15590409,30.0,Male,,,RNA-seq,,,primary tumor,,,Homo sapiens,syn4939902,Middle Back,geneExpression,syn15590409,2,,GC2A3,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,151,JH-2-029-7AE7F,raw,rRNAdepletion,JH-2-029,experimentalData,NTAP,,"",bulk cell,,JH_batch1,,,,,more information in parent folder description,Illumina HiSeq 2500,25M,-/-,+/+,TRUE,,,,,,TruSeq,,,,3391263,REQUEST ACCESS,TRUE,No,Biobank,No,NTAP Biobank,,,,, +syn47902580,19.0,Female,45,b0db632c-5522-41b3-9f9d-95d6ab296d25,RNA-seq,079_D20,079_R20,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,left leg below knee,raw counts,syn47902580,1,RNASeqTemplate,22CC8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-079-HBHGH,raw,rRNAdepletion,JH-2-079,experimentalData,NTAP,JH-2-079-d_MPNST_RT_left_leg_below_knee,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47878172,37.0,Male,6,b820dc9e-8461-4068-8d1a-0027abc9dd3a,RNA-seq,038_D2,038_R2,primary tumor,years,pairedEnd,Homo sapiens,syn4939902,Scalp,raw counts,syn47878172,2,RNASeqTemplate,2HBA1,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Cutaneous Neurofibroma,fastq,Open Proposal Program,No,No,150,JH-2-038-1D23G,raw,rRNAdepletion,JH-2-038,experimentalData,NTAP,JH-2-038-c_cNF_PT_Scalp,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, +syn47903154,19.0,Female,47,43b86f68-ace9-469a-bacb-ff845d57cc37,RNA-seq,079_D20,079_R20,recurrent tumor,years,pairedEnd,Homo sapiens,syn4939902,left leg below knee,raw counts,syn47903154,1,RNASeqTemplate,22CC8,Neurofibromatosis type 1,The Johns Hopkins NF1 biospecimen repository,Malignant Peripheral Nerve Sheath Tumor,fastq,Open Proposal Program,No,No,150,JH-2-079-HBHGH,raw,rRNAdepletion,JH-2-079,experimentalData,NTAP,JH-2-079-d_MPNST_RT_left_leg_below_knee,"",bulk cell,Not Applicable,WU_batch3,Flash frozen,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, diff --git a/vignettes/revalidation-workflows.Rmd b/vignettes/revalidation-workflows.Rmd new file mode 100644 index 00000000..aa3096c5 --- /dev/null +++ b/vignettes/revalidation-workflows.Rmd @@ -0,0 +1,499 @@ +--- +title: "Revalidation workflows" +output: rmarkdown::html_vignette +vignette: > + %\VignetteIndexEntry{revalidation-workflows} + %\VignetteEngine{knitr::rmarkdown} + %\VignetteEncoding{UTF-8} +--- + + +This vignette demonstrates variants of metadata revalidation workflows. + + + +First set up as usual. + +```r + +library(nfportalutils) +syn_login(Sys.getenv("SYNAPSE_AUTH_TOKEN")) +``` + +## Basics with Schematic API service + +Schematic API only works with dataset folders currently. Find a dataset folder. + +1. To validate metadata, a manifest must be reconstituted. +Type `?manifest_generate` to read the docs. + +As seen in the params below, you do need to know the `data_type` to validate against. +The `data_type` is the same as the "Component" in the schematic data model (and so the exact term depends on the data model). +If feeling lucky, try `infer_data_type`. + +```r + +my_dataset <- "syn25386362" + +inferred <- infer_data_type(my_dataset) +inferred +#> $result +#> [1] "GenomicsAssayTemplate" +#> +#> $notes +#> [1] "" + +data_type <- inferred$result + +manifest_generate(data_type, + dataset_id = my_dataset, + schema_url = "https://raw.githubusercontent.com/nf-osi/nf-metadata-dictionary/main/NF.jsonld", + output_format = "google_sheet") # otherwise excel +#> Manifest generated as Googlesheet(s) +#> [[1]] +#> [1] "https://docs.google.com/spreadsheets/d/11ymlnESzn7XhHS3vHzlRFsDPhafJJehlhuCL9HgICt8" +``` + +2. Go to google_sheet and download as `.csv`. If Excel was chosen, open in some spreadsheet editor and resave file as `.csv`. +Then validate. + +```r +manifest_validate(data_type = data_type, + file_name = "GenomicsAssayTemplate - Sheet1.csv") +#> $errors +#> $errors[[1]] +#> $errors[[1]][[1]] +#> [1] "2" +#> +#> $errors[[1]][[2]] +#> [1] "assay" +#> +#> $errors[[1]][[3]] +#> [1] "'' is not one of ['NIH Toolbox', 'STR profile', 'traction force microscopy', 'massively parallel reporter assay', 'gait measurement', 'conventional MRI', 'functional MRI', 'immunoassay', 'contextual conditioning behavior assay', 'genotyping', 'DNA optical mapping', 'NOMe-seq', 'Social Responsiveness Scale', 'targeted exome sequencing', '2D AlamarBlue fluorescence', 'TMT quantitation', 'liquid chromatography-electrochemical detection', 'whole genome sequencing', 'Riccardi and Ablon scales', 'cell" +#> +#> $errors[[1]][[4]] +#> [1] "" +#> +#> +#> $errors[[2]] +#> $errors[[2]][[1]] +#> [1] "2" +#> +#> $errors[[2]][[2]] +#> [1] "specimenID" +#> +#> $errors[[2]][[3]] +#> [1] "'' is too short" +#> +#> $errors[[2]][[4]] +#> [1] "" +#> +#> +#> $errors[[3]] +#> $errors[[3]][[1]] +#> [1] "2" +#> +#> $errors[[3]][[2]] +#> [1] "libraryStrand" +#> +#> $errors[[3]][[3]] +#> [1] "'' is not one of ['FirstStranded', 'Unstranded', 'Not Applicable', 'SecondStranded']" +#> +#> $errors[[3]][[4]] +#> [1] "" +#> +#> +#> $errors[[4]] +#> $errors[[4]][[1]] +#> [1] "2" +#> +#> $errors[[4]][[2]] +#> [1] "tumorType" +#> +#> $errors[[4]][[3]] +#> [1] "'' is not one of ['Anaplastic Ganglioglioma', 'Anaplastic Astrocytoma', 'Nodular Neurofibroma', 'Meningioma', 'Fibrosarcoma', 'Localized Neurofibroma', 'Glioblastoma', 'Malignant Peripheral Nerve Sheath Tumor', 'Anaplastic Pleomorphic Xanthoastrocytoma', 'Atypical Neurofibroma', 'tumor', 'Colorectal Adenocarcinoma', 'Recurrent MPNST', 'Pilocytic Astrocytoma', 'Ganglioglioma', 'Optic Pathway Glioma', 'Neurofibroma', 'Necrotic Neoplasm', 'Glioma', 'Teratoma', 'Cutaneous Neurofibroma', 'Fibromatosi" +#> +#> $errors[[4]][[4]] +#> [1] "" +#> +#> +#> $errors[[5]] +#> $errors[[5]][[1]] +#> [1] "2" +#> +#> $errors[[5]][[2]] +#> [1] "libraryPreparationMethod" +#> +#> $errors[[5]][[3]] +#> [1] "'' is not one of ['CEL-seq', 'NEBNext mRNA Library Prep Reagent Set for Illumina', '10x', 'GTAC@WUSTL in-house prep', 'KAPA mRNA HyperPrep Kit', 'TruSeq', 'unknown', 'KAPA HyperPrep Kit PCR-free', 'Illumina TruSeq DNA Nano', 'TruSeq standard total RNA library kit', 'QuantSeq FWD V2 with UDI', 'Drop-Seq', 'KAPA RNA HyperPrep Kit with RiboErase (HMR)', 'Smart-seq4', 'IDT xGen Exome Research Panel', 'Smart-seq2', 'Omni-ATAC']" +#> +#> $errors[[5]][[4]] +#> [1] "" +#> +#> +#> $errors[[6]] +#> $errors[[6]][[1]] +#> [1] "2" +#> +#> $errors[[6]][[2]] +#> [1] "individualID" +#> +#> $errors[[6]][[3]] +#> [1] "'' is too short" +#> +#> $errors[[6]][[4]] +#> [1] "" +#> +#> +#> $errors[[7]] +#> $errors[[7]][[1]] +#> [1] "2" +#> +#> $errors[[7]][[2]] +#> [1] "platform" +#> +#> $errors[[7]][[3]] +#> [1] "'' is not one of ['Illumina Genome Analyzer IIx', 'Illumina HiSeq X', 'Perlegen 300Karray', 'Vevo 3100 Imaging System', 'Illumina MouseWG-6 v2.0 expression beadchip', 'Illumina Infinium MethylationEPIC BeadChip v2.0 (935k)', 'Vectra H1 3D Imaging System', 'Nanostring Counter', 'Illumina Infinium MethylationEPIC BeadChip v1.0 (850k)', 'Illumina HumanOmniExpress-24 v1.0 BeadChip', 'Illumina HumanOmni1-Quadv1.0', 'LifeViz Micro System', 'LI-COR Odyssey CLx', 'Illumina HumanMethylation450', 'Illumin" +#> +#> $errors[[7]][[4]] +#> [1] "" +#> +#> +#> $errors[[8]] +#> $errors[[8]][[1]] +#> [1] "2" +#> +#> $errors[[8]][[2]] +#> [1] "specimenPreparationMethod" +#> +#> $errors[[8]][[3]] +#> [1] "'' is not one of ['FFPE', 'OCT', 'RNAlater', 'Viably frozen', 'Fresh collected', 'Cryopreserved', 'formalin-fixed', 'Flash frozen', 'ethanol']" +#> +#> $errors[[8]][[4]] +#> [1] "" +#> +#> +#> $errors[[9]] +#> $errors[[9]][[1]] +#> [1] "2" +#> +#> $errors[[9]][[2]] +#> [1] "species" +#> +#> $errors[[9]][[3]] +#> [1] "'' is not one of ['Rattus norvegicus', 'Gallus gallus', 'Danio rerio', 'Sus scrofa', 'Drosophila melanogaster', 'Oryctolagus cuniculus', 'Pan troglodytes', 'Rhesus macaque', 'Mus musculus (humanized)', 'Homo sapiens', 'Mus musculus']" +#> +#> $errors[[9]][[4]] +#> [1] "" +#> +#> +#> $errors[[10]] +#> $errors[[10]][[1]] +#> [1] "3" +#> +#> $errors[[10]][[2]] +#> [1] "assay" +#> +#> $errors[[10]][[3]] +#> [1] "'' is not one of ['NIH Toolbox', 'STR profile', 'traction force microscopy', 'massively parallel reporter assay', 'gait measurement', 'conventional MRI', 'functional MRI', 'immunoassay', 'contextual conditioning behavior assay', 'genotyping', 'DNA optical mapping', 'NOMe-seq', 'Social Responsiveness Scale', 'targeted exome sequencing', '2D AlamarBlue fluorescence', 'TMT quantitation', 'liquid chromatography-electrochemical detection', 'whole genome sequencing', 'Riccardi and Ablon scales', 'cell" +#> +#> $errors[[10]][[4]] +#> [1] "" +#> +#> +#> $errors[[11]] +#> $errors[[11]][[1]] +#> [1] "3" +#> +#> $errors[[11]][[2]] +#> [1] "specimenID" +#> +#> $errors[[11]][[3]] +#> [1] "'' is too short" +#> +#> $errors[[11]][[4]] +#> [1] "" +#> +#> +#> $errors[[12]] +#> $errors[[12]][[1]] +#> [1] "3" +#> +#> $errors[[12]][[2]] +#> [1] "libraryStrand" +#> +#> $errors[[12]][[3]] +#> [1] "'' is not one of ['FirstStranded', 'Unstranded', 'Not Applicable', 'SecondStranded']" +#> +#> $errors[[12]][[4]] +#> [1] "" +#> +#> +#> $errors[[13]] +#> $errors[[13]][[1]] +#> [1] "3" +#> +#> $errors[[13]][[2]] +#> [1] "tumorType" +#> +#> $errors[[13]][[3]] +#> [1] "'' is not one of ['Anaplastic Ganglioglioma', 'Anaplastic Astrocytoma', 'Nodular Neurofibroma', 'Meningioma', 'Fibrosarcoma', 'Localized Neurofibroma', 'Glioblastoma', 'Malignant Peripheral Nerve Sheath Tumor', 'Anaplastic Pleomorphic Xanthoastrocytoma', 'Atypical Neurofibroma', 'tumor', 'Colorectal Adenocarcinoma', 'Recurrent MPNST', 'Pilocytic Astrocytoma', 'Ganglioglioma', 'Optic Pathway Glioma', 'Neurofibroma', 'Necrotic Neoplasm', 'Glioma', 'Teratoma', 'Cutaneous Neurofibroma', 'Fibromatosi" +#> +#> $errors[[13]][[4]] +#> [1] "" +#> +#> +#> $errors[[14]] +#> $errors[[14]][[1]] +#> [1] "3" +#> +#> $errors[[14]][[2]] +#> [1] "libraryPreparationMethod" +#> +#> $errors[[14]][[3]] +#> [1] "'' is not one of ['CEL-seq', 'NEBNext mRNA Library Prep Reagent Set for Illumina', '10x', 'GTAC@WUSTL in-house prep', 'KAPA mRNA HyperPrep Kit', 'TruSeq', 'unknown', 'KAPA HyperPrep Kit PCR-free', 'Illumina TruSeq DNA Nano', 'TruSeq standard total RNA library kit', 'QuantSeq FWD V2 with UDI', 'Drop-Seq', 'KAPA RNA HyperPrep Kit with RiboErase (HMR)', 'Smart-seq4', 'IDT xGen Exome Research Panel', 'Smart-seq2', 'Omni-ATAC']" +#> +#> $errors[[14]][[4]] +#> [1] "" +#> +#> +#> $errors[[15]] +#> $errors[[15]][[1]] +#> [1] "3" +#> +#> $errors[[15]][[2]] +#> [1] "individualID" +#> +#> $errors[[15]][[3]] +#> [1] "'' is too short" +#> +#> $errors[[15]][[4]] +#> [1] "" +#> +#> +#> $errors[[16]] +#> $errors[[16]][[1]] +#> [1] "3" +#> +#> $errors[[16]][[2]] +#> [1] "platform" +#> +#> $errors[[16]][[3]] +#> [1] "'' is not one of ['Illumina Genome Analyzer IIx', 'Illumina HiSeq X', 'Perlegen 300Karray', 'Vevo 3100 Imaging System', 'Illumina MouseWG-6 v2.0 expression beadchip', 'Illumina Infinium MethylationEPIC BeadChip v2.0 (935k)', 'Vectra H1 3D Imaging System', 'Nanostring Counter', 'Illumina Infinium MethylationEPIC BeadChip v1.0 (850k)', 'Illumina HumanOmniExpress-24 v1.0 BeadChip', 'Illumina HumanOmni1-Quadv1.0', 'LifeViz Micro System', 'LI-COR Odyssey CLx', 'Illumina HumanMethylation450', 'Illumin" +#> +#> $errors[[16]][[4]] +#> [1] "" +#> +#> +#> $errors[[17]] +#> $errors[[17]][[1]] +#> [1] "3" +#> +#> $errors[[17]][[2]] +#> [1] "specimenPreparationMethod" +#> +#> $errors[[17]][[3]] +#> [1] "'' is not one of ['FFPE', 'OCT', 'RNAlater', 'Viably frozen', 'Fresh collected', 'Cryopreserved', 'formalin-fixed', 'Flash frozen', 'ethanol']" +#> +#> $errors[[17]][[4]] +#> [1] "" +#> +#> +#> $errors[[18]] +#> $errors[[18]][[1]] +#> [1] "3" +#> +#> $errors[[18]][[2]] +#> [1] "species" +#> +#> $errors[[18]][[3]] +#> [1] "'' is not one of ['Rattus norvegicus', 'Gallus gallus', 'Danio rerio', 'Sus scrofa', 'Drosophila melanogaster', 'Oryctolagus cuniculus', 'Pan troglodytes', 'Rhesus macaque', 'Mus musculus (humanized)', 'Homo sapiens', 'Mus musculus']" +#> +#> $errors[[18]][[4]] +#> [1] "" +#> +#> +#> +#> $warnings +#> $warnings[[1]] +#> $warnings[[1]][[1]] +#> [1] "2" +#> +#> $warnings[[1]][[2]] +#> [1] "age" +#> +#> $warnings[[1]][[3]] +#> [1] "On row 2 the attribute age does not contain the proper value type num." +#> +#> $warnings[[1]][[4]] +#> [1] "" +#> +#> +#> $warnings[[2]] +#> $warnings[[2]][[1]] +#> [1] "3" +#> +#> $warnings[[2]][[2]] +#> [1] "age" +#> +#> $warnings[[2]][[3]] +#> [1] "On row 3 the attribute age does not contain the proper value type num." +#> +#> $warnings[[2]][[4]] +#> [1] "" +#> +#> +#> $warnings[[3]] +#> $warnings[[3]][[1]] +#> $warnings[[3]][[1]][[1]] +#> [1] "2" +#> +#> $warnings[[3]][[1]][[2]] +#> [1] "3" +#> +#> +#> $warnings[[3]][[2]] +#> [1] "readPair" +#> +#> $warnings[[3]][[3]] +#> [1] "readPair values in rows ['2', '3'] are out of the specified range." +#> +#> $warnings[[3]][[4]] +#> $warnings[[3]][[4]][[1]] +#> [1] "" +#> +#> +#> +#> $warnings[[4]] +#> $warnings[[4]][[1]] +#> [1] "2" +#> +#> $warnings[[4]][[2]] +#> [1] "readLength" +#> +#> $warnings[[4]][[3]] +#> [1] "On row 2 the attribute readLength does not contain the proper value type int." +#> +#> $warnings[[4]][[4]] +#> [1] "" +#> +#> +#> $warnings[[5]] +#> $warnings[[5]][[1]] +#> [1] "3" +#> +#> $warnings[[5]][[2]] +#> [1] "readLength" +#> +#> $warnings[[5]][[3]] +#> [1] "On row 3 the attribute readLength does not contain the proper value type int." +#> +#> $warnings[[5]][[4]] +#> [1] "" +#> +#> +#> $warnings[[6]] +#> $warnings[[6]][[1]] +#> [1] "2" +#> +#> $warnings[[6]][[2]] +#> [1] "readDepth" +#> +#> $warnings[[6]][[3]] +#> [1] "On row 2 the attribute readDepth does not contain the proper value type int." +#> +#> $warnings[[6]][[4]] +#> [1] "" +#> +#> +#> $warnings[[7]] +#> $warnings[[7]][[1]] +#> [1] "3" +#> +#> $warnings[[7]][[2]] +#> [1] "readDepth" +#> +#> $warnings[[7]][[3]] +#> [1] "On row 3 the attribute readDepth does not contain the proper value type int." +#> +#> $warnings[[7]][[4]] +#> [1] "" +#> +#> +#> $warnings[[8]] +#> $warnings[[8]][[1]] +#> [1] "2" +#> +#> $warnings[[8]][[2]] +#> [1] "experimentalTimepoint" +#> +#> $warnings[[8]][[3]] +#> [1] "On row 2 the attribute experimentalTimepoint does not contain the proper value type num." +#> +#> $warnings[[8]][[4]] +#> [1] "" +#> +#> +#> $warnings[[9]] +#> $warnings[[9]][[1]] +#> [1] "3" +#> +#> $warnings[[9]][[2]] +#> [1] "experimentalTimepoint" +#> +#> $warnings[[9]][[3]] +#> [1] "On row 3 the attribute experimentalTimepoint does not contain the proper value type num." +#> +#> $warnings[[9]][[4]] +#> [1] "" +``` + +3. Make corrections in the `.csv` according to validation laundry list. + +4. Submit corrected manifest via DCA. + +## Alternative with dataset entity + +For working with dataset entities or doing extra checks, this slightly different workflow can be applied instead. +Dataset entities may be more complicated because they can combine files in different times and places (batches). + +1. Generate a manifest for Synapse dataset entity. +We need to use `remanifest`; to understand differences, read the docs by running `?remanifest`. + +```r +datasets <- list_project_datasets(project_id = "syn4939902", type = "dataset") +new_datasets <- Filter(function(d) as.Date(d$createdOn) > as.Date("2023-12-01"), datasets) # or filter by name +``` + +We will use the first item as the demo. + +```r +test <- new_datasets[[1]]$id +remanifest(test, file = "manifest_rd1.csv") +#> ✔️ Saved manifest as manifest_rd1.csv +``` + +For reproducibility this original manifest "manifest_rd1.csv" is in the vignettes folder. + +2. Run precheck. + +```r +precheck_manifest("manifest_rd1.csv") +#> ❌ Multiple components detected in a single manifest: 'RNASeqTemplate', 'GenomicsAssayTemplate', ''. This can happen when files were annotated at different eras. +#> Suggestions: 1) Split up the manifest because schematic can only validate one type at a type. 2) Harmonize the components if this is sensible. +#> For example, RNASeqTemplate is an alias for GenomicsAssayTemplate +#> ❌ Blank value '' for Component detected. This can happen because files were annotated before 2022, when Component was introduced for most DCCs. +#> ❌ The pattern of these attribute names suggest duplicates: '...1', '...44', '...46'. This may happen when metadata is supplemented programmatically with a data-type mismatch +#> ⚠️ An attribute `Uuid` is present and should preferably be removed. See issue # . +#> ⚠️ An attribute `eTag` is present and preferably be removed. +#> ℹ️ Custom attributes (not documented in data model) were found: 'entityId', '...1', 'Uuid', 'DNA_ID', 'RNA_ID', 'tissue', 'bodyPart', 'parentSpecimenId', 'eTag', '...44', '...46', 'accessTeam', 'accessType', 'sciDataRelease', 'specimenIdSource', 'timePointUnit', 'transplantationDonorTissue', 'transplantationDonorSpecies'. In general, custom attributes added by the researcher to help with data management are fine. +#> Just check that they are not PHI or added by mistake. If they are deemed generally useful or important enough, they can also be documented officially in the data model for others to reference. +``` + +3. Make a copy of "manifest_rd1.csv", e.g. "manifest_rd1_corrected.csv" and use precheck notes to help make corrections. + +4. Validate "manifest_rd1_corrected.csv" using schematic service (same as above, not run since general validation output has already been shown). + +5. Make *more* corrections as needed. + +6. Finally submit corrected manifest. diff --git a/vignettes/revalidation-workflows.Rmd.orig b/vignettes/revalidation-workflows.Rmd.orig new file mode 100644 index 00000000..5f638574 --- /dev/null +++ b/vignettes/revalidation-workflows.Rmd.orig @@ -0,0 +1,95 @@ +--- +title: "Revalidation workflows" +output: rmarkdown::html_vignette +vignette: > + %\VignetteIndexEntry{revalidation-workflows} + %\VignetteEngine{knitr::rmarkdown} + %\VignetteEncoding{UTF-8} +--- + + +This vignette demonstrates variants of metadata revalidation workflows. + +```{r, include = FALSE} +knitr::opts_chunk$set( + collapse = TRUE, + comment = "#>" +) +``` + +First set up as usual. +```{r setup, cache=TRUE} + +library(nfportalutils) +syn_login(Sys.getenv("SYNAPSE_AUTH_TOKEN")) +``` + +## Basics with Schematic API service + +Schematic API only works with dataset folders currently. Find a dataset folder. + +1. To validate metadata, a manifest must be reconstituted. +Type `?manifest_generate` to read the docs. + +As seen in the params below, you do need to know the `data_type` to validate against. +The `data_type` is the same as the "Component" in the schematic data model (and so the exact term depends on the data model). +If feeling lucky, try `infer_data_type`. +```{r} + +my_dataset <- "syn25386362" + +inferred <- infer_data_type(my_dataset) +inferred + +data_type <- inferred$result + +manifest_generate(data_type, + dataset_id = my_dataset, + schema_url = "https://raw.githubusercontent.com/nf-osi/nf-metadata-dictionary/main/NF.jsonld", + output_format = "google_sheet") # otherwise excel +``` + +2. Go to google_sheet and download as `.csv`. If Excel was chosen, open in some spreadsheet editor and resave file as `.csv`. +Then validate. +```{r} +manifest_validate(data_type = data_type, + file_name = "GenomicsAssayTemplate - Sheet1.csv") +``` + +3. Make corrections in the `.csv` according to validation laundry list. + +4. Submit corrected manifest via DCA. + +## Alternative with dataset entity + +For working with dataset entities or doing extra checks, this slightly different workflow can be applied instead. +Dataset entities may be more complicated because they can combine files in different times and places (batches). + +1. Generate a manifest for Synapse dataset entity. +We need to use `remanifest`; to understand differences, read the docs by running `?remanifest`. +```{r} +datasets <- list_project_datasets(project_id = "syn4939902", type = "dataset") +new_datasets <- Filter(function(d) as.Date(d$createdOn) > as.Date("2023-12-01"), datasets) # or filter by name + +``` + +We will use the first item as the demo. +```{r} +test <- new_datasets[[1]]$id +remanifest(test, file = "manifest_rd1.csv") +``` + +For reproducibility this original manifest "manifest_rd1.csv" is in the vignettes folder. + +2. Run precheck. +```{r} +precheck_manifest("manifest_rd1.csv") +``` + +3. Make a copy of "manifest_rd1.csv", e.g. "manifest_rd1_corrected.csv" and use precheck notes to help make corrections. + +4. Validate "manifest_rd1_corrected.csv" using schematic service (same as above, not run since general validation output has already been shown). + +5. Make *more* corrections as needed. + +6. Finally submit corrected manifest.