Skip to content

Commit

Permalink
check()
Browse files Browse the repository at this point in the history
  • Loading branch information
romainfrancois committed Mar 30, 2024
1 parent e810ba7 commit 43b4f3f
Show file tree
Hide file tree
Showing 5 changed files with 67 additions and 16 deletions.
20 changes: 14 additions & 6 deletions R/chat.R
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
#' Chat with the Mistral api
#'
#' @param messages Messages
#' @param text some text
#' @param model which model to use. See [models()] for more information about which models are available
#' @param dry_run if TRUE the request is not performed
#' @inheritParams httr2::req_perform
#' @inheritParams rlang::args_dots_empty
#' @inheritParams rlang::args_error_context
#'
#' @return A tibble with columns `role` and `content` with class `chat_tibble` or a request
#' if this is a `dry_run`
Expand All @@ -13,7 +13,9 @@
#' chat("Top 5 R packages", dry_run = TRUE)
#'
#' @export
chat <- function(messages, model = "mistral-tiny", dry_run = FALSE, error_call = current_env()) {
chat <- function(messages, model = "mistral-tiny", dry_run = FALSE, ..., error_call = current_env()) {
check_dots_empty()

req <- req_chat(messages, model = model, error_call = error_call, dry_run = dry_run)
if (is_true(dry_run)) {
return(req)
Expand All @@ -29,7 +31,9 @@ print.chat <- function(x, ...) {
invisible(x)
}

req_chat <- function(messages, model = "mistral-tiny", stream = FALSE, dry_run = FALSE, error_call = caller_env()) {
req_chat <- function(messages, model = "mistral-tiny", stream = FALSE, dry_run = FALSE, ..., error_call = caller_env()) {
check_dots_empty()

if (!is_true(dry_run)) {
check_model(model, error_call = error_call)
}
Expand All @@ -50,8 +54,12 @@ req_chat <- function(messages, model = "mistral-tiny", stream = FALSE, dry_run =

#' @export
as.data.frame.chat_response <- function(x, ...) {
df_req <- map_dfr(resp$request$body$data$messages, as.data.frame)
df_resp <- as.data.frame(resp_body_json(resp)$choices[[1]]$message[c("role", "content")])
req_messages <- x$request$body$data$messages
df_req <- map_dfr(req_messages, as.data.frame)

df_resp <- as.data.frame(
resp_body_json(x)$choices[[1]]$message[c("role", "content")]
)

rbind(df_req, df_resp)
}
Expand Down
29 changes: 21 additions & 8 deletions R/messages.R
Original file line number Diff line number Diff line change
@@ -1,24 +1,37 @@
#' Convert object into a messages list
#'
#' @param messages object to convert to messages
#' @param ... ignored
#' @inheritParams rlang::args_error_context
#'
#' @examples
#' as_messages("hello")
#' as_messages(list("hello"))
#' as_messages(list(assistant = "hello", user = "hello"))
#'
#' @export
as_messages <- function(messages, ...) {
as_messages <- function(messages, ..., error_call = current_env()) {
UseMethod("as_messages")
}

#' @export
as_messages.character <- function(x, ..., error_call = current_env()) {
check_scalar_string(x, error_call = error_call)
check_unnamed_string(x, error_call = error_call)
as_messages.character <- function(messages, ..., error_call = current_env()) {
check_dots_empty(call = error_call)
check_scalar_string(messages, error_call = error_call)
check_unnamed_string(messages, error_call = error_call)

list(
list(role = "user", content = x)
list(role = "user", content = messages)
)
}

#' @export
as_messages.list <- function(x, ..., error_call = caller_env()) {
as_messages.list <- function(messages, ..., error_call = caller_env()) {
check_dots_empty()

bits <- map2(x, names2(x), as_msg, error_call = error_call)
out <- list_flatten(bits)
out <- list_flatten(
map2(messages, names2(messages), as_msg, error_call = error_call)
)
names(out) <- NULL
out
}
Expand Down
27 changes: 27 additions & 0 deletions man/as_messages.Rd

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

5 changes: 3 additions & 2 deletions man/chat.Rd

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

2 changes: 2 additions & 0 deletions man/stream.Rd

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

0 comments on commit 43b4f3f

Please sign in to comment.