Skip to content

Commit

Permalink
Add version endpoint and update create
Browse files Browse the repository at this point in the history
  • Loading branch information
hauselin committed Jan 28, 2025
1 parent 40633f3 commit 77fdeea
Show file tree
Hide file tree
Showing 13 changed files with 110 additions and 45 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ export(test_connection)
export(validate_message)
export(validate_messages)
export(validate_options)
export(ver)
importFrom(crayon,green)
importFrom(crayon,red)
importFrom(glue,glue)
3 changes: 3 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
# ollamar (development version)

- Add `ver()` function to [retrieve Ollama version](https://github.com/ollama/ollama/blob/main/docs/api.md#version).
- Update `create()` function.

# ollamar 1.2.2

- `generate()` and `chat()` support [structured output](https://ollama.com/blog/structured-outputs) via `format` parameter.
Expand Down
74 changes: 48 additions & 26 deletions R/ollama.R
Original file line number Diff line number Diff line change
Expand Up @@ -289,14 +289,14 @@ chat <- function(model, messages, tools = list(), stream = FALSE, format = list(



#' Create a model from a Modelfile
#' Create a model
#'
#' It is recommended to set `modelfile` to the content of the Modelfile rather than just set path.
#' Create a model from another model, a safetensors directory (not implemented), or a GGUF file (not implemented).
#'
#' @param name Name of the model to create.
#' @param modelfile Contents of the Modelfile as character string. Default is NULL.
#' @param model Name of the model to create.
#' @param from Name of an existing model to create the new model from.
#' @param system System prompt for the model. Default is NULL.
#' @param stream Enable response streaming. Default is FALSE.
#' @param path The path to the Modelfile. Default is NULL.
#' @param endpoint The endpoint to create the model. Default is "/api/create".
#' @param host The base URL to use. Default is NULL, which uses Ollama's default base URL.
#'
Expand All @@ -307,34 +307,22 @@ chat <- function(model, messages, tools = list(), stream = FALSE, format = list(
#' @export
#'
#' @examplesIf test_connection(logical = TRUE)
#' create("mario", "FROM llama3\nSYSTEM You are mario from Super Mario Bros.")
#' create("mario", "deepseek-r1:1.5b", system = "You are Mario from Super Mario Bros.")
#' model_avail("mario") # check mario model has been created
#' list_models() # mario model has been created
#' generate("mario", "who are you?", output = "text") # model should say it's Mario
#' delete("mario") # delete the model created above
create <- function(name, modelfile = NULL, stream = FALSE, path = NULL, endpoint = "/api/create", host = NULL) {

if (is.null(modelfile) && is.null(path)) {
stop("Either modelfile or path must be provided. Using modelfile is recommended.")
}

if (!is.null(modelfile) && !is.null(path)) {
stop("Only one of modelfile or path should be provided.")
}

if (!is.null(path)) {
if (file.exists(path)) {
modelfile <- paste0(readLines("inst/extdata/example_modefile.txt", warn = FALSE), collapse = "\n")
cat(paste0("Modefile\n", modelfile, "\n"))
} else {
stop("The path provided does not exist.")
}
}
#' model_avail("mario") # model no longer exists
create <- function(model, from, system = NULL, stream = FALSE, endpoint = "/api/create", host = NULL) {

req <- create_request(endpoint, host)
req <- httr2::req_method(req, "POST")

# TODO: add other parameters
body_json <- list(
name = name,
modelfile = modelfile,
model = model,
from = from,
system = system,
stream = stream
)

Expand Down Expand Up @@ -896,6 +884,40 @@ ps <- function(output = c("df", "resp", "jsonlist", "raw", "text"), endpoint = "



#' Retrieve Ollama version
#'
#' @param endpoint The endpoint to list the running models. Default is "/api/version".
#' @param host The base URL to use. Default is NULL, which uses Ollama's default base URL.
#'
#' @references
#' [API documentation](https://github.com/ollama/ollama/blob/main/docs/api.md#version)
#'
#' @return A character string of the Ollama version.
#' @export
#'
#' @examplesIf test_connection(logical = TRUE)
#' ver()
ver <- function(endpoint = "/api/version", host = NULL) {
req <- create_request(endpoint, host)
req <- httr2::req_method(req, "GET")
tryCatch(
{
resp <- httr2::req_perform(req)
return(resp_process(resp = resp, output = "text"))
},
error = function(e) {
stop(e)
}
)
}











Expand Down
2 changes: 2 additions & 0 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -275,6 +275,8 @@ resp_process <- function(resp, output = c("df", "jsonlist", "raw", "resp", "text
} else if (output == "text") {
return(df_response$name)
}
} else if (grepl("api/version", resp$url)) {
return(httr2::resp_body_json(resp)$version)
}
}

Expand Down
1 change: 1 addition & 0 deletions _pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ reference:
- embed
- embeddings
- ps
- ver

- subtitle: API helpers
desc: Work with and extend the Ollama API.
Expand Down
23 changes: 13 additions & 10 deletions man/create.Rd

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

27 changes: 27 additions & 0 deletions man/ver.Rd

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

2 changes: 1 addition & 1 deletion tests/testthat/test-chat.R
Original file line number Diff line number Diff line change
Expand Up @@ -262,7 +262,7 @@ test_that("structured output", {
)

msg <- create_message("tell me about canada")
resp <- chat("llama3.1", msg, format = format)
resp <- chat("llama3.1:8b", msg, format = format)
# content <- httr2::resp_body_json(resp)$message$content
structured_output <- resp_process(resp, "structured")
expect_equal(tolower(structured_output$name), "canada")
Expand Down
6 changes: 1 addition & 5 deletions tests/testthat/test-create.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,7 @@ library(ollamar)
test_that("create function works with basic input", {
skip_if_not(test_connection(logical = TRUE), "Ollama server not available")

expect_error(create("mario"))
expect_error(create("mario", modelfile = "abc", path = "abc"))
expect_error(create("mario", path = "abc"))

resp <- create("mario", "FROM llama3\nSYSTEM You are mario from Super Mario Bros.")
resp <- create("mario", "deepseek-r1:1.5b")
expect_s3_class(resp, "httr2_response")
expect_equal(resp$status_code, 200)
expect_true(model_avail("mario"))
Expand Down
2 changes: 1 addition & 1 deletion tests/testthat/test-generate.R
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ test_that("structured output", {
)

msg <- "tell me about canada"
resp <- generate("llama3.1", prompt = msg, format = format)
resp <- generate("llama3.1:8b", prompt = msg, format = format)
# response <- httr2::resp_body_json(resp)$response
structured_output <- resp_process(resp, "structured")
expect_equal(tolower(structured_output$name), "canada")
Expand Down
2 changes: 1 addition & 1 deletion tests/testthat/test-ps.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ test_that("ps list running models endpoint", {
g1 <- generate('llama3', "tell me a 5 word story")

result <- ps()
expect_true(nrow(result) > 1)
expect_true(nrow(result) >= 1)
expect_true(all(c("name", "size", "parameter_size", "quantization_level", "digest", "expires_at") %in% names(result)))
expect_s3_class(ps("df"), "data.frame")
expect_s3_class(ps("resp"), "httr2_response")
Expand Down
4 changes: 3 additions & 1 deletion tests/testthat/test-pull.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ test_that("pull function works", {
expect_vector(result$body)

# correct model
result <- pull('llama3', stream = TRUE)
result <- pull('snowflake-arctic-embed:22m', stream = TRUE)
# for this endpoint, even when stream = FALSE, the response is chunked)
expect_true(httr2::resp_headers(result)$`Transfer-Encoding` == "chunked")
expect_s3_class(result, "httr2_response")
Expand All @@ -51,5 +51,7 @@ test_that("pull function works", {
expect_s3_class(pull('sdafd', stream = TRUE, insecure = TRUE), "httr2_response")
expect_s3_class(pull('sdafd', stream = TRUE, insecure = FALSE), "httr2_response")

delete("snowflake-arctic-embed:22m")

})

8 changes: 8 additions & 0 deletions tests/testthat/test-ver.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
library(testthat)
library(ollamar)

test_that("ps list running models endpoint", {
skip_if_not(test_connection(logical = TRUE), "Ollama server not available")

expect_type(ver(), "character")
})

0 comments on commit 77fdeea

Please sign in to comment.