remove xcolor latex dependency
diff --git a/R/kable_styling.R b/R/kable_styling.R
index 0a43f74..ffa474c 100644
--- a/R/kable_styling.R
+++ b/R/kable_styling.R
@@ -285,42 +285,8 @@
 }
 
 styling_latex_striped <- function(x, table_info, color) {
-  # gray!6 is the same as shadecolor ({RGB}{248, 248, 248}) in pdf_document
-  if (table_info$tabular == "longtable" & !is.na(table_info$caption)) {
-    row_color <- sprintf("\\rowcolors{%s}{white}{%s}",
-                         1 + table_info$position_offset, color)
-  } else {
-    if (table_info$position_offset == 0) {
-      row_color <- sprintf("\\rowcolors{1}{white}{%s}", color)
-    } else {
-      row_color <- sprintf("\\rowcolors{2}{%s}{white}", color)
-    }
-  }
-
-  x <- read_lines(x)
-  if (table_info$booktabs) {
-    header_rows_start <- which(trimws(x) == "\\toprule")[1]
-    if (is.null(table_info$colnames)) {
-      header_rows_end <- header_rows_start
-    } else {
-      header_rows_end <- which(trimws(x) == "\\midrule")[1]
-    }
-  } else {
-    header_rows_start <- which(trimws(x) == "\\hline")[1]
-    header_rows_end <- which(trimws(x) == "\\hline")[2]
-  }
-
-  x <- c(
-    row_color,
-    x[1:(header_rows_start - 1)],
-    "\\hiderowcolors",
-    x[header_rows_start:header_rows_end],
-    "\\showrowcolors",
-    x[(header_rows_end + 1):length(x)],
-    "\\rowcolors{2}{white}{white}"
-  )
-  x <- paste0(x, collapse = "\n")
-  return(x)
+  striped_rows <- seq(1, table_info$nrow, 2)
+  row_spec(x, striped_rows, background = color)
 }
 
 styling_latex_hold_position <- function(x) {
diff --git a/R/save_kable.R b/R/save_kable.R
index 5a5cbc0..85ed54a 100644
--- a/R/save_kable.R
+++ b/R/save_kable.R
@@ -4,35 +4,59 @@
 #' kableExtra
 #' @param file save to files. If the input table is in HTML and the output file
 #' ends with `.png`, `.pdf` and `.jpeg`, `webshot` will be used to do the
-#' conversion
-#'
+#' conversion.
 #' @param bs_theme Which Bootstrap theme to use
 #' @param self_contained Will the files be self-contained?
-#' @param ... Additional variables being passed to `webshot::webshot`.`
+#' @param extra_dependencies Additional HTML dependencies. For example,
+#' `list(`
+#' @param ... Additional variables being passed to `webshot::webshot`. This
+#' is for HTML only.
+#' @param latex_header_includes A character vector of extra LaTeX header stuff.
+#' Each element is a row. You can have things like
+#' `c("\\\\usepackage{threeparttable}", "\\\\usepackage{icons}")`  You could
+#' probably add your language package here if you use non-English text in your
+#' table, such as `\\\\usepackage[magyar]{babel}`.
+#' @param keep_tex A T/F option to control if the latex file that is initially created
+#' should be kept. Default is `FALSE`.
 #'
 #' @export
 save_kable <- function(x, file,
-                       bs_theme = "simplex", self_contained = TRUE, ...) {
+                       bs_theme = "simplex", self_contained = TRUE,
+                       extra_dependencies = NULL, ...,
+                       latex_header_includes = NULL, keep_tex = FALSE) {
   if (attr(x, "format") == "latex") {
-    return(save_kable_latex(x, file))
+    return(save_kable_latex(x, file, latex_header_includes, keep_tex))
   }
-  return(save_kable_html(x, file, bs_theme, self_contained, ...))
+  return(save_kable_html(x, file, bs_theme, self_contained,
+                         extra_dependencies, ...))
 }
 
-save_kable_html <- function(x, file, bs_theme, self_contained, ...) {
-  html_header <- htmltools::tags$head(
+save_kable_html <- function(x, file, bs_theme, self_contained,
+                            extra_dependencies, ...) {
+  dependencies <- list(
     rmarkdown::html_dependency_jquery(),
     rmarkdown::html_dependency_bootstrap(theme = bs_theme),
     html_dependency_kePrint()
   )
+  if (!is.null(extra_dependencies)) {
+    dependencies <- append(dependencies, extra_dependencies)
+  }
+
+  html_header <- htmltools::tag("head", dependencies)
   html_table <- htmltools::HTML(as.character(x))
   html_result <- htmltools::tagList(html_header, html_table)
 
   # Use webshot if necessary
   if (tools::file_ext(file) %in% c("png", "jpg", "jpeg", "pdf")) {
+    message("Putting together a HTML file...")
     file_html <- paste0(tools::file_path_sans_ext(file), ".html")
     htmltools::save_html(html_result, file = file_html)
+    message("Converting HTML to ", tools::file_ext(file), "...")
     webshot::webshot(file_html, file, ...)
+    message("Done. ")
+    if (tools::file_ext(file) == "pdf") {
+      message("Note that HTML color may not be displayed on PDF properly.")
+    }
     unlink(file_html)
     unlink("lib", recursive = TRUE)
   } else {
@@ -44,6 +68,53 @@
   }
 }
 
-save_kable_latex <- function(x, file) {
+save_kable_latex <- function(x, file, latex_header_includes, keep_tex) {
+  temp_tex <- c(
+    "\\documentclass[border=1mm, preview]{standalone}",
+    "\\usepackage[active,tightpage]{preview}",
+    "\\usepackage{varwidth}",
+    "\\usepackage{amssymb, amsmath}",
+    "\\usepackage{ifxetex,ifluatex}",
+    "\\usepackage{fixltx2e}",
+    "\\usepackage{polyglossia}",
+    "\\setmainlanguage{$mainlang$}",
+    latex_pkg_list(),
+    "\\usepackage{graphicx}",
+    "\\usepackage{mathspec}",
+    "\\usepackage{xltxtra,xunicode}",
+    latex_header_includes,
+    "\\begin{document}",
+    solve_enc(x),
+    "\\end{document}"
+  )
+  temp_tex <- paste(temp_tex, collapse = "\n")
 
+  temp_tex_file <- tools::file_path_sans_ext(file)
+  writeLines(temp_tex, temp_tex_file, useBytes = T)
+  system(paste0("xelatex -interaction=batchmode ", temp_tex_file))
+  if (!keep_tex) {
+    temp_file_delete <- paste0(tools::file_path_sans_ext(file),
+                               c(".tex", ".aux", ".log"))
+    unlink(temp_file_delete)
+  }
+
+  table_img_pdf <- try(magick::image_read(paste0(temp_file, ".pdf"),
+                                          density = density),
+                       silent = T)
+  if (class(table_img_pdf) == "try-error") {
+    stop("Ghostscript is required to read PDF on windows. ",
+         "Please download it here: https://ghostscript.com/")
+  }
+  if (!keep_pdf) {
+    unlink(paste0(temp_file, ".pdf"))
+  }
+  table_img <- magick::image_convert(table_img_pdf, file_format)
+  if (!is.null(filename)) {
+    temp_img <- paste0(filename, ".", file_format)
+  } else {
+    temp_img <- tempfile(fileext = paste0(".", file_format))
+  }
+  magick::image_write(table_img, temp_img)
+
+  include_graphics(temp_img)
 }
diff --git a/R/util.R b/R/util.R
index 6e174d7..790d949 100644
--- a/R/util.R
+++ b/R/util.R
@@ -45,7 +45,11 @@
 }
 
 latex_row_cells <- function(x) {
-  strsplit(x, " \\& ")
+  out <- unlist(strsplit(x, " \\& "))
+  if (substr(x, nchar(x) - 2, nchar(x)) == " & ") {
+    out <- c(out, "")
+  }
+  return(out)
 }
 
 regex_escape <- function(x, double_backslash = FALSE) {
@@ -100,7 +104,6 @@
     "\\usepackage{longtable}",
     "\\usepackage{array}",
     "\\usepackage{multirow}",
-    "\\usepackage[table]{xcolor}",
     "\\usepackage{wrapfig}",
     "\\usepackage{float}",
     "\\usepackage{colortbl}",
diff --git a/R/zzz.R b/R/zzz.R
index e7b3c60..2aa54f0 100644
--- a/R/zzz.R
+++ b/R/zzz.R
@@ -5,7 +5,6 @@
     usepackage_latex("longtable")
     usepackage_latex("array")
     usepackage_latex("multirow")
-    usepackage_latex("xcolor", "table")
     usepackage_latex("wrapfig")
     usepackage_latex("float")
     usepackage_latex("colortbl")