R/dec.R

Defines functions dec dec.Rcpp_FandV_sk

Documented in dec

#' Decrypt a ciphertext
#' 
#' This decrypts an integer message which has been encrypted under one of the 
#' homomorphic schemes supported by this package.
#' 
#' Note that the scheme specified by the private key, \code{sk}, and the ciphertext,
#' \code{ct}, must match.
#' 
#' If a symmetric key scheme is being used, then the secret key should be provided
#' for the \code{sk} argument.
#' 
#' @param sk a private/secret key for any scheme as generated by the \code{\link{keygen}}.
#' function.
#' 
#' @param ct a ciphertext as produced from a call to \code{\link{enc}}.
#' 
#' @return
#' The decrypted integer message.  If the value is in the range of a standard
#' integer in R (-2147483647 to 2147483647) then an integer will be returned,
#' otherwise a \code{\link[gmp]{bigz}} big integer object from the gmp package
#' will be returned.
#' 
#' @seealso
#' \code{\link{enc}} to encrypt messages to ciphertexts which this function decrypts.
#' 
#' @examples
#' p <- pars("FandV")
#' keys <- keygen(p)
#' ct <- enc(keys$pk, 1)
#' dec(keys$sk, ct)
#' 
#' @author Louis Aslett
dec <- function(sk, ct) {
  if(is.null(attr(ct, "FHEt")) || (attr(ct, "FHEt")!="ct" && attr(ct, "FHEt")!="ctvec" && attr(ct, "FHEt")!="ctmat")) stop("ct argument does not contain a cipher text.")
  if(is.null(attr(sk, "FHEt")) || attr(sk, "FHEt")!="sk") stop("sk argument is not a secret key.")
  if(is.null(attr(ct, "FHEs")) || is.null(attr(sk, "FHEs")) || attr(ct, "FHEs")!=attr(sk, "FHEs")) stop("Mismatch between cryptographic scheme specified by key and cipher text.")
  UseMethod("dec", sk)
}

dec.Rcpp_FandV_sk <- function(sk, ct) {
  if(class(ct) == "Rcpp_FandV_ct") {
    res <- as.bigz(sk$dec(ct))
    if(res < 2147483647 && res > -2147483647)
      return(as.integer(res))
    else
      return(res)
  } else if(class(ct) == "Rcpp_FandV_ct_vec") {
    res <- as.bigz(sk$dec(ct[1]))
    
    for(i in 2:ct$size()) {
      res <- c(res, as.bigz(sk$dec(ct[i])))
    }
    
    if(sum(res > 2147483647 | res < -2147483647) == 0)
      return(as.integer(res))
    else
      return(res)
  } else if(class(ct) == "Rcpp_FandV_ct_mat") {
    res <- as.bigz(sk$dec(ct[1]))
    
    if(ct$size()>1) {
      for(i in 2:ct$size()) {
        res <- c(res, as.bigz(sk$dec(ct[i])))
      }
    }
    
    if(sum(res > 2147483647 | res < -2147483647) == 0)
      return(matrix(as.integer(res), nrow=ct$nrow, ncol=ct$ncol))
    else
      return(matrix(res, nrow=ct$nrow, ncol=ct$ncol))
  }
}

# # Note: currently this CRT code does not work for big integers in the way the 
# # regular FandV does because we call into the numbers package to do CRT
# # reconstruction ... on the to-do list to bring that in house and do bigints
# dec.CRT <- function(sk, crt) {
#   # Decrypt the raw polynomials
#   aL <- list()
#   m <- NULL
#   for(i in 1:length(crt@ct)) {
#     aL[[i]] <- sk[[i]]$decraw(crt@ct[[i]])
#     m <- c(m, crt@ct[[i]]$p$get_t())
#   }
#   # Even up the number of elements in each list item so that we can rbind them
#   mx <- max(unlist(lapply(aL, length)))
#   aL <- lapply(aL, function(x, max) { c(x, rep(0, max-length(x))) }, max=mx) # NB could do this better by unlisting and straight into matrix byrow, BUT not if aL ever becomes bigz's so leaving like this for now
#   a <- aL[[1]]
#   for(i in 2:length(aL)) {
#     a <- rbind(a, aL[[i]])
#   }
#   #print(a)
#   #print(as.integer(m))
#   # Do CRT recovery on each coefficient to get the result polynomial
#   res <- chinese(as.bigz(a[,1]), as.bigz(m))
#   if(dim(a)[2]>1)
#     for(i in 2:(dim(a)[2])) {
#       res <- c(res, chinese(as.bigz(a[,i]), as.bigz(m)))
#     }
#   #print(res)
#   res[res>prod(as.bigz(m))%/%2] <- res[res>prod(as.bigz(m))%/%2]-prod(as.bigz(m)) # centered reduction
#   #print(res)
#   # Recover value
#   c(t(res) %*% 2^(0:(length(res)-1)))
# }
# 
# dec.FandV_CRT_sk <- function(sk, ct) {
#   if(attr(ct@ct[[1]], "FHEt") == "ct") {
#     res <- dec.CRT(sk, ct)
#     if(res < 2147483647 && res > -2147483647)
#       return(as.integer(res))
#     else
#       return(res)
#   } else if(attr(ct@ct[[1]], "FHEt") == "ctvec") {
#     # Construct crt object containing just first element of vector
#     crt <- new("CRT", ct=list())
#     for(i in 1:length(ct@ct))
#       crt@ct[[i]] <- ct@ct[[i]][1]
#     # Decrypt this
#     res <- dec.CRT(sk, crt)
#     # Rinse and repeat for remaining elements
#     for(j in 2:length(ct@ct[[i]])) {
#       for(i in 1:length(ct@ct))
#         crt@ct[[i]] <- ct@ct[[i]][j]
#       res <- c(res, dec.CRT(sk, crt))
#     }
#   } else if(attr(ct@ct[[1]], "FHEt") == "ctmat") {
#     
#   }
#   
# }
iamtrask/R-Homomorphic-Encryption-Package documentation built on May 29, 2019, 2:56 p.m.