diff --git a/Clickable/DOM.hs b/Clickable/DOM.hs index c88ca7c..7f87e4d 100644 --- a/Clickable/DOM.hs +++ b/Clickable/DOM.hs @@ -32,7 +32,7 @@ defaultListenerOptions = ListenerOptions { } addEventListener :: FromJSVal a => (Event a -> JSExp) -> (a -> JSM ()) -> JSM () -addEventListener addScript k = +addEventListener script k = reactive add >>= jsCmd where add scope s = (s''', cmd) where k' = localScope scope . k @@ -41,7 +41,7 @@ addEventListener addScript k = s'' = subscribeEventFn (unsafeFromEventId eventId) (mapM_ k' . fromJSVal . unsafeCoerce) scope s' s''' = installFinalizerFn (jsCmd $ Apply (Ref unsub) []) scope s'' - cmd = AssignRef unsub $ addScript $ Event eventId + cmd = AssignRef scope unsub $ script $ Event eventId class EventName eventName where type EventListenerCb eventName :: Type diff --git a/Clickable/HTML.hs b/Clickable/HTML.hs index 456bd62..f81d937 100644 --- a/Clickable/HTML.hs +++ b/Clickable/HTML.hs @@ -2,18 +2,12 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE StrictData #-} {-# LANGUAGE OverloadedRecordDot #-} -{-# LANGUAGE DeriveAnyClass #-} -{-# LANGUAGE DerivingVia #-} {-# LANGUAGE BlockArguments #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE AllowAmbiguousTypes #-} -{-# LANGUAGE DataKinds #-} {-# OPTIONS_GHC -Wall #-} module Clickable.HTML where import Clickable.Internal import Clickable.Types -import Control.Monad import Control.Monad.Trans import Data.IORef import Data.Text (Text) @@ -46,7 +40,7 @@ dynText contentDyn = HTML \s e -> do c <- readDyn contentDyn refId <- newRefId.unJSM e e.ien_command $ PushStack $ CreateText c - e.ien_command $ AssignRef refId (PeekStack 0) + e.ien_command $ AssignRef e.ien_scope refId (PeekStack 0) e.ien_command PopIns let k nval = JSM \e' -> e'.ien_command $ UpdateText (Ref refId) nval @@ -116,7 +110,7 @@ saveStackHead = HTML \s e -> case s of Nothing -> do refId <- newRefId.unJSM e - e.ien_command $ AssignRef refId $ PeekStack 0 + e.ien_command $ AssignRef e.ien_scope refId $ PeekStack 0 return (refId, Just refId) Just saved -> pure (saved, s) @@ -127,24 +121,23 @@ blank = pure () dyn :: Dynamic (HTML ()) -> HTML () dyn val = do - brackets <- liftJSM insertBrackets scope <- liftJSM newScope - initialVal <- liftJSM $ readDyn val - let - update html = do - liftJSM $ clearBrackets brackets - html - exec h = - localScope scope $ customize (Ref brackets) h - liftJSM $ exec $ update initialVal + place <- liftJSM insertPlaceholder + initial <- liftJSM $ readDyn val + liftJSM $ update scope place initial liftJSM $ subscribe val \newVal -> do freeScope scope - exec $ update newVal + update scope place newVal + where + update scope place content = + localScope scope do + clearPlaceholder place + execHTML (Ref place) content -- | Auxilliary datatype used in 'simpleList' implementation -data ElemEnv a = ElemEnv { - brackets :: RefId, - state_var :: DynVar a, +data InternalElem a = InternalElem { + placeholder :: RefId, + elem_state :: DynVar a, elem_scope :: ScopeId } @@ -152,69 +145,64 @@ data ElemEnv a = ElemEnv { -- a` do not automatically propagate into the larger state. See -- `OverrideVar` and todomvc example to see one way to upstream -- changes into the larger state. -simpleList :: - forall a. Dynamic [a] -> - (Int -> DynVar a -> HTML ()) -> +simpleList :: forall a. + Dynamic [a] -> + (DynVar a -> HTML ()) -> HTML () -simpleList listDyn h = liftJSM do - internalStateRef <- liftIO $ newIORef ([] :: [ElemEnv a]) - brackets <- insertBrackets - let - exec brackets' scope = - localScope scope . customize (Ref brackets') - exec1 brackets' = customize (Ref brackets') - - setup :: Int -> [a] -> [ElemEnv a] -> JSM [ElemEnv a] - setup idx new existing = case (existing, new) of - ([], []) -> return [] +simpleList listDyn h = do + ref <- liftIO $ newIORef ([] :: [InternalElem a]) + place <- liftJSM insertPlaceholder + initial <- readDyn listDyn + liftJSM $ execHTML (Ref place) $ liftJSM $ updateList ref initial + liftJSM $ subscribe listDyn $ execHTML (Ref place) . liftJSM . updateList ref + where + synchronize :: [a] -> [InternalElem a] -> JSM [InternalElem a] + synchronize [] [] = return [] + synchronize (x:xs) [] = do -- New list is longer, append new elements - ([], x:xs) -> do - e <- newElem x - exec e.brackets e.elem_scope $ h idx e.state_var - fmap (e:) $ setup (idx + 1) xs [] + ie <- newElem x + localScope ie.elem_scope $ execHTML (Ref ie.placeholder) $ h ie.elem_state + fmap (ie:) $ synchronize xs [] + synchronize [] (r:rs) = do -- New list is shorter, delete the elements that no longer -- present in the new list - (r:rs, []) -> do - finalizeElems True (r:rs) - return [] + mapM_ dropElem (r:rs) + pure [] + synchronize (y:ys) (r:rs) = do -- Update existing elements along the way - (r:rs, y:ys) -> do - writeVar r.state_var y - fmap (r:) $ setup (idx + 1) ys rs - newElem :: a -> JSM (ElemEnv a) + writeVar r.elem_state y + fmap (r:) $ synchronize ys rs + newElem :: a -> JSM (InternalElem a) newElem a = do - elem_scope <- newScope - localScope elem_scope do - state_var <- newVar a - brackets' <- insertBrackets - return ElemEnv {elem_scope, state_var, brackets = brackets'} - finalizeElems :: Bool -> [ElemEnv a] -> JSM () - finalizeElems remove = mapM_ \ee -> do - when remove $ detachBrackets ee.brackets - destroyScope ee.elem_scope - updateList :: [a] -> JSM () - updateList new = do - eenvs <- liftIO $ readIORef internalStateRef - newEenvs <- setup 0 new eenvs - liftIO $ writeIORef internalStateRef newEenvs - initialVal <- readDyn listDyn - exec1 brackets $ liftJSM $ updateList initialVal - subscribe listDyn $ exec1 brackets . liftJSM . updateList - -insertBrackets :: JSM RefId -insertBrackets = do - brackets <- newRefId - jsCmd $ AssignRef brackets InsertBrackets - pure brackets - -clearBrackets :: RefId -> JSM () -clearBrackets rid = jsCmd $ ClearBrackets $ Ref rid - -detachBrackets :: RefId -> JSM () -detachBrackets rid = jsCmd $ DetachBrackets $ Ref rid - -customize :: JSExp -> HTML a -> JSM a -customize elm action = JSM \e -> do + scope <- newScope + localScope scope do + elem_state <- newVar a + place' <- insertPlaceholder + pure InternalElem {elem_scope = scope, elem_state, placeholder = place'} + dropElem :: InternalElem a -> JSM () + dropElem ie = do + destroyScope ie.elem_scope + detachPlaceholder ie.placeholder + updateList :: IORef [InternalElem a] -> [a] -> JSM () + updateList ref new = do + ies <- liftIO $ readIORef ref + ies' <- synchronize new ies + liftIO $ writeIORef ref ies' + +insertPlaceholder :: JSM RefId +insertPlaceholder = JSM \e -> do + ref <- newRefId.unJSM e + e.ien_command $ AssignRef e.ien_scope ref InsertPlaceholder + pure ref + +clearPlaceholder :: RefId -> JSM () +clearPlaceholder rid = jsCmd $ ClearPlaceholder $ Ref rid + +detachPlaceholder :: RefId -> JSM () +detachPlaceholder rid = jsCmd $ DetachPlaceholder $ Ref rid + +execHTML :: JSExp -> HTML a -> JSM a +execHTML elm action = JSM \e -> do e.ien_command $ PushStack elm (r, _) <- action.unHTML Nothing e e.ien_command PopStack diff --git a/Clickable/Internal.hs b/Clickable/Internal.hs index d6d2934..c7cbecb 100644 --- a/Clickable/Internal.hs +++ b/Clickable/Internal.hs @@ -196,48 +196,65 @@ newRefId = reactive newRefIdFn {-# INLINE newRefId #-} newRefIdFn :: ScopeId -> InternalState -> (InternalState, RefId) -newRefIdFn e s = (s {ist_id_supply = s.ist_id_supply + 1}, RefId e s.ist_id_supply) +newRefIdFn _e s = (s {ist_id_supply = s.ist_id_supply + 1}, RefId s.ist_id_supply) {-# INLINE newRefIdFn #-} freeScope :: ScopeId -> JSM () -freeScope s = do - mres <- state $ swap . freeScopeFn s - forM_ mres \r -> forM_ r.rsr_linked destroyScope - forM_ mres \r -> sequence_ r.rsr_finalizers -{-# INLINE freeScope #-} - -freeScopeFn :: ScopeId -> InternalState -> (InternalState, Maybe Resources) -freeScopeFn scope s = (s', resources) +freeScope scope = do + mres <- state updateState + forM_ mres \res -> do + forM_ (res.rsr_linked) destroyScope + sequence_ (res.rsr_finalizers) + jsCmd $ FreeScope scope where - subs = Map.map (List.filter filterSub) s.ist_subscriptions - filterSub sub = sub.sub_scope /= scope - (resources, rsr) = Map.alterF (,Nothing) scope s.ist_resources - s' = s {ist_subscriptions = subs, ist_resources = rsr} -{-# INLINE freeScopeFn #-} + updateState :: InternalState -> (Maybe Resources, InternalState) + updateState s = (res, s') + where + subs = Map.map (filter (not . isTargetScope)) s.ist_subscriptions + isTargetScope sub = sub.sub_scope == scope + (res, rsr) = Map.alterF (, Nothing) scope s.ist_resources + s' = s {ist_subscriptions = subs, ist_resources = rsr} destroyScope :: ScopeId -> JSM () -destroyScope s = do - mres <- state $ swap . destroyScopeFn s - forM_ mres \r -> forM_ r.rsr_linked destroyScope - forM_ mres \r -> sequence_ r.rsr_finalizers -{-# INLINE destroyScope #-} - -destroyScopeFn :: ScopeId -> InternalState -> (InternalState, Maybe Resources) -destroyScopeFn scope s = (s', resources) +destroyScope scope = do + mres <- state updateState + forM_ mres \res -> do + forM_ (res.rsr_linked) destroyScope + sequence_ (res.rsr_finalizers) + jsCmd $ FreeScope scope where - subs = Map.map (List.filter filterSub) s.ist_subscriptions - filterSub x = x.sub_scope /= scope - remove = Map.alterF (,Nothing) scope - unlink m = case resources of - Just r -> Map.adjust adj r.rsr_parent m - Nothing -> m - adj r = r {rsr_linked = List.filter (/=scope) r.rsr_linked} - (resources, rsr) = remove s.ist_resources - s' = s {ist_subscriptions = subs, ist_resources = unlink rsr} -{-# INLINE destroyScopeFn #-} + updateState :: InternalState -> (Maybe Resources, InternalState) + updateState s = (res, s') + where + subs = Map.map (filter (not . isTargetScope)) s.ist_subscriptions + isTargetScope sub = sub.sub_scope == scope + remove = Map.alterF (,Nothing) scope + unlink m = case res of + Just r -> Map.adjust adj r.rsr_parent m + Nothing -> m + adj r = r {rsr_linked = List.filter (/=scope) r.rsr_linked} + (res, rsr) = remove s.ist_resources + s' = s {ist_subscriptions = subs, ist_resources = unlink rsr} + +moveScope :: ScopeId -> ScopeId -> JSM () +moveScope src dest = do + modify updateState + jsCmd $ MoveScope src dest + where + updateState :: InternalState -> InternalState + updateState s + | Just srcRes <- Map.lookup src s.ist_resources = + s {ist_resources = Map.adjust (updateRes srcRes) dest s.ist_resources} + | otherwise = s + where + updateRes :: Resources -> Resources -> Resources + updateRes src' dest' = dest' { + rsr_linked = src'.rsr_linked <> dest'.rsr_linked, + rsr_finalizers = src'.rsr_finalizers <> dest'.rsr_finalizers + } installFinalizer :: JSM () -> JSM () -installFinalizer = reactive_ . installFinalizerFn +installFinalizer f = reactive_ $ installFinalizerFn f {-# INLINE installFinalizer #-} installFinalizerFn :: JSM () -> ScopeId -> InternalState -> InternalState diff --git a/Clickable/Types.hs b/Clickable/Types.hs index 0627490..4b868b5 100644 --- a/Clickable/Types.hs +++ b/Clickable/Types.hs @@ -127,10 +127,10 @@ data JSExp where Apply :: JSExp -> [JSExp] -> JSExp Call :: JSExp -> Text -> [JSExp] -> JSExp - AssignRef :: RefId -> JSExp -> JSExp - FreeRef :: RefId -> JSExp + AssignRef :: ScopeId -> RefId -> JSExp -> JSExp Ref :: RefId -> JSExp FreeScope :: ScopeId -> JSExp + MoveScope :: ScopeId -> ScopeId -> JSExp PeekStack :: Word8 -> JSExp PushStack :: JSExp -> JSExp @@ -141,9 +141,9 @@ data JSExp where ElementAttr :: JSExp -> Text -> Text -> JSExp ClassListAdd :: JSExp -> Text -> JSExp ClassListRemove :: JSExp -> Text -> JSExp - InsertBrackets :: JSExp - ClearBrackets :: JSExp -> JSExp - DetachBrackets :: JSExp -> JSExp + InsertPlaceholder :: JSExp + ClearPlaceholder :: JSExp -> JSExp + DetachPlaceholder :: JSExp -> JSExp CreateElement :: Text -> JSExp CreateElementNS :: Text -> Text -> JSExp @@ -175,9 +175,8 @@ newtype StartFlags = StartFlags {unStartFlags :: JSVal} newtype ScopeId = ScopeId {unScopeId :: Word32} deriving newtype (Binary, Eq, Ord, Show) -data RefId = RefId ScopeId Word32 - deriving stock (Eq, Show, Generic) - deriving anyclass (Binary) +newtype RefId = RefId {unRefId :: Word32} + deriving newtype (Binary, Eq, Ord, Show) newtype EventId = EventId {unEventId :: Word32} deriving newtype (Show, Ord, Eq, Binary) @@ -520,13 +519,15 @@ prompt (PromptTag t) (IO m) = IO (prompt# t m) control :: forall a b. PromptTag a -> ((IO b -> IO a) -> IO a) -> IO b control (PromptTag t) f = IO (control0# t g) where - g :: ((State# RealWorld -> (# State# RealWorld, b #)) - -> State# RealWorld -> (# State# RealWorld, a #)) - -> State# RealWorld -> (# State# RealWorld, a #) + g :: + ((State# RealWorld -> (# State# RealWorld, b #)) -> + State# RealWorld -> (# State# RealWorld, a #)) -> + State# RealWorld -> (# State# RealWorld, a #) g h = let IO m = f (k h) in m - k :: ((State# RealWorld -> (# State# RealWorld, b #)) - -> State# RealWorld -> (# State# RealWorld, a #)) - -> IO b -> IO a + k :: + ((State# RealWorld -> (# State# RealWorld, b #)) -> + State# RealWorld -> (# State# RealWorld, a #)) -> + IO b -> IO a k l (IO n) = IO (l n) data PromptTag a = PromptTag {unPromptTag :: PromptTag# a} diff --git a/Clickable/WebSocket.hs b/Clickable/WebSocket.hs index 0d607d3..c22f2e8 100644 --- a/Clickable/WebSocket.hs +++ b/Clickable/WebSocket.hs @@ -45,7 +45,7 @@ data ServerConfig = ServerConfig { } data ServerInstance = ServerInstance { - sri_dsc_websocket_state :: IORef (Map ConnectionId DevServerConn) + sri_websocket_state :: IORef (Map ConnectionId DevServerConn) } data TemplateConfig = TemplateConfig { @@ -72,9 +72,9 @@ newtype ConnectionId = ConnectionId {unConnectionId :: Int} newServer :: IO ServerInstance newServer = do - sri_dsc_websocket_state <- newIORef Map.empty + sri_websocket_state <- newIORef Map.empty pure ServerInstance { - sri_dsc_websocket_state + sri_websocket_state } waiApp :: ServerConfig -> ServerInstance -> Application @@ -108,7 +108,7 @@ websocketApp cfg self p = conn <- acceptRequest p newConn conn dropConn (conn::DevServerConn) = do - modifyIORef' self.sri_dsc_websocket_state $ Map.delete conn.dsc_connection_id + modifyIORef' self.sri_websocket_state $ Map.delete conn.dsc_connection_id cfg.cfg_connection_lost conn loop (conn::DevServerConn) = do raceResult <- race @@ -144,7 +144,7 @@ websocketApp cfg self p = (dsc_internal_env, _) <- newInternalEnv (100 * 1024) \(ptr, len) -> do bs <- unsafePackCStringLen (castPtr ptr, len) sendDataMessage dsc_websocket $ Network.WebSockets.Binary $ BSL.fromStrict bs - atomicModifyIORef' self.sri_dsc_websocket_state \m -> + atomicModifyIORef' self.sri_websocket_state \m -> let conn = DevServerConn { dsc_internal_env, dsc_websocket, @@ -201,4 +201,4 @@ defaultTemplate cfg = -- yarn run webpack --mode production && cat dist-newstyle/index.bundle.js | sed 's/\\/\\\\/g' | sed 's/"/\\"/g' jsrts :: Builder jsrts = - "(()=>{\"use strict\";var __webpack_modules__={151:(__unused_webpack_module,__webpack_exports__,__webpack_require__)=>{__webpack_require__.d(__webpack_exports__,{JC:()=>ClientMsgTag,iQ:()=>evalMem,ni:()=>encodeClientMessage});const VAL=0,NEXT=1;function Cons(e,t){return[e,t]}var ExprTag,ClientMsgTag;function evalMem(e){let t=null;for(;e.beginencodeValue(e,t)));if(t instanceof Uint8Array)return e.mem.setUint8(e.begin,ExprTag.U8Arr),e.mem.setBigUint64(e.begin+1,BigInt(t.byteLength),!1),new Uint8Array(e.mem.buffer).set(t,e.begin+9),void(e.begin+=9+t.byteLength);if(null==t)return e.mem.setUint8(e.begin,ExprTag.Null),void e.begin++;const n=Object.entries(t);e.mem.setUint8(e.begin,ExprTag.Obj),e.mem.setBigUint64(e.begin+1,BigInt(n.length),!1),e.begin+=9,n.forEach((([t,n])=>{encodeString(e,t),encodeValue(e,n)}))}function encodeString(e,t){const n=new Uint8Array(e.mem.buffer).subarray(e.begin+8),r=(new TextEncoder).encodeInto(t,n);e.mem.setBigUint64(e.begin,BigInt(r.written),!1),e.begin+=8+r.written}function encodeClientMessage(e,t){switch(t[0]){case ClientMsgTag.StartMsg:return e.mem.setUint8(e.begin,ClientMsgTag.StartMsg),e.begin++,void encodeValue(e,t[1]);case ClientMsgTag.EventMsg:return e.mem.setUint8(e.begin,ClientMsgTag.EventMsg),e.mem.setUint32(e.begin+1,t[1],!1),e.begin+=5,void encodeValue(e,t[2]);case ClientMsgTag.ResumeMsg:return e.mem.setUint8(e.begin,ClientMsgTag.ResumeMsg),e.mem.setUint32(e.begin+1,t[1],!1),e.begin+=5,void encodeValue(e,t[2])}}!function(e){e[e.Null=0]=\"Null\",e[e.Bool=1]=\"Bool\",e[e.I8=2]=\"I8\",e[e.I16=3]=\"I16\",e[e.I32=4]=\"I32\",e[e.I64=5]=\"I64\",e[e.U8=6]=\"U8\",e[e.U16=7]=\"U16\",e[e.U32=8]=\"U32\",e[e.U64=9]=\"U64\",e[e.F32=10]=\"F32\",e[e.F64=11]=\"F64\",e[e.Str=12]=\"Str\",e[e.Arr=13]=\"Arr\",e[e.Obj=14]=\"Obj\",e[e.U8Arr=15]=\"U8Arr\",e[e.Dot=16]=\"Dot\",e[e.SetProp=17]=\"SetProp\",e[e.Ix=18]=\"Ix\",e[e.Id=19]=\"Id\",e[e.Lam=20]=\"Lam\",e[e.Arg=21]=\"Arg\",e[e.Apply=22]=\"Apply\",e[e.Call=23]=\"Call\",e[e.AssignRef=24]=\"AssignRef\",e[e.FreeRef=25]=\"FreeRef\",e[e.Ref=26]=\"Ref\",e[e.FreeScope=27]=\"FreeScope\",e[e.PeekStack=28]=\"PeekStack\",e[e.PushStack=29]=\"PushStack\",e[e.PopStack=30]=\"PopStack\",e[e.PopIns=31]=\"PopIns\",e[e.ElementProp=32]=\"ElementProp\",e[e.ElementAttr=33]=\"ElementAttr\",e[e.ClassListAdd=34]=\"ClassListAdd\",e[e.ClassListRemove=35]=\"ClassListRemove\",e[e.InsertBrackets=36]=\"InsertBrackets\",e[e.ClearBrackets=37]=\"ClearBrackets\",e[e.DetachBrackets=38]=\"DetachBrackets\",e[e.CreateElement=39]=\"CreateElement\",e[e.CreateElementNS=40]=\"CreateElementNS\",e[e.CreateText=41]=\"CreateText\",e[e.UpdateText=42]=\"UpdateText\",e[e.Eval=43]=\"Eval\",e[e.TriggerEvent=44]=\"TriggerEvent\",e[e.Resume=45]=\"Resume\"}(ExprTag||(ExprTag={})),function(e){e[e.StartMsg=0]=\"StartMsg\",e[e.EventMsg=1]=\"EventMsg\",e[e.ResumeMsg=2]=\"ResumeMsg\"}(ClientMsgTag||(ClientMsgTag={}));const decoder=new TextDecoder(\"utf8\");function decodeString(e){const t=Number(e.mem.getBigUint64(e.begin,!1));e.begin+=8;const n=new Uint8Array(e.mem.buffer).subarray(e.begin,e.begin+t);return e.begin+=t,decoder.decode(n)}var utils;!function(e){function t(e,t){e instanceof Comment?e.parentElement.insertBefore(t,e):e.appendChild(t)}function n(e){return e instanceof Comment?e.parentElement:e}function r(e){return e instanceof Comment&&\"ContentBrackets {{\"==e.textContent}e.insert=t,e.prop=function(e,t,n){e instanceof Comment?e.parentElement[t]=n:e[t]=n},e.attr=function(e,t,r){n(e).setAttribute(t,r)},e.addEventListener=function(e,t,r){n(e).addEventListener(t,r)},e.removeEventListener=function(e,t,r){n(e).removeEventListener(t,r)},e.insertBrackets=function(e){const n=document.createComment(\"ContentBrackets {{\"),r=document.createComment(\"}}\");return t(e,n),t(e,r),r},e.clearBrackets=function(e,t){if(e instanceof Comment){let s=0;for(;e.previousSibling&&(0!=s||!r(e.previousSibling));)(n=e.previousSibling)instanceof Comment&&\"}}\"==n.textContent?s++:r(e.previousSibling)&&s--,e.previousSibling.parentNode.removeChild(e.previousSibling);t&&(e.previousSibling.parentNode.removeChild(e.previousSibling),e.parentNode.removeChild(e))}else e.innerHTML=\"\";var n},e.getBuilderElement=n}(utils||(utils={}))}},__webpack_module_cache__={};function __webpack_require__(e){var t=__webpack_module_cache__[e];if(void 0!==t)return t.exports;var n=__webpack_module_cache__[e]={exports:{}};return __webpack_modules__[e](n,n.exports,__webpack_require__),n.exports}__webpack_require__.d=(e,t)=>{for(var n in t)__webpack_require__.o(t,n)&&!__webpack_require__.o(e,n)&&Object.defineProperty(e,n,{enumerable:!0,get:t[n]})},__webpack_require__.g=function(){if(\"object\"==typeof globalThis)return globalThis;try{return this||new Function(\"return this\")()}catch(e){if(\"object\"==typeof window)return window}}(),__webpack_require__.o=(e,t)=>Object.prototype.hasOwnProperty.call(e,t);var __webpack_exports__={},proto=__webpack_require__(151);const outBuf=new ArrayBuffer(102400),mem=new DataView(outBuf);function runWebsocket(e,t=null,n){const r=new WebSocket(e),s={refs:(null==n?void 0:n.refs)||new Map,stack:(null==n?void 0:n.stack)||null,triggerEvent:function(e,t){const n={mem,begin:0,end:outBuf.byteLength};proto.ni(n,[proto.JC.EventMsg,e,t]),r.send(new Uint8Array(outBuf).subarray(0,n.begin))},resumeCont:function(e,t){const n={mem,begin:0,end:outBuf.byteLength};proto.ni(n,[proto.JC.ResumeMsg,e,t]),r.send(new Uint8Array(outBuf).subarray(0,n.begin))}};r.onopen=e=>{const n={mem,begin:0,end:outBuf.byteLength};proto.ni(n,[proto.JC.StartMsg,t]),r.send(new Uint8Array(outBuf).subarray(0,n.begin))},r.onmessage=e=>{convertBlobToUint8Array(e.data).then((e=>{proto.iQ({context:s,mem:new DataView(e),isMutableMem:!1,begin:0,end:e.byteLength})}))},r.onerror=e=>{console.error(\"WebSocket error:\",e)},r.onclose=t=>{console.log(\"WebSocket connection closed, reloading the tab…\"),function t(n){const r=new WebSocket(e),s=Math.min(5e3,2*n);r.onopen=e=>window.location.reload(),r.onclose=e=>{setTimeout((()=>t(s)),n)}}(100)}}function convertBlobToUint8Array(e){return new Promise(((t,n)=>{const r=new FileReader;r.onload=()=>{t(r.result)},r.onerror=e=>{n(e)},r.readAsArrayBuffer(e)}))}const FD_STDIN=0,FD_STDOUT=1,FD_STDERR=2,CLOCKID_REALTIME=0,CLOCKID_MONOTONIC=1,CLOCKID_PROCESS_CPUTIME_ID=2,CLOCKID_THREAD_CPUTIME_ID=3,ERRNO_SUCCESS=0,ERRNO_2BIG=1,ERRNO_ACCES=2,ERRNO_ADDRINUSE=3,ERRNO_ADDRNOTAVAIL=4,ERRNO_AFNOSUPPORT=5,ERRNO_AGAIN=6,ERRNO_ALREADY=7,ERRNO_BADF=8,ERRNO_BADMSG=9,ERRNO_BUSY=10,ERRNO_CANCELED=11,ERRNO_CHILD=12,ERRNO_CONNABORTED=13,ERRNO_CONNREFUSED=14,ERRNO_CONNRESET=15,ERRNO_DEADLK=16,ERRNO_DESTADDRREQ=17,ERRNO_DOM=18,ERRNO_DQUOT=19,ERRNO_EXIST=20,ERRNO_FAULT=21,ERRNO_FBIG=22,ERRNO_HOSTUNREACH=23,ERRNO_IDRM=24,ERRNO_ILSEQ=25,ERRNO_INPROGRESS=26,ERRNO_INTR=27,ERRNO_INVAL=28,ERRNO_IO=29,ERRNO_ISCONN=30,ERRNO_ISDIR=31,ERRNO_LOOP=32,ERRNO_MFILE=33,ERRNO_MLINK=34,ERRNO_MSGSIZE=35,ERRNO_MULTIHOP=36,ERRNO_NAMETOOLONG=37,ERRNO_NETDOWN=38,ERRNO_NETRESET=39,ERRNO_NETUNREACH=40,ERRNO_NFILE=41,ERRNO_NOBUFS=42,ERRNO_NODEV=43,ERRNO_NOENT=44,ERRNO_NOEXEC=45,ERRNO_NOLCK=46,ERRNO_NOLINK=47,ERRNO_NOMEM=48,ERRNO_NOMSG=49,ERRNO_NOPROTOOPT=50,ERRNO_NOSPC=51,ERRNO_NOSYS=52,ERRNO_NOTCONN=53,ERRNO_NOTDIR=54,ERRNO_NOTEMPTY=55,ERRNO_NOTRECOVERABLE=56,ERRNO_NOTSOCK=57,ERRNO_NOTSUP=58,ERRNO_NOTTY=59,ERRNO_NXIO=60,ERRNO_OVERFLOW=61,ERRNO_OWNERDEAD=62,ERRNO_PERM=63,ERRNO_PIPE=64,ERRNO_PROTO=65,ERRNO_PROTONOSUPPORT=66,ERRNO_PROTOTYPE=67,ERRNO_RANGE=68,ERRNO_ROFS=69,ERRNO_SPIPE=70,ERRNO_SRCH=71,ERRNO_STALE=72,ERRNO_TIMEDOUT=73,ERRNO_TXTBSY=74,ERRNO_XDEV=75,ERRNO_NOTCAPABLE=76,RIGHTS_FD_DATASYNC=null,RIGHTS_FD_READ=null,RIGHTS_FD_SEEK=null,RIGHTS_FD_FDSTAT_SET_FLAGS=null,RIGHTS_FD_SYNC=null,RIGHTS_FD_TELL=null,RIGHTS_FD_WRITE=64,RIGHTS_FD_ADVISE=null,RIGHTS_FD_ALLOCATE=null,RIGHTS_PATH_CREATE_DIRECTORY=null,RIGHTS_PATH_CREATE_FILE=null,RIGHTS_PATH_LINK_SOURCE=null,RIGHTS_PATH_LINK_TARGET=null,RIGHTS_PATH_OPEN=null,RIGHTS_FD_READDIR=null,RIGHTS_PATH_READLINK=null,RIGHTS_PATH_RENAME_SOURCE=null,RIGHTS_PATH_RENAME_TARGET=null,RIGHTS_PATH_FILESTAT_GET=null,RIGHTS_PATH_FILESTAT_SET_SIZE=null,RIGHTS_PATH_FILESTAT_SET_TIMES=null,RIGHTS_FD_FILESTAT_GET=null,RIGHTS_FD_FILESTAT_SET_SIZE=null,RIGHTS_FD_FILESTAT_SET_TIMES=null,RIGHTS_PATH_SYMLINK=null,RIGHTS_PATH_REMOVE_DIRECTORY=null,RIGHTS_PATH_UNLINK_FILE=null,RIGHTS_POLL_FD_READWRITE=null,RIGHTS_SOCK_SHUTDOWN=null;class Iovec{static read_bytes(e,t){const n=new Iovec;return n.buf=e.getUint32(t,!0),n.buf_len=e.getUint32(t+4,!0),n}static read_bytes_array(e,t,n){const r=[];for(let s=0;s{}}const debug=new Debug(!1);class WASIProcExit extends Error{constructor(e){super(\"exit with exit code \"+e),this.code=e}}let WASI=class{start(e){this.inst=e;try{return e.exports._start(),0}catch(e){if(e instanceof WASIProcExit)return e.code;throw e}}initialize(e){this.inst=e,e.exports._initialize&&e.exports._initialize()}constructor(e,t,n,r={}){this.args=[],this.env=[],this.fds=[],debug.enable(r.debug),this.args=e,this.env=t,this.fds=n;const s=this;this.wasiImport={args_sizes_get(e,t){const n=new DataView(s.inst.exports.memory.buffer);n.setUint32(e,s.args.length,!0);let r=0;for(const e of s.args)r+=e.length+1;return n.setUint32(t,r,!0),debug.log(n.getUint32(e,!0),n.getUint32(t,!0)),0},args_get(e,t){const n=new DataView(s.inst.exports.memory.buffer),r=new Uint8Array(s.inst.exports.memory.buffer),i=t;for(let i=0;inull!=s.fds[e]?ERRNO_SUCCESS:ERRNO_BADF,fd_allocate:(e,t,n)=>null!=s.fds[e]?s.fds[e].fd_allocate(t,n):ERRNO_BADF,fd_close(e){if(null!=s.fds[e]){const t=s.fds[e].fd_close();return s.fds[e]=void 0,t}return ERRNO_BADF},fd_datasync:e=>null!=s.fds[e]?s.fds[e].fd_sync():ERRNO_BADF,fd_fdstat_get(e,t){if(null!=s.fds[e]){const{ret:n,fdstat:r}=s.fds[e].fd_fdstat_get();return null!=r&&r.write_bytes(new DataView(s.inst.exports.memory.buffer),t),n}return ERRNO_BADF},fd_fdstat_set_flags:(e,t)=>null!=s.fds[e]?s.fds[e].fd_fdstat_set_flags(t):ERRNO_BADF,fd_fdstat_set_rights:(e,t,n)=>null!=s.fds[e]?s.fds[e].fd_fdstat_set_rights(t,n):ERRNO_BADF,fd_filestat_get(e,t){if(null!=s.fds[e]){const{ret:n,filestat:r}=s.fds[e].fd_filestat_get();return null!=r&&r.write_bytes(new DataView(s.inst.exports.memory.buffer),t),n}return ERRNO_BADF},fd_filestat_set_size:(e,t)=>null!=s.fds[e]?s.fds[e].fd_filestat_set_size(t):ERRNO_BADF,fd_filestat_set_times:(e,t,n,r)=>null!=s.fds[e]?s.fds[e].fd_filestat_set_times(t,n,r):ERRNO_BADF,fd_pread(e,t,n,r,i){const a=new DataView(s.inst.exports.memory.buffer),l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const o=Iovec.read_bytes_array(a,t,n);let _=0;for(const t of o){const{ret:n,data:o}=s.fds[e].fd_pread(t.buf_len,r);if(n!=ERRNO_SUCCESS)return a.setUint32(i,_,!0),n;if(l.set(o,t.buf),_+=o.length,r+=BigInt(o.length),o.length!=t.buf_len)break}return a.setUint32(i,_,!0),ERRNO_SUCCESS}return ERRNO_BADF},fd_prestat_get(e,t){const n=new DataView(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const{ret:r,prestat:i}=s.fds[e].fd_prestat_get();return null!=i&&i.write_bytes(n,t),r}return ERRNO_BADF},fd_prestat_dir_name(e,t,n){if(null!=s.fds[e]){const{ret:r,prestat:i}=s.fds[e].fd_prestat_get();if(null==i)return r;const a=i.inner.pr_name;return new Uint8Array(s.inst.exports.memory.buffer).set(a.slice(0,n),t),a.byteLength>n?ERRNO_NAMETOOLONG:ERRNO_SUCCESS}return ERRNO_BADF},fd_pwrite(e,t,n,r,i){const a=new DataView(s.inst.exports.memory.buffer),l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const o=Ciovec.read_bytes_array(a,t,n);let _=0;for(const t of o){const n=l.slice(t.buf,t.buf+t.buf_len),{ret:o,nwritten:f}=s.fds[e].fd_pwrite(n,r);if(o!=ERRNO_SUCCESS)return a.setUint32(i,_,!0),o;if(_+=f,r+=BigInt(f),f!=n.byteLength)break}return a.setUint32(i,_,!0),ERRNO_SUCCESS}return ERRNO_BADF},fd_read(e,t,n,r){const i=new DataView(s.inst.exports.memory.buffer),a=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const l=Iovec.read_bytes_array(i,t,n);let o=0;for(const t of l){const{ret:n,data:l}=s.fds[e].fd_read(t.buf_len);if(n!=ERRNO_SUCCESS)return i.setUint32(r,o,!0),n;if(a.set(l,t.buf),o+=l.length,l.length!=t.buf_len)break}return i.setUint32(r,o,!0),ERRNO_SUCCESS}return ERRNO_BADF},fd_readdir(e,t,n,r,i){const a=new DataView(s.inst.exports.memory.buffer),l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){let o=0;for(;;){const{ret:_,dirent:f}=s.fds[e].fd_readdir_single(r);if(0!=_)return a.setUint32(i,o,!0),_;if(null==f)break;if(n-onull!=s.fds[e]?s.fds[e].fd_sync():ERRNO_BADF,fd_tell(e,t){const n=new DataView(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const{ret:r,offset:i}=s.fds[e].fd_tell();return n.setBigUint64(t,i,!0),r}return ERRNO_BADF},fd_write(e,t,n,r){const i=new DataView(s.inst.exports.memory.buffer),a=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const l=Ciovec.read_bytes_array(i,t,n);let o=0;for(const t of l){const n=a.slice(t.buf,t.buf+t.buf_len),{ret:l,nwritten:_}=s.fds[e].fd_write(n);if(l!=ERRNO_SUCCESS)return i.setUint32(r,o,!0),l;if(o+=_,_!=n.byteLength)break}return i.setUint32(r,o,!0),ERRNO_SUCCESS}return ERRNO_BADF},path_create_directory(e,t,n){const r=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const i=new TextDecoder(\"utf-8\").decode(r.slice(t,t+n));return s.fds[e].path_create_directory(i)}return ERRNO_BADF},path_filestat_get(e,t,n,r,i){const a=new DataView(s.inst.exports.memory.buffer),l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const o=new TextDecoder(\"utf-8\").decode(l.slice(n,n+r)),{ret:_,filestat:f}=s.fds[e].path_filestat_get(t,o);return null!=f&&f.write_bytes(a,i),_}return ERRNO_BADF},path_filestat_set_times(e,t,n,r,i,a,l){const o=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const _=new TextDecoder(\"utf-8\").decode(o.slice(n,n+r));return s.fds[e].path_filestat_set_times(t,_,i,a,l)}return ERRNO_BADF},path_link(e,t,n,r,i,a,l){const o=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]&&null!=s.fds[i]){const _=new TextDecoder(\"utf-8\").decode(o.slice(n,n+r)),f=new TextDecoder(\"utf-8\").decode(o.slice(a,a+l)),{ret:u,inode_obj:c}=s.fds[e].path_lookup(_,t);return null==c?u:s.fds[i].path_link(f,c,!1)}return ERRNO_BADF},path_open(e,t,n,r,i,a,l,o,_){const f=new DataView(s.inst.exports.memory.buffer),u=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const c=new TextDecoder(\"utf-8\").decode(u.slice(n,n+r));debug.log(c);const{ret:E,fd_obj:d}=s.fds[e].path_open(t,c,i,a,l,o);if(0!=E)return E;s.fds.push(d);const R=s.fds.length-1;return f.setUint32(_,R,!0),0}return ERRNO_BADF},path_readlink(e,t,n,r,i,a){const l=new DataView(s.inst.exports.memory.buffer),o=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const _=new TextDecoder(\"utf-8\").decode(o.slice(t,t+n));debug.log(_);const{ret:f,data:u}=s.fds[e].path_readlink(_);if(null!=u){const e=(new TextEncoder).encode(u);if(e.length>i)return l.setUint32(a,0,!0),ERRNO_BADF;o.set(e,r),l.setUint32(a,e.length,!0)}return f}return ERRNO_BADF},path_remove_directory(e,t,n){const r=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const i=new TextDecoder(\"utf-8\").decode(r.slice(t,t+n));return s.fds[e].path_remove_directory(i)}return ERRNO_BADF},path_rename(e,t,n,r,i,a){const l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]&&null!=s.fds[r]){const o=new TextDecoder(\"utf-8\").decode(l.slice(t,t+n)),_=new TextDecoder(\"utf-8\").decode(l.slice(i,i+a));let{ret:f,inode_obj:u}=s.fds[e].path_unlink(o);if(null==u)return f;if(f=s.fds[r].path_link(_,u,!0),f!=ERRNO_SUCCESS&&s.fds[e].path_link(o,u,!0)!=ERRNO_SUCCESS)throw\"path_link should always return success when relinking an inode back to the original place\";return f}return ERRNO_BADF},path_symlink(e,t,n,r,i){const a=new Uint8Array(s.inst.exports.memory.buffer);return null!=s.fds[n]?(new TextDecoder(\"utf-8\").decode(a.slice(e,e+t)),new TextDecoder(\"utf-8\").decode(a.slice(r,r+i)),ERRNO_NOTSUP):ERRNO_BADF},path_unlink_file(e,t,n){const r=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const i=new TextDecoder(\"utf-8\").decode(r.slice(t,t+n));return s.fds[e].path_unlink_file(i)}return ERRNO_BADF},poll_oneoff(e,t,n){throw\"async io not supported\"},proc_exit(e){throw new WASIProcExit(e)},proc_raise(e){throw\"raised signal \"+e},sched_yield(){},random_get(e,t){const n=new Uint8Array(s.inst.exports.memory.buffer);for(let r=0;re+t);else{const n=new Uint8Array(Number(e+t));n.set(this.file.data,0),this.file.data=n}return ERRNO_SUCCESS}fd_fdstat_get(){return{ret:0,fdstat:new Fdstat(FILETYPE_REGULAR_FILE,0)}}fd_filestat_set_size(e){if(this.file.size>e)this.file.data=new Uint8Array(this.file.data.buffer.slice(0,Number(e)));else{const t=new Uint8Array(Number(e));t.set(this.file.data,0),this.file.data=t}return ERRNO_SUCCESS}fd_read(e){const t=this.file.data.slice(Number(this.file_pos),Number(this.file_pos+BigInt(e)));return this.file_pos+=BigInt(t.length),{ret:0,data:t}}fd_pread(e,t){return{ret:0,data:this.file.data.slice(Number(t),Number(t+BigInt(e)))}}fd_seek(e,t){let n;switch(t){case WHENCE_SET:n=e;break;case WHENCE_CUR:n=this.file_pos+e;break;case WHENCE_END:n=BigInt(this.file.data.byteLength)+e;break;default:return{ret:ERRNO_INVAL,offset:0n}}return n<0?{ret:ERRNO_INVAL,offset:0n}:(this.file_pos=n,{ret:0,offset:this.file_pos})}fd_tell(){return{ret:0,offset:this.file_pos}}fd_write(e){if(this.file.readonly)return{ret:ERRNO_BADF,nwritten:0};if(this.file_pos+BigInt(e.byteLength)>this.file.size){const t=this.file.data;this.file.data=new Uint8Array(Number(this.file_pos+BigInt(e.byteLength))),this.file.data.set(t)}return this.file.data.set(e,Number(this.file_pos)),this.file_pos+=BigInt(e.byteLength),{ret:0,nwritten:e.byteLength}}fd_pwrite(e,t){if(this.file.readonly)return{ret:ERRNO_BADF,nwritten:0};if(t+BigInt(e.byteLength)>this.file.size){const n=this.file.data;this.file.data=new Uint8Array(Number(t+BigInt(e.byteLength))),this.file.data.set(n)}return this.file.data.set(e,Number(t)),{ret:0,nwritten:e.byteLength}}fd_filestat_get(){return{ret:0,filestat:this.file.stat()}}constructor(e){super(),this.file_pos=0n,this.file=e}}class OpenDirectory extends Fd{fd_seek(e,t){return{ret:ERRNO_BADF,offset:0n}}fd_tell(){return{ret:ERRNO_BADF,offset:0n}}fd_allocate(e,t){return ERRNO_BADF}fd_fdstat_get(){return{ret:0,fdstat:new Fdstat(FILETYPE_DIRECTORY,0)}}fd_readdir_single(e){if(debug.enabled&&(debug.log(\"readdir_single\",e),debug.log(e,this.dir.contents.keys())),0n==e)return{ret:ERRNO_SUCCESS,dirent:new Dirent(1n,\".\",FILETYPE_DIRECTORY)};if(1n==e)return{ret:ERRNO_SUCCESS,dirent:new Dirent(2n,\"..\",FILETYPE_DIRECTORY)};if(e>=BigInt(this.dir.contents.size)+2n)return{ret:0,dirent:null};const[t,n]=Array.from(this.dir.contents.entries())[Number(e-2n)];return{ret:0,dirent:new Dirent(e+1n,t,n.stat().filetype)}}path_filestat_get(e,t){const{ret:n,path:r}=Path.from(t);if(null==r)return{ret:n,filestat:null};const{ret:s,entry:i}=this.dir.get_entry_for_path(r);return null==i?{ret:s,filestat:null}:{ret:0,filestat:i.stat()}}path_lookup(e,t){const{ret:n,path:r}=Path.from(e);if(null==r)return{ret:n,inode_obj:null};const{ret:s,entry:i}=this.dir.get_entry_for_path(r);return null==i?{ret:s,inode_obj:null}:{ret:ERRNO_SUCCESS,inode_obj:i}}path_open(e,t,n,r,s,i){const{ret:a,path:l}=Path.from(t);if(null==l)return{ret:a,fd_obj:null};let{ret:o,entry:_}=this.dir.get_entry_for_path(l);if(null==_){if(o!=ERRNO_NOENT)return{ret:o,fd_obj:null};if((n&OFLAGS_CREAT)!=OFLAGS_CREAT)return{ret:ERRNO_NOENT,fd_obj:null};{const{ret:e,entry:r}=this.dir.create_entry_for_path(t,(n&OFLAGS_DIRECTORY)==OFLAGS_DIRECTORY);if(null==r)return{ret:e,fd_obj:null};_=r}}else if((n&OFLAGS_EXCL)==OFLAGS_EXCL)return{ret:ERRNO_EXIST,fd_obj:null};return(n&OFLAGS_DIRECTORY)==OFLAGS_DIRECTORY&&_.stat().filetype!==FILETYPE_DIRECTORY?{ret:ERRNO_NOTDIR,fd_obj:null}:_.path_open(n,r,i)}path_create_directory(e){return this.path_open(0,e,OFLAGS_CREAT|OFLAGS_DIRECTORY,0n,0n,0).ret}path_link(e,t,n){const{ret:r,path:s}=Path.from(e);if(null==s)return r;if(s.is_dir)return ERRNO_NOENT;const{ret:i,parent_entry:a,filename:l,entry:o}=this.dir.get_parent_dir_and_entry_for_path(s,!0);if(null==a||null==l)return i;if(null!=o){const e=t.stat().filetype==FILETYPE_DIRECTORY,r=o.stat().filetype==FILETYPE_DIRECTORY;if(e&&r){if(!(n&&o instanceof Directory))return ERRNO_EXIST;if(0!=o.contents.size)return ERRNO_NOTEMPTY}else{if(e&&!r)return ERRNO_NOTDIR;if(!e&&r)return ERRNO_ISDIR;if(t.stat().filetype!=FILETYPE_REGULAR_FILE||o.stat().filetype!=FILETYPE_REGULAR_FILE)return ERRNO_EXIST}}return n||t.stat().filetype!=FILETYPE_DIRECTORY?(a.contents.set(l,t),ERRNO_SUCCESS):ERRNO_PERM}path_unlink(e){const{ret:t,path:n}=Path.from(e);if(null==n)return{ret:t,inode_obj:null};const{ret:r,parent_entry:s,filename:i,entry:a}=this.dir.get_parent_dir_and_entry_for_path(n,!0);return null==s||null==i?{ret:r,inode_obj:null}:null==a?{ret:ERRNO_NOENT,inode_obj:null}:(s.contents.delete(i),{ret:ERRNO_SUCCESS,inode_obj:a})}path_unlink_file(e){const{ret:t,path:n}=Path.from(e);if(null==n)return t;const{ret:r,parent_entry:s,filename:i,entry:a}=this.dir.get_parent_dir_and_entry_for_path(n,!1);return null==s||null==i||null==a?r:a.stat().filetype===FILETYPE_DIRECTORY?ERRNO_ISDIR:(s.contents.delete(i),ERRNO_SUCCESS)}path_remove_directory(e){const{ret:t,path:n}=Path.from(e);if(null==n)return t;const{ret:r,parent_entry:s,filename:i,entry:a}=this.dir.get_parent_dir_and_entry_for_path(n,!1);return null==s||null==i||null==a?r:a instanceof Directory&&a.stat().filetype===FILETYPE_DIRECTORY?0!==a.contents.size?ERRNO_NOTEMPTY:s.contents.delete(i)?ERRNO_SUCCESS:ERRNO_NOENT:ERRNO_NOTDIR}fd_filestat_get(){return{ret:0,filestat:this.dir.stat()}}fd_filestat_set_size(e){return ERRNO_BADF}fd_read(e){return{ret:ERRNO_BADF,data:new Uint8Array}}fd_pread(e,t){return{ret:ERRNO_BADF,data:new Uint8Array}}fd_write(e){return{ret:ERRNO_BADF,nwritten:0}}fd_pwrite(e,t){return{ret:ERRNO_BADF,nwritten:0}}constructor(e){super(),this.dir=e}}class PreopenDirectory extends OpenDirectory{fd_prestat_get(){return{ret:0,prestat:Prestat.dir(this.prestat_name)}}constructor(e,t){super(new Directory(t)),this.prestat_name=e}}class File extends Inode{path_open(e,t,n){if(this.readonly&&(t&BigInt(RIGHTS_FD_WRITE))==BigInt(RIGHTS_FD_WRITE))return{ret:ERRNO_PERM,fd_obj:null};if((e&OFLAGS_TRUNC)==OFLAGS_TRUNC){if(this.readonly)return{ret:ERRNO_PERM,fd_obj:null};this.data=new Uint8Array([])}const r=new OpenFile(this);return n&FDFLAGS_APPEND&&r.fd_seek(0n,WHENCE_END),{ret:ERRNO_SUCCESS,fd_obj:r}}get size(){return BigInt(this.data.byteLength)}stat(){return new Filestat(FILETYPE_REGULAR_FILE,this.size)}constructor(e,t){super(),this.data=new Uint8Array(e),this.readonly=!!t?.readonly}}let Path=class e{static from(t){const n=new e;if(n.is_dir=t.endsWith(\"/\"),t.startsWith(\"/\"))return{ret:ERRNO_NOTCAPABLE,path:null};if(t.includes(\"\\0\"))return{ret:ERRNO_INVAL,path:null};for(const e of t.split(\"/\"))if(\"\"!==e&&\".\"!==e)if(\"..\"!==e)n.parts.push(e);else if(null==n.parts.pop())return{ret:ERRNO_NOTCAPABLE,path:null};return{ret:ERRNO_SUCCESS,path:n}}to_path_string(){let e=this.parts.join(\"/\");return this.is_dir&&(e+=\"/\"),e}constructor(){this.parts=[],this.is_dir=!1}},inst;class Directory extends Inode{path_open(e,t,n){return{ret:ERRNO_SUCCESS,fd_obj:new OpenDirectory(this)}}stat(){return new Filestat(FILETYPE_DIRECTORY,0n)}get_entry_for_path(e){let t=this;for(const n of e.parts){if(!(t instanceof Directory))return{ret:ERRNO_NOTDIR,entry:null};const e=t.contents.get(n);if(void 0===e)return debug.log(n),{ret:ERRNO_NOENT,entry:null};t=e}return e.is_dir&&t.stat().filetype!=FILETYPE_DIRECTORY?{ret:ERRNO_NOTDIR,entry:null}:{ret:ERRNO_SUCCESS,entry:t}}get_parent_dir_and_entry_for_path(e,t){const n=e.parts.pop();if(void 0===n)return{ret:ERRNO_INVAL,parent_entry:null,filename:null,entry:null};const{ret:r,entry:s}=this.get_entry_for_path(e);if(null==s)return{ret:r,parent_entry:null,filename:null,entry:null};if(!(s instanceof Directory))return{ret:ERRNO_NOTDIR,parent_entry:null,filename:null,entry:null};const i=s.contents.get(n);return void 0===i?t?{ret:ERRNO_SUCCESS,parent_entry:s,filename:n,entry:null}:{ret:ERRNO_NOENT,parent_entry:null,filename:null,entry:null}:e.is_dir&&i.stat().filetype!=FILETYPE_DIRECTORY?{ret:ERRNO_NOTDIR,parent_entry:null,filename:null,entry:null}:{ret:ERRNO_SUCCESS,parent_entry:s,filename:n,entry:i}}create_entry_for_path(e,t){const{ret:n,path:r}=Path.from(e);if(null==r)return{ret:n,entry:null};let s,{ret:i,parent_entry:a,filename:l,entry:o}=this.get_parent_dir_and_entry_for_path(r,!0);return null==a||null==l?{ret:i,entry:null}:null!=o?{ret:ERRNO_EXIST,entry:null}:(debug.log(\"create\",r),s=t?new Directory(new Map):new File(new ArrayBuffer(0)),a.contents.set(l,s),o=s,{ret:ERRNO_SUCCESS,entry:o})}constructor(e){super(),this.contents=e instanceof Array?new Map(e):e}}class ConsoleStdout extends Fd{fd_filestat_get(){return{ret:0,filestat:new Filestat(FILETYPE_CHARACTER_DEVICE,BigInt(0))}}fd_fdstat_get(){const e=new Fdstat(FILETYPE_CHARACTER_DEVICE,0);return e.fs_rights_base=BigInt(RIGHTS_FD_WRITE),{ret:0,fdstat:e}}fd_write(e){return this.write(e),{ret:0,nwritten:e.byteLength}}static lineBuffered(e){const t=new TextDecoder(\"utf-8\",{fatal:!1});let n=\"\";return new ConsoleStdout((r=>{n+=t.decode(r,{stream:!0});const s=n.split(\"\\n\");for(const[t,r]of s.entries())te+t||this.file.handle.truncate(Number(e+t)),ERRNO_SUCCESS}fd_fdstat_get(){return{ret:0,fdstat:new Fdstat(FILETYPE_REGULAR_FILE,0)}}fd_filestat_get(){return{ret:0,filestat:new Filestat(FILETYPE_REGULAR_FILE,BigInt(this.file.handle.getSize()))}}fd_filestat_set_size(e){return this.file.handle.truncate(Number(e)),ERRNO_SUCCESS}fd_read(e){const t=new Uint8Array(e),n=this.file.handle.read(t,{at:Number(this.position)});return this.position+=BigInt(n),{ret:0,data:t.slice(0,n)}}fd_seek(e,t){let n;switch(t){case WHENCE_SET:n=BigInt(e);break;case WHENCE_CUR:n=this.position+BigInt(e);break;case WHENCE_END:n=BigInt(this.file.handle.getSize())+BigInt(e);break;default:return{ret:ERRNO_INVAL,offset:0n}}return n<0?{ret:ERRNO_INVAL,offset:0n}:(this.position=n,{ret:ERRNO_SUCCESS,offset:this.position})}fd_write(e){if(this.file.readonly)return{ret:ERRNO_BADF,nwritten:0};const t=this.file.handle.write(e,{at:Number(this.position)});return this.position+=BigInt(t),{ret:ERRNO_SUCCESS,nwritten:t}}fd_sync(){return this.file.handle.flush(),ERRNO_SUCCESS}constructor(e){super(),this.position=0n,this.file=e}}function runWasm(e,t=null,n){const r={refs:(null==n?void 0:n.refs)||new Map,stack:(null==n?void 0:n.stack)||null,triggerEvent:function(){},resumeCont:function(){}},s=new WASI([],[],[new OpenFile(new File([])),new OpenFile(new File([])),new OpenFile(new File([]))]);function i(e,t){const n=new DataView(inst.exports.memory.buffer),s={context:Object.assign(Object.assign({},r),{resumeCont:function(r,s){const i={mem:n,begin:e,end:e+t};proto.ni(i,[proto.JC.ResumeMsg,r,s]),inst.exports.wasm_app(e)},triggerEvent:function(r,s){const i={mem:n,begin:e,end:e+t};proto.ni(i,[proto.JC.EventMsg,r,s]),inst.exports.wasm_app(e)}}),mem:n,isMutableMem:!0,begin:e,end:e+t};proto.iQ(s)}WebAssembly.compileStreaming(fetch(e)).then((e=>WebAssembly.instantiate(e,{wasi_snapshot_preview1:s.wasiImport,env:{clickable_eval_buffer:i}}))).then((e=>{inst=e,s.initialize(e),e.exports.hs_init(),e.exports.wasm_app(0)}))}function evalUint8Array(e,t){const n={context:{refs:(null==t?void 0:t.refs)||new Map,stack:(null==t?void 0:t.stack)||null,triggerEvent:(null==t?void 0:t.triggerEvent)||function(){},resumeCont:(null==t?void 0:t.resumeCont)||function(){}},mem:new DataView(e.buffer),isMutableMem:!1,begin:0,end:e.byteLength};return proto.iQ(n)}function evalBase64(e,t){return evalUint8Array(Uint8Array.from(atob(e),(function(e){return e.charCodeAt(0)})),t)}window.clickable={runWebsocket,runWasm,evalUint8Array,evalBase64}})();" + "(()=>{\"use strict\";var __webpack_modules__={151:(__unused_webpack_module,__webpack_exports__,__webpack_require__)=>{__webpack_require__.d(__webpack_exports__,{JC:()=>ClientMsgTag,PG:()=>RefStore,iQ:()=>evalMem,ni:()=>encodeClientMessage});const VAL=0,NEXT=1;function Cons(e,t){return[e,t]}var ExprTag,ClientMsgTag;function evalMem(e){let t=null;for(;e.beginencodeValue(e,t)));if(t instanceof Uint8Array)return e.mem.setUint8(e.begin,ExprTag.U8Arr),e.mem.setBigUint64(e.begin+1,BigInt(t.byteLength),!1),new Uint8Array(e.mem.buffer).set(t,e.begin+9),void(e.begin+=9+t.byteLength);if(null==t)return e.mem.setUint8(e.begin,ExprTag.Null),void e.begin++;const n=Object.entries(t);e.mem.setUint8(e.begin,ExprTag.Obj),e.mem.setBigUint64(e.begin+1,BigInt(n.length),!1),e.begin+=9,n.forEach((([t,n])=>{encodeString(e,t),encodeValue(e,n)}))}function encodeString(e,t){const n=new Uint8Array(e.mem.buffer).subarray(e.begin+8),r=(new TextEncoder).encodeInto(t,n);e.mem.setBigUint64(e.begin,BigInt(r.written),!1),e.begin+=8+r.written}function encodeClientMessage(e,t){switch(t[0]){case ClientMsgTag.StartMsg:return e.mem.setUint8(e.begin,ClientMsgTag.StartMsg),e.begin++,void encodeValue(e,t[1]);case ClientMsgTag.EventMsg:return e.mem.setUint8(e.begin,ClientMsgTag.EventMsg),e.mem.setUint32(e.begin+1,t[1],!1),e.begin+=5,void encodeValue(e,t[2]);case ClientMsgTag.ResumeMsg:return e.mem.setUint8(e.begin,ClientMsgTag.ResumeMsg),e.mem.setUint32(e.begin+1,t[1],!1),e.begin+=5,void encodeValue(e,t[2])}}!function(e){e[e.Null=0]=\"Null\",e[e.Bool=1]=\"Bool\",e[e.I8=2]=\"I8\",e[e.I16=3]=\"I16\",e[e.I32=4]=\"I32\",e[e.I64=5]=\"I64\",e[e.U8=6]=\"U8\",e[e.U16=7]=\"U16\",e[e.U32=8]=\"U32\",e[e.U64=9]=\"U64\",e[e.F32=10]=\"F32\",e[e.F64=11]=\"F64\",e[e.Str=12]=\"Str\",e[e.Arr=13]=\"Arr\",e[e.Obj=14]=\"Obj\",e[e.U8Arr=15]=\"U8Arr\",e[e.Dot=16]=\"Dot\",e[e.SetProp=17]=\"SetProp\",e[e.Ix=18]=\"Ix\",e[e.Id=19]=\"Id\",e[e.Lam=20]=\"Lam\",e[e.Arg=21]=\"Arg\",e[e.Apply=22]=\"Apply\",e[e.Call=23]=\"Call\",e[e.AssignRef=24]=\"AssignRef\",e[e.Ref=25]=\"Ref\",e[e.FreeScope=26]=\"FreeScope\",e[e.MoveScope=27]=\"MoveScope\",e[e.PeekStack=28]=\"PeekStack\",e[e.PushStack=29]=\"PushStack\",e[e.PopStack=30]=\"PopStack\",e[e.PopIns=31]=\"PopIns\",e[e.ElementProp=32]=\"ElementProp\",e[e.ElementAttr=33]=\"ElementAttr\",e[e.ClassListAdd=34]=\"ClassListAdd\",e[e.ClassListRemove=35]=\"ClassListRemove\",e[e.InsertPlaceholder=36]=\"InsertPlaceholder\",e[e.ClearPlaceholder=37]=\"ClearPlaceholder\",e[e.DetachPlaceholder=38]=\"DetachPlaceholder\",e[e.CreateElement=39]=\"CreateElement\",e[e.CreateElementNS=40]=\"CreateElementNS\",e[e.CreateText=41]=\"CreateText\",e[e.UpdateText=42]=\"UpdateText\",e[e.Eval=43]=\"Eval\",e[e.TriggerEvent=44]=\"TriggerEvent\",e[e.Resume=45]=\"Resume\"}(ExprTag||(ExprTag={})),function(e){e[e.StartMsg=0]=\"StartMsg\",e[e.EventMsg=1]=\"EventMsg\",e[e.ResumeMsg=2]=\"ResumeMsg\"}(ClientMsgTag||(ClientMsgTag={}));const decoder=new TextDecoder(\"utf8\");function decodeString(e){const t=Number(e.mem.getBigUint64(e.begin,!1));e.begin+=8;const n=new Uint8Array(e.mem.buffer).subarray(e.begin,e.begin+t);return e.begin+=t,decoder.decode(n)}var utils;!function(e){function t(e,t){e instanceof Comment?e.parentElement.insertBefore(t,e):e.appendChild(t)}function n(e){return e instanceof Comment?e.parentElement:e}function r(e){return e instanceof Comment&&\"Placeholder {{{\"==e.textContent}e.insert=t,e.prop=function(e,t,n){e instanceof Comment?e.parentElement[t]=n:e[t]=n},e.attr=function(e,t,r){n(e).setAttribute(t,r)},e.addEventListener=function(e,t,r){n(e).addEventListener(t,r)},e.removeEventListener=function(e,t,r){n(e).removeEventListener(t,r)},e.insertPlaceholder=function(e){const n=document.createComment(\"Placeholder {{{\"),r=document.createComment(\"}}}\");return t(e,n),t(e,r),r},e.clearPlaceholder=function(e,t){if(e instanceof Comment){let s=0;for(;e.previousSibling&&(0!=s||!r(e.previousSibling));)(n=e.previousSibling)instanceof Comment&&\"}}}\"==n.textContent?s++:r(e.previousSibling)&&s--,e.previousSibling.parentNode.removeChild(e.previousSibling);t&&(e.previousSibling.parentNode.removeChild(e.previousSibling),e.parentNode.removeChild(e))}else e.innerHTML=\"\";var n},e.getBuilderElement=n}(utils||(utils={}));class RefStore{constructor(e=new Map,t=new Map){this.scopes=e,this.refs=t}assignRef(e,t,n){const r=this.scopes.get(e),s=r||new Set;r||this.scopes.set(e,s),s.add(t),this.refs.set(t,n)}moveScope(e,t){const n=this.scopes.get(e),r=this.scopes.get(t);n&&r&&(n.forEach((e=>r.add(e))),this.scopes.delete(e))}freeScope(e){const t=this.scopes.get(e);t&&(t.forEach((e=>this.refs.delete(e))),this.scopes.delete(e))}}}},__webpack_module_cache__={};function __webpack_require__(e){var t=__webpack_module_cache__[e];if(void 0!==t)return t.exports;var n=__webpack_module_cache__[e]={exports:{}};return __webpack_modules__[e](n,n.exports,__webpack_require__),n.exports}__webpack_require__.d=(e,t)=>{for(var n in t)__webpack_require__.o(t,n)&&!__webpack_require__.o(e,n)&&Object.defineProperty(e,n,{enumerable:!0,get:t[n]})},__webpack_require__.g=function(){if(\"object\"==typeof globalThis)return globalThis;try{return this||new Function(\"return this\")()}catch(e){if(\"object\"==typeof window)return window}}(),__webpack_require__.o=(e,t)=>Object.prototype.hasOwnProperty.call(e,t);var __webpack_exports__={},proto=__webpack_require__(151);const outBuf=new ArrayBuffer(102400),mem=new DataView(outBuf);function runWebsocket(e,t=null,n){const r=new WebSocket(e),s={refs:(null==n?void 0:n.refs)||new proto.PG,stack:(null==n?void 0:n.stack)||null,triggerEvent:function(e,t){const n={mem,begin:0,end:outBuf.byteLength};proto.ni(n,[proto.JC.EventMsg,e,t]),r.send(new Uint8Array(outBuf).subarray(0,n.begin))},resumeCont:function(e,t){const n={mem,begin:0,end:outBuf.byteLength};proto.ni(n,[proto.JC.ResumeMsg,e,t]),r.send(new Uint8Array(outBuf).subarray(0,n.begin))}};r.onopen=e=>{const n={mem,begin:0,end:outBuf.byteLength};proto.ni(n,[proto.JC.StartMsg,t]),r.send(new Uint8Array(outBuf).subarray(0,n.begin))},r.onmessage=e=>{convertBlobToUint8Array(e.data).then((e=>{proto.iQ({context:s,mem:new DataView(e),isMutableMem:!1,begin:0,end:e.byteLength})}))},r.onerror=e=>{console.error(\"WebSocket error:\",e)},r.onclose=t=>{console.log(\"WebSocket connection closed, reloading the tab…\"),function t(n){const r=new WebSocket(e),s=Math.min(5e3,2*n);r.onopen=e=>window.location.reload(),r.onclose=e=>{setTimeout((()=>t(s)),n)}}(100)}}function convertBlobToUint8Array(e){return new Promise(((t,n)=>{const r=new FileReader;r.onload=()=>{t(r.result)},r.onerror=e=>{n(e)},r.readAsArrayBuffer(e)}))}const FD_STDIN=0,FD_STDOUT=1,FD_STDERR=2,CLOCKID_REALTIME=0,CLOCKID_MONOTONIC=1,CLOCKID_PROCESS_CPUTIME_ID=2,CLOCKID_THREAD_CPUTIME_ID=3,ERRNO_SUCCESS=0,ERRNO_2BIG=1,ERRNO_ACCES=2,ERRNO_ADDRINUSE=3,ERRNO_ADDRNOTAVAIL=4,ERRNO_AFNOSUPPORT=5,ERRNO_AGAIN=6,ERRNO_ALREADY=7,ERRNO_BADF=8,ERRNO_BADMSG=9,ERRNO_BUSY=10,ERRNO_CANCELED=11,ERRNO_CHILD=12,ERRNO_CONNABORTED=13,ERRNO_CONNREFUSED=14,ERRNO_CONNRESET=15,ERRNO_DEADLK=16,ERRNO_DESTADDRREQ=17,ERRNO_DOM=18,ERRNO_DQUOT=19,ERRNO_EXIST=20,ERRNO_FAULT=21,ERRNO_FBIG=22,ERRNO_HOSTUNREACH=23,ERRNO_IDRM=24,ERRNO_ILSEQ=25,ERRNO_INPROGRESS=26,ERRNO_INTR=27,ERRNO_INVAL=28,ERRNO_IO=29,ERRNO_ISCONN=30,ERRNO_ISDIR=31,ERRNO_LOOP=32,ERRNO_MFILE=33,ERRNO_MLINK=34,ERRNO_MSGSIZE=35,ERRNO_MULTIHOP=36,ERRNO_NAMETOOLONG=37,ERRNO_NETDOWN=38,ERRNO_NETRESET=39,ERRNO_NETUNREACH=40,ERRNO_NFILE=41,ERRNO_NOBUFS=42,ERRNO_NODEV=43,ERRNO_NOENT=44,ERRNO_NOEXEC=45,ERRNO_NOLCK=46,ERRNO_NOLINK=47,ERRNO_NOMEM=48,ERRNO_NOMSG=49,ERRNO_NOPROTOOPT=50,ERRNO_NOSPC=51,ERRNO_NOSYS=52,ERRNO_NOTCONN=53,ERRNO_NOTDIR=54,ERRNO_NOTEMPTY=55,ERRNO_NOTRECOVERABLE=56,ERRNO_NOTSOCK=57,ERRNO_NOTSUP=58,ERRNO_NOTTY=59,ERRNO_NXIO=60,ERRNO_OVERFLOW=61,ERRNO_OWNERDEAD=62,ERRNO_PERM=63,ERRNO_PIPE=64,ERRNO_PROTO=65,ERRNO_PROTONOSUPPORT=66,ERRNO_PROTOTYPE=67,ERRNO_RANGE=68,ERRNO_ROFS=69,ERRNO_SPIPE=70,ERRNO_SRCH=71,ERRNO_STALE=72,ERRNO_TIMEDOUT=73,ERRNO_TXTBSY=74,ERRNO_XDEV=75,ERRNO_NOTCAPABLE=76,RIGHTS_FD_DATASYNC=null,RIGHTS_FD_READ=null,RIGHTS_FD_SEEK=null,RIGHTS_FD_FDSTAT_SET_FLAGS=null,RIGHTS_FD_SYNC=null,RIGHTS_FD_TELL=null,RIGHTS_FD_WRITE=64,RIGHTS_FD_ADVISE=null,RIGHTS_FD_ALLOCATE=null,RIGHTS_PATH_CREATE_DIRECTORY=null,RIGHTS_PATH_CREATE_FILE=null,RIGHTS_PATH_LINK_SOURCE=null,RIGHTS_PATH_LINK_TARGET=null,RIGHTS_PATH_OPEN=null,RIGHTS_FD_READDIR=null,RIGHTS_PATH_READLINK=null,RIGHTS_PATH_RENAME_SOURCE=null,RIGHTS_PATH_RENAME_TARGET=null,RIGHTS_PATH_FILESTAT_GET=null,RIGHTS_PATH_FILESTAT_SET_SIZE=null,RIGHTS_PATH_FILESTAT_SET_TIMES=null,RIGHTS_FD_FILESTAT_GET=null,RIGHTS_FD_FILESTAT_SET_SIZE=null,RIGHTS_FD_FILESTAT_SET_TIMES=null,RIGHTS_PATH_SYMLINK=null,RIGHTS_PATH_REMOVE_DIRECTORY=null,RIGHTS_PATH_UNLINK_FILE=null,RIGHTS_POLL_FD_READWRITE=null,RIGHTS_SOCK_SHUTDOWN=null;class Iovec{static read_bytes(e,t){const n=new Iovec;return n.buf=e.getUint32(t,!0),n.buf_len=e.getUint32(t+4,!0),n}static read_bytes_array(e,t,n){const r=[];for(let s=0;s{}}const debug=new Debug(!1);class WASIProcExit extends Error{constructor(e){super(\"exit with exit code \"+e),this.code=e}}let WASI=class{start(e){this.inst=e;try{return e.exports._start(),0}catch(e){if(e instanceof WASIProcExit)return e.code;throw e}}initialize(e){this.inst=e,e.exports._initialize&&e.exports._initialize()}constructor(e,t,n,r={}){this.args=[],this.env=[],this.fds=[],debug.enable(r.debug),this.args=e,this.env=t,this.fds=n;const s=this;this.wasiImport={args_sizes_get(e,t){const n=new DataView(s.inst.exports.memory.buffer);n.setUint32(e,s.args.length,!0);let r=0;for(const e of s.args)r+=e.length+1;return n.setUint32(t,r,!0),debug.log(n.getUint32(e,!0),n.getUint32(t,!0)),0},args_get(e,t){const n=new DataView(s.inst.exports.memory.buffer),r=new Uint8Array(s.inst.exports.memory.buffer),i=t;for(let i=0;inull!=s.fds[e]?ERRNO_SUCCESS:ERRNO_BADF,fd_allocate:(e,t,n)=>null!=s.fds[e]?s.fds[e].fd_allocate(t,n):ERRNO_BADF,fd_close(e){if(null!=s.fds[e]){const t=s.fds[e].fd_close();return s.fds[e]=void 0,t}return ERRNO_BADF},fd_datasync:e=>null!=s.fds[e]?s.fds[e].fd_sync():ERRNO_BADF,fd_fdstat_get(e,t){if(null!=s.fds[e]){const{ret:n,fdstat:r}=s.fds[e].fd_fdstat_get();return null!=r&&r.write_bytes(new DataView(s.inst.exports.memory.buffer),t),n}return ERRNO_BADF},fd_fdstat_set_flags:(e,t)=>null!=s.fds[e]?s.fds[e].fd_fdstat_set_flags(t):ERRNO_BADF,fd_fdstat_set_rights:(e,t,n)=>null!=s.fds[e]?s.fds[e].fd_fdstat_set_rights(t,n):ERRNO_BADF,fd_filestat_get(e,t){if(null!=s.fds[e]){const{ret:n,filestat:r}=s.fds[e].fd_filestat_get();return null!=r&&r.write_bytes(new DataView(s.inst.exports.memory.buffer),t),n}return ERRNO_BADF},fd_filestat_set_size:(e,t)=>null!=s.fds[e]?s.fds[e].fd_filestat_set_size(t):ERRNO_BADF,fd_filestat_set_times:(e,t,n,r)=>null!=s.fds[e]?s.fds[e].fd_filestat_set_times(t,n,r):ERRNO_BADF,fd_pread(e,t,n,r,i){const a=new DataView(s.inst.exports.memory.buffer),l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const o=Iovec.read_bytes_array(a,t,n);let _=0;for(const t of o){const{ret:n,data:o}=s.fds[e].fd_pread(t.buf_len,r);if(n!=ERRNO_SUCCESS)return a.setUint32(i,_,!0),n;if(l.set(o,t.buf),_+=o.length,r+=BigInt(o.length),o.length!=t.buf_len)break}return a.setUint32(i,_,!0),ERRNO_SUCCESS}return ERRNO_BADF},fd_prestat_get(e,t){const n=new DataView(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const{ret:r,prestat:i}=s.fds[e].fd_prestat_get();return null!=i&&i.write_bytes(n,t),r}return ERRNO_BADF},fd_prestat_dir_name(e,t,n){if(null!=s.fds[e]){const{ret:r,prestat:i}=s.fds[e].fd_prestat_get();if(null==i)return r;const a=i.inner.pr_name;return new Uint8Array(s.inst.exports.memory.buffer).set(a.slice(0,n),t),a.byteLength>n?ERRNO_NAMETOOLONG:ERRNO_SUCCESS}return ERRNO_BADF},fd_pwrite(e,t,n,r,i){const a=new DataView(s.inst.exports.memory.buffer),l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const o=Ciovec.read_bytes_array(a,t,n);let _=0;for(const t of o){const n=l.slice(t.buf,t.buf+t.buf_len),{ret:o,nwritten:f}=s.fds[e].fd_pwrite(n,r);if(o!=ERRNO_SUCCESS)return a.setUint32(i,_,!0),o;if(_+=f,r+=BigInt(f),f!=n.byteLength)break}return a.setUint32(i,_,!0),ERRNO_SUCCESS}return ERRNO_BADF},fd_read(e,t,n,r){const i=new DataView(s.inst.exports.memory.buffer),a=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const l=Iovec.read_bytes_array(i,t,n);let o=0;for(const t of l){const{ret:n,data:l}=s.fds[e].fd_read(t.buf_len);if(n!=ERRNO_SUCCESS)return i.setUint32(r,o,!0),n;if(a.set(l,t.buf),o+=l.length,l.length!=t.buf_len)break}return i.setUint32(r,o,!0),ERRNO_SUCCESS}return ERRNO_BADF},fd_readdir(e,t,n,r,i){const a=new DataView(s.inst.exports.memory.buffer),l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){let o=0;for(;;){const{ret:_,dirent:f}=s.fds[e].fd_readdir_single(r);if(0!=_)return a.setUint32(i,o,!0),_;if(null==f)break;if(n-onull!=s.fds[e]?s.fds[e].fd_sync():ERRNO_BADF,fd_tell(e,t){const n=new DataView(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const{ret:r,offset:i}=s.fds[e].fd_tell();return n.setBigUint64(t,i,!0),r}return ERRNO_BADF},fd_write(e,t,n,r){const i=new DataView(s.inst.exports.memory.buffer),a=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const l=Ciovec.read_bytes_array(i,t,n);let o=0;for(const t of l){const n=a.slice(t.buf,t.buf+t.buf_len),{ret:l,nwritten:_}=s.fds[e].fd_write(n);if(l!=ERRNO_SUCCESS)return i.setUint32(r,o,!0),l;if(o+=_,_!=n.byteLength)break}return i.setUint32(r,o,!0),ERRNO_SUCCESS}return ERRNO_BADF},path_create_directory(e,t,n){const r=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const i=new TextDecoder(\"utf-8\").decode(r.slice(t,t+n));return s.fds[e].path_create_directory(i)}return ERRNO_BADF},path_filestat_get(e,t,n,r,i){const a=new DataView(s.inst.exports.memory.buffer),l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const o=new TextDecoder(\"utf-8\").decode(l.slice(n,n+r)),{ret:_,filestat:f}=s.fds[e].path_filestat_get(t,o);return null!=f&&f.write_bytes(a,i),_}return ERRNO_BADF},path_filestat_set_times(e,t,n,r,i,a,l){const o=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const _=new TextDecoder(\"utf-8\").decode(o.slice(n,n+r));return s.fds[e].path_filestat_set_times(t,_,i,a,l)}return ERRNO_BADF},path_link(e,t,n,r,i,a,l){const o=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]&&null!=s.fds[i]){const _=new TextDecoder(\"utf-8\").decode(o.slice(n,n+r)),f=new TextDecoder(\"utf-8\").decode(o.slice(a,a+l)),{ret:u,inode_obj:c}=s.fds[e].path_lookup(_,t);return null==c?u:s.fds[i].path_link(f,c,!1)}return ERRNO_BADF},path_open(e,t,n,r,i,a,l,o,_){const f=new DataView(s.inst.exports.memory.buffer),u=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const c=new TextDecoder(\"utf-8\").decode(u.slice(n,n+r));debug.log(c);const{ret:E,fd_obj:d}=s.fds[e].path_open(t,c,i,a,l,o);if(0!=E)return E;s.fds.push(d);const R=s.fds.length-1;return f.setUint32(_,R,!0),0}return ERRNO_BADF},path_readlink(e,t,n,r,i,a){const l=new DataView(s.inst.exports.memory.buffer),o=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const _=new TextDecoder(\"utf-8\").decode(o.slice(t,t+n));debug.log(_);const{ret:f,data:u}=s.fds[e].path_readlink(_);if(null!=u){const e=(new TextEncoder).encode(u);if(e.length>i)return l.setUint32(a,0,!0),ERRNO_BADF;o.set(e,r),l.setUint32(a,e.length,!0)}return f}return ERRNO_BADF},path_remove_directory(e,t,n){const r=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const i=new TextDecoder(\"utf-8\").decode(r.slice(t,t+n));return s.fds[e].path_remove_directory(i)}return ERRNO_BADF},path_rename(e,t,n,r,i,a){const l=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]&&null!=s.fds[r]){const o=new TextDecoder(\"utf-8\").decode(l.slice(t,t+n)),_=new TextDecoder(\"utf-8\").decode(l.slice(i,i+a));let{ret:f,inode_obj:u}=s.fds[e].path_unlink(o);if(null==u)return f;if(f=s.fds[r].path_link(_,u,!0),f!=ERRNO_SUCCESS&&s.fds[e].path_link(o,u,!0)!=ERRNO_SUCCESS)throw\"path_link should always return success when relinking an inode back to the original place\";return f}return ERRNO_BADF},path_symlink(e,t,n,r,i){const a=new Uint8Array(s.inst.exports.memory.buffer);return null!=s.fds[n]?(new TextDecoder(\"utf-8\").decode(a.slice(e,e+t)),new TextDecoder(\"utf-8\").decode(a.slice(r,r+i)),ERRNO_NOTSUP):ERRNO_BADF},path_unlink_file(e,t,n){const r=new Uint8Array(s.inst.exports.memory.buffer);if(null!=s.fds[e]){const i=new TextDecoder(\"utf-8\").decode(r.slice(t,t+n));return s.fds[e].path_unlink_file(i)}return ERRNO_BADF},poll_oneoff(e,t,n){throw\"async io not supported\"},proc_exit(e){throw new WASIProcExit(e)},proc_raise(e){throw\"raised signal \"+e},sched_yield(){},random_get(e,t){const n=new Uint8Array(s.inst.exports.memory.buffer);for(let r=0;re+t);else{const n=new Uint8Array(Number(e+t));n.set(this.file.data,0),this.file.data=n}return ERRNO_SUCCESS}fd_fdstat_get(){return{ret:0,fdstat:new Fdstat(FILETYPE_REGULAR_FILE,0)}}fd_filestat_set_size(e){if(this.file.size>e)this.file.data=new Uint8Array(this.file.data.buffer.slice(0,Number(e)));else{const t=new Uint8Array(Number(e));t.set(this.file.data,0),this.file.data=t}return ERRNO_SUCCESS}fd_read(e){const t=this.file.data.slice(Number(this.file_pos),Number(this.file_pos+BigInt(e)));return this.file_pos+=BigInt(t.length),{ret:0,data:t}}fd_pread(e,t){return{ret:0,data:this.file.data.slice(Number(t),Number(t+BigInt(e)))}}fd_seek(e,t){let n;switch(t){case WHENCE_SET:n=e;break;case WHENCE_CUR:n=this.file_pos+e;break;case WHENCE_END:n=BigInt(this.file.data.byteLength)+e;break;default:return{ret:ERRNO_INVAL,offset:0n}}return n<0?{ret:ERRNO_INVAL,offset:0n}:(this.file_pos=n,{ret:0,offset:this.file_pos})}fd_tell(){return{ret:0,offset:this.file_pos}}fd_write(e){if(this.file.readonly)return{ret:ERRNO_BADF,nwritten:0};if(this.file_pos+BigInt(e.byteLength)>this.file.size){const t=this.file.data;this.file.data=new Uint8Array(Number(this.file_pos+BigInt(e.byteLength))),this.file.data.set(t)}return this.file.data.set(e,Number(this.file_pos)),this.file_pos+=BigInt(e.byteLength),{ret:0,nwritten:e.byteLength}}fd_pwrite(e,t){if(this.file.readonly)return{ret:ERRNO_BADF,nwritten:0};if(t+BigInt(e.byteLength)>this.file.size){const n=this.file.data;this.file.data=new Uint8Array(Number(t+BigInt(e.byteLength))),this.file.data.set(n)}return this.file.data.set(e,Number(t)),{ret:0,nwritten:e.byteLength}}fd_filestat_get(){return{ret:0,filestat:this.file.stat()}}constructor(e){super(),this.file_pos=0n,this.file=e}}class OpenDirectory extends Fd{fd_seek(e,t){return{ret:ERRNO_BADF,offset:0n}}fd_tell(){return{ret:ERRNO_BADF,offset:0n}}fd_allocate(e,t){return ERRNO_BADF}fd_fdstat_get(){return{ret:0,fdstat:new Fdstat(FILETYPE_DIRECTORY,0)}}fd_readdir_single(e){if(debug.enabled&&(debug.log(\"readdir_single\",e),debug.log(e,this.dir.contents.keys())),0n==e)return{ret:ERRNO_SUCCESS,dirent:new Dirent(1n,\".\",FILETYPE_DIRECTORY)};if(1n==e)return{ret:ERRNO_SUCCESS,dirent:new Dirent(2n,\"..\",FILETYPE_DIRECTORY)};if(e>=BigInt(this.dir.contents.size)+2n)return{ret:0,dirent:null};const[t,n]=Array.from(this.dir.contents.entries())[Number(e-2n)];return{ret:0,dirent:new Dirent(e+1n,t,n.stat().filetype)}}path_filestat_get(e,t){const{ret:n,path:r}=Path.from(t);if(null==r)return{ret:n,filestat:null};const{ret:s,entry:i}=this.dir.get_entry_for_path(r);return null==i?{ret:s,filestat:null}:{ret:0,filestat:i.stat()}}path_lookup(e,t){const{ret:n,path:r}=Path.from(e);if(null==r)return{ret:n,inode_obj:null};const{ret:s,entry:i}=this.dir.get_entry_for_path(r);return null==i?{ret:s,inode_obj:null}:{ret:ERRNO_SUCCESS,inode_obj:i}}path_open(e,t,n,r,s,i){const{ret:a,path:l}=Path.from(t);if(null==l)return{ret:a,fd_obj:null};let{ret:o,entry:_}=this.dir.get_entry_for_path(l);if(null==_){if(o!=ERRNO_NOENT)return{ret:o,fd_obj:null};if((n&OFLAGS_CREAT)!=OFLAGS_CREAT)return{ret:ERRNO_NOENT,fd_obj:null};{const{ret:e,entry:r}=this.dir.create_entry_for_path(t,(n&OFLAGS_DIRECTORY)==OFLAGS_DIRECTORY);if(null==r)return{ret:e,fd_obj:null};_=r}}else if((n&OFLAGS_EXCL)==OFLAGS_EXCL)return{ret:ERRNO_EXIST,fd_obj:null};return(n&OFLAGS_DIRECTORY)==OFLAGS_DIRECTORY&&_.stat().filetype!==FILETYPE_DIRECTORY?{ret:ERRNO_NOTDIR,fd_obj:null}:_.path_open(n,r,i)}path_create_directory(e){return this.path_open(0,e,OFLAGS_CREAT|OFLAGS_DIRECTORY,0n,0n,0).ret}path_link(e,t,n){const{ret:r,path:s}=Path.from(e);if(null==s)return r;if(s.is_dir)return ERRNO_NOENT;const{ret:i,parent_entry:a,filename:l,entry:o}=this.dir.get_parent_dir_and_entry_for_path(s,!0);if(null==a||null==l)return i;if(null!=o){const e=t.stat().filetype==FILETYPE_DIRECTORY,r=o.stat().filetype==FILETYPE_DIRECTORY;if(e&&r){if(!(n&&o instanceof Directory))return ERRNO_EXIST;if(0!=o.contents.size)return ERRNO_NOTEMPTY}else{if(e&&!r)return ERRNO_NOTDIR;if(!e&&r)return ERRNO_ISDIR;if(t.stat().filetype!=FILETYPE_REGULAR_FILE||o.stat().filetype!=FILETYPE_REGULAR_FILE)return ERRNO_EXIST}}return n||t.stat().filetype!=FILETYPE_DIRECTORY?(a.contents.set(l,t),ERRNO_SUCCESS):ERRNO_PERM}path_unlink(e){const{ret:t,path:n}=Path.from(e);if(null==n)return{ret:t,inode_obj:null};const{ret:r,parent_entry:s,filename:i,entry:a}=this.dir.get_parent_dir_and_entry_for_path(n,!0);return null==s||null==i?{ret:r,inode_obj:null}:null==a?{ret:ERRNO_NOENT,inode_obj:null}:(s.contents.delete(i),{ret:ERRNO_SUCCESS,inode_obj:a})}path_unlink_file(e){const{ret:t,path:n}=Path.from(e);if(null==n)return t;const{ret:r,parent_entry:s,filename:i,entry:a}=this.dir.get_parent_dir_and_entry_for_path(n,!1);return null==s||null==i||null==a?r:a.stat().filetype===FILETYPE_DIRECTORY?ERRNO_ISDIR:(s.contents.delete(i),ERRNO_SUCCESS)}path_remove_directory(e){const{ret:t,path:n}=Path.from(e);if(null==n)return t;const{ret:r,parent_entry:s,filename:i,entry:a}=this.dir.get_parent_dir_and_entry_for_path(n,!1);return null==s||null==i||null==a?r:a instanceof Directory&&a.stat().filetype===FILETYPE_DIRECTORY?0!==a.contents.size?ERRNO_NOTEMPTY:s.contents.delete(i)?ERRNO_SUCCESS:ERRNO_NOENT:ERRNO_NOTDIR}fd_filestat_get(){return{ret:0,filestat:this.dir.stat()}}fd_filestat_set_size(e){return ERRNO_BADF}fd_read(e){return{ret:ERRNO_BADF,data:new Uint8Array}}fd_pread(e,t){return{ret:ERRNO_BADF,data:new Uint8Array}}fd_write(e){return{ret:ERRNO_BADF,nwritten:0}}fd_pwrite(e,t){return{ret:ERRNO_BADF,nwritten:0}}constructor(e){super(),this.dir=e}}class PreopenDirectory extends OpenDirectory{fd_prestat_get(){return{ret:0,prestat:Prestat.dir(this.prestat_name)}}constructor(e,t){super(new Directory(t)),this.prestat_name=e}}class File extends Inode{path_open(e,t,n){if(this.readonly&&(t&BigInt(RIGHTS_FD_WRITE))==BigInt(RIGHTS_FD_WRITE))return{ret:ERRNO_PERM,fd_obj:null};if((e&OFLAGS_TRUNC)==OFLAGS_TRUNC){if(this.readonly)return{ret:ERRNO_PERM,fd_obj:null};this.data=new Uint8Array([])}const r=new OpenFile(this);return n&FDFLAGS_APPEND&&r.fd_seek(0n,WHENCE_END),{ret:ERRNO_SUCCESS,fd_obj:r}}get size(){return BigInt(this.data.byteLength)}stat(){return new Filestat(FILETYPE_REGULAR_FILE,this.size)}constructor(e,t){super(),this.data=new Uint8Array(e),this.readonly=!!t?.readonly}}let Path=class e{static from(t){const n=new e;if(n.is_dir=t.endsWith(\"/\"),t.startsWith(\"/\"))return{ret:ERRNO_NOTCAPABLE,path:null};if(t.includes(\"\\0\"))return{ret:ERRNO_INVAL,path:null};for(const e of t.split(\"/\"))if(\"\"!==e&&\".\"!==e)if(\"..\"!==e)n.parts.push(e);else if(null==n.parts.pop())return{ret:ERRNO_NOTCAPABLE,path:null};return{ret:ERRNO_SUCCESS,path:n}}to_path_string(){let e=this.parts.join(\"/\");return this.is_dir&&(e+=\"/\"),e}constructor(){this.parts=[],this.is_dir=!1}},inst;class Directory extends Inode{path_open(e,t,n){return{ret:ERRNO_SUCCESS,fd_obj:new OpenDirectory(this)}}stat(){return new Filestat(FILETYPE_DIRECTORY,0n)}get_entry_for_path(e){let t=this;for(const n of e.parts){if(!(t instanceof Directory))return{ret:ERRNO_NOTDIR,entry:null};const e=t.contents.get(n);if(void 0===e)return debug.log(n),{ret:ERRNO_NOENT,entry:null};t=e}return e.is_dir&&t.stat().filetype!=FILETYPE_DIRECTORY?{ret:ERRNO_NOTDIR,entry:null}:{ret:ERRNO_SUCCESS,entry:t}}get_parent_dir_and_entry_for_path(e,t){const n=e.parts.pop();if(void 0===n)return{ret:ERRNO_INVAL,parent_entry:null,filename:null,entry:null};const{ret:r,entry:s}=this.get_entry_for_path(e);if(null==s)return{ret:r,parent_entry:null,filename:null,entry:null};if(!(s instanceof Directory))return{ret:ERRNO_NOTDIR,parent_entry:null,filename:null,entry:null};const i=s.contents.get(n);return void 0===i?t?{ret:ERRNO_SUCCESS,parent_entry:s,filename:n,entry:null}:{ret:ERRNO_NOENT,parent_entry:null,filename:null,entry:null}:e.is_dir&&i.stat().filetype!=FILETYPE_DIRECTORY?{ret:ERRNO_NOTDIR,parent_entry:null,filename:null,entry:null}:{ret:ERRNO_SUCCESS,parent_entry:s,filename:n,entry:i}}create_entry_for_path(e,t){const{ret:n,path:r}=Path.from(e);if(null==r)return{ret:n,entry:null};let s,{ret:i,parent_entry:a,filename:l,entry:o}=this.get_parent_dir_and_entry_for_path(r,!0);return null==a||null==l?{ret:i,entry:null}:null!=o?{ret:ERRNO_EXIST,entry:null}:(debug.log(\"create\",r),s=t?new Directory(new Map):new File(new ArrayBuffer(0)),a.contents.set(l,s),o=s,{ret:ERRNO_SUCCESS,entry:o})}constructor(e){super(),this.contents=e instanceof Array?new Map(e):e}}class ConsoleStdout extends Fd{fd_filestat_get(){return{ret:0,filestat:new Filestat(FILETYPE_CHARACTER_DEVICE,BigInt(0))}}fd_fdstat_get(){const e=new Fdstat(FILETYPE_CHARACTER_DEVICE,0);return e.fs_rights_base=BigInt(RIGHTS_FD_WRITE),{ret:0,fdstat:e}}fd_write(e){return this.write(e),{ret:0,nwritten:e.byteLength}}static lineBuffered(e){const t=new TextDecoder(\"utf-8\",{fatal:!1});let n=\"\";return new ConsoleStdout((r=>{n+=t.decode(r,{stream:!0});const s=n.split(\"\\n\");for(const[t,r]of s.entries())te+t||this.file.handle.truncate(Number(e+t)),ERRNO_SUCCESS}fd_fdstat_get(){return{ret:0,fdstat:new Fdstat(FILETYPE_REGULAR_FILE,0)}}fd_filestat_get(){return{ret:0,filestat:new Filestat(FILETYPE_REGULAR_FILE,BigInt(this.file.handle.getSize()))}}fd_filestat_set_size(e){return this.file.handle.truncate(Number(e)),ERRNO_SUCCESS}fd_read(e){const t=new Uint8Array(e),n=this.file.handle.read(t,{at:Number(this.position)});return this.position+=BigInt(n),{ret:0,data:t.slice(0,n)}}fd_seek(e,t){let n;switch(t){case WHENCE_SET:n=BigInt(e);break;case WHENCE_CUR:n=this.position+BigInt(e);break;case WHENCE_END:n=BigInt(this.file.handle.getSize())+BigInt(e);break;default:return{ret:ERRNO_INVAL,offset:0n}}return n<0?{ret:ERRNO_INVAL,offset:0n}:(this.position=n,{ret:ERRNO_SUCCESS,offset:this.position})}fd_write(e){if(this.file.readonly)return{ret:ERRNO_BADF,nwritten:0};const t=this.file.handle.write(e,{at:Number(this.position)});return this.position+=BigInt(t),{ret:ERRNO_SUCCESS,nwritten:t}}fd_sync(){return this.file.handle.flush(),ERRNO_SUCCESS}constructor(e){super(),this.position=0n,this.file=e}}function runWasm(e,t=null,n){const r={refs:(null==n?void 0:n.refs)||new proto.PG,stack:(null==n?void 0:n.stack)||null,triggerEvent:function(){},resumeCont:function(){}},s=new WASI([],[],[new OpenFile(new File([])),new OpenFile(new File([])),new OpenFile(new File([]))]);function i(e,t){const n=new DataView(inst.exports.memory.buffer),s={context:Object.assign(Object.assign({},r),{resumeCont:function(r,s){const i={mem:n,begin:e,end:e+t};proto.ni(i,[proto.JC.ResumeMsg,r,s]),inst.exports.wasm_app(e)},triggerEvent:function(r,s){const i={mem:n,begin:e,end:e+t};proto.ni(i,[proto.JC.EventMsg,r,s]),inst.exports.wasm_app(e)}}),mem:n,isMutableMem:!0,begin:e,end:e+t};proto.iQ(s)}WebAssembly.compileStreaming(fetch(e)).then((e=>WebAssembly.instantiate(e,{wasi_snapshot_preview1:s.wasiImport,env:{clickable_eval_buffer:i}}))).then((e=>{inst=e,s.initialize(e),e.exports.hs_init(),e.exports.wasm_app(0)}))}function evalUint8Array(e,t){const n={context:{refs:(null==t?void 0:t.refs)||new proto.PG,stack:(null==t?void 0:t.stack)||null,triggerEvent:(null==t?void 0:t.triggerEvent)||function(){},resumeCont:(null==t?void 0:t.resumeCont)||function(){}},mem:new DataView(e.buffer),isMutableMem:!1,begin:0,end:e.byteLength};return proto.iQ(n)}function evalBase64(e,t){return evalUint8Array(Uint8Array.from(atob(e),(function(e){return e.charCodeAt(0)})),t)}window.clickable={runWebsocket,runWasm,evalUint8Array,evalBase64}})();" diff --git a/jsbits/misc.ts b/jsbits/misc.ts index 1dbf998..d9d5033 100644 --- a/jsbits/misc.ts +++ b/jsbits/misc.ts @@ -4,7 +4,7 @@ import * as proto from "./proto"; export function evalUint8Array(command: Uint8Array, options?: Partial): unknown { const context: EvalContext = { - refs: options?.refs || new Map(), + refs: options?.refs || new proto.RefStore(), stack: options?.stack || null, triggerEvent: options?.triggerEvent || function() {}, resumeCont: options?.resumeCont || function() {}, diff --git a/jsbits/proto.ts b/jsbits/proto.ts index 215a2af..80f8cbf 100644 --- a/jsbits/proto.ts +++ b/jsbits/proto.ts @@ -62,9 +62,9 @@ export enum ExprTag { Call, AssignRef, - FreeRef, Ref, FreeScope, + MoveScope, PeekStack, PushStack, @@ -75,9 +75,9 @@ export enum ExprTag { ElementAttr, ClassListAdd, ClassListRemove, - InsertBrackets, - ClearBrackets, - DetachBrackets, + InsertPlaceholder, + ClearPlaceholder, + DetachPlaceholder, CreateElement, CreateElementNS, @@ -116,9 +116,9 @@ export type Expr = | [ExprTag.Call, Expr, string, [Expr]] | [ExprTag.AssignRef, number, number, Expr] - | [ExprTag.FreeRef, number, number] - | [ExprTag.Ref, number, number] + | [ExprTag.Ref, number] | [ExprTag.FreeScope, number] + | [ExprTag.MoveScope, number, number] | [ExprTag.PeekStack, number] | [ExprTag.PushStack, Expr] @@ -129,9 +129,9 @@ export type Expr = | [ExprTag.ElementAttr, string, string] | [ExprTag.ClassListAdd, Expr, string[]] | [ExprTag.ClassListRemove, Expr, string[]] - | [ExprTag.InsertBrackets] - | [ExprTag.ClearBrackets, Expr] - | [ExprTag.DetachBrackets, Expr] + | [ExprTag.InsertPlaceholder] + | [ExprTag.ClearPlaceholder, Expr] + | [ExprTag.DetachPlaceholder, Expr] | [ExprTag.CreateElement, string] | [ExprTag.CreateElementNS, string, string] @@ -159,7 +159,7 @@ export type EvalState = { export type EvalContext = { readonly triggerEvent: (eventId: EventId, arg: unknown) => void; readonly resumeCont: (contId: number, res: unknown) => void; - readonly refs: Map>; + readonly refs: RefStore; stack: List; }; @@ -364,42 +364,29 @@ export function evalNext(self: EvalState, args: List = null, prevRes: u }; case ExprTag.AssignRef: { - const scopeId = self.mem.getUint32(self.begin, false); - const refId = self.mem.getUint32(self.begin + 4, false); + const scope = self.mem.getUint32(self.begin, false); + const ref = self.mem.getUint32(self.begin + 4, false); self.begin += 8; const val = evalNext(self, args, prevRes); - if (self.context.refs.has(scopeId)) { - const scopeMap = self.context.refs.get(scopeId)!; - scopeMap.set(refId, val); - } else { - const scopeMap = new Map(); - scopeMap.set(refId, val); - self.context.refs.set(scopeId, scopeMap); - } + self.context.refs.assignRef(scope, ref, val); return val; }; - case ExprTag.FreeRef: { - const scopeId = self.mem.getUint32(self.begin, false); - const refId = self.mem.getUint32(self.begin + 4, false); - self.begin += 8; - const scopeMap = self.context.refs.get(scopeId); - if (!scopeMap) return null; - scopeMap.delete(refId); - if (scopeMap.size == 0) { - self.context.refs.delete(scopeId); - } - return null; - }; case ExprTag.Ref: { - const scopeId = self.mem.getUint32(self.begin, false); - const refId = self.mem.getUint32(self.begin + 4, false); - self.begin += 8; - return self.context.refs.get(scopeId)?.get(refId); + const ref = self.mem.getUint32(self.begin, false); + self.begin += 4; + return self.context.refs.refs.get(ref); }; case ExprTag.FreeScope: { - const scopeId = self.mem.getUint32(self.begin, false); + const scope = self.mem.getUint32(self.begin, false); self.begin += 4; - self.context.refs.delete(scopeId); + self.context.refs.freeScope(scope); + return null; + }; + case ExprTag.MoveScope: { + const src = self.mem.getUint32(self.begin, false); + const dest = self.mem.getUint32(self.begin + 4, false); + self.begin += 8; + self.context.refs.moveScope(src, dest); return null; }; @@ -468,21 +455,21 @@ export function evalNext(self: EvalState, args: List = null, prevRes: u const className = decodeString(self); return el.classList.remove(className); }; - case ExprTag.InsertBrackets: { + case ExprTag.InsertPlaceholder: { if (!self.context.stack) { - throw new Error("InsertBrackets: empty stack"); + throw new Error("InsertPlaceholder: empty stack"); } const el = self.context.stack[VAL] as any; - return utils.insertBrackets(el); + return utils.insertPlaceholder(el); }; - case ExprTag.ClearBrackets: { + case ExprTag.ClearPlaceholder: { const node = evalNext(self, args, prevRes); - utils.clearBrackets(node as any, false); + utils.clearPlaceholder(node as any, false); return null; }; - case ExprTag.DetachBrackets: { + case ExprTag.DetachPlaceholder: { const node = evalNext(self, args, prevRes); - utils.clearBrackets(node as any, true); + utils.clearPlaceholder(node as any, true); return null; }; case ExprTag.CreateElement: { @@ -634,15 +621,15 @@ export function lookaheadNext(mem: DataView, ptr: Ptr): Ptr { case ExprTag.AssignRef: { return ptr + 8; }; - case ExprTag.FreeRef: { - return ptr + 8; - }; case ExprTag.Ref: { - return ptr + 8; + return ptr + 4; }; case ExprTag.FreeScope: { return ptr + 4; }; + case ExprTag.MoveScope: { + return ptr + 8; + }; case ExprTag.PeekStack: { return ptr + 1; @@ -675,13 +662,13 @@ export function lookaheadNext(mem: DataView, ptr: Ptr): Ptr { const newPtr0 = lookaheadNext(mem, ptr); return lookaheadString(mem, newPtr0); }; - case ExprTag.InsertBrackets: { + case ExprTag.InsertPlaceholder: { return ptr; }; - case ExprTag.ClearBrackets: { + case ExprTag.ClearPlaceholder: { return lookaheadNext(mem, ptr); }; - case ExprTag.DetachBrackets: { + case ExprTag.DetachPlaceholder: { return lookaheadNext(mem, ptr); }; case ExprTag.CreateElement: { @@ -873,31 +860,31 @@ namespace utils { element.removeEventListener(eventName, listener); } - export function insertBrackets(builder: Element|Comment): Comment { - const begin = document.createComment('ContentBrackets {{'); - const end = document.createComment('}}'); + export function insertPlaceholder(builder: Element|Comment): Comment { + const begin = document.createComment('Placeholder {{{'); + const end = document.createComment('}}}'); insert(builder, begin); insert(builder, end); return end; } - export function clearBrackets(bracket: Comment|Element, detach: boolean): void { - if (bracket instanceof Comment) { + export function clearPlaceholder(placeholder: Comment|Element, detach: boolean): void { + if (placeholder instanceof Comment) { let nestedCounter = 0; for (;;){ - if (!bracket.previousSibling || - (nestedCounter == 0 && isOpenBracket(bracket.previousSibling)) + if (!placeholder.previousSibling || + (nestedCounter == 0 && isOpenPlaceholder(placeholder.previousSibling)) ) break; - if (isClosingBracket(bracket.previousSibling)) nestedCounter++; - else if (isOpenBracket(bracket.previousSibling)) nestedCounter--; - bracket.previousSibling!.parentNode!.removeChild(bracket.previousSibling!); + if (isClosingPlaceholder(placeholder.previousSibling)) nestedCounter++; + else if (isOpenPlaceholder(placeholder.previousSibling)) nestedCounter--; + placeholder.previousSibling!.parentNode!.removeChild(placeholder.previousSibling!); } if (detach) { - bracket.previousSibling!.parentNode!.removeChild(bracket.previousSibling!); - bracket.parentNode!.removeChild(bracket); + placeholder.previousSibling!.parentNode!.removeChild(placeholder.previousSibling!); + placeholder.parentNode!.removeChild(placeholder); } } else { - bracket.innerHTML = ''; + placeholder.innerHTML = ''; } } @@ -908,17 +895,47 @@ namespace utils { return builder; } - function isOpenBracket(node: Node): boolean { - if (node instanceof Comment && node.textContent == 'ContentBrackets {{') { + function isOpenPlaceholder(node: Node): boolean { + if (node instanceof Comment && node.textContent == 'Placeholder {{{') { return true; } return false; } - function isClosingBracket(node: Node): boolean { - if (node instanceof Comment && node.textContent == '}}') { + function isClosingPlaceholder(node: Node): boolean { + if (node instanceof Comment && node.textContent == '}}}') { return true; } return false; } }; + +export class RefStore { + constructor( + public scopes = new Map>, + public refs = new Map, + ) {} + + assignRef(scope: ScopeId, refId: RefId, value: unknown) { + const refs0 = this.scopes.get(scope); + const refs1 = refs0 || new Set(); + if (!refs0) this.scopes.set(scope, refs1); + refs1.add(refId); + this.refs.set(refId, value); + } + + moveScope(src: ScopeId, dest: ScopeId) { + const srcRefs = this.scopes.get(src); + const destRefs = this.scopes.get(dest); + if (!srcRefs || !destRefs) return; + srcRefs.forEach(s => destRefs.add(s)); + this.scopes.delete(src); + } + + freeScope(scope: ScopeId) { + const refs = this.scopes.get(scope); + if (!refs) return; + refs.forEach(s => this.refs.delete(s)); + this.scopes.delete(scope); + } +} diff --git a/jsbits/wasm.ts b/jsbits/wasm.ts index f852de4..442c528 100644 --- a/jsbits/wasm.ts +++ b/jsbits/wasm.ts @@ -6,7 +6,7 @@ let inst: WebAssembly.Instance; export function runWasm(wasmUri: string, startFlags: unknown = null, options?: Partial) { const context: EvalContext = { - refs: options?.refs || new Map(), + refs: options?.refs || new proto.RefStore(), stack: options?.stack || null, triggerEvent: function() {}, resumeCont: function() {}, diff --git a/jsbits/websocket.ts b/jsbits/websocket.ts index 799c04c..2dd10ba 100644 --- a/jsbits/websocket.ts +++ b/jsbits/websocket.ts @@ -7,7 +7,7 @@ const mem = new DataView(outBuf); export function runWebsocket(devSocketUri: string, startFlags: unknown = null, options?: Partial) { const websocket = new WebSocket(devSocketUri); const context: EvalContext = { - refs: options?.refs || new Map(), + refs: options?.refs || new proto.RefStore(), stack: options?.stack || null, triggerEvent, resumeCont,