Skip to content

Instantly share code, notes, and snippets.

@atomashevic
Created October 2, 2025 17:01
Show Gist options
  • Select an option

  • Save atomashevic/dfbc3f3408e3fc5a85c9fa659844e7dd to your computer and use it in GitHub Desktop.

Select an option

Save atomashevic/dfbc3f3408e3fc5a85c9fa659844e7dd to your computer and use it in GitHub Desktop.

This is part of the RAG function where we load different models, this is the pipeline for Gemma models which require HF token.

      "gemma3-1b" = {
        repo <- "google/gemma-3-1b-it"
        load_sc <- function() setup_hf_llm(
          llama_index, prompt, device,
          model_name = repo, tokenizer_name = repo,
          context_window = 32000L,
          temperature = temperature, do_sample = do_sample,
          max_new_tokens = max_new_tokens, top_p = top_p
        )
        sc_try <- try(load_sc(), silent = TRUE)
        if (inherits(sc_try, "try-error") && .is_hf_auth_error(sc_try)) { ## Function 1: check if there is auth error
          if (interactive()) {
            tok <- .hf_prompt_token() ## Function 2: if this is interactive R session prompt user for token
            sc_try <- try(with_hf_token(tok, { load_sc() }), silent = TRUE) # Function 3: tries to load the model with the token
            if (inherits(sc_try, "try-error")) stop(sc_try)
          } else {
            stop( # If not interactive session, we just abort.
              paste0(
                "Gemma 3 model download requires a token. Run interactively to be prompted, ",
                "or wrap your call with with_hf_token('<token>', { rag(...) }) after accepting the model license."
              ), call. = FALSE
            )
          }
        }
        sc_try
      },

Here are 3 functions.

Checking for auth error.

.is_hf_auth_error <- function(err) {
msg <- paste(capture.output(print(err)), collapse = "\n")
grepl("401|Unauthorized|Forbidden|gated|not authorized|requires authorization|You are not logged in",
      msg, ignore.case = TRUE)
}

Prompting for token. It's a little bit messy because we can have all sorts of situations with some users storing old tokens in the environment, some having blank values stored, etc.

.hf_prompt_token <- function() {
  message(
    "A Hugging Face access token is required to use Gemma 3 models (gated repos).\n",
    "Open https://huggingface.co/settings/tokens and create a token with WRITE scope.\n"
  )
  tok <- trimws(readline(prompt = "Paste your Hugging Face token (starts with 'hf_'): "))
  if (!nzchar(tok)) stop("No token provided. Aborting.", call. = FALSE)
  return(tok)
}
with_hf_token <- function(token, expr) {
  stopifnot(is.character(token), length(token) == 1L, nzchar(token))
  old_hf <- Sys.getenv("HF_TOKEN", unset = NA_character_)
  old_hub <- Sys.getenv("HUGGINGFACE_HUB_TOKEN", unset = NA_character_)
  on.exit({
    if (is.na(old_hf) || !nzchar(old_hf)) Sys.unsetenv("HF_TOKEN") else Sys.setenv(HF_TOKEN = old_hf)
    if (is.na(old_hub) || !nzchar(old_hub)) Sys.unsetenv("HUGGINGFACE_HUB_TOKEN") else Sys.setenv(HUGGINGFACE_HUB_TOKEN = old_hub)
  }, add = TRUE)
  Sys.setenv(HF_TOKEN = token)
  Sys.setenv(HUGGINGFACE_HUB_TOKEN = token)
  eval.parent(substitute(expr))
}

This is temporary token, won't interfere with their env values, if any.

Third function:

with_hf_token <- function(token, expr) {
  stopifnot(is.character(token), length(token) == 1L, nzchar(token))
  old_hf <- Sys.getenv("HF_TOKEN", unset = NA_character_)
  old_hub <- Sys.getenv("HUGGINGFACE_HUB_TOKEN", unset = NA_character_)
  on.exit({
    if (is.na(old_hf) || !nzchar(old_hf)) Sys.unsetenv("HF_TOKEN") else Sys.setenv(HF_TOKEN = old_hf)
    if (is.na(old_hub) || !nzchar(old_hub)) Sys.unsetenv("HUGGINGFACE_HUB_TOKEN") else Sys.setenv(HUGGINGFACE_HUB_TOKEN = old_hub)
  }, add = TRUE)
  Sys.setenv(HF_TOKEN = token)
  Sys.setenv(HUGGINGFACE_HUB_TOKEN = token)
  eval.parent(substitute(expr))
}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment