diff options
Diffstat (limited to 'desk')
-rw-r--r-- | desk/app/nostrill.hoon | 59 | ||||
-rw-r--r-- | desk/lib/json/nostrill.hoon | 51 | ||||
-rw-r--r-- | desk/lib/json/trill.hoon | 30 | ||||
-rw-r--r-- | desk/lib/nostrill.hoon | 2 | ||||
-rw-r--r-- | desk/lib/nostrill/comms.hoon | 99 | ||||
-rw-r--r-- | desk/lib/nostrill/mutations.hoon | 19 | ||||
-rw-r--r-- | desk/lib/shim.hoon | 10 | ||||
-rw-r--r-- | desk/lib/trill/feed.hoon | 37 | ||||
-rw-r--r-- | desk/lib/trill/gate.hoon | 79 | ||||
-rw-r--r-- | desk/mar/json.hoon | 26 | ||||
-rw-r--r-- | desk/mar/tang.hoon | 25 | ||||
-rw-r--r-- | desk/sur/nostr.hoon | 10 | ||||
-rw-r--r-- | desk/sur/nostrill.hoon | 22 | ||||
-rw-r--r-- | desk/sur/nostrill/comms.hoon | 22 | ||||
-rw-r--r-- | desk/ted/beg.hoon | 31 |
15 files changed, 469 insertions, 53 deletions
diff --git a/desk/app/nostrill.hoon b/desk/app/nostrill.hoon index e311b5f..17732e7 100644 --- a/desk/app/nostrill.hoon +++ b/desk/app/nostrill.hoon @@ -1,7 +1,7 @@ /- sur=nostrill, nsur=nostr /+ lib=nostrill, nlib=nostr, sr=sortug, shim, dbug, muta=nostrill-mutations, jsonlib=json-nostrill, - trill=trill-post + trill=trill-post, comms=nostrill-comms /= web /web/router |% +$ versioned-state $%(state-0:sur) @@ -16,6 +16,7 @@ cards ~(. cards:lib bowl) mutat ~(. muta [state bowl]) shimm ~(. shim [state bowl]) + coms ~(. comms [state bowl]) ++ on-init ^- (quip card:agent:gall agent:gall) =/ default (default-state:lib bowl) @@ -34,17 +35,26 @@ ?- -.old-state %0 `this(state old-state) == + :: `this(state (default-state:lib bowl)) :: ++ on-poke |~ [=mark =vase] ^- (quip card:agent:gall agent:gall) |^ ?+ mark `this - %noun debug - %json on-ui + %noun handle-comms + %json on-ui %handle-http-request handle-shim == - :: handling shim events + ++ handle-comms + =/ pok (cast-poke:coms q.vase) + ?: ?=(%dbug -.pok) (debug +.pok) + =^ cs state + ?- -.pok + %req (handle-req:coms +.pok) + %res (handle-res:coms +.pok) + == + [cs this] ++ handle-shim =/ order !<(order:web vase) :: ~& request.req.order @@ -68,6 +78,7 @@ ?- -.u.upoke %keys handle-cycle-keys %fols (handle-fols +.u.upoke) + %begs (handle-begs +.u.upoke) %prof (handle-prof +.u.upoke) %post (handle-post +.u.upoke) %rela (handle-rela +.u.upoke) @@ -95,19 +106,39 @@ %rt `this %del `this == + ++ handle-begs |= poke=begs-poke:ui:sur + ?- -.poke + %feed + =/ cs ~ + [cs this] + %thread + =/ cs ~ + [cs this] + == ++ handle-fols |= poke=fols-poke:ui:sur - `this + ?- -.poke + %add `this + %del `this + == ++ handle-prof |= poke=prof-poke:ui:sur ?- -.poke %add - =. profiles (~(put by profiles) +<.poke +>.poke) + =. profiles (~(put by profiles) pub.i.keys +.poke) `this %del - =. profiles (~(del by profiles) +.poke) + =. profiles (~(del by profiles) pub.i.keys) `this == ++ handle-rela |= poke=relay-poke:ui:sur ?- -.poke + %add =. relays (~(put by relays) +.poke *relay-stats:nsur) + `this + %del =. relays (~(del by relays) +.poke) + `this + :: + %sync =^ cs state get-posts:shimm + [cs this] + :: %send =/ upoast (get-poast:mutat host.poke id.poke) ?~ upoast `this @@ -119,8 +150,7 @@ :: - ++ debug - =/ noun !<(* vase) + ++ debug |= noun=* ?+ noun `this %wtf =/ lol=(unit @) ~ @@ -211,12 +241,19 @@ :: ++ on-watch |= =(pole knot) - ?> .=(our.bowl src.bowl) + ~& on-watch=`path`pole ?+ pole !! + [%beg %feed ~] + :_ this give-feed:coms + [%beg %thread ids=@t ~] + =/ id (slaw:sr %uw ids.pole) + ?~ id ~& error-parsing-ted-id=pole `this + :_ this (give-ted:coms u.id) [%ui ~] + ?> .=(our.bowl src.bowl) :_ this =/ jon (state:en:jsonlib state) - [%give %fact ~ [%json !>(jon)]]^~ + [%give %fact ~[/ui] [%json !>(jon)]]^~ == :: ++ on-leave diff --git a/desk/lib/json/nostrill.hoon b/desk/lib/json/nostrill.hoon index bd34acc..b5a619c 100644 --- a/desk/lib/json/nostrill.hoon +++ b/desk/lib/json/nostrill.hoon @@ -1,4 +1,4 @@ -/- sur=nostrill, nsur=nostr, feed=trill-feed +/- sur=nostrill, nsur=nostr, feed=trill-feed, comms=nostrill-comms /+ sr=sortug, common=json-common, trill=json-trill, nostr=json-nostr |% ++ en @@ -70,9 +70,13 @@ %+ frond %fact %+ frond -.f ?- -.f - %post (postfact +.f) - %enga (enga +.f) + %nostr (en-nostr-feed +.f) + %post (postfact +.f) + %enga (enga +.f) == + ++ tedfact |= pf=post-fact:ui:sur ^- json + %+ frond -.pf + (post-wrapper +.pf) ++ postfact |= pf=post-fact:ui:sur ^- json %+ frond -.pf (post-wrapper +.pf) @@ -93,6 +97,21 @@ =. l ?~ relay.p l :_ l ['relay' %s u.relay.p] =. l ?~ pr.p l :_ l ['profile' (user-meta:en:nostr u.pr.p)] %- pairs l + + ++ beg-res |= =res:comms ^- json + %+ frond %begs %+ frond -.res + ?- -.res + %ok (resd +.res) + %ng [%s msg.res] + == + ++ resd |= rd=res-data:comms ^- json + %+ frond -.rd + ?- -.rd + %feed (feed-with-cursor:en:trill +.rd) + :: TODO wrap it for nostr shit + %thread (full-node:en:trill +.rd) + %prof (user-meta:en:nostr +.rd) + == -- ++ de =, dejs-soft:format @@ -102,6 +121,7 @@ %- of :~ keys+ul fols+ui-fols + begs+ui-begs prof+ui-prof post+ui-post rela+ui-relay @@ -111,15 +131,21 @@ add+hex:de:common del+hex:de:common == +++ ui-begs + %- of :~ + feed+(se:de:common %p) + thread+de-pid + == +++ de-pid + %- ot :~ + host+(se:de:common %p) + id+de-atom-id + == ++ ui-prof %- of :~ - add+add-prof - del+hex:de:common + add+user-meta:de:nostr + del+ul == -++ add-prof %- ot :~ - pubkey+hex:de:common - meta+user-meta:de:nostr -== ++ ui-post %- of :~ add+de-post @@ -138,9 +164,12 @@ == ++ ui-relay %- of :~ - send+de-relay + add+so + del+so + sync+ul + send+de-relay-send == -++ de-relay %- ot :~ +++ de-relay-send %- ot :~ host+(se:de:common %p) id+de-atom-id relays+(ar so) diff --git a/desk/lib/json/trill.hoon b/desk/lib/json/trill.hoon index efa4ffc..415d2f4 100644 --- a/desk/lib/json/trill.hoon +++ b/desk/lib/json/trill.hoon @@ -185,7 +185,35 @@ :~ ship+(patp:en:common ship.pid) id+(ud:en:common id.pid) == - :: + ++ full-node + |= p=full-node:post ^- json + %- pairs + :~ id+(ud:en:common id.p) + host+(patp:en:common host.p) + author+(patp:en:common author.p) + thread+(ud:en:common thread.p) + parent+?~(parent.p ~ (ud:en:common u.parent.p)) + contents+(content contents.p) + hash+(b64:en:common hash.p) + engagement+(engagement engagement.p) + children+(internal-graph children.p) + time+(time id.p) + == + ++ internal-graph + |= int=internal-graph:post ^- json + ?- -.int + %empty ~ + %full (full-graph +.int) + == + ++ full-graph + |= f=full-graph:post + ^- json + %- pairs + %+ turn (tap:form:post f) + |= [post-id=@da fn=full-node:post] + ^- [@ta json] + :- (crip (scow:sr %ud `@ud`post-id)) + (full-node fn) :: -- -- diff --git a/desk/lib/nostrill.hoon b/desk/lib/nostrill.hoon index 0570dbc..6d22adc 100644 --- a/desk/lib/nostrill.hoon +++ b/desk/lib/nostrill.hoon @@ -5,7 +5,7 @@ ++ default-state |= =bowl:gall ^- state:sur =/ s *state-0:sur =/ l public-relays:nsur - =/ l (scag 1 l) + :: =/ l (scag 1 l) :: =/ l ~['wss://relay.damus.io' 'wss://nos.lol'] =/ rl %+ turn l |= t=@t [t *relay-stats:nsur] :: =/ l ~[['wss://relay.damus.io' ~]] diff --git a/desk/lib/nostrill/comms.hoon b/desk/lib/nostrill/comms.hoon new file mode 100644 index 0000000..833c07d --- /dev/null +++ b/desk/lib/nostrill/comms.hoon @@ -0,0 +1,99 @@ +/- sur=nostrill, nsur=nostr, comms=nostrill-comms, feed=trill-feed +/+ js=json-nostr, sr=sortug, nlib=nostr, constants, gatelib=trill-gate, feedlib=trill-feed, jsonlib=json-nostrill +|_ [=state:sur =bowl:gall] +++ cast-poke + |= raw=* ^- poke:comms + ;; poke:comms raw +:: Req +++ handle-req |= =req:comms + ?- -.req + %feed handle-feed + %thread (handle-thread +.req) + %prof handle-prof + == +++ handle-feed + =/ can (can-access:gatelib src.bowl lock.feed-perms.state bowl) + ?. can + :: TODO keep track of the requests at the feed-perms struct + =/ crd (res-poke [%ng 'not allowed']) + :_ state :~(crd) + :: + =/ lp latest-page:feedlib + =/ lp2 lp(count backlog.feed-perms.state) + =/ =fc:feed (lp2 feed.state) + =/ crd (res-poke [%ok %feed fc]) + :_ state :~(crd) + +++ give-feed + ~& give-feed=src.bowl + =/ can (can-access:gatelib src.bowl lock.feed-perms.state bowl) + ?. can + :: TODO keep track of the requests at the feed-perms struct + (res-fact [%ng 'not allowed']) + :: + =/ lp latest-page:feedlib + =/ lp2 lp(count backlog.feed-perms.state) + =/ =fc:feed (lp2 feed.state) + (res-fact [%ok %feed fc]) + +++ give-ted |= id=@ + =/ ted (get:orm:feed feed.state id) + ?~ ted + (res-fact [%ng 'no such thread']) + =/ can (can-access:gatelib src.bowl read.u.ted bowl) + ?. can + (res-fact [%ng 'not allowed']) + :: + =/ fn (node-to-full:feedlib u.ted feed.state) + (res-fact [%ok %thread fn]) +:: +++ handle-prof + =/ can (can-access:gatelib src.bowl lock.feed-perms.state bowl) + ?. can + :: TODO keep track of the requests at the feed-perms struct + =/ crd (res-poke [%ng 'not allowed']) + :_ state :~(crd) + :: + :: TODO @p or keys... wat do + :: =/ up (~(get by profiles.state) our.bowl) + =/ up (~(get by profiles.state) pub.i.keys.state) + ?~ up + =/ crd (res-poke [%ng 'dont have one']) + :_ state :~(crd) + + =/ crd (res-poke [%ok %prof u.up]) + :_ state :~(crd) + +++ handle-thread |= id=@da + =/ ted (get:orm:feed feed.state id) + ?~ ted + =/ crd (res-poke [%ng 'no such thread']) + :_ state :~(crd) + =/ can (can-access:gatelib src.bowl read.u.ted bowl) + ?. can + =/ crd (res-poke [%ng 'not allowed']) + :_ state :~(crd) + :: + =/ fn (node-to-full:feedlib u.ted feed.state) + =/ crd (res-poke [%ok %thread fn]) + :_ state :~(crd) +:: res +++ handle-res |= =res:comms + `state +:: +++ res-poke |= =res:comms ^- card:agent:gall + =/ =poke:comms [%res res] + =/ cage [%noun !>(poke)] + [%pass /poke %agent [src.bowl dap.bowl] %poke cage] +++ res-fact |= =res:comms ^- (list card:agent:gall) + =/ paths ~[/beg/feed] + =/ =poke:comms [%res res] + ~& > giving-res-fact=res + =/ jon (beg-res:en:jsonlib res) + =/ cage [%json !>(jon)] + :~ + [%give %fact paths cage] + [%give %kick paths ~] + == + +-- diff --git a/desk/lib/nostrill/mutations.hoon b/desk/lib/nostrill/mutations.hoon index 4dda095..f493bcf 100644 --- a/desk/lib/nostrill/mutations.hoon +++ b/desk/lib/nostrill/mutations.hoon @@ -2,6 +2,7 @@ post=trill-post, gate=trill-gate, feed=trill-feed /+ appjs=json-nostrill, + lib=nostrill, njs=json-nostr, postlib=trill-post, shim, @@ -57,12 +58,6 @@ -:: ++ handle-shim-msg |= msg=res:shim:nsur -:: ^- (quip card _state) -:: ?- -.msg -:: %ws (handle-ws +.msg) -:: %http (handle-http +.msg) -:: == ++ handle-http |= [sub-id=@t msgs=(list relay-msg:nsur)] @@ -92,8 +87,10 @@ ++ handle-ws |= [relay=@t msg=relay-msg:nsur] =/ rs (~(get by relays.state) relay) - ?~ rs `state + ?~ rs :: TODO do we really + `state =^ cards state + ~& handle-ws=-.msg ?- -.msg %ok (handle-ok relay +.msg) %event @@ -102,11 +99,13 @@ %eose :: TODO do unsub for replaceable/addressable events - :: =/ creq (~(get by reqs.u.rs) +.msg) - :: ?~ creq `state + =/ creq (~(get by reqs.u.rs) +.msg) + ?~ creq `state :: =. reqs.u.rs (~(del by reqs.u.rs) +.msg) :: =. relays.state (~(put by relays.state) relay u.rs) - `state + =/ cardslib ~(. cards:lib bowl) + =/ c (update-ui:cardslib [%nostr nostr-feed.state]) + :_ state :~(c) %closed =. reqs.u.rs (~(del by reqs.u.rs) sub-id.msg) =. relays.state (~(put by relays.state) relay u.rs) `state diff --git a/desk/lib/shim.hoon b/desk/lib/shim.hoon index f2e0b8a..1b78f0a 100644 --- a/desk/lib/shim.hoon +++ b/desk/lib/shim.hoon @@ -13,7 +13,9 @@ ++ parse-body |= jstring=@t =/ ures (de:json:html jstring) ?~ ures ~ - (shim-res:de:js u.ures) + =/ ur (shim-res:de:js u.ures) + ?~ ur ~& >>> shim-msg-parsing-failed=jstring ~ + ur :: __ ++ get-req |= fs=(list filter:nsur) ^- [bulk-req:shim:nsur _state] @@ -74,8 +76,11 @@ |= req=bulk-req:shim:nsur ^- card:agent:gall =/ req-body (bulk-req:en:js req) :: ~& shim-req-json=(en:json:html req-body) + =/ host .^(hart:eyre %e /(scot %p our.bowl)/host/(scot %da now.bowl)) + =/ origin %- crip (head:en-purl:html host) =/ headers :~ [key='content-type' value='application/json'] + [key='origin' value=origin] == =/ =request:http [%'POST' url:shim:nsur headers `(json-body:web req-body)] =/ pat /shim @@ -86,8 +91,11 @@ ^- card:agent:gall =/ req-body (http-req:en:js req) :: ~& shim-req-json=(en:json:html req-body) + =/ host .^(hart:eyre %e /(scot %p our.bowl)/host/(scot %da now.bowl)) + =/ origin %- crip (head:en-purl:html host) =/ headers :~ [key='content-type' value='application/json'] + [key='origin' value=origin] == =/ =request:http [%'POST' url:shim:nsur headers `(json-body:web req-body)] [%pass /http/[sub-id.req] %arvo %k %fard dap.bowl %fetch %noun !>(request)] diff --git a/desk/lib/trill/feed.hoon b/desk/lib/trill/feed.hoon index c21feb3..721a596 100644 --- a/desk/lib/trill/feed.hoon +++ b/desk/lib/trill/feed.hoon @@ -1,14 +1,16 @@ -/- feed=trill-feed, sur=nostrill +/- feed=trill-feed, post=trill-post, sur=nostrill /+ sr=sortug, constants |% -++ latest-page |= f=feed:feed ^- fc:feed +++ latest-page +=/ count feed-page-size:constants +|= f=feed:feed ^- fc:feed =/ nodelist (tap:orm:feed f) - =/ subset (scag feed-page-size:constants nodelist) + =/ subset (scag count nodelist) ?~ subset [f ~ ~] - =/ start `id.i.subset + =/ start `-.i.subset =/ rev (flop subset) ?~ rev [f ~ ~] - =/ end `id.i.rev + =/ end `-.i.rev =/ nf (gas:orm:feed *feed:feed subset) [nf start end] :: @@ -16,20 +18,20 @@ =/ nodelist (tap:norm:sur f) =/ subset (scag feed-page-size:constants nodelist) ?~ subset [f ~ ~] - =/ start `id.i.subset + =/ start (some `@da`-.i.subset) =/ rev (flop subset) ?~ rev [f ~ ~] - =/ end `id.i.rev + =/ end (some `@da`-.i.rev) =/ nf (gas:norm:sur *nostr-feed:sur subset) [nf start end] :: :: NOTE START IS OLD, END IS NEW ++ subset +=/ count feed-page-size:constants |= [=fc:feed replies=? now=@da] ^- fc:feed ?: ?&(?=(%~ start.fc) ?=(%~ end.fc)) (latest-page feed.fc) - =/ count feed-page-size:constants =/ start ?~ start.fc 0 u.start.fc =/ end ?~ end.fc now u.end.fc =/ nodelist (tap:orm:feed feed.fc) @@ -43,9 +45,26 @@ == ?& (lte id start) (gte id end) == =/ thread-count (lent threads) - =/ result=(list [id:post post:post]) ?: newest (scag count threads) (flop (scag count (flop threads))) + :: TODO I remember something was weird about this + :: =/ result=(list [id:post post:post]) ?: newest (scag count threads) (flop (scag count (flop threads))) + =/ result=(list [id:post post:post]) (scag count threads) =/ cursors=[(unit @da) (unit @da)] ?~ result [~ ~] ?~ threads [~ ~] :- ?: .=((head result) (head threads)) ~ `id:(head result) ?: .=((rear result) (rear threads)) ~ `id:(rear result) [(gas:orm:feed *feed:feed result) -.cursors +.cursors] +:: posts +++ node-to-full +|= [p=post:post f=feed:feed] ^- full-node:post + p(children (convert-children children.p f)) +++ convert-children +|= [children=(set id:post) f=feed:feed] + ^- internal-graph:post + =/ g=full-graph:post %- ~(rep in children) + |= [=id:post acc=full-graph:post] + =/ n (get:orm:feed f id) + ?~ n acc + =/ full-node (node-to-full u.n f) + (put:form:post acc id full-node) + ?~ children [%empty ~] + :- %full g -- diff --git a/desk/lib/trill/gate.hoon b/desk/lib/trill/gate.hoon new file mode 100644 index 0000000..ebb78b8 --- /dev/null +++ b/desk/lib/trill/gate.hoon @@ -0,0 +1,79 @@ +/- gate=trill-gate +|% +++ mask-lock +|= =lock:gate ^- lock:gate + :* ?: public.rank.lock rank.lock [~ %| %|] + ?: public.luk.lock luk.lock [~ %| %|] + ?: public.ship.lock ship.lock [~ %| %|] + ?: public.tags.lock tags.lock [~ %| %|] + ?: public.custom.lock custom.lock [~ %|] + == +++ can-access +|= [=ship =lock:gate =bowl:gall] ^- ? + ?^ fn.custom.lock %- u.fn.custom.lock ship + =/ in-luk (~(has in caveats.ship.lock) ship) + =/ fu (sein:title our.bowl now.bowl ship) + =/ ye (sein:title our.bowl now.bowl fu) + =/ ze (sein:title our.bowl now.bowl ye) + =/ in-ship ?| + (~(has in caveats.luk.lock) fu) + (~(has in caveats.luk.lock) ye) + (~(has in caveats.luk.lock) ze) + == + =/ in-rank (~(has in caveats.rank.lock) (clan:title ship)) + :: =/ in-tags (~(has in (scry-pals-tags caveats.tags.lock)) ship) + =/ can |= [pit=? has=?] ^- ? ?: pit has !has + =/ as-ship (can locked.ship.lock in-ship) + =/ as-luk (can locked.ship.lock in-luk) + =/ as-rank (can locked.ship.lock in-rank) + ::=/ as-tags (can locked.ship.lock in-tags) + ?&(as-ship as-luk as-rank) + +++ scry-pals-tags +|= tags=(set @t) ^- (set @p) + :: .^() + ~ +++ apply-change +|= [=lock:gate =change:gate] ^- lock:gate + ?- -.change + %set-rank lock(rank +.change) + %set-luk lock(luk +.change) + %set-ship lock(ship +.change) + %set-tags lock(tags +.change) + %set-custom lock ::TODO + == +++ open-all +|= =lock:gate ^- lock:gate + %= lock + rank rank.lock(locked .n) + luk luk.lock(locked .n) + ship ship.lock(locked .n) + tags tags.lock(locked .n) + == +++ lock-all +|= =lock:gate ^- lock:gate +%= lock +rank rank.lock(locked .y) +luk luk.lock(locked .y) +ship ship.lock(locked .y) +tags tags.lock(locked .y) +== +++ toggle-rank +|= [r=rank:title setting=[caveats=(set rank:title) locked=? public=?]] + =/ new-caveats=(set rank:title) ?: locked.setting + (~(put in caveats.setting) r) + (~(del in caveats.setting) r) + setting(caveats new-caveats) +++ toggle-ship +|= [s=ship setting=[caveats=(set ship) locked=? public=?]] + =/ new-caveats=(set ship) ?: locked.setting + (~(put in caveats.setting) s) + (~(del in caveats.setting) s) + setting(caveats new-caveats) +++ toggle-tag +|= [t=@t setting=[caveats=(set @t) locked=? public=?]] + =/ new-caveats=(set @t) ?: locked.setting + (~(put in caveats.setting) t) + (~(del in caveats.setting) t) + setting(caveats new-caveats) +-- diff --git a/desk/mar/json.hoon b/desk/mar/json.hoon new file mode 100644 index 0000000..7d6fcbf --- /dev/null +++ b/desk/mar/json.hoon @@ -0,0 +1,26 @@ +:: +:::: /hoon/json/mar + :: +/? 310 + :: +:::: compute + :: +=, eyre +=, format +=, html +|_ jon=^json +:: +++ grow :: convert to + |% + ++ mime [/application/json (as-octs:mimes -:txt)] :: convert to %mime + ++ txt [(en:json jon)]~ + -- +++ grab + |% :: convert from + ++ mime |=([p=mite q=octs] (fall (de:json (@t q.q)) *^json)) + ++ noun ^json :: clam from %noun + ++ numb numb:enjs + ++ time time:enjs + -- +++ grad %mime +-- diff --git a/desk/mar/tang.hoon b/desk/mar/tang.hoon new file mode 100644 index 0000000..9fdd314 --- /dev/null +++ b/desk/mar/tang.hoon @@ -0,0 +1,25 @@ +:: +:::: /hoon/tang/mar + :: +/? 310 +:: +=, format +|_ tan=(list tank) +++ grad %noun +++ grow + |% + ++ noun tan + ++ json + =/ result=(each (list ^json) tang) + (mule |.((turn tan tank:enjs:format))) + ?- -.result + %& a+p.result + %| a+[a+[%s '[[output rendering error]]']~]~ + == + -- +++ grab :: convert from + |% + ++ noun (list ^tank) :: clam from %noun + ++ tank |=(a=^tank [a]~) + -- +-- diff --git a/desk/sur/nostr.hoon b/desk/sur/nostr.hoon index ff5ad6b..a1b54d1 100644 --- a/desk/sur/nostr.hoon +++ b/desk/sur/nostr.hoon @@ -77,10 +77,12 @@ $% [%event sub-id=@t =event] :: https://github.com/sesseor/nostr-relays-list/blob/main/relays.txt ++ public-relays ^- (list @t) - :~ 'wss://nos.lol' - :: 'wss://relay.damus.io' - :: 'wss://nostr.wine' - :: 'wss://offchain.pub' + :~ + 'wss://n.urbit.cloud' + 'wss://nos.lol' + 'wss://relay.damus.io' + 'wss://nostr.wine' + 'wss://offchain.pub' == :: 'wss://knostr.neutrine.com' -- diff --git a/desk/sur/nostrill.hoon b/desk/sur/nostrill.hoon index a9ef8f3..70ce480 100644 --- a/desk/sur/nostrill.hoon +++ b/desk/sur/nostrill.hoon @@ -1,4 +1,4 @@ -/- trill=trill-feed, tp=trill-post, nostr +/- nostr, trill=trill-feed, tp=trill-post, gate=trill-gate |% +$ state state-0 +$ state-0 @@ -8,6 +8,7 @@ keys=(lest keys:nostr) :: cycled, i.keys is current one :: own feed feed=feed:trill + feed-perms=gate:gate :: nostr feed from relays =nostr-feed :: profiles @@ -34,12 +35,17 @@ $: pub=(unit @ux) |% +$ poke $% [%fols fols-poke] + [%begs begs-poke] [%post post-poke] :: [%reac reac-poke] [%prof prof-poke] [%keys ~] :: cycle-keys [%rela relay-poke] == + +$ begs-poke + $% [%feed p=@p] + [%thread p=@p id=@da] + == +$ post-poke $% [%add content=@t] [%rt id=@ux pubkey=@ux relay=@t] :: NIP-18 @@ -50,15 +56,21 @@ $: pub=(unit @ux) [%del pubkey=@ux] == +$ prof-poke - $% [%add pubkey=@ux meta=user-meta:nostr] - [%del pubkey=@ux] + $% [%add meta=user-meta:nostr] + [%del ~] == +$ relay-poke - $% [%send host=@p id=@ relays=(list @t)] + $% [%add p=@t] + [%del p=@t] + :: + [%sync ~] + :: send event for... relaying + [%send host=@p id=@ relays=(list @t)] == :: facts +$ fact - $% [%post post-fact] + $% [%nostr feed=nostr-feed] + [%post post-fact] [%enga p=post-wrapper reaction=*] == +$ post-fact diff --git a/desk/sur/nostrill/comms.hoon b/desk/sur/nostrill/comms.hoon new file mode 100644 index 0000000..d3dc8e1 --- /dev/null +++ b/desk/sur/nostrill/comms.hoon @@ -0,0 +1,22 @@ +/- sur=nostrill, nsur=nostr, feed=trill-feed, post=trill-post +|% ++$ poke + $% [%req req] + [%res res] + [%dbug *] + == ++$ req + $% [%feed ~] + [%thread id=@da] + [%prof ~] + == ++$ res + $% [%ok p=res-data] + [%ng msg=@t] + == ++$ res-data + $% [%feed =fc:feed] + [%thread p=full-node:post] + [%prof p=user-meta:nsur] + == +-- diff --git a/desk/ted/beg.hoon b/desk/ted/beg.hoon new file mode 100644 index 0000000..2cabbea --- /dev/null +++ b/desk/ted/beg.hoon @@ -0,0 +1,31 @@ +/- spider +/+ strandio, jsonlib=json-nostrill +=, strand=strand:spider +=, strand-fail=strand-fail:libstrand:spider +^- thread:spider +|= arg=vase + =/ m (strand ,vase) ^- form:m + |^ + =/ ujon !<((unit json) arg) + :: ~& ujon=ujon + ?~ ujon (pure:m !>(bail)) + =/ req (ui:de:jsonlib u.ujon) + ?~ req (pure:m !>(bail)) + ?. ?=(%begs -.u.req) (pure:m !>(bail)) + ?- +<.u.req + %feed + ;< =bowl:spider bind:m get-bowl:strandio + =/ desk q.byk.bowl + ~& dock=[+>.u.req desk] + ;< =cage bind:m (watch-one:strandio /beg/feed [+>.u.req desk] /beg/feed) + ~& > watch-cage=-.cage + =/ j !<(json +.cage) + (pure:m !>(j)) + + %thread + (pure:m !>(bail)) + == + ++ bail ^- json + %+ frond:enjs:format %error + s+'error' + -- |