R/x509.R

Defines functions PKI.get.cert.info PKI.get.subject PKI.pubkey PKI.verifyCA PKI.load.cert

Documented in PKI.get.cert.info PKI.get.subject PKI.load.cert PKI.pubkey PKI.verifyCA

PKI.load.cert <- function(what, format = c("PEM", "DER"), file) {
    format <- match.arg(format)
    if (!missing(file) && !missing(what)) stop("what and file are mutually exclusive")
    binary <- isTRUE(format == "DER")
    if (!missing(file)) {
        what <- con <- file(file, if (binary) "rb" else "r")
        on.exit(close(con))
    }
    if (inherits(what, "connection"))
        what <- if (binary) readBin(what, raw(), chunk) else readLines(what)
    if (is.character(what)) {
        if (binary) stop("DER format selected but input is text")
        i <- grep("-BEGIN CERTIFICATE-", what, fixed=TRUE)
        j <- grep("-END CERTIFICATE-", what, fixed=TRUE)
        if (length(i) >= 1L && length(j) >= 1L && i[1] < j[1])
            what <- base64enc::base64decode(what[(i + 1L):(j - 1L)])
        else
            stop("invalid PEM format")
    }
    .Call(PKI_load_DER_X509, what)
}

PKI.verifyCA <- function(certificate, ca, default=FALSE, partial=FALSE)
    .Call(PKI_verify_cert, ca, certificate, default, partial)

PKI.pubkey <- function(certificate) .Call(PKI_cert_public_key, certificate)

PKI.get.subject <- function(certificate) .Call(PKI_get_subject, certificate)

PKI.get.cert.info <- function(certificate) {
  i <- .Call(PKI_get_cert_info, certificate)
  names(i) <- c("subject", "issuer", "fingerprint", "validity", "ca")
  i[[4]] <- .POSIXct(i[[4]])
  i
}

Try the PKI package in your browser

Any scripts or data that you put into this service are public.

PKI documentation built on Nov. 28, 2022, 9:05 a.m.