Skip to content

Commit

Permalink
Merge pull request #9 from CRI-iAtlas/new_api
Browse files Browse the repository at this point in the history
updated to use new api
  • Loading branch information
andrewelamb authored Jun 29, 2023
2 parents 5f431f6 + c08256a commit 26faec0
Show file tree
Hide file tree
Showing 17 changed files with 220 additions and 146 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ export(query_immunomodulators)
export(query_io_targets)
export(query_mutation_statuses)
export(query_mutations)
export(query_neoantigens)
export(query_nodes)
export(query_patient_slides)
export(query_patients)
Expand Down
2 changes: 1 addition & 1 deletion R/api_cohorts_queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ query_cohort_features <- function(
),
...
)
if(nrow(tbl) == 0) return(tbl)
if (nrow(tbl) == 0) return(tbl)
else {
tbl <- tbl %>%
tidyr::unnest(cols = "features", keep_empty = T) %>%
Expand Down
1 change: 1 addition & 0 deletions R/api_functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ perform_api_query <- function(
if(!is.null(.GlobalEnv$API_URL)){
api_url <- .GlobalEnv$API_URL
}
api_url <- "https://api-staging.cri-iatlas.org/api"
ghql_con <- ghql::GraphqlClient$new(api_url)
ghql_query_obj <- ghql::Query$new()
query_path <- file.path(query_dir, query_file)
Expand Down
2 changes: 1 addition & 1 deletion R/api_genes_queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -264,7 +264,7 @@ query_gene_nanostring_expression <- function(
),
...
)
if(nrow(tbl) == 0) return(tbl)
if (nrow(tbl) == 0) return(tbl)
else {
tbl %>%
tidyr::unnest(cols = "samples", keep_empty = T) %>%
Expand Down
44 changes: 44 additions & 0 deletions R/api_neoantigens_queries.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
#' Query Neoantigens
#'
#' @param pmhcs A vector of strings
#' @param entrez A vector of integers
#' @param patients A vector of strings
#' @param paging A named list
#' @param ... Arguments to create_result_from_api_query
#'
#' @export
query_neoantigens <- function(
pmhcs = NA,
entrez = NA,
patients = NA,
paging = NA,
...
){
create_result_from_cursor_paginated_api_query(
query_args = list(
"pmhc" = pmhcs,
"entrez" = entrez,
"patient" = patients,
"paging" = paging,
"distinct" = F
),
query_file = "neoantigens.txt",
default_tbl = dplyr::tibble(
"tpm" = double(),
"pmhc" = character(),
"freq_pmhc" = integer(),
"patient" = character(),
"gene_entrez" = integer(),
"gene_hgnc" = character(),
),
select_cols = c(
"tpm" = "tpm",
"pmhc" = "pmhc",
"freq_pmhc" = "freqPmhc",
"patient" = "patient.barcode",
"gene_entrez" = "gene.entrez",
"gene_hgnc" = "gene.hgnc"
),
...
)
}
38 changes: 38 additions & 0 deletions inst/queries/neoantigens.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
query Neoantigens(
$paging: PagingInput
$distinct:Boolean
$entrez: [Int!]
$patient: [String!]
$pmhc: [String!]
){
neoantigens(
paging: $paging
distinct: $distinct
entrez: $entrez
patient: $patient
pmhc: $pmhc
){
items {
tpm
pmhc
freqPmhc
patient { barcode }
gene {
entrez
hgnc
}
}
paging{
type
pages
total
page
limit
hasNextPage
hasPreviousPage
startCursor
endCursor
}
error
}
}
22 changes: 22 additions & 0 deletions man/query_neoantigens.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions tests/testthat/helper-globals.R
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
query_dir <- system.file("queries", package = "iatlasGraphQLClient")
api_url <- "https://api.cri-iatlas.org/api"
test_api_url <- "https://api-staging.cri-iatlas.org/api"
local_api_url <- "http://localhost:5000/graphiql"
55 changes: 8 additions & 47 deletions tests/testthat/test-api_cohorts_queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -22,29 +22,22 @@ test_that("query_cohorts", {
expect_named(result1, expected_columns1)
expect_equal(nrow(result1), 1)


result2 <- query_cohorts(
cohort = "TCGA_Gender",
cohort = "TCGA",
query_dir = query_dir
)

expect_named(result2, expected_columns1)
expect_named(result2, expected_columns2)
expect_equal(nrow(result2), 1)

result3 <- query_cohorts(
cohort = "TCGA",
query_dir = query_dir
)

expect_named(result3, expected_columns2)
expect_equal(nrow(result3), 1)

result4 <- query_cohorts(
cohort = "not_a_cohort",
query_dir = query_dir
)

expect_named(result4, c('name'))
expect_equal(nrow(result4), 0)
expect_named(result3, c('name'))
expect_equal(nrow(result3), 0)
})

test_that("query_cohort_features", {
Expand All @@ -62,16 +55,8 @@ test_that("query_cohort_features", {
expect_named(result1, expected_columns)
expect_true(nrow(result1) > 1)

result2 <- query_cohort_features(
cohorts = "PCAWG_Gender",
query_dir = query_dir
)

expect_named(result2, expected_columns)
expect_true(nrow(result2) > 1)

result3 <- query_cohort_features(
cohort = "PCAWG",
cohort = "TCGA",
query_dir = query_dir
)

Expand Down Expand Up @@ -102,14 +87,6 @@ test_that("query_cohort_genes", {
expect_named(result1, expected_columns)
expect_true(nrow(result1) > 1)

result2 <- query_cohort_genes(
cohorts = "TCGA_Gender",
query_dir = query_dir
)

expect_named(result2, expected_columns)
expect_true(nrow(result2) > 1)

result3 <- query_cohort_genes(
cohort = "TCGA",
query_dir = query_dir
Expand Down Expand Up @@ -149,14 +126,6 @@ test_that("query_cohort_mutations", {
expect_named(result1, expected_columns1)
expect_true(nrow(result1) > 1)

result2 <- query_cohort_mutations(
cohorts = "TCGA_Gender",
query_dir = query_dir
)

expect_named(result2, expected_columns1)
expect_true(nrow(result2) > 1)

result3 <- query_cohort_mutations(
cohort = "TCGA",
query_dir = query_dir
Expand Down Expand Up @@ -197,23 +166,15 @@ test_that("query_cohort_samples", {
)

result1 <- query_cohort_samples(
cohorts = "PCAWG_Immune_Subtype",
cohorts = "TCGA_Immune_Subtype",
query_dir = query_dir
)

expect_named(result1, expected_columns1)
expect_true(nrow(result1) > 1)

result2 <- query_cohort_samples(
cohorts = "PCAWG_Gender",
query_dir = query_dir
)

expect_named(result2, expected_columns1)
expect_true(nrow(result2) > 1)

result3 <- query_cohort_samples(
cohort = "PCAWG",
cohort = "TCGA",
query_dir = query_dir
)

Expand Down
1 change: 0 additions & 1 deletion tests/testthat/test-api_copy_number_result_queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ test_that("query_copy_number_results",{
datasets = "TCGA",
tags = "C1",
max_p_value = 0.000000000000000000000000000000000000000000000001,
entrez = 1,
query_dir = query_dir
)
expect_named(result1, expected_columns)
Expand Down
2 changes: 1 addition & 1 deletion tests/testthat/test-api_datasets_queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ test_that("query_dataset_tags", {
"dataset_type"
)

result1 <- query_dataset_tags(datasets = "PCAWG", query_dir = query_dir)
result1 <- query_dataset_tags(datasets = "TCGA", query_dir = query_dir)
expect_named(result1, expected_names)
expect_true(nrow(result1) > 0)

Expand Down
4 changes: 2 additions & 2 deletions tests/testthat/test-api_features_queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ test_that("query_feature_values", {
test_that("query_features_range", {
expected_columns <- c("name", "display", "value_min", "value_max")
result1 <- query_features_range(
cohorts = "PCAWG_Gender",
cohorts = "TCGA_Immune_Subtype",
features = "Lymphocytes_Aggregate1",
query_dir = query_dir
)
Expand All @@ -63,7 +63,7 @@ test_that("query_features_range", {
expect_true(result1$value_min <= result1$value_max)

result2 <- query_features_range(
cohorts = "PCAWG_Gender",
cohorts = "TCGA_Immune_Subtype",
features = "not_a_feature",
query_dir = query_dir
)
Expand Down
13 changes: 0 additions & 13 deletions tests/testthat/test-api_functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -248,19 +248,6 @@ test_that("do_cursor_paginated_api_query", {

test_that("do_offset_paginated_api_query", {

result1 <- do_offset_paginated_api_query(
query_args = list(
paging = list("limit" = 10),
feature = "frac_altered",
maxPValue = 0.1e-170,
distinct = T
),
query_file = "pagination_test.txt",
query_dir = query_dir
)
expect_type(result1, "list")
expect_true(length(result1) > 1)

result2 <- do_offset_paginated_api_query(
query_args = list(
paging = list("first" = 10),
Expand Down
4 changes: 2 additions & 2 deletions tests/testthat/test-api_genes_queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -86,8 +86,8 @@ test_that("query_gene_nanostring_expression", {
"nanostring_expr"
)
result1 <- query_gene_nanostring_expression(
entrez = 259L,
samples = "Prins_GBM_2019-SK08-ar-A07",
entrez = 4282L,
samples = "Chen_CanDisc_2016-c25-ar-c25_pre",
query_dir = query_dir
)
expect_named(result1, expected_columns)
Expand Down
12 changes: 6 additions & 6 deletions tests/testthat/test-api_germline_gwas_results_queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ test_that("query_germline_gwas_results",{
)
result1 <- query_germline_gwas_results(
datasets = "TCGA",
feature = "Attractors_G_SIGLEC9",
snps = "2:206655924:C:T",
feature = "Module3_IFN_score",
snps = "3:133016759:C:G",
query_dir = query_dir
)

Expand All @@ -27,14 +27,14 @@ test_that("query_germline_gwas_results",{

result2 <- query_germline_gwas_results(
datasets = "TCGA",
min_p_value = 4.24e-25,
max_p_value = 5.25e-25,
min_p_value = 1.0e-07,
max_p_value = 9.9e-07,
query_dir = query_dir
)
expect_named(result2, expected_columns)
expect_true(nrow(result2) > 0)
expect_true(all(result2$p_value >= 4.24e-25))
expect_true(all(result2$p_value <= 5.25e-25))
expect_true(all(result2$p_value >= 1.0e-07))
expect_true(all(result2$p_value <= 9.9e-07))

result3 <- query_germline_gwas_results(
datasets = "TCGA",
Expand Down
24 changes: 24 additions & 0 deletions tests/testthat/test-api_neoantigens.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@

test_that("query_neoantigens",{
expected_columns <- c(
"tpm",
"pmhc",
"freq_pmhc",
"patient",
"gene_entrez",
"gene_hgnc"
)
result1 <- query_neoantigens(
pmhcs = list("RLMELQEAV HLA_A*02:01 SPAG9"),
patients = list("VanAllen_antiCTLA4_2015-p126"),
query_dir = query_dir
)
result2 <- query_neoantigens(
pmhcs = list("xxx"),
query_dir = query_dir
)
expect_named(result1, expected_columns)
expect_named(result2, expected_columns)
expect_true(nrow(result1) > 0)
expect_equal(nrow(result2), 0)
})
Loading

0 comments on commit 26faec0

Please sign in to comment.