From 850c960385bcb6dfb9660dc00af1a978b261cf26 Mon Sep 17 00:00:00 2001 From: shikokuchuo <53399081+shikokuchuo@users.noreply.github.com> Date: Mon, 18 Mar 2024 10:23:30 +0000 Subject: [PATCH] adds SHA-256 HMAC --- DESCRIPTION | 2 +- NEWS.md | 5 +-- R/base.R | 44 ++++++++++++++--------- README.Rmd | 28 +++++++++------ README.md | 36 +++++++++++-------- man/sha256.Rd | 16 +++++++-- man/siphash13.Rd | 21 +++++------ src/init.c | 4 +-- src/secret.h | 5 +-- src/secret2.c | 91 ++++++++++++++++++++++++++++++++++++++++-------- src/secret3.c | 27 ++++---------- tests/tests.R | 10 +++--- 12 files changed, 188 insertions(+), 101 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 1b872a2..0f633c8 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,7 +1,7 @@ Package: secretbase Type: Package Title: Cryptographic Hash and Extendable-Output Functions -Version: 0.3.0.9003 +Version: 0.3.0.9004 Description: Fast and memory-efficient streaming hash functions. Performs direct hashing of strings, raw bytes, and files potentially larger than memory, as well as hashing in-memory objects through R's serialization mechanism, diff --git a/NEWS.md b/NEWS.md index c0329b7..166aaa4 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,6 +1,7 @@ -# secretbase 0.3.0.9003 (development) +# secretbase 0.3.0.9004 (development) -* Adds SipHash-1-3 pseudorandom function (PRF). +* Adds HMAC generation to `sha256()`. +* Adds SipHash-1-3 pseudo-random function (PRF) as a fast, cryptographically-strong keyed hash. # secretbase 0.3.0.1 diff --git a/R/base.R b/R/base.R index 8115e22..566c63c 100644 --- a/R/base.R +++ b/R/base.R @@ -101,9 +101,14 @@ sha3 <- function(x, bits = 256L, convert = TRUE, file) #' Cryptographic Hashing Using the SHA-256 Algorithm #' -#' Returns a SHA-256 hash of the supplied object or file. +#' Returns a SHA-256 hash of the supplied object or file, or an HMAC if a secret +#' key is supplied. #' #' @inheritParams sha3 +#' @param key [default NULL] If NULL, the SHA-256 hash of 'x' is returned. +#' Alternatively, supply a secret key as a character string or raw vector to +#' generate an HMAC. Note: for character vectors only the first element is +#' used. #' #' @return A character string, raw or integer vector depending on 'convert'. #' @@ -126,23 +131,30 @@ sha3 <- function(x, bits = 256L, convert = TRUE, file) #' file <- tempfile(); cat("secret base", file = file) #' sha256(file = file) #' unlink(file) +#' +#' # SHA-256 HMAC using a character string secret key: +#' sha256("secret", key = "base") +#' +#' # SHA-256 HMAC using a raw vector secret key: +#' sha256("secret", key = charToRaw("base")) #' #' @export #' -sha256 <- function(x, convert = TRUE, file) - if (missing(file)) .Call(secretbase_sha256, x, convert) else - .Call(secretbase_sha256_file, file, convert) +sha256 <- function(x, key = NULL, convert = TRUE, file) + if (missing(file)) .Call(secretbase_sha256, x, key, convert) else + .Call(secretbase_sha256_file, file, key, convert) #' Hashing Using the SipHash-1-3 Pseudorandom Function #' -#' Returns a fast, cryptographically-strong SipHash-1-3 hash of the supplied -#' object or file. +#' Returns a fast, cryptographically-strong SipHash-1-3 keyed hash of the +#' supplied object or file. #' #' @inheritParams sha3 -#' @param key [default NULL] an atomic vector comprising the 16 byte (128 bit) -#' key data, or else NULL which is equivalent to '0'. If a longer vector is -#' supplied, only the first 16 bytes are used, and if shorter, padded with -#' trailing '0'. Note: for character vectors only the first element is used. +#' @param key [default NULL] a character string or raw vector comprising the 16 +#' byte (128 bit) key data, or else NULL which is equivalent to '0'. If a +#' longer vector is supplied, only the first 16 bytes are used, and if +#' shorter, padded with trailing '0'. Note: for character vectors only the +#' first element is used. #' #' @return A character string, raw or integer vector depending on 'convert'. #' @@ -161,16 +173,16 @@ sha256 <- function(x, convert = TRUE, file) #' @examples #' # SipHash-1-3 hash as character string: #' siphash13("secret base") -#' -#' # SipHash-1-3 hash using a complex number (16 byte) key: -#' siphash13("secret base", key = 1.2 + 3.4i) -#' -#' # SipHash-1-3 hash using a character string key: -#' siphash13("secret", key = "base") #' #' # SipHash-1-3 hash as raw vector: #' siphash13("secret base", convert = FALSE) #' +#' # SipHash-1-3 hash using a character string key: +#' siphash13("secret", key = "base") +#' +#' # SipHash-1-3 hash using a raw vector key: +#' siphash13("secret", key = charToRaw("base")) +#' #' # SipHash-1-3 hash a file: #' file <- tempfile(); cat("secret base", file = file) #' siphash13(file = file) diff --git a/README.Rmd b/README.Rmd index faceedb..87d542c 100644 --- a/README.Rmd +++ b/README.Rmd @@ -67,8 +67,8 @@ sha3("秘密の基地の中", bits = 512) ##### Hash arbitrary R objects: - - uses memory-efficient 'streaming' serialization (no allocation of serialized object) - - portable as always uses R serialization version 3 big-endian representation, skipping headers (which contain R version and native encoding information) + - Uses memory-efficient 'streaming' serialization, without allocation of the serialized object + - Portable as always uses R serialization version 3 big-endian representation, skipping headers (which contain R version and native encoding information) ```{r streaming} sha3(data.frame(a = 1, b = 2), bits = 160) @@ -78,7 +78,7 @@ sha3(NULL) ##### Hash files: - - in a streaming fashion, accepting files larger than memory + - Performed in a streaming fashion, accepting files larger than memory ```{r files} file <- tempfile(); cat("secret base", file = file) @@ -90,8 +90,8 @@ unlink(file) ##### Hash to integer: - - specify 'convert' as `NA` (and 'bits' as `32` for a single integer value) - - may be supplied as deterministic random seeds for R's pseudo random number generators (RNGs) + - Specify 'convert' as `NA` (and 'bits' as `32` for a single integer value) + - May be supplied as deterministic random seeds for R's pseudo random number generators (RNGs) ```{r integer} sha3("秘密の基地の中", bits = 384, convert = NA) @@ -101,15 +101,21 @@ sha3("秘密の基地の中", bits = 32, convert = NA) For use in parallel computing, this is a valid method for reducing to a negligible probability that RNGs in each process may overlap. This may be especially suitable when first-best alternatives such as using recursive streams are too expensive or unable to preserve reproducibility. [2] -##### Using a keyed hash: +##### Generating a SHA-256 HMAC: -- Use `siphash13()` passing an atomic vector to 'key'. -- Up to 16 bytes (128 bits) of the key data is used i.e. the length of 1 complex number, 2 doubles, 4 integers, or 16 individual characters / raw bytes. +- Use `sha256()` passing a character string or raw vector to 'key'. -```{r siphash} -siphash13("secret base", key = "秘密の基地の中") +```{r hmac} +sha256("secret base", key = "秘密の基地の中") +``` + +##### Using SipHash: -siphash13("secret base", key = 1.2 + 3.4i) +- SipHash is a fast, cryptographically-strong keyed hash. The SipHash-1-3 parameters are optimized for performance. +- Pass a character string or raw vector to 'key'. Up to 16 bytes (128 bits) of the key data is used. + +```{r siphash} +siphash13("secret base", key = charToRaw("秘密の基地の中")) ``` ### References diff --git a/README.md b/README.md index 4ecf327..1b46481 100644 --- a/README.md +++ b/README.md @@ -83,9 +83,9 @@ sha3("秘密の基地の中", bits = 512) ##### Hash arbitrary R objects: -- uses memory-efficient ‘streaming’ serialization (no allocation of - serialized object) -- portable as always uses R serialization version 3 big-endian +- Uses memory-efficient ‘streaming’ serialization, without allocation of + the serialized object +- Portable as always uses R serialization version 3 big-endian representation, skipping headers (which contain R version and native encoding information) @@ -99,7 +99,7 @@ sha3(NULL) ##### Hash files: -- in a streaming fashion, accepting files larger than memory +- Performed in a streaming fashion, accepting files larger than memory ``` r file <- tempfile(); cat("secret base", file = file) @@ -109,9 +109,9 @@ sha3(file = file) ##### Hash to integer: -- specify ‘convert’ as `NA` (and ‘bits’ as `32` for a single integer +- Specify ‘convert’ as `NA` (and ‘bits’ as `32` for a single integer value) -- may be supplied as deterministic random seeds for R’s pseudo random +- May be supplied as deterministic random seeds for R’s pseudo random number generators (RNGs) ``` r @@ -129,19 +129,25 @@ be especially suitable when first-best alternatives such as using recursive streams are too expensive or unable to preserve reproducibility. \[2\] -##### Using a keyed hash: +##### Generating a SHA-256 HMAC: -- Use `siphash13()` passing an atomic vector to ‘key’. -- Up to 16 bytes (128 bits) of the key data is used i.e. the length of 1 - complex number, 2 doubles, 4 integers, or 16 individual characters / - raw bytes. +- Use `sha256()` passing a character string or raw vector to ‘key’. ``` r -siphash13("secret base", key = "秘密の基地の中") -#> [1] "a1f0a751892cc7dd" +sha256("secret base", key = "秘密の基地の中") +#> [1] "ec58099ab21325e792bef8f1aafc0a70e1a7227463cfc410931112705d753392" +``` + +##### Using SipHash: -siphash13("secret base", key = 1.2 + 3.4i) -#> [1] "931a7b8f07c863a4" +- SipHash is a fast, cryptographically-strong keyed hash. The + SipHash-1-3 parameters are optimized for performance. +- Pass a character string or raw vector to ‘key’. Up to 16 bytes (128 + bits) of the key data is used. + +``` r +siphash13("secret base", key = charToRaw("秘密の基地の中")) +#> [1] "a1f0a751892cc7dd" ``` ### References diff --git a/man/sha256.Rd b/man/sha256.Rd index 801a917..7388966 100644 --- a/man/sha256.Rd +++ b/man/sha256.Rd @@ -4,7 +4,7 @@ \alias{sha256} \title{Cryptographic Hashing Using the SHA-256 Algorithm} \usage{ -sha256(x, convert = TRUE, file) +sha256(x, key = NULL, convert = TRUE, file) } \arguments{ \item{x}{object to hash. A character string or raw vector (without @@ -14,6 +14,11 @@ object. To ensure portability, serialization version 3 big-endian represenation is always used with headers skipped (as these contain R version and native encoding information).} +\item{key}{[default NULL] If NULL, the SHA-256 hash of 'x' is returned. +Alternatively, supply a secret key as a character string or raw vector to +generate an HMAC. Note: for character vectors only the first element is +used.} + \item{convert}{[default TRUE] if TRUE, the hash is converted to its hex representation as a character string, if FALSE, output directly as a raw vector, or if NA, a vector of (32-bit) integer values.} @@ -25,7 +30,8 @@ file is stream hashed, thus capable of handling files larger than memory.} A character string, raw or integer vector depending on 'convert'. } \description{ -Returns a SHA-256 hash of the supplied object or file. +Returns a SHA-256 hash of the supplied object or file, or an HMAC if a secret + key is supplied. } \details{ The SHA-256 Secure Hash Standard was published by the National @@ -48,4 +54,10 @@ file <- tempfile(); cat("secret base", file = file) sha256(file = file) unlink(file) +# SHA-256 HMAC using a character string secret key: +sha256("secret", key = "base") + +# SHA-256 HMAC using a raw vector secret key: +sha256("secret", key = charToRaw("base")) + } diff --git a/man/siphash13.Rd b/man/siphash13.Rd index 3957bc1..31a2725 100644 --- a/man/siphash13.Rd +++ b/man/siphash13.Rd @@ -14,10 +14,11 @@ object. To ensure portability, serialization version 3 big-endian represenation is always used with headers skipped (as these contain R version and native encoding information).} -\item{key}{[default NULL] an atomic vector comprising the 16 byte (128 bit) -key data, or else NULL which is equivalent to '0'. If a longer vector is -supplied, only the first 16 bytes are used, and if shorter, padded with -trailing '0'. Note: for character vectors only the first element is used.} +\item{key}{[default NULL] a character string or raw vector comprising the 16 +byte (128 bit) key data, or else NULL which is equivalent to '0'. If a +longer vector is supplied, only the first 16 bytes are used, and if +shorter, padded with trailing '0'. Note: for character vectors only the +first element is used.} \item{convert}{[default TRUE] if TRUE, the hash is converted to its hex representation as a character string, if FALSE, output directly as a raw @@ -30,8 +31,8 @@ file is stream hashed, thus capable of handling files larger than memory.} A character string, raw or integer vector depending on 'convert'. } \description{ -Returns a fast, cryptographically-strong SipHash-1-3 hash of the supplied - object or file. +Returns a fast, cryptographically-strong SipHash-1-3 keyed hash of the + supplied object or file. } \details{ The SipHash family of cryptographically-strong pseudorandom @@ -50,14 +51,14 @@ The SipHash family of cryptographically-strong pseudorandom # SipHash-1-3 hash as character string: siphash13("secret base") -# SipHash-1-3 hash using a complex number (16 byte) key: -siphash13("secret base", key = 1.2 + 3.4i) +# SipHash-1-3 hash as raw vector: +siphash13("secret base", convert = FALSE) # SipHash-1-3 hash using a character string key: siphash13("secret", key = "base") -# SipHash-1-3 hash as raw vector: -siphash13("secret base", convert = FALSE) +# SipHash-1-3 hash using a raw vector key: +siphash13("secret", key = charToRaw("base")) # SipHash-1-3 hash a file: file <- tempfile(); cat("secret base", file = file) diff --git a/src/init.c b/src/init.c index abc4f5f..c5031ad 100644 --- a/src/init.c +++ b/src/init.c @@ -21,8 +21,8 @@ static const R_CallMethodDef callMethods[] = { {"secretbase_sha3", (DL_FUNC) &secretbase_sha3, 3}, {"secretbase_sha3_file", (DL_FUNC) &secretbase_sha3_file, 3}, - {"secretbase_sha256", (DL_FUNC) &secretbase_sha256, 2}, - {"secretbase_sha256_file", (DL_FUNC) &secretbase_sha256_file, 2}, + {"secretbase_sha256", (DL_FUNC) &secretbase_sha256, 3}, + {"secretbase_sha256_file", (DL_FUNC) &secretbase_sha256_file, 3}, {"secretbase_siphash13", (DL_FUNC) &secretbase_siphash13, 3}, {"secretbase_siphash13_file", (DL_FUNC) &secretbase_siphash13_file, 3}, {NULL, NULL, 0} diff --git a/src/secret.h b/src/secret.h index eb591a9..68cdf76 100644 --- a/src/secret.h +++ b/src/secret.h @@ -37,6 +37,7 @@ #endif #define SB_SHA256_SIZE 32 +#define SB_SHA256_BLK 64 #define SB_SIPH_SIZE 8 #define SB_SKEY_SIZE 16 @@ -100,8 +101,8 @@ SEXP hash_to_sexp(unsigned char *, size_t, int); SEXP secretbase_sha3(SEXP, SEXP, SEXP); SEXP secretbase_sha3_file(SEXP, SEXP, SEXP); -SEXP secretbase_sha256(SEXP, SEXP); -SEXP secretbase_sha256_file(SEXP, SEXP); +SEXP secretbase_sha256(SEXP, SEXP, SEXP); +SEXP secretbase_sha256_file(SEXP, SEXP, SEXP); SEXP secretbase_siphash13(SEXP, SEXP, SEXP); SEXP secretbase_siphash13_file(SEXP, SEXP, SEXP); diff --git a/src/secret2.c b/src/secret2.c index 74c5ae8..5ee0901 100644 --- a/src/secret2.c +++ b/src/secret2.c @@ -133,6 +133,17 @@ static inline uint64_t mbedtls_bswap64(uint64_t x) { } \ } \ +static inline void mbedtls_xor(unsigned char *r, + const unsigned char *a, + const unsigned char *b, + size_t n) +{ + size_t i = 0; + for (; i < n; i++) { + r[i] = a[i] ^ b[i]; + } +} + static void mbedtls_sha256_init(mbedtls_sha256_context *ctx) { memset(ctx, 0, sizeof(mbedtls_sha256_context)); @@ -430,34 +441,84 @@ static void hash_object(mbedtls_sha256_context *ctx, const SEXP x) { } -static SEXP secretbase_sha256_impl(const SEXP x, const SEXP convert, +static SEXP secretbase_sha256_impl(const SEXP x, SEXP key, const SEXP convert, void (*const hash_func)(mbedtls_sha256_context *, SEXP)) { const int conv = LOGICAL(convert)[0]; - const size_t sz = SB_SHA256_SIZE; - unsigned char buf[sz]; - - mbedtls_sha256_context ctx; - mbedtls_sha256_init(&ctx); - mbedtls_sha256_starts(&ctx); - hash_func(&ctx, x); - mbedtls_sha256_finish(&ctx, buf); - clear_buffer(&ctx, sizeof(mbedtls_sha256_context)); + unsigned char buf[SB_SHA256_SIZE]; + + if (key == R_NilValue) { + mbedtls_sha256_context ctx; + mbedtls_sha256_init(&ctx); + mbedtls_sha256_starts(&ctx); + hash_func(&ctx, x); + mbedtls_sha256_finish(&ctx, buf); + clear_buffer(&ctx, sizeof(mbedtls_sha256_context)); + } else { + + size_t klen; + unsigned char sum[SB_SHA256_BLK], ipad[SB_SHA256_BLK], opad[SB_SHA256_BLK]; + unsigned char tmp[SB_SHA256_SIZE]; + mbedtls_sha256_context ctx; + memset(sum, 0, SB_SHA256_BLK); + unsigned char *data; + + switch (TYPEOF(key)) { + case STRSXP: ; + data = (unsigned char *) CHAR(STRING_ELT(key, 0)); + klen = strlen((char *) data); + break; + case RAWSXP: + data = (unsigned char *) STDVEC_DATAPTR(key); + klen = XLENGTH(key); + break; + default: + Rf_error("'key' must be a character string, raw vector or NULL"); + } + + if (klen > SB_SHA256_BLK) { + mbedtls_sha256_init(&ctx); + mbedtls_sha256_starts(&ctx); + hash_object(&ctx, key); + mbedtls_sha256_finish(&ctx, sum); + } else { + memcpy(sum, data, klen); + } + + memset(ipad, 0x36, SB_SHA256_BLK); + memset(opad, 0x5C, SB_SHA256_BLK); + + mbedtls_xor(ipad, ipad, sum, SB_SHA256_BLK); + mbedtls_xor(opad, opad, sum, SB_SHA256_BLK); + + mbedtls_sha256_init(&ctx); + mbedtls_sha256_starts(&ctx); + mbedtls_sha256_update(&ctx, ipad, SB_SHA256_BLK); + hash_func(&ctx, x); + mbedtls_sha256_finish(&ctx, tmp); + mbedtls_sha256_init(&ctx); + mbedtls_sha256_starts(&ctx); + mbedtls_sha256_update(&ctx, opad, SB_SHA256_BLK); + mbedtls_sha256_update(&ctx, tmp, SB_SHA256_SIZE); + mbedtls_sha256_finish(&ctx, buf); + clear_buffer(&ctx, sizeof(mbedtls_sha256_context)); + + } - return hash_to_sexp(buf, sz, conv); + return hash_to_sexp(buf, SB_SHA256_SIZE, conv); } // secretbase - exported functions --------------------------------------------- -SEXP secretbase_sha256(SEXP x, SEXP convert) { +SEXP secretbase_sha256(SEXP x, SEXP key, SEXP convert) { - return secretbase_sha256_impl(x, convert, hash_object); + return secretbase_sha256_impl(x, key, convert, hash_object); } -SEXP secretbase_sha256_file(SEXP x, SEXP convert) { +SEXP secretbase_sha256_file(SEXP x, SEXP key, SEXP convert) { - return secretbase_sha256_impl(x, convert, hash_file); + return secretbase_sha256_impl(x, key, convert, hash_file); } diff --git a/src/secret3.c b/src/secret3.c index a37097e..7269137 100644 --- a/src/secret3.c +++ b/src/secret3.c @@ -268,7 +268,6 @@ static SEXP secretbase_siphash13_impl(const SEXP x, const SEXP key, const SEXP c const int conv = LOGICAL(convert)[0]; uint64_t hash; - const size_t sz = SB_SIPH_SIZE; CSipHash ctx; if (key == R_NilValue) { @@ -276,40 +275,28 @@ static SEXP secretbase_siphash13_impl(const SEXP x, const SEXP key, const SEXP c } else { uint8_t seed[SB_SKEY_SIZE]; memset(seed, 0, SB_SKEY_SIZE); + unsigned char * data; size_t klen; switch (TYPEOF(key)) { case STRSXP: ; - const char *s = CHAR(STRING_ELT(key, 0)); - klen = strlen(s); - memcpy(seed, (unsigned char *) s, klen < SB_SKEY_SIZE ? klen : SB_SKEY_SIZE); - break; - case REALSXP: - klen = XLENGTH(key) * sizeof(double); - memcpy(seed, (unsigned char *) DATAPTR_RO(key), klen < SB_SKEY_SIZE ? klen : SB_SKEY_SIZE); - break; - case INTSXP: - case LGLSXP: - klen = XLENGTH(key) * sizeof(int); - memcpy(seed, (unsigned char *) DATAPTR_RO(key), klen < SB_SKEY_SIZE ? klen : SB_SKEY_SIZE); - break; - case CPLXSXP: - klen = XLENGTH(key) * 2 * sizeof(double); - memcpy(seed, (unsigned char *) DATAPTR_RO(key), klen < SB_SKEY_SIZE ? klen : SB_SKEY_SIZE); + data = (unsigned char *) CHAR(STRING_ELT(key, 0)); + klen = strlen((char *) data); break; case RAWSXP: + data = (unsigned char *) STDVEC_DATAPTR(key); klen = XLENGTH(key); - memcpy(seed, (unsigned char *) STDVEC_DATAPTR(key), klen < SB_SKEY_SIZE ? klen : SB_SKEY_SIZE); break; default: - Rf_error("'key' must be an atomic vector or NULL"); + Rf_error("'key' must be a character string, raw vector or NULL"); } + memcpy(seed, data, klen < SB_SKEY_SIZE ? klen : SB_SKEY_SIZE); c_siphash_init(&ctx, seed); } hash_func(&ctx, x); hash = c_siphash_finalize_13(&ctx); clear_buffer(&ctx, sizeof(CSipHash)); - return hash_to_sexp((unsigned char *) &hash, sz, conv); + return hash_to_sexp((unsigned char *) &hash, SB_SIPH_SIZE, conv); } diff --git a/tests/tests.R b/tests/tests.R index 9f70ef9..9aff897 100644 --- a/tests/tests.R +++ b/tests/tests.R @@ -62,18 +62,18 @@ test_equal(hash_func(tempfile(), "secret base"), "1951c1ca3d50e95e6ede2b1c26fefd test_error(hash_func("", ""), "file not found or no read permission") if (.Platform[["OS.type"]] == "unix") test_error(sha256(file = "~/"), "file read error") test_equal(sha256(paste(1:888, collapse = "")), "ec5df945d0ff0c927812ec503fe9ffd5cbdf7cf79b5391ad5002b3a80760183b") +test_equal(sha256("secret", key = "base"), "14b24e4c66bd03c1d6b59bc59e1e47468a437001662ae4be2cb30e0483e13e44") +test_equal(sha256("secret base", key = paste(rep("secret base ", 21L), collapse = "")), "5dab9794515ad176763276bd46f49b029b4578795c52c984243dd636dc0ac11f") +test_equal(sha256("secret base", key = as.raw(1L)), "35a0fc031777e1a16b2c11a614532fbbee5e2ce83271230f62808432a4d13337") +test_equal(sha256("secret base", key = rep(c(as.raw(1L), as.raw(2L)), 64L)), "0d9cbfe4872e0d9ef16f86fbbe5397fd4ed30b7e50b4c5c7722ccf4786aa58d2") # SipHash13 tests: test_equal(siphash13(""), "2c530c1562a7fbd1") test_equal(siphash13("", key = ""), "2c530c1562a7fbd1") test_equal(siphash13("secret base"), "48c60a316babef0e") test_equal(siphash13("secret base", key = "secret base"), "2cf27a8f22f02e59") test_equal(siphash13("secret base", key = c("secret base", "more")), "2cf27a8f22f02e59") -test_equal(siphash13("secret base", key = 1 + 2i), "6bf5397aec2bfacd") -test_equal(siphash13("secret base", key = c(1.2, 3.4)), "931a7b8f07c863a4") -test_equal(siphash13("secret base", key = c(0L, 1L)), "fad330c07a6226c6") -test_equal(siphash13("secret base", key = c(FALSE, TRUE, FALSE, FALSE)), "fad330c07a6226c6") test_equal(siphash13("secret base", key = as.raw(1L)), "5ecd894f7d269521") -test_error(siphash13("", key = list()), "'key' must be an atomic vector or NULL") +test_error(siphash13("", key = list()), "'key' must be a character string, raw vector or NULL") test_equal(siphash13("secret base", convert = NA)[2L], 250588011L) test_equal(siphash13(siphash13("secret base", convert = FALSE)), "498db1332ca02148") test_equal(siphash13(data.frame(a = 1, b = 2)), "e91a1e412627d654")