Skip to content
Snippets Groups Projects
Commit 81aba64d authored by Cheng Shao's avatar Cheng Shao
Browse files

ghci: use improved Pipe logic for wasm iserv

This commit makes wasm iserv take advantage of the Pipe refactoring by
passing binary receiver/sender js callbacks from the dyld script. This
paves the way for piping the binary messages through WebSockets in
order to run wasm iserv in the browser, but more importantly, it
allows us to get rid of a horrible hack in the dyld script: we no
longer have to fake magical wasi file descriptors that are backed by
nodejs blocking I/O! The legacy hack was due to these facts:

- iserv only supported exchanging binary messages via handles backed
  by file descriptors
- In wasi you can't access host file descriptors passed by host ghc
- The nodejs wasi implementation only allows mapping host directories
  into the wasi vfs, not host file descriptors
- Named pipes with file paths (mkfifo) doesn't work well with nodejs
  wasi implementation, causes spurious testsuite failures on macos

But starting from this point, we can fully take advantage of
non-blocking I/O on the js side.

(cherry picked from commit a2103fd2)
parent 4148bc13
No related branches found
No related tags found
No related merge requests found
......@@ -21,7 +21,7 @@ module GHCi.Message
, ResumeContext(..)
, QState(..)
, getMessage, putMessage, getTHMessage, putTHMessage
, Pipe, mkPipeFromHandles, remoteCall, remoteTHCall, readPipe, writePipe
, Pipe, mkPipeFromHandles, mkPipeFromContinuations, remoteCall, remoteTHCall, readPipe, writePipe
, BreakModule
, LoadedDLL
) where
......@@ -662,6 +662,12 @@ mkPipeFromHandles pipeRead pipeWrite = do
pipeLeftovers <- newIORef Nothing
pure $ Pipe { getSome, putAll, pipeLeftovers }
-- | Make a 'Pipe' from a reader function and a writer function.
mkPipeFromContinuations :: IO ByteString -> (B.Builder -> IO ()) -> IO Pipe
mkPipeFromContinuations getSome putAll = do
pipeLeftovers <- newIORef Nothing
pure $ Pipe { getSome, putAll, pipeLeftovers }
remoteCall :: Binary a => Pipe -> Message a -> IO a
remoteCall pipe msg = do
writePipe pipe (putMessage msg)
......
......@@ -9,10 +9,19 @@ import Prelude
import GHCi.Run
import GHCi.TH
import GHCi.Message
#if !defined(wasm32_HOST_ARCH)
#if defined(wasm32_HOST_ARCH)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Builder as B
import qualified Data.ByteString.Internal as B
import qualified Data.ByteString.Unsafe as B
import qualified Data.ByteString.Lazy as LB
import Foreign
import Foreign.ForeignPtr.Unsafe
import GHC.Wasm.Prim
#else
import GHCi.Signals
#endif
import GHCi.Utils
#endif
import Control.DeepSeq
import Control.Exception
......@@ -97,6 +106,12 @@ serv verbose hook pipe restore = loop
_ -> return ()
-- | Default server
#if defined(wasm32_HOST_ARCH)
defaultServer :: Callback (IO JSUint8Array) -> Callback (JSUint8Array -> IO ()) -> IO ()
defaultServer cb_recv cb_send = do
args <- getArgs
let rest = args
#else
defaultServer :: IO ()
defaultServer = do
args <- getArgs
......@@ -107,6 +122,7 @@ defaultServer = do
outh <- readGhcHandle arg0
return (outh, inh, rest)
_ -> dieWithUsage
#endif
(verbose, rest') <- case rest of
"-v":rest' -> return (True, rest')
......@@ -119,14 +135,14 @@ defaultServer = do
unless (null rest'') $
dieWithUsage
#if defined(wasm32_HOST_ARCH)
pipe <- mkPipeFromContinuations (recv_buf cb_recv) (send_buf cb_send)
#else
when verbose $
printf "GHC iserv starting (in: %s; out: %s)\n" (show inh) (show outh)
#if !defined(wasm32_HOST_ARCH)
installSignalHandlers
#endif
pipe <- mkPipeFromHandles inh outh
#endif
when wait $ do
when verbose $
......@@ -152,6 +168,37 @@ dieWithUsage = do
#if defined(wasm32_HOST_ARCH)
foreign export javascript "defaultServer" defaultServer :: IO ()
newtype Callback a = Callback JSVal
newtype JSUint8Array = JSUint8Array { unJSUint8Array :: JSVal }
recv_buf :: Callback (IO JSUint8Array) -> IO ByteString
recv_buf cb = do
buf <- js_recv_buf cb
len <- js_buf_len buf
fp <- mallocForeignPtrBytes len
js_download_buf buf $ unsafeForeignPtrToPtr fp
freeJSVal $ unJSUint8Array buf
evaluate $ B.fromForeignPtr0 fp len
send_buf :: Callback (JSUint8Array -> IO ()) -> B.Builder -> IO ()
send_buf cb b = do
buf <- evaluate $ LB.toStrict $ B.toLazyByteString b
B.unsafeUseAsCStringLen buf $ \(ptr, len) -> js_send_buf cb ptr len
foreign import javascript "dynamic"
js_recv_buf :: Callback (IO JSUint8Array) -> IO JSUint8Array
foreign import javascript unsafe "$1.byteLength"
js_buf_len :: JSUint8Array -> IO Int
foreign import javascript unsafe "(new Uint8Array(__exports.memory.buffer, $2, $1.byteLength)).set($1)"
js_download_buf :: JSUint8Array -> Ptr a -> IO ()
foreign import javascript unsafe "$1(new Uint8Array(__exports.memory.buffer, $2, $3))"
js_send_buf :: Callback (JSUint8Array -> IO ()) -> Ptr a -> Int -> IO ()
foreign export javascript "defaultServer"
defaultServer :: Callback (IO JSUint8Array) -> Callback (JSUint8Array -> IO ()) -> IO ()
#endif
......@@ -90,9 +90,9 @@
// to dump the iserv messages.
import assert from "node:assert/strict";
import fs from "node:fs/promises";
import fsSync from "node:fs";
import fs from "node:fs";
import path from "node:path";
import stream from "node:stream";
import { WASI } from "node:wasi";
import { JSValManager } from "./prelude.mjs";
import { parseRecord, parseSections } from "./post-link.mjs";
......@@ -242,23 +242,10 @@ class DyLD {
"__wasm_call_ctors",
]);
// Virtual file descriptors designated for IPC logic and passed to
// iserv main. uvwasi doesn't support preopening host file
// descriptors as wasi file descriptors so we designate them and
// hook certain wasi syscalls on them, so that the pipe file
// descriptors passed from GHC can be used to communicate with the
// wasm side.
static read_fd = 0x7ffffffe;
static write_fd = 0x7fffffff;
// The WASI instance to provide wasi imports, shared across all wasm
// instances
#wasi;
// The actual wasi_snapshot_preview1 import object, after hooking
// the wasi syscalls provided by uvwasi.
#wasiImport;
// Wasm memory & table
#memory = new WebAssembly.Memory({ initial: 1 });
#table = new WebAssembly.Table({ element: "anyfunc", initial: 1 });
......@@ -309,7 +296,7 @@ class DyLD {
// Global STG registers
#regs = {};
constructor({ args, out_fd, in_fd }) {
constructor({ args }) {
this.#wasi = new WASI({
version: "preview1",
args,
......@@ -317,134 +304,6 @@ class DyLD {
preopens: { "/": "/" },
});
this.#wasiImport = {};
// https://gitlab.haskell.org/ghc/wasi-libc/-/blob/master/libc-bottom-half/headers/public/wasi/api.h
for (const k in this.#wasi.wasiImport) {
switch (k) {
case "fd_fdstat_get": {
this.#wasiImport[k] = (fd, retptr0) => {
switch (fd) {
case DyLD.read_fd: {
const fdstat = new DataView(this.#memory.buffer, retptr0, 24);
fdstat.setUint8(0, 6); // __wasi_filetype_t fs_filetype;
fdstat.setUint16(2, 0, true); // __wasi_fdflags_t fs_flags;
fdstat.setBigUint64(8, (1n << 1n) | (1n << 21n), true); // __wasi_rights_t fs_rights_base;
fdstat.setBigUint64(16, (1n << 1n) | (1n << 21n), true); // __wasi_rights_t fs_rights_inheriting;
return 0;
}
case DyLD.write_fd: {
const fdstat = new DataView(this.#memory.buffer, retptr0, 24);
fdstat.setUint8(0, 6); // __wasi_filetype_t fs_filetype;
fdstat.setUint16(2, 0, true); // __wasi_fdflags_t fs_flags;
fdstat.setBigUint64(8, (1n << 6n) | (1n << 21n), true); // __wasi_rights_t fs_rights_base;
fdstat.setBigUint64(16, (1n << 1n) | (1n << 21n), true); // __wasi_rights_t fs_rights_inheriting;
return 0;
}
default: {
return this.#wasi.wasiImport[k](fd, retptr0);
}
}
};
break;
}
case "fd_filestat_get": {
this.#wasiImport[k] = (fd, retptr0) => {
switch (fd) {
case DyLD.read_fd: {
const filestat = new DataView(this.#memory.buffer, retptr0, 64);
filestat.setBigUint64(0, 109n, true); // __wasi_device_t dev;
filestat.setBigUint64(8, BigInt(DyLD.read_fd), true); // __wasi_inode_t ino;
filestat.setUint8(16, 6); // __wasi_filetype_t filetype;
filestat.setBigUint64(24, 1n, true); // __wasi_linkcount_t nlink;
filestat.setBigUint64(32, 0n, true); // __wasi_filesize_t size;
filestat.setBigUint64(40, 0n, true); // __wasi_timestamp_t atim;
filestat.setBigUint64(48, 0n, true); // __wasi_timestamp_t mtim;
filestat.setBigUint64(56, 0n, true); // __wasi_timestamp_t ctim;
return 0;
}
case DyLD.write_fd: {
const filestat = new DataView(this.#memory.buffer, retptr0, 64);
filestat.setBigUint64(0, 109n, true); // __wasi_device_t dev;
filestat.setBigUint64(8, BigInt(DyLD.read_fd), true); // __wasi_inode_t ino;
filestat.setUint8(16, 6); // __wasi_filetype_t filetype;
filestat.setBigUint64(24, 1n, true); // __wasi_linkcount_t nlink;
filestat.setBigUint64(32, 0n, true); // __wasi_filesize_t size;
filestat.setBigUint64(40, 0n, true); // __wasi_timestamp_t atim;
filestat.setBigUint64(48, 0n, true); // __wasi_timestamp_t mtim;
filestat.setBigUint64(56, 0n, true); // __wasi_timestamp_t ctim;
return 0;
}
default: {
return this.#wasi.wasiImport[k](fd, retptr0);
}
}
};
break;
}
case "fd_read": {
this.#wasiImport[k] = (fd, iovs, iovs_len, retptr0) => {
switch (fd) {
case DyLD.read_fd: {
assert(iovs_len === 1);
const iov = new DataView(this.#memory.buffer, iovs, 8);
const buf = iov.getUint32(0, true),
buf_len = iov.getUint32(4, true);
const bytes_read = fsSync.readSync(
in_fd,
new Uint8Array(this.#memory.buffer, buf, buf_len)
);
new DataView(this.#memory.buffer, retptr0, 4).setUint32(
0,
bytes_read,
true
);
return 0;
}
default: {
return this.#wasi.wasiImport[k](fd, iovs, iovs_len, retptr0);
}
}
};
break;
}
case "fd_write": {
this.#wasiImport[k] = (fd, iovs, iovs_len, retptr0) => {
switch (fd) {
case DyLD.write_fd: {
assert(iovs_len === 1);
const iov = new DataView(this.#memory.buffer, iovs, 8);
const buf = iov.getUint32(0, true),
buf_len = iov.getUint32(4, true);
const bytes_written = fsSync.writeSync(
out_fd,
new Uint8Array(this.#memory.buffer, buf, buf_len)
);
new DataView(this.#memory.buffer, retptr0, 4).setUint32(
0,
bytes_written,
true
);
return 0;
}
default: {
return this.#wasi.wasiImport[k](fd, iovs, iovs_len, retptr0);
}
}
};
break;
}
default: {
this.#wasiImport[k] = (...args) => this.#wasi.wasiImport[k](...args);
break;
}
}
}
// Keep this in sync with rts/wasm/Wasm.S!
for (let i = 1; i <= 10; ++i) {
this.#regs[`__R${i}`] = new WebAssembly.Global({
......@@ -485,14 +344,14 @@ class DyLD {
// non-existent.
async findSystemLibrary(f) {
if (path.isAbsolute(f)) {
await fs.access(f, fs.constants.R_OK);
await fs.promises.access(f, fs.promises.constants.R_OK);
return f;
}
const r = (
await Promise.allSettled(
[...this.#rpaths].map(async (p) => {
const r = path.resolve(p, f);
await fs.access(r, fs.constants.R_OK);
await fs.promises.access(r, fs.promises.constants.R_OK);
return r;
})
)
......@@ -532,7 +391,7 @@ class DyLD {
p = await this.findSystemLibrary(p);
}
const buf = await fs.readFile(p);
const buf = await fs.promises.readFile(p);
const modp = WebAssembly.compile(buf);
// Parse dylink.0 from the raw buffer, not via
// WebAssembly.Module.customSections(). At this point we only care
......@@ -560,7 +419,7 @@ class DyLD {
soname,
} of await this.#downsweep(p)) {
const import_obj = {
wasi_snapshot_preview1: this.#wasiImport,
wasi_snapshot_preview1: this.#wasi.wasiImport,
env: {
memory: this.#memory,
__indirect_function_table: this.#table,
......@@ -837,17 +696,36 @@ if (isMain()) {
const libdir = process.argv[2],
ghci_so_path = process.argv[3];
// Inherited pipe file descriptors from GHC
const out_fd = Number.parseInt(process.argv[4]),
in_fd = Number.parseInt(process.argv[5]);
const dyld = new DyLD({
args: ["dyld.so", DyLD.write_fd, DyLD.read_fd, ...process.argv.slice(6)],
out_fd,
in_fd,
args: ["dyld.so", ...process.argv.slice(6)],
});
dyld.addLibrarySearchPath(libdir);
await dyld.loadDLL(ghci_so_path);
await dyld.exportFuncs.defaultServer();
// Inherited pipe file descriptors from GHC
const out_fd = Number.parseInt(process.argv[4]),
in_fd = Number.parseInt(process.argv[5]);
const in_stream = stream.Readable.toWeb(
fs.createReadStream(undefined, { fd: in_fd })
);
const out_stream = stream.Writable.toWeb(
fs.createWriteStream(undefined, { fd: out_fd })
);
const reader = in_stream.getReader();
const writer = out_stream.getWriter();
const cb_recv = async () => {
const { done, value } = await reader.read();
if (done) {
throw new Error("not enough bytes");
}
return value;
};
const cb_send = (buf) => {
writer.write(new Uint8Array(buf));
};
await dyld.exportFuncs.defaultServer(cb_recv, cb_send);
}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment