From edce2ce015d491afce71a94733b4a10228196b6d Mon Sep 17 00:00:00 2001 From: SuperCoolYun Date: Tue, 23 Jan 2024 17:04:05 -0500 Subject: [PATCH 1/9] %near-gateway added, %gossip implemented --- desk/app/near-gateways.hoon | 137 +++++++ desk/desk.bill | 1 + desk/gen/poke.hoon | 13 + desk/lib/gossip.hoon | 749 ++++++++++++++++++++++++++++++++++++ desk/lib/pals.hoon | 21 + desk/lib/verb.hoon | 105 +++++ desk/mar/near/action.hoon | 14 + desk/mar/near/metadata.hoon | 12 + desk/sur/near-handler.hoon | 5 + desk/sur/pals.hoon | 41 ++ desk/sur/verb.hoon | 12 + 11 files changed, 1110 insertions(+) create mode 100644 desk/app/near-gateways.hoon create mode 100644 desk/gen/poke.hoon create mode 100644 desk/lib/gossip.hoon create mode 100644 desk/lib/pals.hoon create mode 100644 desk/lib/verb.hoon create mode 100644 desk/mar/near/action.hoon create mode 100644 desk/mar/near/metadata.hoon create mode 100644 desk/sur/pals.hoon create mode 100644 desk/sur/verb.hoon diff --git a/desk/app/near-gateways.hoon b/desk/app/near-gateways.hoon new file mode 100644 index 000000000..aca0d7e7c --- /dev/null +++ b/desk/app/near-gateways.hoon @@ -0,0 +1,137 @@ +/- *near-handler +/+ dbug, default-agent, *near-handler, gossip +/$ grab-metadata %noun %near-metadata +:: +|% +:: ++$ versioned-state + $% state-0 + == +:: ++$ state-0 + $: %0 + :: (map identifier=[ship id] metadata=[name url]) + heard=(map identifier metadata) + published=(map identifier metadata) + installed=(map identifier metadata) + == +:: ++$ card $+(card card:agent:gall) +-- +:: +=| state-0 +=* state - +:: +%- %+ agent:gossip + [2 %anybody %anybody |] + %+ ~(put by *(map mark $-(* vase))) + %metadata + |=(n=* !>((grab-metadata n))) +:: +^- agent:gall +:: +=< + |_ =bowl:gall + +* this . + def ~(. (default-agent this %|) bowl) + hc ~(. +> [bowl ~]) + :: + ++ on-init + ^- (quip card _this) + =^ cards state abet:init:hc + [cards this] + :: + ++ on-save + ^- vase + !>(state) + :: + ++ on-load + |= =vase + ^- (quip card _this) + =^ cards state abet:(load:hc vase) + [cards this] + :: + ++ on-poke + |= [=mark =vase] + ^- (quip card _this) + =^ cards state abet:(poke:hc mark vase) + [cards this] + :: + ++ on-watch + |= =path + ^- (quip card _this) + =^ cards state abet:(watch:hc path) + [cards this] + :: + ++ on-agent + |= [=wire =sign:agent:gall] + ^- (quip card _this) + =^ cards state abet:(agent:hc wire sign) + [cards this] + :: + ++ on-peek on-peek:def + ++ on-arvo on-arvo:def + ++ on-fail on-fail:def + ++ on-leave on-leave:def + -- +|_ [=bowl:gall deck=(list card)] ++* that . +++ emit |=(=card that(deck [card deck])) +++ emil |=(lac=(list card) that(deck (welp lac deck))) +++ abet ^-((quip card _state) [(flop deck) state]) +:: +++ from-self =(our src):bowl +:: +++ init + ^+ that + that +:: +++ load + |= vaz=vase + ^+ that + ?> ?=([%0 *] q.vaz) + that(state !<(state-0 vaz)) +:: +++ poke + |= [=mark =vase] + ^+ that + ?+ mark that + %near-action + ?> from-self + =+ !<(act=gateway-action vase) + ?- -.act + %publish + :: add metadata to published-state + :: send update to gossip + =/ id=identifier [our.bowl `@ud`eny.bowl] ::what entropy to use ? + =. published (~(put by published) id +.act) + %- emit + %+ invent:gossip + %metadata + !> ^- [identifier metadata] + [id +.act] + == +== +++ watch + |= =path + ^+ that + ?+ path ~|(bad-watch-path+path !!) + [%~.~ %gossip %source ~] that + == +++ agent + |= [=wire =sign:agent:gall] + ^+ that + ?+ wire ~|(bad-agent-wire+wire !!) + [%~.~ %gossip %gossip ~] + ?+ -.sign ~|([%unexpected-gossip-sign -.sign] !!) + %fact + =* mark p.cage.sign + =* vase q.cage.sign + ?. =(%metadata mark) that + ::add new gateway to heard + =+ !<([id=identifier =metadata] vase) + =. heard (~(put by heard) id metadata) + that + == + == + -- \ No newline at end of file diff --git a/desk/desk.bill b/desk/desk.bill index df51c395f..e86ee5efc 100644 --- a/desk/desk.bill +++ b/desk/desk.bill @@ -1,2 +1,3 @@ :~ %near-handler + %near-gateways == diff --git a/desk/gen/poke.hoon b/desk/gen/poke.hoon new file mode 100644 index 000000000..bb75a39f6 --- /dev/null +++ b/desk/gen/poke.hoon @@ -0,0 +1,13 @@ +!: +:- %say +:: :near-gateways +near-handler!poke %publish ['url' 'test'] +|= $: [now=@da eny=@uvJ bec=beak] + $: act=?(%publish) + metadata=[url=@t name=@t] + ~ + == + ~ + == +?- act +%publish [%near-action [%publish metadata]] +== \ No newline at end of file diff --git a/desk/lib/gossip.hoon b/desk/lib/gossip.hoon new file mode 100644 index 000000000..cd3356a16 --- /dev/null +++ b/desk/lib/gossip.hoon @@ -0,0 +1,749 @@ +:: gossip: data sharing with pals +:: +:: v1.1.0: sneaky whisper +:: +:: automates using /app/pals for peer & content discovery, +:: letting the underlying agent focus on handling the data. +:: +:: usage +:: +:: to use this library, call its +agent arm with an initial +:: configuration and a map of, per mark, noun->vase convertors, +:: then call the resulting gate with the agent's door. +:: +:: data from peers will come in through +on-agent, as %facts with +:: a /~/gossip wire. +:: the mark convertors ensure that this library can reconstitute the +:: appropriate vases from the (cask *)s it sends around internally. +:: if a mark conversion for a received datum isn't available, then +:: the library will inject a %fact with a %gossip-unknown mark instead, +:: containing a (cask *). the agent may either store it for later use, +:: or handle it directly. +:: +:: for new incoming subscriptions, the underlying agent's +on-watch is +:: called, with /~/gossip/source, so that it may give initial results. +::TODO but this is somewhat wrong for multi-hop subscriptions, right? +:: /source is only intended to give _locally originating_ data. +:: if hops are >1, should we do both /source and /gossip? +:: doesn't this result in a lot of traffic, for know-a-lot cases? +:: +:: when data originates locally and needs to be given to our peers, +:: simply produce a normal %fact on the /~/gossip/source path. +:: the +invent helper can be used to do this. +:: refrain from re-emitting received %facts manually. the library will +:: handle this for you, based on the current configuration. +:: +:: to change the configuration after the agent has been started, emit +:: a %fact with the %gossip-config mark on the /~/gossip/config path. +:: the +configure helper can be used to do this. +:: the +read-config helper scries out the current configuration. +:: setting hops to 1 distributes the data to direct pals only. +:: setting hops to 0 prevents emission of any gossip data at all, +:: even during initial subscription setup. +:: setting pass to true causes 50% of locally-originating data to be +:: proxied through a random "tell" peer. note that the proxy will have +:: a 50% chance of proxying in turn. for low amounts of hops, data could +:: escape the local social graph entirely. +:: +:: (we introduce the /~/etc path prefix convention to indicate paths +:: that are for library-specific use only. +:: the advantage this has over the "mutated agent" pattern (for example, +:: /lib/shoe) is that the library consumes a normal $agent:gall, making +:: it theoretically easier to compose with other agent libraries. +:: the disavantage, of course, is that internal interaction with the +:: wrapper library isn't type-checked anymore. helper functions make +:: that less of a problem, but the developer must stay vigilant about +:: casting all the relevant outputs.) +:: +:: when considering the types of data to be sent through gossip, keep +:: in mind that the library keeps track of (hashes of) all the individual +:: datums it has heard. as such, if your data is of the shape @t, and we +:: hear a 'hello' once, we will completely ignore any 'hello' that come +:: afterward, even if they originate from distinct events. +:: if this is a problem for your use case, consider including a timestamp +:: or other source of uniqueness with each distinct datum. +:: +:: note that this library and its protocol are currently not in the +:: business of providing anonymized gossip. any slightly motivated actor +:: will have no problem modifying this library to detect and record +:: sources of data with good accuracy. +:: +:: wip, libdev thoughts +:: +:: we may want to include additional metadata alongside gossip facts, +:: such as a hop counter, set of informed peers, origin timestamp, etc. +:: we may want to use pokes exclusively, instead of watches/facts, +:: making it easier to exclude the src.bowl, include metadata, etc. +:: +:: we currently only emit every rumor as a fact once at most. but we might +:: receive it again later, with a higher hop count. if we want to try for +:: maximum reach within the given hops, we should re-send if we receive a +:: known rumor with higher hop counter. but this may not be worth the added +:: complexity... +:: +:: what if this was a userspace-infrastructure app instead of a wrapper? +:: how would ensuring installation of this app-dependency work? +:: it gains us... a higher chance of peers having this installed. +:: what if it was just part of pals? +:: would let us more-reliably poke mutuals and leeches, if we wanted to do +:: a proxy-broadcast thing. +:: +:: when considering adding features like rumor signing, keep in mind that +:: this library is mostly in the business of ferrying casks. perhaps +:: features like signing should be left up to applications themselves. +:: +:: internal logic +:: +:: - on-init or during first on-load, watch pals for targets & leeches. +:: - if pals is not running, the watch will simply pend until it starts. +:: - if pals ever watch-nacks (it shouldn't), we try rewatching after ~m1. +:: +:: - for facts produced on /~/gossip/source, we +:: - 50% chance to redirect into the "pass flow" (see below) +:: - wrap them as %gossip-rumor to send them out on /~/gossip/gossip +:: - for new pals matching the hear mode, we watch their /~/gossip/gossip +:: - for gone pals, we leave that watch +:: - for facts on those watches +:: - ensure they're %gossip-rumors, ignoring otherwise +:: - unwrap them and +on-agent /~/gossip/gossip into the inner agent, and +:: - re-emit them as facts on /~/gossip/gossip if there are hops left +:: - for nacks on those watches, we retry after ~m30 +:: +:: - other gossip instances may poke us with rumors directly +:: - the inner agent learns the rumor normally, as if it came from a fact +:: - based on randomness (50/50), we do one of two things: +:: - publish the rumor as a fact to our subscribers, like the above +:: - poke a randomly selected peer (in the "tell" set) with the rumor +:: - when poking, store the rumor until we receive a poke-ack +:: - upon receiving a positive poke-ack, delete the local datum +:: - upon receiving a negative poke-ack, do the 50/50 again +:: - if we do not receive a poke-ack within some time, do the 50/50 again +:: +/- pals +/+ lp=pals, dbug, verb +:: +|% ++$ rumor + $: [kind=@ meta=*] + data=(cask *) + == ++$ meta-0 hops=_0 +:: ++$ hash @uv +:: ++$ whos + $? %anybody :: any ship discoverable through pals + %targets :: any ship we've added as a pal + %mutuals :: any mutual pal + == +:: ++$ config + $: hops=_1 :: how far away gossip may travel + :: (1 hop is pals only, 0 stops exposing data at all) + hear=whos :: who to subscribe to + tell=whos :: who to allow subscriptions from + pass=? :: whether to (50/50) emit through proxy + == +:: +++ pass-timeout ~s30 +:: +++ invent + |= =cage + ^- card:agent:gall + [%give %fact [/~/gossip/source]~ cage] +:: +++ configure + |= =config + ^- card:agent:gall + [%give %fact [/~/gossip/config]~ %gossip-config !>(config)] +:: +++ read-config + |= bowl:gall + ^- config + .^(config %gx /(scot %p our)/[dap]/(scot %da now)/~/gossip/config/noun) +:: +++ agent + |= $: init=config + grab=(map mark $-(* vase)) + == + ^- $-(agent:gall agent:gall) + |^ agent + :: + +$ state-1 + $: %1 + manner=config :: latest config + memory=(set hash) :: datums seen (by inner agent) + shared=(set hash) :: datums shared (as fact) + passed=(map hash [rumor @da]) :: pending relays & timeouts + future=(list rumor) :: rumors of unknown kinds + == + :: + +$ card card:agent:gall + :: + ++ helper + |_ [=bowl:gall state-1] + +* state +<+ + pals ~(. lp bowl) + ++ en-cage + |= =(cask *) + ^- cage + ?^ to=(~(get by grab) p.cask) + ::TODO +soft or otherwise virtualize? don't want to risk crashes, right? + [p.cask (u.to q.cask)] + ~& [gossip+dap.bowl %no-mark p.cask] + [%gossip-unknown !>(cask)] + :: + ++ de-cage + |=(cage `(cask *)`[p q.q]) + :: + ++ en-rumor ::NOTE assumes !=(0 hops.manner) + |= =cage + ^- rumor + :_ (de-cage cage) + ~| [%en-rumor initial-hops=hops.manner] + [%0 `meta-0`(dec hops.manner)] + :: + ++ en-hash + |= rumor + (sham data) + :: + ++ play-card :: en-rumor relevant facts, handle config changes + |= =card + ^- (quip ^card _state) + ?. ?=([%give %fact *] card) [[card]~ state] + ?: =(~ paths.p.card) [[card]~ state] + =/ [int=(list path) ext=(list path)] + %+ skid paths.p.card + |= =path + ?=([%~.~ %gossip *] path) + =/ caz=(list ^card) + ?: =(~ ext) ~ + [card(paths.p ext)]~ + ?: ?=(~ int) [caz state] + =* path i.int + :: there may only be one gossip-internal path per card + :: + ?. =(~ t.int) + ~& [gossip+dap.bowl %too-many-internal-targets int] + ~|([%too-many-internal-targets int] !!) + ?: =(/~/gossip/config path) + ~| [%weird-fact-on-config p.cage.p.card] + ?> =(%gossip-config p.cage.p.card) + =/ old=config manner + =. manner !<(config q.cage.p.card) + :_ state + ;: weld + (hear-changed hear.old) + (tell-changed tell.old) + caz + == + ~| [%strange-internal-target path] + ?> =(/~/gossip/source path) + :: if hops is configured at 0, we don't broadcast at all. + :: + =/ =rumor (en-rumor cage.p.card) + =. memory (~(put in memory) (en-hash rumor)) + ?: =(0 hops.manner) + [caz state] + =^ cas state (emit-rumor rumor) + [(weld cas caz) state] + :: + ++ emit-rumor :: gossip a rumor as-is + |= =rumor + ^- (quip card _state) + =/ =hash (en-hash rumor) + =* fact + :- [%give %fact [/~/gossip/gossip]~ %gossip-rumor !>(rumor)]~ + %_ state + passed (~(del by passed) hash) + shared (~(put in shared) hash) + == + :: if we don't want to proxy, always send as fact + :: + ?. pass.manner + fact + :: if we want to proxy, do so 50% of the time + :: + ?. =(0 (~(rad og eny.bowl) 2)) + fact + :: if we're proxying, but there's no reasonable targets, send as fact + :: + =/ aides=(set ship) + :: reasonable targets do not include ourselves, or whoever + :: caused us to want to (re)send this rumor + :: + =- (~(del in (~(del in -) our.bowl)) src.bowl) + ?- tell.manner + %anybody (~(uni in (targets:pals ~.)) leeches:pals) + %targets (targets:pals ~.) + %mutuals (mutuals:pals ~.) + == + =/ count=@ud ~(wyt in aides) + ?: =(0 count) + fact + :: poke a randomly chosen proxy with the rumor + :: + =/ proxy=ship (snag (~(rad og +(eny.bowl)) count) ~(tap in aides)) + =/ =time (add now.bowl pass-timeout) + =. passed (~(put by passed) hash [rumor time]) + :_ state + =/ =wire /~/gossip/passed/(scot %uv hash) + =/ =cage gossip-rumor+!>(rumor) + :~ [%pass wire %agent [proxy dap.bowl] %poke cage] + [%pass wire %arvo %b %wait time] + == + :: + ++ play-cards + |= cards=(list card) + ^- (quip card _state) + =| out=(list card) + |- + ?~ cards [out state] + =^ caz state (play-card i.cards) + $(out (weld out caz), cards t.cards) + :: + ++ play-first-cards + |= cards=(list card) + ^- (quip card _state) + =| out=(list card) + |- + ?~ cards [out state] + ?. ?=([%give %fact ~ *] i.cards) + =^ caz state (play-card i.cards) + $(out (weld out caz), cards t.cards) + :: if hops is set to 0, we block even the initial response + :: + ?: =(0 hops.manner) $(cards t.cards) + =. cage.p.i.cards + [%gossip-rumor !>((en-rumor cage.p.i.cards))] + $(out (snoc out i.cards), cards t.cards) + :: + ++ jump-rumor :: relay a rumor if we haven't yet + |= =rumor + ^- (quip card _state) + =/ =hash (en-hash rumor) + ?: (~(has in shared) hash) [~ state] + ?> =(%0 kind.rumor) ::NOTE should have been checked for already + ?~ meta=((soft ,hops=@ud) meta.rumor) [~ state] + =* hops hops.u.meta + ?: =(0 hops) [~ state] + =. meta.rumor (dec hops) + :- [%give %fact [/~/gossip/gossip]~ %gossip-rumor !>(rumor)]~ + state(shared (~(put in shared) (en-hash rumor))) + :: + ++ may-watch + |= who=ship + ?- tell.manner + %anybody & + %targets (~(has in (targets:pals ~.)) who) + %mutuals (~(has in (mutuals:pals ~.)) who) + == + :: + :: + ++ watch-pals + ^- (list card) + =/ =gill:gall [our.bowl %pals] + :~ [%pass /~/gossip/pals/targets %agent gill %watch /targets] + [%pass /~/gossip/pals/leeches %agent gill %watch /leeches] + == + :: + ++ watching-target + |= s=ship + %- ~(has by wex.bowl) + [/~/gossip/gossip/(scot %p s) s dap.bowl] + :: + ++ want-target + %~ has in + ?- hear.manner + %anybody (~(uni in leeches:pals) (targets:pals ~.)) + %targets (targets:pals ~.) + %mutuals (mutuals:pals ~.) + == + :: + ++ retry-timer + |= [t=@dr p=path] + ^- card + :+ %pass [%~.~ %gossip %retry p] + [%arvo %b %wait (add now.bowl t)] + :: + ++ watch-target + |= s=ship + ^- (list card) + ?: (watching-target s) ~ + :_ ~ + :+ %pass /~/gossip/gossip/(scot %p s) + [%agent [s dap.bowl] %watch /~/gossip/gossip] + :: + ++ leave-target + |= s=ship + ^- card + :+ %pass /~/gossip/gossip/(scot %p s) + [%agent [s dap.bowl] %leave ~] + :: + ++ kick-target + |= s=ship + ^- card + [%give %kick [/~/gossip/gossip]~ `s] + :: + ++ hear-changed + |= old=whos + ^- (list card) + =* new hear.manner + ?: =(old new) ~ + =/ listen=(set ship) + ?- new + %anybody (~(uni in leeches:pals) (targets:pals ~.)) + %targets (targets:pals ~.) + %mutuals (mutuals:pals ~.) + == + =/ hearing=(set ship) + %- ~(gas in *(set ship)) + %+ murn ~(tap by wex.bowl) + |= [[=wire =ship =term] [acked=? =path]] + ^- (unit ^ship) + ?. ?=([%~.~ %gossip %gossip @ ~] wire) ~ + `ship + %+ weld + (turn ~(tap in (~(dif in hearing) listen)) leave-target) + ^- (list card) + (zing (turn ~(tap in (~(dif in listen) hearing)) watch-target)) + :: + ++ tell-changed + |= old=whos + ^- (list card) + =* new tell.manner + ?: =(old new) ~ + ?- [old new] + $? [* %anybody] + [%mutuals *] + == + :: perms got broader, we can just no-op + :: + ~ + :: + [* ?(%targets %mutuals)] + :: perms got tighter, we need to kick stragglers + :: + =/ allowed=(set ship) + ?- new + %anybody !! + %targets (targets:pals ~.) + %mutuals (mutuals:pals ~.) + == + %+ murn ~(val by sup.bowl) + |= [s=ship p=path] + ^- (unit card) + =; kick=? + ?.(kick ~ `(kick-target s)) + ?& ?=([%~.~ %gossip %gossip ~] p) + !(~(has in allowed) s) + == + == + -- + :: + ++ agent + |= inner=agent:gall + =| state-1 + =* state - + %+ verb | + %- agent:dbug + ^- agent:gall + |_ =bowl:gall + +* this . + pals ~(. lp bowl) + def ~(. (default-agent this %|) bowl) + og ~(. inner bowl) + up ~(. helper bowl state) + ++ on-init + ^- (quip card _this) + =. manner init + =^ cards inner on-init:og + =^ cards state (play-cards:up cards) + [(weld watch-pals:up cards) this] + :: + ++ on-save !>([[%gossip state] on-save:og]) + ++ on-load + |= ole=vase + ^- (quip card _this) + ?. ?=([[%gossip *] *] q.ole) + =. manner init + =^ cards inner (on-load:og ole) + =^ cards state (play-cards:up cards) + [(weld watch-pals:up cards) this] + :: + |^ =+ !<([[%gossip old=state-any] ile=vase] ole) + =? old ?=(%0 -.old) (state-0-to-1 old) + ?> ?=(%1 -.old) + =. state old + =^ cards inner (on-load:og ile) + =^ cards state (play-cards:up cards) + ::TODO for later versions, add :future retry logic as needed + [cards this] + :: + +$ state-any $%(state-0 state-1) + :: + +$ state-0 [%0 manner=config-0 memory=(set hash) future=(list rumor)] + +$ config-0 [hops=_1 hear=whos tell=whos] + ++ state-0-to-1 + |= state-0 + ^- state-1 + [%1 (config-0-to-1 manner) memory memory ~ future] + ++ config-0-to-1 + |= config-0 + ^- config + [hops hear tell pass.init] + -- + :: + ++ on-watch + |= =path + ^- (quip card _this) + ?. ?=([%~.~ %gossip *] path) + =^ cards inner (on-watch:og path) + =^ cards state (play-cards:up cards) + [cards this] + :: /~/gossip/gossip + ?> =(/gossip t.t.path) + ?. (may-watch:up src.bowl) + ~|(%gossip-forbidden !!) + =^ cards inner (on-watch:og /~/gossip/source) + =^ cards state (play-first-cards:up cards) + [cards this] + :: + ++ on-poke + |= [=mark =vase] + ^- (quip card _this) + ::TODO gossip config pokes + ?. =(%gossip-rumor mark) + =^ cards inner (on-poke:og +<) + =^ cards state (play-cards:up cards) + [cards this] + ?. (want-target:up src.bowl) + ~|(%gossip-rejected !!) + =+ !<(=rumor vase) + ::TODO dedupe with +on-agent %fact + =/ =hash (en-hash:up rumor) + ?: (~(has in memory) hash) + [~ this] + ?. =(%0 kind.rumor) + ~& [gossip+dap.bowl %delaying-unknown-rumor-kind kind.rumor] + [~ this(future [rumor future])] + =. memory (~(put in memory) hash) + =/ mage=cage (en-cage:up data.rumor) + =^ cards inner (on-agent:og /~/gossip/gossip %fact mage) + =^ caz1 state (play-cards:up cards) + =^ caz2 state (emit-rumor:up rumor) + [(weld caz1 caz2) this] + :: + ++ on-agent + |= [=wire =sign:agent:gall] + ^- (quip card _this) + ?. ?=([%~.~ %gossip *] wire) + =^ cards inner (on-agent:og wire sign) + =^ cards state (play-cards:up cards) + [cards this] + :: + ?+ t.t.wire ~|([%gossip %unexpected-wire wire] !!) + [%gossip @ ~] + ~| t.t.wire + ?> =(src.bowl (slav %p i.t.t.t.wire)) + ?- -.sign + %fact + =* mark p.cage.sign + =* vase q.cage.sign + ?. =(%gossip-rumor mark) + ~& [gossip+dap.bowl %ignoring-unexpected-fact mark=mark] + [~ this] + ::TODO de-dupe with +on-poke + =+ !<(=rumor vase) + =/ =hash (en-hash:up rumor) + ?: (~(has in memory) hash) + =^ cards state (jump-rumor:up rumor) + [cards this] + ?. =(%0 kind.rumor) + ~& [gossip+dap.bowl %delaying-unknown-rumor-kind kind.rumor] + [~ this(future [rumor future])] + =. memory (~(put in memory) hash) + =/ mage=cage (en-cage:up data.rumor) + =^ cards inner (on-agent:og /~/gossip/gossip sign(cage mage)) + =^ caz1 state (play-cards:up cards) + =^ caz2 state (jump-rumor:up rumor) + [(weld caz1 caz2) this] + :: + %watch-ack + :_ this + ?~ p.sign ~ + :: 30 minutes might cost us some responsiveness when the other + :: party changes their local config, but in return we save both + :: ourselves and others from a lot of needless retries. + :: (notably, "do we still care" check also lives in %wake logic.) + :: + [(retry-timer:up ~m30 /watch/(scot %p src.bowl))]~ + :: + %kick + :_ this + :: to prevent pathological kicks from exploding, we always + :: wait a couple seconds before resubscribing. + :: perhaps this is overly careful, but we cannot tell the + :: difference between "clog" kicks and "missing mark" kicks, + :: so we cannot take more accurate/appropriate action here. + :: (notably, "do we still care" check also lives in %wake logic.) + :: + [(retry-timer:up ~s15 /watch/(scot %p src.bowl))]~ + :: + %poke-ack + ~& [gossip+dap.bowl %unexpected-poke-ack wire] + [~ this] + == + :: + [%passed @ ~] + ?. ?=(%poke-ack -.sign) + ~& [gossip+dap.bowl %unexpected-sign wire -.sign] + [~ this] + ~| t.t.wire + =/ =hash (slav %uv i.t.t.t.wire) + ?~ rum=(~(get by passed) hash) + [~ this] + ::NOTE emitting rest is cute, but doesn't actually work reliably, + :: due to userspace duct shenanigans. %wake logic will have to + :: be defensive... + =/ rest=card [%pass wire %arvo %b %rest +.u.rum] + ?~ p.sign [[rest]~ this(passed (~(del by passed) hash))] + =^ caz state (emit-rumor:up -.u.rum) + [[rest caz] this] + :: + [%pals @ ~] + ?- -.sign + %poke-ack ~&([gossip+dap.bowl %unexpected-poke-ack wire] [~ this]) + %kick [watch-pals:up this] + :: + %watch-ack + :_ this + ?~ p.sign ~ + %- (slog 'gossip: failed to subscribe on %pals!!' u.p.sign) + [(retry-timer:up ~m1 t.t.wire)]~ + :: + %fact + =* mark p.cage.sign + =* vase q.cage.sign + ?. =(%pals-effect mark) + ~& [gossip+dap.bowl %unexpected-fact-mark mark wire] + [~ this] + =+ !<(=effect:^pals vase) + :_ this + =* ship ship.effect + =* kick [(kick-target:up ship)]~ + =* view (watch-target:up ship) + =* flee [(leave-target:up ship)]~ + ?- -.effect + %meet + ?- hear.manner + %anybody view + %targets view + %mutuals ?:((mutual:pals ~. ship) view ~) + == + :: + %part + %+ weld + ?- tell.manner + %anybody ~ + %targets kick + %mutuals kick + == + ?- hear.manner + %anybody ?:((leeche:pals ship) ~ flee) + %targets flee + %mutuals flee + == + :: + %near + ?- hear.manner + %anybody view + %targets ~ + %mutuals ?:((mutual:pals ~. ship) view ~) + == + :: + %away + %+ weld + ?- tell.manner + %anybody ~ + %targets ~ + %mutuals kick + == + ?- hear.manner + %anybody ?:((target:pals ~. ship) ~ flee) + %targets ~ + %mutuals flee + == + == + == + == + :: + ++ on-peek + |= =path + ^- (unit (unit cage)) + ?: =(/x/whey path) + :+ ~ ~ + :- %mass + !> ^- (list mass) + :- %gossip^&+state + =/ dat (on-peek:og path) + ?: ?=(?(~ [~ ~]) dat) ~ + (fall ((soft (list mass)) q.q.u.u.dat) ~) + ?: =(/x/dbug/state path) + ``noun+(slop on-save:og !>(gossip=state)) + ?. ?=([@ %~.~ %gossip *] path) + (on-peek:og path) + ?. ?=(%x i.path) [~ ~] + ?+ t.t.t.path [~ ~] + [%config ~] ``noun+!>(manner) + == + :: + ++ on-leave + |= =path + ^- (quip card _this) + ?: ?=([%~.~ %gossip *] path) + [~ this] + =^ cards inner (on-leave:og path) + =^ cards state (play-cards:up cards) + [cards this] + :: + ++ on-arvo + |= [=wire sign=sign-arvo:agent:gall] + ^- (quip card _this) + ?. ?=([%~.~ %gossip *] wire) + =^ cards inner (on-arvo:og wire sign) + =^ cards state (play-cards:up cards) + [cards this] + ?+ t.t.wire ~|(wire !!) + [%passed @ ~] + =/ =hash (slav %uv i.t.t.t.wire) + ?~ rum=(~(get by passed) hash) [~ this] + ?: (gth +.u.rum now.bowl) [~ this] + =^ cards state (emit-rumor:up -.u.rum) + [cards this] + :: + [%retry *] + ?> ?=(%wake +<.sign) + ?+ t.t.t.wire ~|(wire !!) + [%pals *] + ::NOTE this might result in subscription wire re-use, + :: but if we hit this path we should be loud anyway. + [watch-pals:up this] + :: + [%watch @ ~] + :_ this + =/ target=ship (slav %p i.t.t.t.t.wire) + ?. (want-target:up target) ~ + (watch-target:up target) + == + == + :: + ++ on-fail + |= [term tang] + ^- (quip card _this) + =^ cards inner (on-fail:og +<) + =^ cards state (play-cards:up cards) + [cards this] + -- + -- +-- diff --git a/desk/lib/pals.hoon b/desk/lib/pals.hoon new file mode 100644 index 000000000..180fbf058 --- /dev/null +++ b/desk/lib/pals.hoon @@ -0,0 +1,21 @@ +:: pals: manual peer discovery +:: +|_ bowl:gall +++ leeches (s (set ship) /leeches) +++ targets |= list=@ta (s (set ship) %targets ?~(list / /[list])) +++ mutuals |= list=@ta (s (set ship) %mutuals ?~(list / /[list])) +++ leeche |= =ship (s _| /leeches/(scot %p ship)) +++ target |= [list=@ta =ship] (s _| /mutuals/[list]/(scot %p ship)) +++ mutual |= [list=@ta =ship] (s _| /mutuals/[list]/(scot %p ship)) +:: +++ labels ?. running `(set @ta)`~ + ~(key by dir:.^(arch %gy (snoc base %targets))) +:: +++ base ~+ `path`/(scot %p our)/pals/(scot %da now) +++ running ~+ .^(? %gu (snoc base %$)) +:: +++ s + |* [=mold =path] ~+ + ?. running *mold + .^(mold %gx (weld base (snoc `^path`path %noun))) +-- diff --git a/desk/lib/verb.hoon b/desk/lib/verb.hoon new file mode 100644 index 000000000..2737addfc --- /dev/null +++ b/desk/lib/verb.hoon @@ -0,0 +1,105 @@ +:: Print what your agent is doing. +:: +/- verb +:: +|= [loud=? =agent:gall] +=| bowl-print=_| +^- agent:gall +|^ !. +|_ =bowl:gall ++* this . + ag ~(. agent bowl) +:: +++ on-init + ^- (quip card:agent:gall agent:gall) + %- (print bowl |.("{}: on-init")) + =^ cards agent on-init:ag + [[(emit-event %on-init ~) cards] this] +:: +++ on-save + ^- vase + %- (print bowl |.("{}: on-save")) + on-save:ag +:: +++ on-load + |= old-state=vase + ^- (quip card:agent:gall agent:gall) + %- (print bowl |.("{}: on-load")) + =^ cards agent (on-load:ag old-state) + [[(emit-event %on-load ~) cards] this] +:: +++ on-poke + |= [=mark =vase] + ^- (quip card:agent:gall agent:gall) + %- (print bowl |.("{}: on-poke with mark {}")) + ?: ?=(%verb mark) + ?- !<(?(%loud %bowl) vase) + %loud `this(loud !loud) + %bowl `this(bowl-print !bowl-print) + == + =^ cards agent (on-poke:ag mark vase) + [[(emit-event %on-poke mark) cards] this] +:: +++ on-watch + |= =path + ^- (quip card:agent:gall agent:gall) + %- (print bowl |.("{}: on-watch on path {}")) + =^ cards agent + ?: ?=([%verb %events ~] path) + [~ agent] + (on-watch:ag path) + [[(emit-event %on-watch path) cards] this] +:: +++ on-leave + |= =path + ^- (quip card:agent:gall agent:gall) + %- (print bowl |.("{}: on-leave on path {}")) + ?: ?=([%verb %event ~] path) + [~ this] + =^ cards agent (on-leave:ag path) + [[(emit-event %on-leave path) cards] this] +:: +++ on-peek + |= =path + ^- (unit (unit cage)) + %- (print bowl |.("{}: on-peek on path {}")) + (on-peek:ag path) +:: +++ on-agent + |= [=wire =sign:agent:gall] + ^- (quip card:agent:gall agent:gall) + %- (print bowl |.("{}: on-agent on wire {}, {<-.sign>}")) + =^ cards agent (on-agent:ag wire sign) + [[(emit-event %on-agent wire -.sign) cards] this] +:: +++ on-arvo + |= [=wire =sign-arvo] + ^- (quip card:agent:gall agent:gall) + %- %+ print bowl |. + "{}: on-arvo on wire {}, {<[- +<]:sign-arvo>}" + =^ cards agent (on-arvo:ag wire sign-arvo) + [[(emit-event %on-arvo wire [- +<]:sign-arvo) cards] this] +:: +++ on-fail + |= [=term =tang] + ^- (quip card:agent:gall agent:gall) + %- (print bowl |.("{}: on-fail with term {}")) + =^ cards agent (on-fail:ag term tang) + [[(emit-event %on-fail term) cards] this] +-- +:: +++ print + |= [=bowl:gall render=(trap tape)] + ^+ same + =? . bowl-print + %- (slog >bowl< ~) + . + ?. loud same + %- (slog [%leaf $:render] ~) + same +:: +++ emit-event + |= =event:verb + ^- card:agent:gall + [%give %fact ~[/verb/events] %verb-event !>(event)] +-- diff --git a/desk/mar/near/action.hoon b/desk/mar/near/action.hoon new file mode 100644 index 000000000..4eeab70fc --- /dev/null +++ b/desk/mar/near/action.hoon @@ -0,0 +1,14 @@ +/- *near-handler +/+ *near-handler +|_ =gateway-action +++ grab + |% + ++ noun gateway-action + ::++ json act:dejs + -- +++ grow + |% + ++ noun gateway-action + -- +++ grad %noun +-- \ No newline at end of file diff --git a/desk/mar/near/metadata.hoon b/desk/mar/near/metadata.hoon new file mode 100644 index 000000000..483dd978f --- /dev/null +++ b/desk/mar/near/metadata.hoon @@ -0,0 +1,12 @@ +/- *near-handler +|_ gateway=[identifier metadata] +++ grad %noun +++ grow + |% + ++ noun gateway + -- +++ grab + |% + ++ noun [identifier metadata] + -- +-- diff --git a/desk/sur/near-handler.hoon b/desk/sur/near-handler.hoon index 7906be6cb..455ab2729 100644 --- a/desk/sur/near-handler.hoon +++ b/desk/sur/near-handler.hoon @@ -1,5 +1,7 @@ |% +$ acc @uxH ++$ metadata [name=@t url=@t] ++$ identifier [=ship id=@ud] +$ action $% [%add =acc] [%del =acc] @@ -8,4 +10,7 @@ +$ update $% [%accs accs=(set acc)] == ++$ gateway-action + $% [%publish =metadata] + == -- \ No newline at end of file diff --git a/desk/sur/pals.hoon b/desk/sur/pals.hoon new file mode 100644 index 000000000..793552672 --- /dev/null +++ b/desk/sur/pals.hoon @@ -0,0 +1,41 @@ +:: pals: manual neighboring +:: +|% ++$ records :: local state + $: outgoing=(jug ship @ta) + incoming=(set ship) + :: + :: receipts: for all outgoing, status + :: + :: if ship not in receipts, poke awaiting ack + :: if ship present as true, poke acked positively + :: if ship present as false, poke acked negatively + :: + receipts=(map ship ?) + == +:: ++$ gesture :: to/from others + $% [%hey ~] + [%bye ~] + == +:: ++$ command :: from ourselves + $% [%meet =ship in=(set @ta)] :: empty set allowed + [%part =ship in=(set @ta)] :: empty set implies un-targeting + == +:: ++$ effect :: to ourselves + $% target-effect + leeche-effect + == +:: ++$ target-effect + $% [%meet =ship] :: hey to target + [%part =ship] :: bye to target + == +:: ++$ leeche-effect + $% [%near =ship] :: hey from leeche + [%away =ship] :: bye from leeche + == +-- diff --git a/desk/sur/verb.hoon b/desk/sur/verb.hoon new file mode 100644 index 000000000..13c70386c --- /dev/null +++ b/desk/sur/verb.hoon @@ -0,0 +1,12 @@ +|% ++$ event + $% [%on-init ~] + [%on-load ~] + [%on-poke =mark] + [%on-watch =path] + [%on-leave =path] + [%on-agent =wire sign=term] + [%on-arvo =wire vane=term sign=term] + [%on-fail =term] + == +-- From cd0548fa17768e27ce0a66f701b825f0204809e6 Mon Sep 17 00:00:00 2001 From: ~hanfel-dovned <95324536+hanfel-dovned@users.noreply.github.com> Date: Mon, 22 Jan 2024 14:50:10 -0700 Subject: [PATCH 2/9] Update build-check.yml `cd` into the `near` directory before running this test --- .github/workflows/build-check.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.github/workflows/build-check.yml b/.github/workflows/build-check.yml index cf51a9819..33265c287 100644 --- a/.github/workflows/build-check.yml +++ b/.github/workflows/build-check.yml @@ -17,6 +17,7 @@ jobs: - name: Copy dist/index.js run: | + cd near mkdir target cp dist/index.js target/index.js From dbe8e3a69f4f8cf9d6772cb2d9eb7ecae9bc6aac Mon Sep 17 00:00:00 2001 From: ~hanfel-dovned <95324536+hanfel-dovned@users.noreply.github.com> Date: Mon, 22 Jan 2024 14:54:33 -0700 Subject: [PATCH 3/9] Update build-check.yml --- .github/workflows/build-check.yml | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/.github/workflows/build-check.yml b/.github/workflows/build-check.yml index 33265c287..22d71d004 100644 --- a/.github/workflows/build-check.yml +++ b/.github/workflows/build-check.yml @@ -15,20 +15,22 @@ jobs: with: node-version: "16.x" - - name: Copy dist/index.js + - name: Create target directory and copy file run: | - cd near - mkdir target - cp dist/index.js target/index.js + mkdir -p near/target + cp near/dist/index.js near/target/index.js - name: Install dependencies run: yarn + working-directory: ./near - name: Build run: yarn build + working-directory: ./near - name: Check dist/index.js run: cmp dist/index.js target/index.js + working-directory: ./near - name: Failure message if: failure() @@ -36,3 +38,4 @@ jobs: with: script: | core.setFailed('The dist/index.js seems to be stale. Please run *yarn build* and commit the dist/index.js file.') + working-directory: ./near From bc20f986b9b2ffe661a92ab6e07efaf29e7a1960 Mon Sep 17 00:00:00 2001 From: ~hanfel-dovned <95324536+hanfel-dovned@users.noreply.github.com> Date: Mon, 22 Jan 2024 14:58:06 -0700 Subject: [PATCH 4/9] Update README.md --- README.md | 2 -- 1 file changed, 2 deletions(-) diff --git a/README.md b/README.md index 09c0162f1..6c57b6882 100644 --- a/README.md +++ b/README.md @@ -3,5 +3,3 @@ The NEAR BOS has a thriving ecosystem of developers and an innovative method for composing frontends via components stored on the NEAR blockchain. Urbit can enhance the BOS by acting as a private server that new components can interact with, unlocking decentralized interfaces populated by personal data. To enable these new components, Urbit Labs is forking the NEAR Social VM and adding a new Urbit object with methods that wrap the @urbit/http-api library. - -Right now, Urbit-served frontends can poke and scry any agent on that urbit, rather than being restricted to only agents within the same deskā€”but this will change with userspace permissions later this year. In order to allow BOS developers to write apps that interact with the entirety of the user's urbit, we're developing the %near-handler agent, which will act as a relay for pokes and scries. From e0003658fd1fea75fd51b3e57ec04d083b86981b Mon Sep 17 00:00:00 2001 From: SuperCoolYun Date: Wed, 24 Jan 2024 12:46:53 -0500 Subject: [PATCH 5/9] mar file added, bug fixed --- desk/app/near-gateways.hoon | 5 ++++- desk/mar/gossip/rumor.hoon | 11 +++++++++++ desk/mar/near/metadata.hoon | 2 +- 3 files changed, 16 insertions(+), 2 deletions(-) create mode 100644 desk/mar/gossip/rumor.hoon diff --git a/desk/app/near-gateways.hoon b/desk/app/near-gateways.hoon index aca0d7e7c..63540a6b0 100644 --- a/desk/app/near-gateways.hoon +++ b/desk/app/near-gateways.hoon @@ -117,18 +117,21 @@ ^+ that ?+ path ~|(bad-watch-path+path !!) [%~.~ %gossip %source ~] that - == + == ++ agent |= [=wire =sign:agent:gall] ^+ that ?+ wire ~|(bad-agent-wire+wire !!) [%~.~ %gossip %gossip ~] + ~& >> [wire sign] ?+ -.sign ~|([%unexpected-gossip-sign -.sign] !!) %fact =* mark p.cage.sign =* vase q.cage.sign ?. =(%metadata mark) that ::add new gateway to heard + ~& >> 'got fact' + ~& >> !<([id=identifier =metadata] vase) =+ !<([id=identifier =metadata] vase) =. heard (~(put by heard) id metadata) that diff --git a/desk/mar/gossip/rumor.hoon b/desk/mar/gossip/rumor.hoon new file mode 100644 index 000000000..8f1cb3fed --- /dev/null +++ b/desk/mar/gossip/rumor.hoon @@ -0,0 +1,11 @@ +|_ rum=[[@ *] (cask *)] +++ grad %noun +++ grow + |% + ++ noun rum + -- +++ grab + |% + ++ noun ,[[@ *] (cask *)] + -- +-- diff --git a/desk/mar/near/metadata.hoon b/desk/mar/near/metadata.hoon index 483dd978f..b74c59952 100644 --- a/desk/mar/near/metadata.hoon +++ b/desk/mar/near/metadata.hoon @@ -7,6 +7,6 @@ -- ++ grab |% - ++ noun [identifier metadata] + ++ noun ,[identifier metadata] -- -- From 4239deaaef0f0783ce22b1ef1f8edee799e81eb9 Mon Sep 17 00:00:00 2001 From: SuperCoolYun Date: Tue, 30 Jan 2024 09:49:30 -0500 Subject: [PATCH 6/9] working on logic for gateway-glob hosting --- desk/app/near-gateways.hoon | 117 +++++++++-- desk/lib/schooner.hoon | 376 ++++++++++++++++++++++++++++++++++++ desk/lib/server.hoon | 159 +++++++++++++++ desk/sur/docket.hoon | 82 ++++++++ desk/sur/near-handler.hoon | 1 + 5 files changed, 717 insertions(+), 18 deletions(-) create mode 100644 desk/lib/schooner.hoon create mode 100644 desk/lib/server.hoon create mode 100644 desk/sur/docket.hoon diff --git a/desk/app/near-gateways.hoon b/desk/app/near-gateways.hoon index 63540a6b0..83a863e1b 100644 --- a/desk/app/near-gateways.hoon +++ b/desk/app/near-gateways.hoon @@ -1,5 +1,5 @@ -/- *near-handler -/+ dbug, default-agent, *near-handler, gossip +/- *near-handler, docket +/+ dbug, default-agent, *near-handler, gossip, server, schooner /$ grab-metadata %noun %near-metadata :: |% @@ -69,8 +69,13 @@ =^ cards state abet:(agent:hc wire sign) [cards this] :: + ++ on-arvo + |= [=wire =sign-arvo] + ^- (quip card _this) + =^ cards state abet:(arvo:hc wire sign-arvo) + [cards this] + :: ++ on-peek on-peek:def - ++ on-arvo on-arvo:def ++ on-fail on-fail:def ++ on-leave on-leave:def -- @@ -84,7 +89,8 @@ :: ++ init ^+ that - that + %- emit + [%pass /eyre/connect %arvo %e %connect [~ /apps/near] %near-gateways] :: ++ load |= vaz=vase @@ -96,45 +102,120 @@ |= [=mark =vase] ^+ that ?+ mark that - %near-action + %handle-http-request + =+ !<([id=@ta request=inbound-request:eyre] vase) + (handle-http-request id request) + %near-action ?> from-self =+ !<(act=gateway-action vase) ?- -.act - %publish - :: add metadata to published-state - :: send update to gossip - =/ id=identifier [our.bowl `@ud`eny.bowl] ::what entropy to use ? + %publish + =/ id=identifier [our.bowl `@ud`eny.bowl] ::entropy? =. published (~(put by published) id +.act) %- emit %+ invent:gossip %metadata - !> ^- [identifier metadata] - [id +.act] + !> ^- [identifier metadata] + [id +.act] + :: + %install + :: get and host glob on handle/get at some path/name/ + :: where would gateways glob file system will be stored, if in docket.hoon state need to scry(doesn't work, return glob.chad as ~) + :: host each path alike payload-from-glob + =. installed (~(put by installed) +.act) + that + :: == == +++ dump [404 ~ [%plain "404 - Not Found"]] +++ handle-http-request + |= [id=@ta inbound-request:eyre] + ^+ that + =/ request-line (parse-request-line:server url.request) + :: %- emil + =+ send=(cury response:schooner id) + ?. authenticated + %- emil + %- send + [302 ~ [%login-redirect './apps/near']] + ?+ method.request + %- emil + %- send [405 ~ [%stock ~]] + :: + %'GET' + ?+ [site ext]:request-line + %- emil + %- send dump + :: + [[%apps %near ~] *] + %- emil + %- send [200 ~ [%plain "welcome to %near-gateway"]] ::for now + :: + [[%apps %near @ *] *] + %- emil + %- send + %+ from-glob + (snag 2 site.request-line) + request-line(site (slag 2 `(list @ta)`site.request-line)) + == + :: + %'POST' + %- emil + %- send dump + == +:: +++ from-glob + |= [from=@ta request=request-line:server] + :: how to get glob files out of docket to host ? + :: returns charges.state without glob + =/ charge-update .^(charge-update:docket %gx /(scot %p our.bowl)/docket/(scot %da now.bowl)/charges/noun) + ~& >> ['suffix' (weld site.request (drop ext.request))] + ?+ -.charge-update [404 ~ [%stock ~]] + %initial + ~& (~(get by initial.charge-update) from) + [200 ~ [%plain "welcome to %near-gateway"]] + == +:: ++ watch |= =path ^+ that - ?+ path ~|(bad-watch-path+path !!) - [%~.~ %gossip %source ~] that - == + ?+ path ~|(bad-watch-path+path !!) + [%http-response *] + that + :: + [%~.~ %gossip %source ~] + %- emil + %+ turn + ~(tap by published) + |= [=identifier =metadata] + ^- card + [%give %fact ~ %metadata !>([identifier metadata])] + == +:: ++ agent |= [=wire =sign:agent:gall] ^+ that ?+ wire ~|(bad-agent-wire+wire !!) [%~.~ %gossip %gossip ~] - ~& >> [wire sign] ?+ -.sign ~|([%unexpected-gossip-sign -.sign] !!) %fact =* mark p.cage.sign =* vase q.cage.sign ?. =(%metadata mark) that - ::add new gateway to heard - ~& >> 'got fact' - ~& >> !<([id=identifier =metadata] vase) =+ !<([id=identifier =metadata] vase) =. heard (~(put by heard) id metadata) that == == +:: +++ arvo + |= [=wire =sign-arvo] + ^+ that + ?+ wire that + [%eyre ~] + ?. ?=([%eyre %bound *] sign-arvo) that + ?: accepted.sign-arvo that + ~& ['Failde to bind' path.binding.sign-arvo] + that + == -- \ No newline at end of file diff --git a/desk/lib/schooner.hoon b/desk/lib/schooner.hoon new file mode 100644 index 000000000..4975fe29b --- /dev/null +++ b/desk/lib/schooner.hoon @@ -0,0 +1,376 @@ + :: /lib/schooner.hoon +:::: Dalten Collective, with modifications by ~hanfel-dovned & ~lagrev-nocfep +:: Version ~2023.8.7 +:: +:: Schooner is a Hoon library intended to de-clutter raw HTTP handling +:: in Gall agents. +:: +:: It expects to receive a [=eyre-id =http-status =headers =resource] +:: which are conveniently defined below. +:: +/+ server +:: +|% +:: ++$ eyre-id @ta ++$ header [key=@t value=@t] ++$ headers (list header) +:: ++$ resource + $% + [%application-javascript p=@] :: js + [%application-json p=@] :: json + [%application-pdf p=@] :: pdf + [%application-rtf p=@] :: rtf + [%application-xml p=@] :: xml + [%audio-aac p=@] :: aac + [%audio-flac p=@] :: flac + [%audio-mid p=@] :: mid, midi + [%audio-mpeg p=@] :: mp3 + [%audio-ogg p=@] :: oga + [%audio-wav p=@] :: wav + [%audio-webm p=@] :: weba + [%font-otf p=@] :: otf + [%font-ttf p=@] :: ttf + [%font-woff2 p=@] :: woff2 + [%html h=cord] :: htm, html + [%image-bmp p=@] :: bmp + [%image-gif p=@] :: gif + [%image-ico p=@] :: ico + [%image-jpeg p=@] :: jpg, jpeg + [%image-png p=@] :: png + [%image-svg p=@] :: svg + [%image-tiff p=@] :: tiff + [%image-webp p=@] :: webp + [%json j=json] :: json (type not mark) + [%manx m=manx] :: manx (type not mark) + [%plain p=tape] :: txt + [%text-css p=@] :: css + [%text-csv p=@] :: csv + [%text-javascript p=@] :: js + [%text-plain p=@] :: txt + [%text-xml p=@] :: xml + [%video-avi p=@] :: avi + [%video-mp4 p=@] :: mp4 + [%video-mpeg p=@] :: mpeg + [%video-ogg p=@] :: ogv + [%video-webm p=@] :: webm + :: + [%login-redirect l=cord] :: + [%none ~] + [%redirect o=cord] + [%stock ~] + == +:: ++$ http-status @ud +:: +++ response + |= [=eyre-id =http-status =headers =resource] + ^- (list card:agent:gall) + %+ give-simple-payload:app:server + eyre-id + ^- simple-payload:http + ?- -.resource + :: + %application-javascript + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'application/javascript']~) + :: + %application-json + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'application/json']~) + :: + %application-pdf + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'application/pdf']~) + :: + %application-rtf + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'application/rtf']~) + :: + %application-xml + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'application/xml']~) + :: + %audio-aac + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'audio/aac']~) + :: + %audio-flac + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'audio/flac']~) + :: + %audio-mid + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'audio/midi']~) + :: + %audio-mpeg + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'audio/mpeg']~) + :: + %audio-ogg + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'audio/ogg']~) + :: + %audio-wav + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'audio/wav']~) + :: + %audio-webm + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'audio/webm']~) + :: + %font-otf + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'font/otf']~) + :: + %font-ttf + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'font/ttf']~) + :: + %font-woff2 + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'fonts/woff2']~) + :: + %html + :- :- http-status + (weld headers ['content-type'^'text/html']~) + `(as-octs:mimes:html h.resource) + :: + %image-bmp + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'image/bmp']~) + :: + %image-gif + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'image/gif']~) + :: + %image-ico + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'image/vnd.microsoft.icon']~) + :: + %image-jpeg + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'image/jpeg']~) + :: + %image-png + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'image/png']~) + :: + %image-svg + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'image/svg+xml']~) + :: + %image-tiff + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'image/tiff']~) + :: + %image-webp + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'image/webp']~) + :: + %json + :- :- http-status + %+ weld headers + ['content-type'^'application/json']~ + `(as-octs:mimes:html (en:json:html j.resource)) + :: + %manx + :- :- http-status + (weld headers ['content-type'^'text/html']~) + `(as-octt:mimes:html (en-xml:html m.resource)) + :: + %plain + :_ `(as-octt:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'text/plain']~) + :: + %text-css + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'text/css']~) + :: + %text-csv + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'text/csv']~) + :: + %text-javascript + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'text/javascript']~) + :: + %text-plain + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'text/plain']~) + :: + %text-xml :: overrides text/ + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'application/xml']~) + :: + %video-avi + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'video/x-msvideo']~) + :: + %video-mp4 + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'video/mp4']~) + :: + %video-mpeg + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'video/mpeg']~) + :: + %video-ogg + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'video/ogg']~) + :: + %video-webm + :_ `(as-octs:mimes:html p.resource) + :- http-status + (weld headers ['content-type'^'video/webm']~) + :: + :: + %login-redirect + =+ %^ cat 3 + '/~/login?redirect=' + l.resource + :_ ~ + :- http-status + (weld headers [['location' -]]~) + :: + %none + [[http-status headers] ~] + :: + %redirect + :_ ~ + :- http-status + (weld headers ['location'^o.resource]~) + :: + %stock + (stock-error headers http-status) + :: + == +:: +:: response when MIME type is not pre-configured as in +response (just octs) +:: +++ general-response + |= [=eyre-id =http-status =headers resource=[term @]] + ^- (list card:agent:gall) + %+ give-simple-payload:app:server + eyre-id + ^- simple-payload:http + :_ `(as-octs:mimes:html +.resource) + :- http-status + =/ a (trip -.resource) + =/ b (need (find "-" a)) + =/ c (crip (snap a b '/')) + (weld headers ['content-type'^c]~) +:: +++ stock-error + |= [=headers code=@ud] + ^- simple-payload:http + :- :- code + (weld headers ['content-type'^'text/html']~) + :- ~ + =+ (title-content code) + %- as-octt:mimes:html + %- en-xml:html + ;html + ;head + ;title:"{-.-}" + ;meta(name "viewport", content "width=device-width, initial-scale=1", charset "utf-8"); + ;style:"{(trip style)}" + == + ;body + ;span(class "blur-banner") + ;h2:"{-.-}" + ;p:"{+.-}" + == + == + == +:: +++ title-content + |= status=@ud + ~& status + ?+ status + :- "500 Error - Internal Server Error" + ;: weld "This urbit is experiencing presence. " + "You might try back later, or ask again. " + "Sorry for the inconvenience." + == + :: + %403 + :- "403 Error - FORBIDDEN!" + ;: weld "Another one of them new worlds. " + "No beer, no women, no pool partners, nothin'. " + "Nothin' to do but throw rocks at tin cans, and we have to bring our own tin cans." + == + :: + %404 + :- "404 Error - Page Not Found" + %+ weld "You've attempted to access absence. " + "Impossible. Try a different path. Sorry for the inconvenience." + :: + %405 + :- "405 Error - Method Not Allowed" + %+ weld "Something went wrong with your request. " + "You should probably just go back. Sorry for the inconvenience." + :: + == +:: +++ style + ''' + .blur-banner { + position: relative; + top: 60%; + left: 0%; + right: 0%; + bottom: 0%; + height: auto; + width: 80%; + padding: 15px 15px 15px 15px; + margin: 0px auto 0px auto; + display: block; + background: rgba(255, 255, 255, 1.0); + font-size: 14pt; + color: #997300; + font-family: Menlo, Consolas, Monaco, "Lucida Console", monospace; + border: 6px #997300 dashed; + border-radius: 20px; + filter: blur(2px) sepia(25%) brightness(100%) saturate(173%); + -webkit-filter: blur(1.5px) sepia(25%) brightness(100%) saturate(175%); + -moz-filter: blur(1.5px) sepia(25%) brightness(100%) saturate(175%); + -ms-filter: blur(1.5px) sepia(25%) brightness(100%) saturate(175%); + -o-filter: blur(1.5px) sepia(25%) brightness(100%) saturate(175%); + } + ''' +-- diff --git a/desk/lib/server.hoon b/desk/lib/server.hoon new file mode 100644 index 000000000..f5cf8f0c5 --- /dev/null +++ b/desk/lib/server.hoon @@ -0,0 +1,159 @@ +=, eyre +|% ++$ request-line + $: [ext=(unit @ta) site=(list @t)] + args=(list [key=@t value=@t]) + == +:: +parse-request-line: take a cord and parse out a url +:: +++ parse-request-line + |= url=@t + ^- request-line + (fall (rush url ;~(plug apat:de-purl:html yque:de-purl:html)) [[~ ~] ~]) +:: +++ manx-to-octs + |= man=manx + ^- octs + (as-octt:mimes:html (en-xml:html man)) +:: +++ json-to-octs + |= jon=json + ^- octs + (as-octs:mimes:html (en:json:html jon)) +:: +++ app + |% + :: + :: +require-authorization: + :: redirect to the login page when unauthenticated + :: otherwise call handler on inbound request + :: + ++ require-authorization + |= $: =inbound-request:eyre + handler=$-(inbound-request:eyre simple-payload:http) + == + ^- simple-payload:http + :: + ?: authenticated.inbound-request + ~! this + ~! +:*handler + (handler inbound-request) + :: + =- [[307 ['location' -]~] ~] + %^ cat 3 + '/~/login?redirect=' + url.request.inbound-request + :: + :: +require-authorization-simple: + :: redirect to the login page when unauthenticated + :: otherwise pass through simple-paylod + :: + ++ require-authorization-simple + |= [=inbound-request:eyre =simple-payload:http] + ^- simple-payload:http + :: + ?: authenticated.inbound-request + ~! this + simple-payload + :: + =- [[307 ['location' -]~] ~] + %^ cat 3 + '/~/login?redirect=' + url.request.inbound-request + :: + ++ give-simple-payload + |= [eyre-id=@ta =simple-payload:http] + ^- (list card:agent:gall) + =/ header-cage + [%http-response-header !>(response-header.simple-payload)] + =/ data-cage + [%http-response-data !>(data.simple-payload)] + :~ [%give %fact ~[/http-response/[eyre-id]] header-cage] + [%give %fact ~[/http-response/[eyre-id]] data-cage] + [%give %kick ~[/http-response/[eyre-id]] ~] + == + -- +++ gen + |% + :: + ++ max-1-da ['cache-control' 'max-age=86400'] + ++ max-1-wk ['cache-control' 'max-age=604800'] + :: + ++ html-response + =| cache=? + |= =octs + ^- simple-payload:http + :_ `octs + [200 [['content-type' 'text/html'] ?:(cache [max-1-wk ~] ~)]] + :: + ++ css-response + =| cache=? + |= =octs + ^- simple-payload:http + :_ `octs + [200 [['content-type' 'text/css'] ?:(cache [max-1-wk ~] ~)]] + :: + ++ js-response + =| cache=? + |= =octs + ^- simple-payload:http + :_ `octs + [200 [['content-type' 'text/javascript'] ?:(cache [max-1-wk ~] ~)]] + :: + ++ png-response + =| cache=? + |= =octs + ^- simple-payload:http + :_ `octs + [200 [['content-type' 'image/png'] ?:(cache [max-1-wk ~] ~)]] + :: + ++ svg-response + =| cache=? + |= =octs + ^- simple-payload:http + :_ `octs + [200 [['content-type' 'image/svg+xml'] ?:(cache [max-1-wk ~] ~)]] + :: + ++ ico-response + |= =octs + ^- simple-payload:http + [[200 [['content-type' 'image/x-icon'] max-1-wk ~]] `octs] + :: + ++ woff2-response + =| cache=? + |= =octs + ^- simple-payload:http + [[200 [['content-type' 'font/woff2'] max-1-wk ~]] `octs] + :: + ++ json-response + =| cache=_| + |= =json + ^- simple-payload:http + :_ `(json-to-octs json) + [200 [['content-type' 'application/json'] ?:(cache [max-1-da ~] ~)]] + :: + ++ manx-response + =| cache=_| + |= man=manx + ^- simple-payload:http + :_ `(manx-to-octs man) + [200 [['content-type' 'text/html'] ?:(cache [max-1-da ~] ~)]] + :: + ++ not-found + ^- simple-payload:http + [[404 ~] ~] + :: + ++ login-redirect + |= =request:http + ^- simple-payload:http + =- [[307 ['location' -]~] ~] + %^ cat 3 + '/~/login?redirect=' + url.request + :: + ++ redirect + |= redirect=cord + ^- simple-payload:http + [[307 ['location' redirect]~] ~] + -- +-- diff --git a/desk/sur/docket.hoon b/desk/sur/docket.hoon new file mode 100644 index 000000000..091c8c9f9 --- /dev/null +++ b/desk/sur/docket.hoon @@ -0,0 +1,82 @@ +|% +:: ++$ version + [major=@ud minor=@ud patch=@ud] +:: ++$ glob (map path mime) +:: ++$ url cord +:: $glob-location: How to retrieve a glob +:: ++$ glob-reference + [hash=@uvH location=glob-location] +:: ++$ glob-location + $% [%http =url] + [%ames =ship] + == +:: $href: Where a tile links to +:: ++$ href + $% [%glob base=term =glob-reference] + [%site =path] + == +:: $chad: State of a docket +:: ++$ chad + $~ [%install ~] + $% :: Done + [%glob =glob] + [%site ~] + :: Waiting + [%install ~] + [%suspend glob=(unit glob)] + :: Error + [%hung err=cord] + == +:: +:: $charge: A realized $docket +:: ++$ charge + $: =docket + =chad + == +:: +:: $clause: A key and value, as part of a docket +:: +:: Only used to parse $docket +:: ++$ clause + $% [%title title=@t] + [%info info=@t] + [%color color=@ux] + [%glob-http url=cord hash=@uvH] + [%glob-ames =ship hash=@uvH] + [%image =url] + [%site =path] + [%base base=term] + [%version =version] + [%website website=url] + [%license license=cord] + == +:: +:: $docket: A description of JS bundles for a desk +:: ++$ docket + $: %1 + title=@t + info=@t + color=@ux + =href + image=(unit url) + =version + website=url + license=cord + == +:: ++$ charge-update + $% [%initial initial=(map desk charge)] + [%add-charge =desk =charge] + [%del-charge =desk] + == +-- diff --git a/desk/sur/near-handler.hoon b/desk/sur/near-handler.hoon index 455ab2729..e66684600 100644 --- a/desk/sur/near-handler.hoon +++ b/desk/sur/near-handler.hoon @@ -12,5 +12,6 @@ == +$ gateway-action $% [%publish =metadata] + [%install =identifier =metadata] == -- \ No newline at end of file From bc6faefee7324604bddc3c0d8e7a59d1fccc59ac Mon Sep 17 00:00:00 2001 From: SuperCoolYun Date: Wed, 31 Jan 2024 12:08:03 -0500 Subject: [PATCH 7/9] logic for glob gateways on %publish --- desk/app/near-gateways.hoon | 84 +++- desk/gen/poke.hoon | 4 +- desk/lib/strand.hoon | 1 + desk/lib/strandio.hoon | 812 ++++++++++++++++++++++++++++++++++++ desk/sur/near-handler.hoon | 2 +- desk/sur/spider.hoon | 27 ++ desk/ted/gateway-glob.hoon | 27 ++ 7 files changed, 934 insertions(+), 23 deletions(-) create mode 100644 desk/lib/strand.hoon create mode 100644 desk/lib/strandio.hoon create mode 100644 desk/sur/spider.hoon create mode 100644 desk/ted/gateway-glob.hoon diff --git a/desk/app/near-gateways.hoon b/desk/app/near-gateways.hoon index 83a863e1b..12a6429c0 100644 --- a/desk/app/near-gateways.hoon +++ b/desk/app/near-gateways.hoon @@ -109,19 +109,14 @@ ?> from-self =+ !<(act=gateway-action vase) ?- -.act - %publish - =/ id=identifier [our.bowl `@ud`eny.bowl] ::entropy? - =. published (~(put by published) id +.act) - %- emit - %+ invent:gossip - %metadata - !> ^- [identifier metadata] - [id +.act] + %publish + %+ start-gateway-glob + %near-handler + path.act :: - %install - :: get and host glob on handle/get at some path/name/ - :: where would gateways glob file system will be stored, if in docket.hoon state need to scry(doesn't work, return glob.chad as ~) - :: host each path alike payload-from-glob + %install + :: get and host glob on handle/get at some path/name/ + :: host each path alike payload-from-glob =. installed (~(put by installed) +.act) that :: @@ -141,7 +136,6 @@ ?+ method.request %- emil %- send [405 ~ [%stock ~]] - :: %'GET' ?+ [site ext]:request-line %- emil @@ -156,6 +150,7 @@ %- send %+ from-glob (snag 2 site.request-line) + ::[ext.request-line site.request-line args.request-line] request-line(site (slag 2 `(list @ta)`site.request-line)) == :: @@ -166,8 +161,8 @@ :: ++ from-glob |= [from=@ta request=request-line:server] - :: how to get glob files out of docket to host ? - :: returns charges.state without glob + :: get glob files out to host + ~& >> [from request] =/ charge-update .^(charge-update:docket %gx /(scot %p our.bowl)/docket/(scot %da now.bowl)/charges/noun) ~& >> ['suffix' (weld site.request (drop ext.request))] ?+ -.charge-update [404 ~ [%stock ~]] @@ -176,6 +171,20 @@ [200 ~ [%plain "welcome to %near-gateway"]] == :: +++ start-gateway-glob +|= [=desk =path] +^+ that +=/ tid `@ta`(cat 3 'near-' (scot %uv (sham eny.bowl))) +=/ ta-now `@ta`(scot %da now.bowl) +=/ arg-vase !>(`[desk path]) +=/ =cage :- %spider-start + !>([~ `tid byk.bowl(r da+now.bowl) %gateway-glob arg-vase]) +=. path (weld /thread/glob/[ta-now] path) +%- emil + :~ [%pass path %agent [our.bowl %spider] %poke cage] + [%pass path %agent [our.bowl %spider] %watch /thread-result/[tid]] + == +:: ++ watch |= =path ^+ that @@ -191,21 +200,56 @@ ^- card [%give %fact ~ %metadata !>([identifier metadata])] == -:: ++ agent |= [=wire =sign:agent:gall] ^+ that ?+ wire ~|(bad-agent-wire+wire !!) - [%~.~ %gossip %gossip ~] - ?+ -.sign ~|([%unexpected-gossip-sign -.sign] !!) - %fact + [%~.~ %gossip %gossip ~] + ?+ -.sign ~|([%unexpected-gossip-sign -.sign] !!) + %fact =* mark p.cage.sign =* vase q.cage.sign ?. =(%metadata mark) that + ::add new gateway to heard + ~& >> 'got fact' + ~& >> !<([id=identifier =metadata] vase) =+ !<([id=identifier =metadata] vase) =. heard (~(put by heard) id metadata) that == + :: + [%thread %glob @ @ *] + ?- -.sign + %kick that + ?(%poke-ack %watch-ack) + ?~ p.sign + that + ~& 'Thread failed to start' + that + :: + %fact + ?+ p.cage.sign that + %thread-fail + ~& >>> ['thread-failed to glob' (slag 2 `(list @ta)`wire)] + ::add some back up logic? + that + :: + %thread-done + =/ hash !<(hash=@t q.cage.sign) + =/ data=metadata + :- 'app-name' ::name of an app ?? + %- crip + :: here we can add s3 path where it will be stored + ;:(weld "http://" (trip hash) ".glob") + =/ id=identifier [our.bowl `@ud`eny.bowl] ::entropy? + =. published (~(put by published) id data) + %- emit + %+ invent:gossip + %metadata + !> ^- [identifier metadata] + [id data] + == + == == :: ++ arvo @@ -215,7 +259,7 @@ [%eyre ~] ?. ?=([%eyre %bound *] sign-arvo) that ?: accepted.sign-arvo that - ~& ['Failde to bind' path.binding.sign-arvo] + ~& ['Failed to bind' path.binding.sign-arvo] that == -- \ No newline at end of file diff --git a/desk/gen/poke.hoon b/desk/gen/poke.hoon index bb75a39f6..6a0491fde 100644 --- a/desk/gen/poke.hoon +++ b/desk/gen/poke.hoon @@ -3,11 +3,11 @@ :: :near-gateways +near-handler!poke %publish ['url' 'test'] |= $: [now=@da eny=@uvJ bec=beak] $: act=?(%publish) - metadata=[url=@t name=@t] + =path ~ == ~ == ?- act -%publish [%near-action [%publish metadata]] +%publish [%near-action [%publish path]] == \ No newline at end of file diff --git a/desk/lib/strand.hoon b/desk/lib/strand.hoon new file mode 100644 index 000000000..b0db35b27 --- /dev/null +++ b/desk/lib/strand.hoon @@ -0,0 +1 @@ +rand diff --git a/desk/lib/strandio.hoon b/desk/lib/strandio.hoon new file mode 100644 index 000000000..c2f213719 --- /dev/null +++ b/desk/lib/strandio.hoon @@ -0,0 +1,812 @@ +/- spider +/+ libstrand=strand +=, strand=strand:libstrand +=, strand-fail=strand-fail:libstrand +|% +++ send-raw-cards + |= cards=(list =card:agent:gall) + =/ m (strand ,~) + ^- form:m + |= strand-input:strand + [cards %done ~] +:: +++ send-raw-card + |= =card:agent:gall + =/ m (strand ,~) + ^- form:m + (send-raw-cards card ~) +:: +++ ignore + |= tin=strand-input:strand + `[%fail %ignore ~] +:: +++ get-bowl + =/ m (strand ,bowl:strand) + ^- form:m + |= tin=strand-input:strand + `[%done bowl.tin] +:: +++ get-beak + =/ m (strand ,beak) + ^- form:m + |= tin=strand-input:strand + `[%done [our q.byk da+now]:bowl.tin] +:: +++ get-time + =/ m (strand ,@da) + ^- form:m + |= tin=strand-input:strand + `[%done now.bowl.tin] +:: +++ get-our + =/ m (strand ,ship) + ^- form:m + |= tin=strand-input:strand + `[%done our.bowl.tin] +:: +++ get-entropy + =/ m (strand ,@uvJ) + ^- form:m + |= tin=strand-input:strand + `[%done eny.bowl.tin] +:: +:: Convert skips to %ignore failures. +:: +:: This tells the main loop to try the next handler. +:: +++ handle + |* a=mold + =/ m (strand ,a) + |= =form:m + ^- form:m + |= tin=strand-input:strand + =/ res (form tin) + =? next.res ?=(%skip -.next.res) + [%fail %ignore ~] + res +:: +:: Wait for a poke with a particular mark +:: +++ take-poke + |= =mark + =/ m (strand ,vase) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ + `[%wait ~] + :: + [~ %poke @ *] + ?. =(mark p.cage.u.in.tin) + `[%skip ~] + `[%done q.cage.u.in.tin] + == +:: +++ take-sign-arvo + =/ m (strand ,[wire sign-arvo]) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ + `[%wait ~] + :: + [~ %sign *] + `[%done [wire sign-arvo]:u.in.tin] + == +:: +:: Wait for a subscription update on a wire +:: +++ take-fact-prefix + |= =wire + =/ m (strand ,[path cage]) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %agent * %fact *] + ?. =(watch+wire (scag +((lent wire)) wire.u.in.tin)) + `[%skip ~] + `[%done (slag (lent wire) wire.u.in.tin) cage.sign.u.in.tin] + == +:: +:: Wait for a subscription update on a wire +:: +++ take-fact + |= =wire + =/ m (strand ,cage) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %agent * %fact *] + ?. =(watch+wire wire.u.in.tin) + `[%skip ~] + `[%done cage.sign.u.in.tin] + == +:: +:: Wait for a subscription close +:: +++ take-kick + |= =wire + =/ m (strand ,~) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %agent * %kick *] + ?. =(watch+wire wire.u.in.tin) + `[%skip ~] + `[%done ~] + == +:: +++ echo + =/ m (strand ,~) + ^- form:m + %- (main-loop ,~) + :~ |= ~ + ^- form:m + ;< =vase bind:m ((handle ,vase) (take-poke %echo)) + =/ message=tape !<(tape vase) + %- (slog leaf+"{message}..." ~) + ;< ~ bind:m (sleep ~s2) + %- (slog leaf+"{message}.." ~) + (pure:m ~) + :: + |= ~ + ^- form:m + ;< =vase bind:m ((handle ,vase) (take-poke %over)) + %- (slog leaf+"over..." ~) + (pure:m ~) + == +:: +++ take-watch + =/ m (strand ,path) + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %watch *] + `[%done path.u.in.tin] + == +:: +++ take-wake + |= until=(unit @da) + =/ m (strand ,~) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %sign [%wait @ ~] %behn %wake *] + ?. |(?=(~ until) =(`u.until (slaw %da i.t.wire.u.in.tin))) + `[%skip ~] + ?~ error.sign-arvo.u.in.tin + `[%done ~] + `[%fail %timer-error u.error.sign-arvo.u.in.tin] + == +:: +++ take-tune + |= =wire + =/ m (strand ,[spar:ames (unit roar:ames)]) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + :: + [~ %sign * %ames %tune ^ *] + ?. =(wire wire.u.in.tin) + `[%skip ~] + `[%done +>.sign-arvo.u.in.tin] + == +:: +++ take-poke-ack + |= =wire + =/ m (strand ,~) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %agent * %poke-ack *] + ?. =(wire wire.u.in.tin) + `[%skip ~] + ?~ p.sign.u.in.tin + `[%done ~] + `[%fail %poke-fail u.p.sign.u.in.tin] + == +:: +++ take-watch-ack + |= =wire + =/ m (strand ,~) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %agent * %watch-ack *] + ?. =(watch+wire wire.u.in.tin) + `[%skip ~] + ?~ p.sign.u.in.tin + `[%done ~] + `[%fail %watch-ack-fail u.p.sign.u.in.tin] + == +:: +++ poke + |= [=dock =cage] + =/ m (strand ,~) + ^- form:m + =/ =card:agent:gall [%pass /poke %agent dock %poke cage] + ;< ~ bind:m (send-raw-card card) + (take-poke-ack /poke) +:: +++ raw-poke + |= [=dock =cage] + =/ m (strand ,~) + ^- form:m + =/ =card:agent:gall [%pass /poke %agent dock %poke cage] + ;< ~ bind:m (send-raw-card card) + =/ m (strand ,~) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ + `[%wait ~] + :: + [~ %agent * %poke-ack *] + ?. =(/poke wire.u.in.tin) + `[%skip ~] + `[%done ~] + == +:: +++ raw-poke-our + |= [app=term =cage] + =/ m (strand ,~) + ^- form:m + ;< =bowl:spider bind:m get-bowl + (raw-poke [our.bowl app] cage) +:: +++ poke-our + |= [=term =cage] + =/ m (strand ,~) + ^- form:m + ;< our=@p bind:m get-our + (poke [our term] cage) +:: +++ watch + |= [=wire =dock =path] + =/ m (strand ,~) + ^- form:m + =/ =card:agent:gall [%pass watch+wire %agent dock %watch path] + ;< ~ bind:m (send-raw-card card) + (take-watch-ack wire) +:: +++ watch-one + |= [=wire =dock =path] + =/ m (strand ,cage) + ^- form:m + ;< ~ bind:m (watch wire dock path) + ;< =cage bind:m (take-fact wire) + ;< ~ bind:m (take-kick wire) + (pure:m cage) +:: +++ watch-our + |= [=wire =term =path] + =/ m (strand ,~) + ^- form:m + ;< our=@p bind:m get-our + (watch wire [our term] path) +:: +++ scry + |* [=mold =path] + =/ m (strand ,mold) + ^- form:m + ?> ?=(^ path) + ?> ?=(^ t.path) + ;< =bowl:spider bind:m get-bowl + %- pure:m + .^(mold i.path (scot %p our.bowl) i.t.path (scot %da now.bowl) t.t.path) +:: +++ leave + |= [=wire =dock] + =/ m (strand ,~) + ^- form:m + =/ =card:agent:gall [%pass watch+wire %agent dock %leave ~] + (send-raw-card card) +:: +++ leave-our + |= [=wire =term] + =/ m (strand ,~) + ^- form:m + ;< our=@p bind:m get-our + (leave wire [our term]) +:: +++ rewatch + |= [=wire =dock =path] + =/ m (strand ,~) + ;< ~ bind:m ((handle ,~) (take-kick wire)) + ;< ~ bind:m (flog-text "rewatching {} {}") + ;< ~ bind:m (watch wire dock path) + (pure:m ~) +:: +++ wait + |= until=@da + =/ m (strand ,~) + ^- form:m + ;< ~ bind:m (send-wait until) + (take-wake `until) +:: +++ keen + |= [=wire =spar:ames] + =/ m (strand ,~) + ^- form:m + (send-raw-card %pass wire %arvo %a %keen spar) +:: +++ sleep + |= for=@dr + =/ m (strand ,~) + ^- form:m + ;< now=@da bind:m get-time + (wait (add now for)) +:: +++ send-wait + |= until=@da + =/ m (strand ,~) + ^- form:m + =/ =card:agent:gall + [%pass /wait/(scot %da until) %arvo %b %wait until] + (send-raw-card card) +:: +++ map-err + |* computation-result=mold + =/ m (strand ,computation-result) + |= [f=$-([term tang] [term tang]) computation=form:m] + ^- form:m + |= tin=strand-input:strand + =* loop $ + =/ c-res (computation tin) + ?: ?=(%cont -.next.c-res) + c-res(self.next ..loop(computation self.next.c-res)) + ?. ?=(%fail -.next.c-res) + c-res + c-res(err.next (f err.next.c-res)) +:: +++ set-timeout + |* computation-result=mold + =/ m (strand ,computation-result) + |= [time=@dr computation=form:m] + ^- form:m + ;< now=@da bind:m get-time + =/ when (add now time) + =/ =card:agent:gall + [%pass /timeout/(scot %da when) %arvo %b %wait when] + ;< ~ bind:m (send-raw-card card) + |= tin=strand-input:strand + =* loop $ + ?: ?& ?=([~ %sign [%timeout @ ~] %behn %wake *] in.tin) + =((scot %da when) i.t.wire.u.in.tin) + == + `[%fail %timeout ~] + =/ c-res (computation tin) + ?: ?=(%cont -.next.c-res) + c-res(self.next ..loop(computation self.next.c-res)) + ?: ?=(%done -.next.c-res) + =/ =card:agent:gall + [%pass /timeout/(scot %da when) %arvo %b %rest when] + c-res(cards [card cards.c-res]) + c-res +:: +++ send-request + |= =request:http + =/ m (strand ,~) + ^- form:m + (send-raw-card %pass /request %arvo %i %request request *outbound-config:iris) +:: +++ send-cancel-request + =/ m (strand ,~) + ^- form:m + (send-raw-card %pass /request %arvo %i %cancel-request ~) +:: +++ take-client-response + =/ m (strand ,client-response:iris) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + :: + [~ %sign [%request ~] %iris %http-response %cancel *] + ::NOTE iris does not (yet?) retry after cancel, so it means failure + :- ~ + :+ %fail + %http-request-cancelled + ['http request was cancelled by the runtime']~ + :: + [~ %sign [%request ~] %iris %http-response %finished *] + `[%done client-response.sign-arvo.u.in.tin] + == +:: +:: Wait until we get an HTTP response or cancelation and unset contract +:: +++ take-maybe-sigh + =/ m (strand ,(unit httr:eyre)) + ^- form:m + ;< rep=(unit client-response:iris) bind:m + take-maybe-response + ?~ rep + (pure:m ~) + :: XX s/b impossible + :: + ?. ?=(%finished -.u.rep) + (pure:m ~) + (pure:m (some (to-httr:iris +.u.rep))) +:: +++ take-maybe-response + =/ m (strand ,(unit client-response:iris)) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %sign [%request ~] %iris %http-response %cancel *] + `[%done ~] + [~ %sign [%request ~] %iris %http-response %finished *] + `[%done `client-response.sign-arvo.u.in.tin] + == +:: +++ extract-body + |= =client-response:iris + =/ m (strand ,cord) + ^- form:m + ?> ?=(%finished -.client-response) + %- pure:m + ?~ full-file.client-response '' + q.data.u.full-file.client-response +:: +++ fetch-cord + |= url=tape + =/ m (strand ,cord) + ^- form:m + =/ =request:http [%'GET' (crip url) ~ ~] + ;< ~ bind:m (send-request request) + ;< =client-response:iris bind:m take-client-response + (extract-body client-response) +:: +++ fetch-json + |= url=tape + =/ m (strand ,json) + ^- form:m + ;< =cord bind:m (fetch-cord url) + =/ json=(unit json) (de:json:html cord) + ?~ json + (strand-fail %json-parse-error ~) + (pure:m u.json) +:: +++ hiss-request + |= =hiss:eyre + =/ m (strand ,(unit httr:eyre)) + ^- form:m + ;< ~ bind:m (send-request (hiss-to-request:html hiss)) + take-maybe-sigh +:: +:: +build-file: build the source file at the specified $beam +:: +++ build-file + |= [[=ship =desk =case] =spur] + =* arg +< + =/ m (strand ,(unit vase)) + ^- form:m + ;< =riot:clay bind:m + (warp ship desk ~ %sing %a case spur) + ?~ riot + (pure:m ~) + ?> =(%vase p.r.u.riot) + (pure:m (some !<(vase q.r.u.riot))) +:: +++ build-file-hard + |= [[=ship =desk =case] =spur] + =* arg +< + =/ m (strand ,vase) + ^- form:m + ;< =riot:clay + bind:m + (warp ship desk ~ %sing %a case spur) + ?> ?=(^ riot) + ?> ?=(%vase p.r.u.riot) + (pure:m !<(vase q.r.u.riot)) +:: +build-mark: build a mark definition to a $dais +:: +++ build-mark + |= [[=ship =desk =case] mak=mark] + =* arg +< + =/ m (strand ,dais:clay) + ^- form:m + ;< =riot:clay bind:m + (warp ship desk ~ %sing %b case /[mak]) + ?~ riot + (strand-fail %build-mark >arg< ~) + ?> =(%dais p.r.u.riot) + (pure:m !<(dais:clay q.r.u.riot)) +:: +build-tube: build a mark conversion gate ($tube) +:: +++ build-tube + |= [[=ship =desk =case] =mars:clay] + =* arg +< + =/ m (strand ,tube:clay) + ^- form:m + ;< =riot:clay bind:m + (warp ship desk ~ %sing %c case /[a.mars]/[b.mars]) + ?~ riot + (strand-fail %build-tube >arg< ~) + ?> =(%tube p.r.u.riot) + (pure:m !<(tube:clay q.r.u.riot)) +:: +:: +build-nave: build a mark definition to a $nave +:: +++ build-nave + |= [[=ship =desk =case] mak=mark] + =* arg +< + =/ m (strand ,vase) + ^- form:m + ;< =riot:clay bind:m + (warp ship desk ~ %sing %e case /[mak]) + ?~ riot + (strand-fail %build-nave >arg< ~) + ?> =(%nave p.r.u.riot) + (pure:m q.r.u.riot) +:: +build-cast: build a mark conversion gate (static) +:: +++ build-cast + |= [[=ship =desk =case] =mars:clay] + =* arg +< + =/ m (strand ,vase) + ^- form:m + ;< =riot:clay bind:m + (warp ship desk ~ %sing %f case /[a.mars]/[b.mars]) + ?~ riot + (strand-fail %build-cast >arg< ~) + ?> =(%cast p.r.u.riot) + (pure:m q.r.u.riot) +:: +:: Read from Clay +:: +++ warp + |= [=ship =riff:clay] + =/ m (strand ,riot:clay) + ;< ~ bind:m (send-raw-card %pass /warp %arvo %c %warp ship riff) + (take-writ /warp) +:: +++ read-file + |= [[=ship =desk =case] =spur] + =* arg +< + =/ m (strand ,cage) + ;< =riot:clay bind:m (warp ship desk ~ %sing %x case spur) + ?~ riot + (strand-fail %read-file >arg< ~) + (pure:m r.u.riot) +:: +++ check-for-file + |= [[=ship =desk =case] =spur] + =/ m (strand ,?) + ;< =riot:clay bind:m (warp ship desk ~ %sing %u case spur) + ?> ?=(^ riot) + (pure:m !<(? q.r.u.riot)) +:: +++ list-tree + |= [[=ship =desk =case] =spur] + =* arg +< + =/ m (strand ,(list path)) + ;< =riot:clay bind:m (warp ship desk ~ %sing %t case spur) + ?~ riot + (strand-fail %list-tree >arg< ~) + (pure:m !<((list path) q.r.u.riot)) +:: +:: Take Clay read result +:: +++ take-writ + |= =wire + =/ m (strand ,riot:clay) + ^- form:m + |= tin=strand-input:strand + ?+ in.tin `[%skip ~] + ~ `[%wait ~] + [~ %sign * ?(%behn %clay) %writ *] + ?. =(wire wire.u.in.tin) + `[%skip ~] + `[%done +>.sign-arvo.u.in.tin] + == +:: +check-online: require that peer respond before timeout +:: +++ check-online + |= [who=ship lag=@dr] + =/ m (strand ,~) + ^- form:m + %+ (map-err ,~) |=(* [%offline *tang]) + %+ (set-timeout ,~) lag + ;< ~ bind:m + (poke [who %hood] %helm-hi !>(~)) + (pure:m ~) +:: +++ eval-hoon + |= [gen=hoon bez=(list beam)] + =/ m (strand ,vase) + ^- form:m + =/ sut=vase !>(..zuse) + |- + ?~ bez + (pure:m (slap sut gen)) + ;< vax=vase bind:m (build-file-hard i.bez) + $(bez t.bez, sut (slop vax sut)) +:: +++ send-thread + |= [=bear:khan =shed:khan =wire] + =/ m (strand ,~) + ^- form:m + (send-raw-card %pass wire %arvo %k %lard bear shed) +:: +:: Queue on skip, try next on fail %ignore +:: +++ main-loop + |* a=mold + =/ m (strand ,~) + =/ m-a (strand ,a) + =| queue=(qeu (unit input:strand)) + =| active=(unit [in=(unit input:strand) =form:m-a forms=(list $-(a form:m-a))]) + =| state=a + |= forms=(lest $-(a form:m-a)) + ^- form:m + |= tin=strand-input:strand + =* top `form:m`..$ + =. queue (~(put to queue) in.tin) + |^ (continue bowl.tin) + :: + ++ continue + |= =bowl:strand + ^- output:m + ?> =(~ active) + ?: =(~ queue) + `[%cont top] + =^ in=(unit input:strand) queue ~(get to queue) + ^- output:m + =. active `[in (i.forms state) t.forms] + ^- output:m + (run bowl in) + :: + ++ run + ^- form:m + |= tin=strand-input:strand + ^- output:m + ?> ?=(^ active) + =/ res (form.u.active tin) + =/ =output:m + ?- -.next.res + %wait `[%wait ~] + %skip `[%cont ..$(queue (~(put to queue) in.tin))] + %cont `[%cont ..$(active `[in.u.active self.next.res forms.u.active])] + %done (continue(active ~, state value.next.res) bowl.tin) + %fail + ?: &(?=(^ forms.u.active) ?=(%ignore p.err.next.res)) + %= $ + active `[in.u.active (i.forms.u.active state) t.forms.u.active] + in.tin in.u.active + == + `[%fail err.next.res] + == + [(weld cards.res cards.output) next.output] + -- +:: +++ retry + |* result=mold + |= [crash-after=(unit @ud) computation=_*form:(strand (unit result))] + =/ m (strand ,result) + =| try=@ud + |- ^- form:m + =* loop $ + ?: =(crash-after `try) + (strand-fail %retry-too-many ~) + ;< ~ bind:m (backoff try ~m1) + ;< res=(unit result) bind:m computation + ?^ res + (pure:m u.res) + loop(try +(try)) +:: +++ backoff + |= [try=@ud limit=@dr] + =/ m (strand ,~) + ^- form:m + ;< eny=@uvJ bind:m get-entropy + %- sleep + %+ min limit + ?: =(0 try) ~s0 + %+ add + (mul ~s1 (bex (dec try))) + (mul ~s0..0001 (~(rad og eny) 1.000)) +:: +:: ---- +:: +:: Output +:: +++ flog + |= =flog:dill + =/ m (strand ,~) + ^- form:m + (send-raw-card %pass / %arvo %d %flog flog) +:: +++ flog-text + |= =tape + =/ m (strand ,~) + ^- form:m + (flog %text tape) +:: +++ flog-tang + |= =tang + =/ m (strand ,~) + ^- form:m + =/ =wall + (zing (turn (flop tang) (cury wash [0 80]))) + |- ^- form:m + =* loop $ + ?~ wall + (pure:m ~) + ;< ~ bind:m (flog-text i.wall) + loop(wall t.wall) +:: +++ trace + |= =tang + =/ m (strand ,~) + ^- form:m + (pure:m ((slog tang) ~)) +:: +++ app-message + |= [app=term =cord =tang] + =/ m (strand ,~) + ^- form:m + =/ msg=tape :(weld (trip app) ": " (trip cord)) + ;< ~ bind:m (flog-text msg) + (flog-tang tang) +:: +:: ---- +:: +:: Handle domains +:: +++ install-domain + |= =turf + =/ m (strand ,~) + ^- form:m + (send-raw-card %pass / %arvo %e %rule %turf %put turf) +:: +:: ---- +:: +:: Threads +:: +++ start-thread + |= file=term + =/ m (strand ,tid:spider) + ;< =bowl:spider bind:m get-bowl + (start-thread-with-args byk.bowl file *vase) +:: +++ start-thread-with-args + |= [=beak file=term args=vase] + =/ m (strand ,tid:spider) + ^- form:m + ;< =bowl:spider bind:m get-bowl + =/ tid + (scot %ta (cat 3 (cat 3 'strand_' file) (scot %uv (sham file eny.bowl)))) + =/ poke-vase !>(`start-args:spider`[`tid.bowl `tid beak file args]) + ;< ~ bind:m (poke-our %spider %spider-start poke-vase) + ;< ~ bind:m (sleep ~s0) :: wait for thread to start + (pure:m tid) +:: ++$ thread-result + (each vase [term tang]) +:: +++ await-thread + |= [file=term args=vase] + =/ m (strand ,thread-result) + ^- form:m + ;< =bowl:spider bind:m get-bowl + =/ tid (scot %ta (cat 3 'strand_' (scot %uv (sham file eny.bowl)))) + =/ poke-vase !>(`start-args:spider`[`tid.bowl `tid byk.bowl file args]) + ;< ~ bind:m (watch-our /awaiting/[tid] %spider /thread-result/[tid]) + ;< ~ bind:m (poke-our %spider %spider-start poke-vase) + ;< ~ bind:m (sleep ~s0) :: wait for thread to start + ;< =cage bind:m (take-fact /awaiting/[tid]) + ;< ~ bind:m (take-kick /awaiting/[tid]) + ?+ p.cage ~|([%strange-thread-result p.cage file tid] !!) + %thread-done (pure:m %& q.cage) + %thread-fail (pure:m %| ;;([term tang] q.q.cage)) + == +-- diff --git a/desk/sur/near-handler.hoon b/desk/sur/near-handler.hoon index e66684600..d4b2e6e6d 100644 --- a/desk/sur/near-handler.hoon +++ b/desk/sur/near-handler.hoon @@ -11,7 +11,7 @@ $% [%accs accs=(set acc)] == +$ gateway-action - $% [%publish =metadata] + $% [%publish =path] ::=metadata] [%install =identifier =metadata] == -- \ No newline at end of file diff --git a/desk/sur/spider.hoon b/desk/sur/spider.hoon new file mode 100644 index 000000000..7c212681f --- /dev/null +++ b/desk/sur/spider.hoon @@ -0,0 +1,27 @@ +/+ libstrand=strand +=, strand=strand:libstrand +|% ++$ thread $-(vase shed:khan) ++$ input [=tid =cage] ++$ tid tid:strand ++$ bowl bowl:strand ++$ http-error + $? %bad-request :: 400 + %forbidden :: 403 + %nonexistent :: 404 + %offline :: 504 + == ++$ start-args + $: parent=(unit tid) + use=(unit tid) + =beak + file=term + =vase + == ++$ inline-args + $: parent=(unit tid) + use=(unit tid) + =beak + =shed:khan + == +-- diff --git a/desk/ted/gateway-glob.hoon b/desk/ted/gateway-glob.hoon new file mode 100644 index 000000000..06c5a5dcb --- /dev/null +++ b/desk/ted/gateway-glob.hoon @@ -0,0 +1,27 @@ +/- spider, docket +/+ strandio +=, strand=strand:spider +^- thread:spider +|= arg=vase +=/ m (strand ,vase) +^- form:m +!: +=+ !<([~ [=desk dir=path]] arg) +~& > [desk dir] +;< =bowl:spider bind:m get-bowl:strandio +=/ home=path /(scot %p our.bowl)/[desk]/(scot %da now.bowl) +=+ .^(paths=(list path) %ct (weld home dir)) +=/ =glob:docket + %- ~(gas by *glob:docket) + %+ turn paths + |= pax=path + ^- [path mime] + :- (slag (lent dir) pax) + =/ mar=mark (rear pax) + =+ .^(vas=vase %cr (weld home pax)) + =+ .^(=tube:clay %cc (weld home /[mar]/mime)) + !<(mime (tube vas)) +~& > paths +::=/ =path /(cat 3 'glob-' (scot %uv (sham glob)))/glob +::;< ~ bind:m (poke-our:strandio %hood drum-put+!>([path (jam glob)])) +(pure:m !>((cat 3 'glob-' (scot %uv (sham glob))))) \ No newline at end of file From 8985115d396b0318d0906551072b1e867882feac Mon Sep 17 00:00:00 2001 From: SuperCoolYun Date: Thu, 1 Feb 2024 20:00:33 -0500 Subject: [PATCH 8/9] working on glob hosting --- desk/app/near-gateways.hoon | 139 ++++++++++++++++++++++-------------- desk/gen/poke.hoon | 5 +- desk/sur/near-handler.hoon | 5 +- desk/ted/gateway-glob.hoon | 27 ------- desk/ted/glob.hoon | 19 +++++ 5 files changed, 109 insertions(+), 86 deletions(-) delete mode 100644 desk/ted/gateway-glob.hoon create mode 100644 desk/ted/glob.hoon diff --git a/desk/app/near-gateways.hoon b/desk/app/near-gateways.hoon index 12a6429c0..cf7aa9af6 100644 --- a/desk/app/near-gateways.hoon +++ b/desk/app/near-gateways.hoon @@ -13,7 +13,7 @@ :: (map identifier=[ship id] metadata=[name url]) heard=(map identifier metadata) published=(map identifier metadata) - installed=(map identifier metadata) + installed=(map identifier glob) == :: +$ card $+(card card:agent:gall) @@ -105,21 +105,27 @@ %handle-http-request =+ !<([id=@ta request=inbound-request:eyre] vase) (handle-http-request id request) + :: %near-action ?> from-self =+ !<(act=gateway-action vase) ?- -.act - %publish - %+ start-gateway-glob - %near-handler - path.act :: - %install - :: get and host glob on handle/get at some path/name/ - :: host each path alike payload-from-glob - =. installed (~(put by installed) +.act) + %publish + ?~ (find ~[metadata.act] ~(val by published)) + =/ id=identifier [our.bowl (sham eny.bowl)] + =. published (~(put by published) id metadata.act) + %+ get-gateway-glob + metadata.act + id + ~& 'Alredy globbed and installed' that :: + %install ::[%install =identifier =metadata] + :: get and host glob on handle/get at some path/name/ + %+ get-gateway-glob + metadata.act + identifier.act == == ++ dump [404 ~ [%plain "404 - Not Found"]] @@ -127,7 +133,6 @@ |= [id=@ta inbound-request:eyre] ^+ that =/ request-line (parse-request-line:server url.request) - :: %- emil =+ send=(cury response:schooner id) ?. authenticated %- emil @@ -145,13 +150,20 @@ %- emil %- send [200 ~ [%plain "welcome to %near-gateway"]] ::for now :: - [[%apps %near @ *] *] + [[%apps %near @ @ *] *] + =/ new-site + %+ weld + %+ slag 4 + ;; (list @ta) site.request-line + %- drop + ext.request-line %- emil - %- send + %+ give-simple-payload:app:server + id %+ from-glob - (snag 2 site.request-line) - ::[ext.request-line site.request-line args.request-line] - request-line(site (slag 2 `(list @ta)`site.request-line)) + :- (slav %p (snag 2 site.request-line)) ::ship + (slav %uv (snag 3 site.request-line)) ::id + request-line(site new-site) == :: %'POST' @@ -160,30 +172,41 @@ == :: ++ from-glob - |= [from=@ta request=request-line:server] - :: get glob files out to host - ~& >> [from request] - =/ charge-update .^(charge-update:docket %gx /(scot %p our.bowl)/docket/(scot %da now.bowl)/charges/noun) - ~& >> ['suffix' (weld site.request (drop ext.request))] - ?+ -.charge-update [404 ~ [%stock ~]] - %initial - ~& (~(get by initial.charge-update) from) - [200 ~ [%plain "welcome to %near-gateway"]] - == + |= [identifier=[=ship id=@uvH] request=request-line:server] + ^- simple-payload:http + ?. (~(has by installed) identifier) not-found:gen:server + =/ =glob (~(got by installed) identifier) + =/ requested ?: (~(has by glob) site.request) + site.request + /index/html + =/ =mime (~(got by glob) requested) + =/ mime-type=@t (rsh 3 (crip )) + =; headers + [[200 headers] `q.mime] + :- content-type+mime-type + ?: =(/index/html requested) ~ + ~[max-1-wk:gen:server] :: -++ start-gateway-glob -|= [=desk =path] -^+ that -=/ tid `@ta`(cat 3 'near-' (scot %uv (sham eny.bowl))) -=/ ta-now `@ta`(scot %da now.bowl) -=/ arg-vase !>(`[desk path]) -=/ =cage :- %spider-start - !>([~ `tid byk.bowl(r da+now.bowl) %gateway-glob arg-vase]) -=. path (weld /thread/glob/[ta-now] path) -%- emil - :~ [%pass path %agent [our.bowl %spider] %poke cage] - [%pass path %agent [our.bowl %spider] %watch /thread-result/[tid]] - == +++ get-gateway-glob + |= [data=metadata =identifier] + ^+ that + =/ tid `@ta`(cat 3 'near-' (scot %uv (sham eny.bowl))) + =/ ta-now `@ta`(scot %da now.bowl) + =/ ted-cage=cage %glob !>(`url.data) + =/ =cage :- %spider-start + !>([~ `tid byk.bowl(r da+now.bowl) ted-cage]) + =/ id-path + ;; (list @ta) + :~ name.data + url.data + (scot %p -.identifier) + (scot %uv +.identifier) + == + =/ path `(list @ta)`(weld /glob/[ta-now] id-path) + %- emil + :~ [%pass path %agent [our.bowl %spider] %poke cage] + [%pass path %agent [our.bowl %spider] %watch /thread-result/[tid]] + == :: ++ watch |= =path @@ -192,7 +215,7 @@ [%http-response *] that :: - [%~.~ %gossip %source ~] + [%~.~ %gossip %source ~] %- emil %+ turn ~(tap by published) @@ -210,48 +233,54 @@ =* mark p.cage.sign =* vase q.cage.sign ?. =(%metadata mark) that - ::add new gateway to heard - ~& >> 'got fact' - ~& >> !<([id=identifier =metadata] vase) =+ !<([id=identifier =metadata] vase) =. heard (~(put by heard) id metadata) that == - :: - [%thread %glob @ @ *] + [%glob @ @ @ *] ?- -.sign %kick that ?(%poke-ack %watch-ack) ?~ p.sign + ~& 'Thread started succesfully' that - ~& 'Thread failed to start' + ~& 'Thread fail to start' that :: %fact ?+ p.cage.sign that %thread-fail ~& >>> ['thread-failed to glob' (slag 2 `(list @ta)`wire)] - ::add some back up logic? + =/ id (id-from-wire wire) + =. published (~(del by published) id) that :: %thread-done - =/ hash !<(hash=@t q.cage.sign) - =/ data=metadata - :- 'app-name' ::name of an app ?? - %- crip - :: here we can add s3 path where it will be stored - ;:(weld "http://" (trip hash) ".glob") - =/ id=identifier [our.bowl `@ud`eny.bowl] ::entropy? - =. published (~(put by published) id data) + =/ glob !<(glob q.cage.sign) + =/ id (id-from-wire wire) + =/ had=metadata (~(got by published) id) + =/ got=metadata + :- (snag 2 wire) + (snag 3 wire) + ?. =(url.had url.got) + ~& >>> 'glob url mismatch' + that + =. installed (~(put by installed) id glob) %- emit %+ invent:gossip %metadata !> ^- [identifier metadata] - [id data] + [id got] == == == :: +++ id-from-wire +|= =wire +^- identifier +:- (slav %p (snag 4 wire)) +(slav %uv (snag 5 wire)) +:: ++ arvo |= [=wire =sign-arvo] ^+ that diff --git a/desk/gen/poke.hoon b/desk/gen/poke.hoon index 6a0491fde..c0850e8fd 100644 --- a/desk/gen/poke.hoon +++ b/desk/gen/poke.hoon @@ -3,11 +3,12 @@ :: :near-gateways +near-handler!poke %publish ['url' 'test'] |= $: [now=@da eny=@uvJ bec=beak] $: act=?(%publish) - =path + name=@t + url=@t ~ == ~ == ?- act -%publish [%near-action [%publish path]] +%publish [%near-action [%publish [name url]]] == \ No newline at end of file diff --git a/desk/sur/near-handler.hoon b/desk/sur/near-handler.hoon index d4b2e6e6d..80dc27bcd 100644 --- a/desk/sur/near-handler.hoon +++ b/desk/sur/near-handler.hoon @@ -1,7 +1,8 @@ |% +$ acc @uxH ++$ glob (map path mime) +$ metadata [name=@t url=@t] -+$ identifier [=ship id=@ud] ++$ identifier [=ship id=@uvH] +$ action $% [%add =acc] [%del =acc] @@ -11,7 +12,7 @@ $% [%accs accs=(set acc)] == +$ gateway-action - $% [%publish =path] ::=metadata] + $% [%publish =metadata] [%install =identifier =metadata] == -- \ No newline at end of file diff --git a/desk/ted/gateway-glob.hoon b/desk/ted/gateway-glob.hoon deleted file mode 100644 index 06c5a5dcb..000000000 --- a/desk/ted/gateway-glob.hoon +++ /dev/null @@ -1,27 +0,0 @@ -/- spider, docket -/+ strandio -=, strand=strand:spider -^- thread:spider -|= arg=vase -=/ m (strand ,vase) -^- form:m -!: -=+ !<([~ [=desk dir=path]] arg) -~& > [desk dir] -;< =bowl:spider bind:m get-bowl:strandio -=/ home=path /(scot %p our.bowl)/[desk]/(scot %da now.bowl) -=+ .^(paths=(list path) %ct (weld home dir)) -=/ =glob:docket - %- ~(gas by *glob:docket) - %+ turn paths - |= pax=path - ^- [path mime] - :- (slag (lent dir) pax) - =/ mar=mark (rear pax) - =+ .^(vas=vase %cr (weld home pax)) - =+ .^(=tube:clay %cc (weld home /[mar]/mime)) - !<(mime (tube vas)) -~& > paths -::=/ =path /(cat 3 'glob-' (scot %uv (sham glob)))/glob -::;< ~ bind:m (poke-our:strandio %hood drum-put+!>([path (jam glob)])) -(pure:m !>((cat 3 'glob-' (scot %uv (sham glob))))) \ No newline at end of file diff --git a/desk/ted/glob.hoon b/desk/ted/glob.hoon new file mode 100644 index 000000000..dff864e52 --- /dev/null +++ b/desk/ted/glob.hoon @@ -0,0 +1,19 @@ +/- spider, *near-handler +/+ strandio +=, strand=strand:spider +^- thread:spider +|= arg=vase +=/ m (strand ,vase) +^- form:m +=+ !<([~ url=@t] arg) +;< =glob bind:m + %+ (retry:strandio ,glob) `5 + =/ n (strand ,(unit glob)) + ;< =cord bind:n (fetch-cord:strandio (trip url)) + ~& > cord + %- pure:n + %- mole + |. + ;;(=glob (cue cord)) +~& >> glob +(pure:m !>(glob)) From 277ee5d290ace9c0dcc68963c53825c406d24d46 Mon Sep 17 00:00:00 2001 From: SuperCoolYun Date: Fri, 2 Feb 2024 10:00:15 -0500 Subject: [PATCH 9/9] gateway glob hosting implemented --- desk/app/near-gateways.hoon | 37 ++++++++++++++++++++++--------------- desk/gen/poke.hoon | 2 +- desk/sur/near-handler.hoon | 2 +- desk/ted/glob.hoon | 10 +++++----- 4 files changed, 29 insertions(+), 22 deletions(-) diff --git a/desk/app/near-gateways.hoon b/desk/app/near-gateways.hoon index cf7aa9af6..5e555edcf 100644 --- a/desk/app/near-gateways.hoon +++ b/desk/app/near-gateways.hoon @@ -13,7 +13,7 @@ :: (map identifier=[ship id] metadata=[name url]) heard=(map identifier metadata) published=(map identifier metadata) - installed=(map identifier glob) + installed=(map identifier glob:docket) == :: +$ card $+(card card:agent:gall) @@ -82,7 +82,7 @@ |_ [=bowl:gall deck=(list card)] +* that . ++ emit |=(=card that(deck [card deck])) -++ emil |=(lac=(list card) that(deck (welp lac deck))) +++ emil |=(lac=(list card) that(deck (welp (flop lac) deck))) ++ abet ^-((quip card _state) [(flop deck) state]) :: ++ from-self =(our src):bowl @@ -122,7 +122,6 @@ that :: %install ::[%install =identifier =metadata] - :: get and host glob on handle/get at some path/name/ %+ get-gateway-glob metadata.act identifier.act @@ -144,19 +143,21 @@ %'GET' ?+ [site ext]:request-line %- emil - %- send dump + %- send [302 ~ [%redirect './apps/near']] :: [[%apps %near ~] *] %- emil %- send [200 ~ [%plain "welcome to %near-gateway"]] ::for now :: - [[%apps %near @ @ *] *] + [[%apps %near @ @ *] *] =/ new-site %+ weld %+ slag 4 ;; (list @ta) site.request-line %- drop ext.request-line + ~& > request-line + ~& >> ['site' (weld (slag 4 `(list @ta)`site.request-line) (drop ext.request-line))] %- emil %+ give-simple-payload:app:server id @@ -174,8 +175,10 @@ ++ from-glob |= [identifier=[=ship id=@uvH] request=request-line:server] ^- simple-payload:http + ~& (~(has by installed) identifier) ?. (~(has by installed) identifier) not-found:gen:server - =/ =glob (~(got by installed) identifier) + =/ =glob:docket (~(got by installed) identifier) + ::?: =(suffix /desk/js) =/ requested ?: (~(has by glob) site.request) site.request /index/html @@ -188,13 +191,14 @@ ~[max-1-wk:gen:server] :: ++ get-gateway-glob - |= [data=metadata =identifier] + |= [data=metadata =identifier] ::[name=@t url=@t] ^+ that =/ tid `@ta`(cat 3 'near-' (scot %uv (sham eny.bowl))) =/ ta-now `@ta`(scot %da now.bowl) - =/ ted-cage=cage %glob !>(`url.data) - =/ =cage :- %spider-start - !>([~ `tid byk.bowl(r da+now.bowl) ted-cage]) + =/ ted-cage=cage :- %glob + !>(`url.data) + =/ cage :- %spider-start + !>([~ `tid byk.bowl(r da+now.bowl) ted-cage]) =/ id-path ;; (list @ta) :~ name.data @@ -205,7 +209,7 @@ =/ path `(list @ta)`(weld /glob/[ta-now] id-path) %- emil :~ [%pass path %agent [our.bowl %spider] %poke cage] - [%pass path %agent [our.bowl %spider] %watch /thread-result/[tid]] + [%pass path %agent [our.bowl %spider] %watch /thread-result/[tid]] == :: ++ watch @@ -233,6 +237,8 @@ =* mark p.cage.sign =* vase q.cage.sign ?. =(%metadata mark) that + ~& >> 'got fact' + ~& >> !<([id=identifier =metadata] vase) =+ !<([id=identifier =metadata] vase) =. heard (~(put by heard) id metadata) that @@ -256,12 +262,13 @@ that :: %thread-done - =/ glob !<(glob q.cage.sign) + =/ glob !<(glob:docket q.cage.sign) =/ id (id-from-wire wire) =/ had=metadata (~(got by published) id) + =/ path ;; (list @ta) wire =/ got=metadata - :- (snag 2 wire) - (snag 3 wire) + :- (snag 2 path) + (snag 3 path) ?. =(url.had url.got) ~& >>> 'glob url mismatch' that @@ -285,7 +292,7 @@ |= [=wire =sign-arvo] ^+ that ?+ wire that - [%eyre ~] + [%eyre %connect ~] ?. ?=([%eyre %bound *] sign-arvo) that ?: accepted.sign-arvo that ~& ['Failed to bind' path.binding.sign-arvo] diff --git a/desk/gen/poke.hoon b/desk/gen/poke.hoon index c0850e8fd..8a06c07b3 100644 --- a/desk/gen/poke.hoon +++ b/desk/gen/poke.hoon @@ -1,6 +1,6 @@ !: :- %say -:: :near-gateways +near-handler!poke %publish ['url' 'test'] +:: :near-gateways +near-handler!poke %publish ['test' 'url'] |= $: [now=@da eny=@uvJ bec=beak] $: act=?(%publish) name=@t diff --git a/desk/sur/near-handler.hoon b/desk/sur/near-handler.hoon index 80dc27bcd..f8d057753 100644 --- a/desk/sur/near-handler.hoon +++ b/desk/sur/near-handler.hoon @@ -1,6 +1,6 @@ |% +$ acc @uxH -+$ glob (map path mime) +:: +$ glob (map path mime) +$ metadata [name=@t url=@t] +$ identifier [=ship id=@uvH] +$ action diff --git a/desk/ted/glob.hoon b/desk/ted/glob.hoon index dff864e52..c14635878 100644 --- a/desk/ted/glob.hoon +++ b/desk/ted/glob.hoon @@ -1,4 +1,4 @@ -/- spider, *near-handler +/- spider, *near-handler, docket /+ strandio =, strand=strand:spider ^- thread:spider @@ -6,14 +6,14 @@ =/ m (strand ,vase) ^- form:m =+ !<([~ url=@t] arg) -;< =glob bind:m - %+ (retry:strandio ,glob) `5 - =/ n (strand ,(unit glob)) +;< =glob:docket bind:m + %+ (retry:strandio ,glob:docket) `5 + =/ n (strand ,(unit glob:docket)) ;< =cord bind:n (fetch-cord:strandio (trip url)) ~& > cord %- pure:n %- mole |. - ;;(=glob (cue cord)) + ;;(=glob:docket (cue cord)) ~& >> glob (pure:m !>(glob))