blob: 0ad640451f93f50001451907f6660161c5440137 [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(
Marc Kupietz8e1b77d2025-07-05 20:21:59 +020034 model = LLM_MODEL,
Marc Kupietz06143702025-07-05 17:49:31 +020035 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 Kupietz8e1b77d2025-07-05 20:21:59 +020058# Configuration variables
59LLM_MODEL <- "gpt-4.1-mini"
Marc Kupietz10dcfee2025-07-05 19:13:27 +020060KORAP_URL <- "https://korap.ids-mannheim.de/instance/wiki"
61
Marc Kupietz06143702025-07-05 17:49:31 +020062# Helper function to create README-guided prompt
63create_readme_prompt <- function(task_description, specific_task) {
64 readme_text <- read_readme_content()
65 if (is.null(readme_text)) {
66 stop("README.md not found")
67 }
68
69 paste0(
70 "You are an expert R programmer. Based on the following README documentation for the RKorAPClient package, ",
71 task_description, "\n\n",
Marc Kupietz8e1b77d2025-07-05 20:21:59 +020072 "IMPORTANT: Use the KorAP URL '", KORAP_URL, "' as the 1st parameter (KorAPUrl) in KorAPConnection.\n\n",
Marc Kupietz06143702025-07-05 17:49:31 +020073 "README Documentation:\n",
74 readme_text,
75 "\n\nTask: ", specific_task,
76 "\n\nProvide only the R code without explanations."
77 )
78}
79
80# Helper function to extract R code from markdown code blocks
81extract_r_code <- function(response_text) {
82 # Remove markdown code blocks if present
83 code <- gsub("```[rR]?\\n?", "", response_text)
84 code <- gsub("```\\n?$", "", code)
85 # Remove leading/trailing whitespace
86 trimws(code)
87}
88
Marc Kupietze759b342025-07-05 19:48:20 +020089# Helper function to test code syntax
90test_code_syntax <- function(code) {
91 tryCatch({
92 parse(text = code)
93 TRUE
94 }, error = function(e) {
95 cat("Syntax error:", as.character(e), "\n")
96 FALSE
97 })
98}
99
100# Helper function to run code if RUN_LLM_CODE is set
101run_code_if_enabled <- function(code, test_name) {
102 if (nzchar(Sys.getenv("RUN_LLM_CODE")) && Sys.getenv("RUN_LLM_CODE") == "true") {
103 cat("Running generated code for", test_name, "...\n")
104 tryCatch({
105 result <- eval(parse(text = code))
106 cat("Code executed successfully. Result type:", class(result), "\n")
107 if (is.data.frame(result)) {
108 cat("Result dimensions:", nrow(result), "rows,", ncol(result), "columns\n")
109 if (nrow(result) > 0) {
110 cat("First few rows:\n")
111 print(head(result, 3))
112 }
113 } else {
114 cat("Result preview:\n")
115 print(result)
116 }
117 return(TRUE)
118 }, error = function(e) {
119 cat("Runtime error:", as.character(e), "\n")
120 return(FALSE)
121 })
122 } else {
123 cat("Skipping code execution (set RUN_LLM_CODE=true to enable)\n")
124 return(NA)
125 }
126}
127
Marc Kupietz8e1b77d2025-07-05 20:21:59 +0200128test_that(paste(LLM_MODEL, "can solve frequency query task with README guidance"), {
Marc Kupietz06143702025-07-05 17:49:31 +0200129 skip_if_not(nzchar(Sys.getenv("OPENAI_API_KEY")), "OPENAI_API_KEY not set")
130 skip_if_not(!is.null(find_readme_path()), "Readme.md not found in current or parent directories")
131
132 # Create the prompt with README context and task
133 prompt <- create_readme_prompt(
134 "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.",
135 "Write R code to query frequency of 'Deutschland' from 2010-2015 using RKorAPClient."
136 )
137
138 # Call OpenAI API
139 generated_response <- call_openai_api(prompt, max_tokens = 500)
140 generated_code <- extract_r_code(generated_response)
141
142 # Basic checks on the generated code
143 expect_true(grepl("KorAPConnection", generated_code), "Generated code should include KorAPConnection")
144 expect_true(grepl("frequencyQuery", generated_code), "Generated code should include frequencyQuery")
145 expect_true(grepl("Deutschland", generated_code), "Generated code should include the search term 'Deutschland'")
146 expect_true(grepl("201[0-5]", generated_code), "Generated code should include years 2010-2015")
Marc Kupietz10dcfee2025-07-05 19:13:27 +0200147 expect_true(grepl(KORAP_URL, generated_code, fixed = TRUE), "Generated code should include the specified KorAP URL")
Marc Kupietz06143702025-07-05 17:49:31 +0200148
149 # Check that the generated code contains essential RKorAPClient patterns
150 expect_true(grepl("\\|>", generated_code) || grepl("%>%", generated_code),
151 "Generated code should use pipe operators")
152
Marc Kupietze759b342025-07-05 19:48:20 +0200153 # Test code syntax
154 syntax_valid <- test_code_syntax(generated_code)
155 expect_true(syntax_valid, "Generated code should be syntactically valid R code")
Marc Kupietz06143702025-07-05 17:49:31 +0200156
157 # Print the generated code for manual inspection
158 cat("Generated code:\n", generated_code, "\n")
Marc Kupietze759b342025-07-05 19:48:20 +0200159
160 # Run the code if RUN_LLM_CODE is set
161 execution_result <- run_code_if_enabled(generated_code, "frequency query")
162 if (!is.na(execution_result)) {
163 expect_true(execution_result, "Generated code should execute without runtime errors")
164 }
Marc Kupietz06143702025-07-05 17:49:31 +0200165})
166
Marc Kupietz8e1b77d2025-07-05 20:21:59 +0200167test_that(paste(LLM_MODEL, "can solve collocation analysis task with README guidance"), {
Marc Kupietz06143702025-07-05 17:49:31 +0200168 skip_if_not(nzchar(Sys.getenv("OPENAI_API_KEY")), "OPENAI_API_KEY not set")
169 skip_if_not(!is.null(find_readme_path()), "Readme.md not found in current or parent directories")
170
171 # Create the prompt for collocation analysis
172 prompt <- create_readme_prompt(
Marc Kupietze759b342025-07-05 19:48:20 +0200173 "write R code to perform a collocation analysis for the lemma 'setzen'. The code should use the RKorAPClient package's collocationAnalysis function.",
Marc Kupietz06143702025-07-05 17:49:31 +0200174 "Write R code to perform collocation analysis for 'setzen' using RKorAPClient."
175 )
176
177 # Call OpenAI API
178 generated_response <- call_openai_api(prompt, max_tokens = 500)
179 generated_code <- extract_r_code(generated_response)
180
181 # Basic checks on the generated code
182 expect_true(grepl("KorAPConnection", generated_code), "Generated code should include KorAPConnection")
183 expect_true(grepl("collocationAnalysis", generated_code), "Generated code should include collocationAnalysis")
184 expect_true(grepl("setzen", generated_code), "Generated code should include the search term 'setzen'")
185 expect_true(grepl("auth", generated_code), "Generated code should include auth() for collocation analysis")
Marc Kupietz10dcfee2025-07-05 19:13:27 +0200186 expect_true(grepl(KORAP_URL, generated_code, fixed = TRUE), "Generated code should include the specified KorAP URL")
Marc Kupietz06143702025-07-05 17:49:31 +0200187
Marc Kupietze759b342025-07-05 19:48:20 +0200188 # Test code syntax
189 syntax_valid <- test_code_syntax(generated_code)
190 expect_true(syntax_valid, "Generated code should be syntactically valid R code")
191
Marc Kupietz06143702025-07-05 17:49:31 +0200192 # Print the generated code for manual inspection
193 cat("Generated collocation analysis code:\n", generated_code, "\n")
Marc Kupietze759b342025-07-05 19:48:20 +0200194
195 # Run the code if RUN_LLM_CODE is set
196 execution_result <- run_code_if_enabled(generated_code, "collocation analysis")
197 if (!is.na(execution_result)) {
198 expect_true(execution_result, "Generated code should execute without runtime errors")
199 }
Marc Kupietz06143702025-07-05 17:49:31 +0200200})
201
Marc Kupietz8e1b77d2025-07-05 20:21:59 +0200202test_that(paste(LLM_MODEL, "can solve corpus query task with README guidance"), {
Marc Kupietz06143702025-07-05 17:49:31 +0200203 skip_if_not(nzchar(Sys.getenv("OPENAI_API_KEY")), "OPENAI_API_KEY not set")
204 skip_if_not(!is.null(find_readme_path()), "Readme.md not found in current or parent directories")
205
206 # Create the prompt for corpus query
207 prompt <- create_readme_prompt(
208 "write R code to perform a simple corpus query for 'Hello world' and fetch all results. The code should use the RKorAPClient package.",
209 "Write R code to query 'Hello world' and fetch all results using RKorAPClient."
210 )
211
212 # Call OpenAI API
213 generated_response <- call_openai_api(prompt, max_tokens = 300)
214 generated_code <- extract_r_code(generated_response)
215
216 # Basic checks on the generated code
217 expect_true(grepl("KorAPConnection", generated_code), "Generated code should include KorAPConnection")
218 expect_true(grepl("corpusQuery", generated_code), "Generated code should include corpusQuery")
219 expect_true(grepl("Hello world", generated_code), "Generated code should include the search term 'Hello world'")
220 expect_true(grepl("fetchAll", generated_code), "Generated code should include fetchAll")
Marc Kupietz10dcfee2025-07-05 19:13:27 +0200221 expect_true(grepl(KORAP_URL, generated_code, fixed = TRUE), "Generated code should include the specified KorAP URL")
Marc Kupietz06143702025-07-05 17:49:31 +0200222
223 # Check that the generated code follows the README example pattern
224 expect_true(grepl("\\|>", generated_code) || grepl("%>%", generated_code),
225 "Generated code should use pipe operators")
226
Marc Kupietze759b342025-07-05 19:48:20 +0200227 # Test code syntax
228 syntax_valid <- test_code_syntax(generated_code)
229 expect_true(syntax_valid, "Generated code should be syntactically valid R code")
230
Marc Kupietz06143702025-07-05 17:49:31 +0200231 # Print the generated code for manual inspection
232 cat("Generated corpus query code:\n", generated_code, "\n")
Marc Kupietze759b342025-07-05 19:48:20 +0200233
234 # Run the code if RUN_LLM_CODE is set
235 execution_result <- run_code_if_enabled(generated_code, "corpus query")
236 if (!is.na(execution_result)) {
237 expect_true(execution_result, "Generated code should execute without runtime errors")
238 }
Marc Kupietz06143702025-07-05 17:49:31 +0200239})