blob: 2aa7137477a359a092aaef2a8c88d771ffdc199c [file] [log] [blame]
Marc Kupietz06143702025-07-05 17:49:31 +02001# Helper function to find README.md file in current or parent directories
2find_readme_path <- function() {
3 readme_paths <- c("Readme.md", "../Readme.md", "../../Readme.md")
4 for (path in readme_paths) {
5 if (file.exists(path)) {
6 return(path)
7 }
8 }
9 return(NULL)
10}
11
12# Helper function to read README content
13read_readme_content <- function() {
14 readme_path <- find_readme_path()
15 if (is.null(readme_path)) {
16 return(NULL)
17 }
18 readme_content <- readLines(readme_path)
19 paste(readme_content, collapse = "\n")
20}
21
22# Helper function to call OpenAI API
23call_openai_api <- function(prompt, max_tokens = 500, temperature = 0.1) {
24 library(httr2)
25 library(jsonlite)
26
27 tryCatch({
28 response <- request("https://api.openai.com/v1/chat/completions") |>
29 req_headers(
30 "Authorization" = paste("Bearer", Sys.getenv("OPENAI_API_KEY")),
31 "Content-Type" = "application/json"
32 ) |>
33 req_body_json(list(
34 model = "gpt-4.1-mini",
35 messages = list(
36 list(role = "user", content = prompt)
37 ),
38 max_tokens = max_tokens,
39 temperature = temperature
40 )) |>
41 req_retry(max_tries = 3) |>
42 req_perform()
43
44 # Parse the response
45 result <- response |> resp_body_json()
46 result$choices[[1]]$message$content
47 }, error = function(e) {
48 if (grepl("429", as.character(e))) {
49 skip("OpenAI API rate limit exceeded - please try again later or check your API key/credits")
50 } else if (grepl("401", as.character(e))) {
51 skip("OpenAI API authentication failed - please check your OPENAI_API_KEY")
52 } else {
53 stop(paste("OpenAI API error:", as.character(e)))
54 }
55 })
56}
57
Marc Kupietz10dcfee2025-07-05 19:13:27 +020058# KorAP URL for testing
59KORAP_URL <- "https://korap.ids-mannheim.de/instance/wiki"
60
Marc Kupietz06143702025-07-05 17:49:31 +020061# Helper function to create README-guided prompt
62create_readme_prompt <- function(task_description, specific_task) {
63 readme_text <- read_readme_content()
64 if (is.null(readme_text)) {
65 stop("README.md not found")
66 }
67
68 paste0(
69 "You are an expert R programmer. Based on the following README documentation for the RKorAPClient package, ",
70 task_description, "\n\n",
Marc Kupietz10dcfee2025-07-05 19:13:27 +020071 "IMPORTANT: Use the KorAP URL '", KORAP_URL, "' as the KorAPUrl parameter in KorAPConnection.\n\n",
Marc Kupietz06143702025-07-05 17:49:31 +020072 "README Documentation:\n",
73 readme_text,
74 "\n\nTask: ", specific_task,
75 "\n\nProvide only the R code without explanations."
76 )
77}
78
79# Helper function to extract R code from markdown code blocks
80extract_r_code <- function(response_text) {
81 # Remove markdown code blocks if present
82 code <- gsub("```[rR]?\\n?", "", response_text)
83 code <- gsub("```\\n?$", "", code)
84 # Remove leading/trailing whitespace
85 trimws(code)
86}
87
88test_that("GPT-4.1 mini can solve frequency query task with README guidance", {
89 skip_if_not(nzchar(Sys.getenv("OPENAI_API_KEY")), "OPENAI_API_KEY not set")
90 skip_if_not(!is.null(find_readme_path()), "Readme.md not found in current or parent directories")
91
92 # Create the prompt with README context and task
93 prompt <- create_readme_prompt(
94 "write R code to perform a frequency query for the word 'Deutschland' across multiple years (2010-2015). The code should use the RKorAPClient package and return a data frame with year and frequency columns.",
95 "Write R code to query frequency of 'Deutschland' from 2010-2015 using RKorAPClient."
96 )
97
98 # Call OpenAI API
99 generated_response <- call_openai_api(prompt, max_tokens = 500)
100 generated_code <- extract_r_code(generated_response)
101
102 # Basic checks on the generated code
103 expect_true(grepl("KorAPConnection", generated_code), "Generated code should include KorAPConnection")
104 expect_true(grepl("frequencyQuery", generated_code), "Generated code should include frequencyQuery")
105 expect_true(grepl("Deutschland", generated_code), "Generated code should include the search term 'Deutschland'")
106 expect_true(grepl("201[0-5]", generated_code), "Generated code should include years 2010-2015")
Marc Kupietz10dcfee2025-07-05 19:13:27 +0200107 expect_true(grepl(KORAP_URL, generated_code, fixed = TRUE), "Generated code should include the specified KorAP URL")
Marc Kupietz06143702025-07-05 17:49:31 +0200108
109 # Check that the generated code contains essential RKorAPClient patterns
110 expect_true(grepl("\\|>", generated_code) || grepl("%>%", generated_code),
111 "Generated code should use pipe operators")
112
113 # Optional: Try to parse the generated code to check for syntax errors
114 parsed_successfully <- tryCatch({
115 parse(text = generated_code)
116 TRUE
117 }, error = function(e) {
118 FALSE
119 })
120
121 expect_true(parsed_successfully, "Generated code should be syntactically valid R code")
122
123 # Print the generated code for manual inspection
124 cat("Generated code:\n", generated_code, "\n")
125})
126
127test_that("GPT-4.1 mini can solve collocation analysis task with README guidance", {
128 skip_if_not(nzchar(Sys.getenv("OPENAI_API_KEY")), "OPENAI_API_KEY not set")
129 skip_if_not(!is.null(find_readme_path()), "Readme.md not found in current or parent directories")
130
131 # Create the prompt for collocation analysis
132 prompt <- create_readme_prompt(
133 "write R code to perform a collocation analysis for the word 'setzen' (looking for light verb constructions). The code should use the RKorAPClient package's collocationAnalysis function.",
134 "Write R code to perform collocation analysis for 'setzen' using RKorAPClient."
135 )
136
137 # Call OpenAI API
138 generated_response <- call_openai_api(prompt, max_tokens = 500)
139 generated_code <- extract_r_code(generated_response)
140
141 # Basic checks on the generated code
142 expect_true(grepl("KorAPConnection", generated_code), "Generated code should include KorAPConnection")
143 expect_true(grepl("collocationAnalysis", generated_code), "Generated code should include collocationAnalysis")
144 expect_true(grepl("setzen", generated_code), "Generated code should include the search term 'setzen'")
145 expect_true(grepl("auth", generated_code), "Generated code should include auth() for collocation analysis")
Marc Kupietz10dcfee2025-07-05 19:13:27 +0200146 expect_true(grepl(KORAP_URL, generated_code, fixed = TRUE), "Generated code should include the specified KorAP URL")
Marc Kupietz06143702025-07-05 17:49:31 +0200147
148 # Check for collocation analysis parameters
149 expect_true(grepl("leftContextSize|rightContextSize", generated_code),
150 "Generated code should include context size parameters")
151
152 # Print the generated code for manual inspection
153 cat("Generated collocation analysis code:\n", generated_code, "\n")
154})
155
156test_that("GPT-4.1 mini can solve corpus query task with README guidance", {
157 skip_if_not(nzchar(Sys.getenv("OPENAI_API_KEY")), "OPENAI_API_KEY not set")
158 skip_if_not(!is.null(find_readme_path()), "Readme.md not found in current or parent directories")
159
160 # Create the prompt for corpus query
161 prompt <- create_readme_prompt(
162 "write R code to perform a simple corpus query for 'Hello world' and fetch all results. The code should use the RKorAPClient package.",
163 "Write R code to query 'Hello world' and fetch all results using RKorAPClient."
164 )
165
166 # Call OpenAI API
167 generated_response <- call_openai_api(prompt, max_tokens = 300)
168 generated_code <- extract_r_code(generated_response)
169
170 # Basic checks on the generated code
171 expect_true(grepl("KorAPConnection", generated_code), "Generated code should include KorAPConnection")
172 expect_true(grepl("corpusQuery", generated_code), "Generated code should include corpusQuery")
173 expect_true(grepl("Hello world", generated_code), "Generated code should include the search term 'Hello world'")
174 expect_true(grepl("fetchAll", generated_code), "Generated code should include fetchAll")
Marc Kupietz10dcfee2025-07-05 19:13:27 +0200175 expect_true(grepl(KORAP_URL, generated_code, fixed = TRUE), "Generated code should include the specified KorAP URL")
Marc Kupietz06143702025-07-05 17:49:31 +0200176
177 # Check that the generated code follows the README example pattern
178 expect_true(grepl("\\|>", generated_code) || grepl("%>%", generated_code),
179 "Generated code should use pipe operators")
180
181 # Print the generated code for manual inspection
182 cat("Generated corpus query code:\n", generated_code, "\n")
183})