Skip to content

Commit

Permalink
Add server impl
Browse files Browse the repository at this point in the history
  • Loading branch information
yutannihilation committed Oct 16, 2024
1 parent 6cba577 commit 77cfaa9
Show file tree
Hide file tree
Showing 10 changed files with 215 additions and 0 deletions.
3 changes: 3 additions & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -15,3 +15,6 @@ Encoding: UTF-8
Roxygen: list(markdown = TRUE)
RoxygenNote: 7.3.2
SystemRequirements: Cargo (Rust's package manager), rustc
Imports:
jsonlite,
tools
5 changes: 5 additions & 0 deletions R/000-wrappers.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,11 @@ NULL
}


`vellogd_with_server_impl` <- function(`filename`, `width`, `height`, `server` = NULL) {
invisible(.Call(savvy_vellogd_with_server_impl__impl, `filename`, `width`, `height`, `server`))
}


`debuggd` <- function() {
invisible(.Call(savvy_debuggd__impl))
}
Expand Down
80 changes: 80 additions & 0 deletions R/download-server.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,80 @@
VELLOGD_SERVER_PATH_ENVVAR <- "VELLOGD_SERVER_PATH"

pkg_cache_dir <- function() {
normalizePath(tools::R_user_dir("vellogd", "cache"), mustWork = FALSE)
}

server_path <- function() {
server_path <- Sys.getenv(VELLOGD_SERVER_PATH_ENVVAR)

# If the server path is provided by the user, return it.
if (!identity(server_path, "")) {
return(server_path)
}

server_path <- server_path_default()

# TODO: check version
if (!file.exists(server_path)) {
download_server()
}

server_path
}

server_path_default <- function() {
bin <- if (Sys.info()[["sysname"]] == "Windows") {
"vellogd-server.exe"
} else {
"vellogd-server"
}

path <- file.path(pkg_cache_dir(), bin)
}

URL_BASE <- "https://github.com/yutannihilation/vellogd/releases/download"

get_latest_release <- function() {
jsonlite::read_json("https://api.github.com/repos/yutannihilation/vellogd/releases/latest")[["tag_name"]]
}

get_download_url <- function() {
latest_release <- get_latest_release()

os <- Sys.info()[["sysname"]]
arch <- Sys.info()[["machine"]]

binary <- switch(os,
Windows = "server-Windows-X64.tar.gz",
Linux = "server-Linux-X64.tar.gz",
Darwin = "server-macOS-ARM64.tar.gz"
)

paste(URL_BASE, latest_release, binary, sep = "/")
}

download_server <- function() {
download_tmp_dir <- tempfile()
extract_tmp_dir <- tempfile()
on.exit(unlink(download_tmp_dir, recursive = TRUE, force = TRUE), add = TRUE)
on.exit(unlink(extract_tmp_dir, recursive = TRUE, force = TRUE), add = TRUE)

# download
dir.create(download_tmp_dir)
download_url <- get_download_url()
archive_file <- file.path(download_tmp_dir, basename(download_url))
utils::download.file(download_url, destfile = archive_file, mode = "wb")

# extract and copy
dst <- server_path()
dir.create(dirname(dst), showWarnings = FALSE)

utils::untar(archive_file, exdir = extract_tmp_dir)
if (Sys.info()[["sysname"]] == "Windows") {
file.copy(file.path(extract_tmp_dir, "vellogd-server.exe"), dst, overwrite = TRUE)
} else {
file.copy(file.path(extract_tmp_dir, "vellogd-server"), dst, overwrite = TRUE)
}

invisible(NULL)
}
10 changes: 10 additions & 0 deletions R/main.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,14 @@
#' Open A 'Vello' Graphics Device.
#'
#' @export
vellogd <- function(filename = "Rplot%03d.png", width = 480, height = 480) {
vellogd_impl(filename, as.numeric(width), as.numeric(height))
}

#' Open A 'Vello' Graphics Device With Server.
#'
#' @export
vellogd <- function(filename = "Rplot%03d.png", width = 480, height = 480) {
server <- server_path()
vellogd_with_server_impl(filename, as.numeric(width), as.numeric(height), server)
}
15 changes: 15 additions & 0 deletions man/vellogd.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

6 changes: 6 additions & 0 deletions src/init.c
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,11 @@ SEXP savvy_vellogd_impl__impl(SEXP c_arg__filename, SEXP c_arg__width, SEXP c_ar
return handle_result(res);
}

SEXP savvy_vellogd_with_server_impl__impl(SEXP c_arg__filename, SEXP c_arg__width, SEXP c_arg__height, SEXP c_arg__server) {
SEXP res = savvy_vellogd_with_server_impl__ffi(c_arg__filename, c_arg__width, c_arg__height, c_arg__server);
return handle_result(res);
}

SEXP savvy_debuggd__impl(void) {
SEXP res = savvy_debuggd__ffi();
return handle_result(res);
Expand All @@ -47,6 +52,7 @@ SEXP savvy_debuggd__impl(void) {

static const R_CallMethodDef CallEntries[] = {
{"savvy_vellogd_impl__impl", (DL_FUNC) &savvy_vellogd_impl__impl, 3},
{"savvy_vellogd_with_server_impl__impl", (DL_FUNC) &savvy_vellogd_with_server_impl__impl, 4},
{"savvy_debuggd__impl", (DL_FUNC) &savvy_debuggd__impl, 0},
{NULL, NULL, 0}
};
Expand Down
1 change: 1 addition & 0 deletions src/rust/api.h
Original file line number Diff line number Diff line change
@@ -1,2 +1,3 @@
SEXP savvy_vellogd_impl__ffi(SEXP c_arg__filename, SEXP c_arg__width, SEXP c_arg__height);
SEXP savvy_vellogd_with_server_impl__ffi(SEXP c_arg__filename, SEXP c_arg__width, SEXP c_arg__height, SEXP c_arg__server);
SEXP savvy_debuggd__ffi(void);
18 changes: 18 additions & 0 deletions src/rust/src/lib.rs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ mod vello_device;
use graphics::DeviceDescriptor;
use graphics::DeviceDriver;
use savvy::savvy;
use vello_device::VelloGraphicsDeviceWithServer;
use vellogd_shared::protocol::UserEvent;
use vellogd_shared::protocol::UserResponse;

Expand Down Expand Up @@ -36,6 +37,23 @@ fn vellogd_impl(filename: &str, width: f64, height: f64) -> savvy::Result<()> {
Ok(())
}

#[savvy]
fn vellogd_with_server_impl(
filename: &str,
width: f64,
height: f64,
server: Option<&str>,
) -> savvy::Result<()> {
let device_driver = VelloGraphicsDeviceWithServer::new(filename, server)?;

// TODO: the actual width and height is kept on the server's side.
let device_descriptor = DeviceDescriptor::new(width, height);

device_driver.create_device::<VelloGraphicsDeviceWithServer>(device_descriptor, "vellogd")?;

Ok(())
}

#[savvy]
fn debuggd() -> savvy::Result<()> {
debuggd_inner();
Expand Down
3 changes: 3 additions & 0 deletions src/rust/src/vello_device/mod.rs
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,6 @@ pub use default::VelloGraphicsDevice;
mod macos;
#[cfg(target_os = "macos")]
pub use macos::VelloGraphicsDevice;

mod with_server;
pub use with_server::VelloGraphicsDeviceWithServer;
74 changes: 74 additions & 0 deletions src/rust/src/vello_device/with_server.rs
Original file line number Diff line number Diff line change
@@ -0,0 +1,74 @@
use ipc_channel::ipc::{IpcOneShotServer, IpcReceiver, IpcSender};
use vellogd_shared::protocol::{UserEvent, UserResponse};

use crate::{graphics::DeviceDriver, WindowController};

pub struct VelloGraphicsDeviceWithServer {
filename: String,
layout: parley::Layout<vello::peniko::Brush>,
process: Option<std::process::Child>,
tx: IpcSender<UserEvent>,
rx: IpcReceiver<UserResponse>,
}

impl VelloGraphicsDeviceWithServer {
pub(crate) fn new(filename: &str, server: Option<&str>) -> savvy::Result<Self> {
// server -> controller
let (rx_server, rx_server_name) = IpcOneShotServer::<UserResponse>::new().unwrap();

let server_process = if let Some(server_bin) = server {
// spawn a server process
let res = std::process::Command::new(server_bin)
.arg(rx_server_name)
// .stdout(std::process::Stdio::piped())
.spawn();

match res {
Ok(c) => {
savvy::r_eprintln!("Server runs at PID {}", c.id());
Some(c)
}
Err(e) => {
let msg = format!("failed to spawn the process: {e}");
return Err(savvy::Error::new(&msg));
}
}
} else {
savvy::r_eprintln!("rx_server_name: {rx_server_name}");
None
};

// establish connections of both direction
let (tx, rx) = match rx_server.accept() {
Ok((rx, UserResponse::Connect { server_name })) => {
savvy::r_eprint!("Connecting to {server_name}...");
let tx: IpcSender<UserEvent> = IpcSender::connect(server_name).unwrap();
tx.send(UserEvent::ConnectionReady).unwrap();
(tx, rx)
}
Ok((_, data)) => panic!("got unexpected data: {data:?}"),
Err(e) => panic!("failed to accept connection: {e}"),
};
savvy::r_eprintln!("connected!");

Ok(Self {
filename: filename.into(),
layout: parley::Layout::new(),
process: server_process,
tx,
rx,
})
}
}

impl WindowController for VelloGraphicsDeviceWithServer {
fn send_event(&self, event: vellogd_shared::protocol::UserEvent) -> savvy::Result<()> {
self.tx.send(event).map_err(|e| e.to_string().into())
}

fn recv_response(&self) -> savvy::Result<vellogd_shared::protocol::UserResponse> {
self.rx.recv().map_err(|e| e.to_string().into())
}
}

impl DeviceDriver for VelloGraphicsDeviceWithServer {}

0 comments on commit 77cfaa9

Please sign in to comment.