diff --git a/pkg/garden/app/hark-store.hoon b/pkg/garden/app/hark-store.hoon index 3472fe8fa..adef676f1 100644 --- a/pkg/garden/app/hark-store.hoon +++ b/pkg/garden/app/hark-store.hoon @@ -25,6 +25,7 @@ state-6 state-7 state-8 + state-9 == :: +$ base-state @@ -56,13 +57,16 @@ +$ state-8 [%8 base-state] :: ++$ state-9 + [%9 base-state] +:: :: +$ cached-state $: by-place=(jug place:store [=lid:store =path]) ~ == +$ inflated-state - [state-8 cached-state] + [state-9 cached-state] :: ++ orm ((ordered-map @da timebox:store) gth) -- @@ -91,31 +95,20 @@ =/ old !<(versioned-state old-vase) =| cards=(list card) - |^ ^- (quip card _this) - ?: ?=(%8 -.old) + |- ^- (quip card _this) + ?+ -.old + :: pre-dist migration + :_ this + (poke-our:pass %hark-graph-hook hark-graph-migrate+old-vase)^~ + :: + %9 =. -.state old - =. +.state inflate + =. +.state inflate:ha :_(this (flop cards)) :: - :_ this - (poke-our:pass %hark-graph-hook hark-graph-migrate+old-vase)^~ - :: - ++ index-timebox - |= [=lid:store =timebox:store out=_by-place] - ^+ by-place - %+ roll ~(tap by timebox) - |= [[=bin:store =notification:store] out=_out] - (~(put ju out) place.bin [lid path.bin]) - :: - ++ inflate - =. by-place (index-timebox seen+~ seen by-place) - =. by-place (index-timebox unseen+~ unseen by-place) - =. by-place - %+ roll (tap:orm archive) - |= [[=time =timebox:store] out=_by-place] - (index-timebox archive/time timebox out) - +.state - -- + %8 + $(-.old %9, archive.old *archive:store) + == :: ++ on-watch |= =path @@ -178,6 +171,10 @@ ?+ val ~|(%bad-noun-poke !!) %print ~&(+.state [~ state]) %clear [~ state(. *inflated-state)] + %sane + ~& +.state + ~& inflate + ?>(=(+.state inflate) `state) == :: ++ poke-us @@ -281,14 +278,12 @@ ^+ poke-core =. poke-core (emit (fact:io hark-update+!>([%add-note bin body]) /notes ~)) - =. by-place - (~(put ju by-place) place.bin unseen+~ path.bin) =/ existing-notif (~(gut by unseen) bin *notification:store) =/ new=notification:store [now.bowl bin [body body.existing-notif]] - =. unseen - (~(put by unseen) bin new) + =. poke-core + (put-lid unseen/~ bin new) (give %added new) :: ++ del-place @@ -312,25 +307,19 @@ =/ =notification:store (need (get-lid lid bin)) =. poke-core (del-lid lid bin) =. poke-core (put-lid archive+now.bowl bin notification) - =? poke-core ?=(%unseen -.lid) - ?~ n=(get-lid seen+~ bin) poke-core - =. archive - %^ ~(job re archive) now.bowl bin - |= og=(unit notification:store) - (merge-notification og u.n) - poke-core (give %archived now.bowl lid notification) :: ++ read-note |= =bin:store =/ =notification:store (~(got by unseen) bin) - =. unseen - (~(del by unseen) bin) + =. poke-core + (del-lid unseen/~ bin) =/ =time (fall timebox:(gut-place place.bin) now.bowl) =. date.notification time - =. archive (~(put re archive) time bin notification) + =. poke-core + (put-lid archive/time bin notification) (give %note-read time bin) :: :: @@ -412,10 +401,11 @@ =/ =time (~(gut by half-open) bin now.bowl) =? half-open !(~(has by half-open) bin) (~(put by half-open) bin now.bowl) - =. archive - %^ ~(job re archive) time bin - |=(n=(unit notification:store) (merge-notification n note)) - =. by-place (~(put ju by-place) place [archive/now.bowl path.bin]) + =/ existing (get-lid archive/time bin) + =/ new (merge-notification existing note) + =. poke-core + (put-lid archive/time bin new) + =. poke-core (del-lid lid bin) =. poke-core (give %archived now.bowl unseen+~ (~(got re archive) time bin)) =. poke-core (give %archived now.bowl seen+~ (~(got re archive) time bin)) $(bins t.bins) @@ -447,18 +437,22 @@ poke-core :: ++ opened - =. seen - %- ~(gas by *timebox:store) - %+ murn ~(tap in (~(uni in ~(key by seen)) ~(key by unseen))) - |= =bin:store - =/ se (~(get by seen) bin) - =/ un (~(get by unseen) bin) - ?~ un - ?~(se ~ `[bin u.se]) - `[bin (merge-notification se u.un)] - =. unseen ~ =. poke-core (turn-places |=(=stats:store stats(timebox ~))) - (give %opened ~) + =. poke-core (give %opened ~) + %+ roll ~(tap in ~(key by unseen)) + |= [=bin:store out=_poke-core] + (opened-note:out bin) + :: + ++ opened-note + |= =bin:store + ^+ poke-core + =/ old + (~(got by unseen) bin) + =. poke-core + (del-lid unseen/~ bin) + =/ se (~(get by seen) bin) + %^ put-lid seen/~ bin + (merge-notification se old) :: ++ archive-all @@ -483,8 +477,13 @@ :: ++ get-lid |= [=lid:store =bin:store] - =/ =timebox:store ?:(?=(%unseen -.lid) unseen seen) - (~(get by timebox) bin) + =; =timebox:store + (~(get by timebox) bin) + ?- -.lid + %unseen unseen + %seen seen + %archive (fall (get:orm archive time.lid) *timebox:store) + == :: ++ merge-notification |= [existing=(unit notification:store) new=notification:store] @@ -522,4 +521,21 @@ ^- (list [@da timebox:store]) %+ skim (tap:orm archive) |=([@da =timebox:store] !=(~(wyt by timebox) 0)) +:: +++ inflate + =. by-place ~ + =. by-place (index-timebox seen+~ seen by-place) + =. by-place (index-timebox unseen+~ unseen by-place) + =. by-place + %+ roll (tap:orm archive) + |= [[=time =timebox:store] out=_by-place] + (index-timebox archive/time timebox out) + +.state +:: +++ index-timebox + |= [=lid:store =timebox:store out=_by-place] + ^+ by-place + %+ roll ~(tap by timebox) + |= [[=bin:store =notification:store] out=_out] + (~(put ju out) place.bin [lid path.bin]) -- diff --git a/pkg/garden/tests/app/hark-store.hoon b/pkg/garden/tests/app/hark-store.hoon new file mode 100644 index 000000000..fe06b6d01 --- /dev/null +++ b/pkg/garden/tests/app/hark-store.hoon @@ -0,0 +1,90 @@ +/- hark=hark-store +/+ *test, re=hark-unreads +/= agent /app/hark-store +|% +++ place + ^- place:hark + [%landscape /graph/~zod/test] +:: +++ bin + ^- bin:hark + [/ place] + +:: +++ body + |= run=@ + :* ~[text/'Title'] + ~[text/(crip "Contents {(scow %ud run)}")] + `time`(add (mul ~s1 run) *time) + / + /test + == +:: +++ add-note + |= run=@ + ^- action:hark + [%add-note bin (body run)] +:: +++ read-count + ^- action:hark + [%read-count place] +:: ++$ state + $: %8 + places=(map place:hark stats:hark) + seen=timebox:hark + unseen=timebox:hark + =archive:hark + half-open=(map bin:hark @da) + == +++ bowl + |= run=@ud + ^- bowl:gall + :* [~zod ~zod %hark-store] + [~ ~] + [run `@uvJ`(shax run) (add (mul run ~s1) *time) [~zod %garden ud+run]] + == +-- +|% +:: +++ test-half-open + =| run=@ud + =^ mov1 agent + (~(on-poke agent (bowl run)) %hark-action !>((add-note run))) + =^ mova agent + (~(on-poke agent (bowl run)) %noun !>(%sane)) + =. run +(run) + =^ mov2 agent + (~(on-poke agent (bowl run)) %hark-action !>(read-count)) + =^ mov3 agent + (~(on-poke agent (bowl run)) %noun !>(%sane)) + =/ expected-archive=notification:hark + [(add *time (mul ~s1 0)) bin ~[(body 0)]] + =+ !<(=state on-save:agent) + =/ actual-archive=notification:hark + (~(got re archive.state) (add *time ~s1) bin) + (expect-eq !>(expected-archive) !>(actual-archive)) +:: +++ test-half-open-double + =| run=@ud + =^ mov1 agent + (~(on-poke agent (bowl run)) %hark-action !>((add-note run))) + =. run +(run) + =^ mov2 agent + (~(on-poke agent (bowl run)) %hark-action !>(read-count)) + =. run +(run) + =^ mov3 agent + (~(on-poke agent (bowl run)) %hark-action !>((add-note run))) + =. run +(run) + =^ mov4 agent + (~(on-poke agent (bowl run)) %hark-action !>(read-count)) + =. run +(run) + =^ mov5 agent + (~(on-poke agent (bowl run)) %noun !>(%sane)) + =/ expected-archive=notification:hark + [(add *time (mul ~s1 2)) bin ~[(body 2) (body 0)]] + =+ !<(=state on-save:agent) + =/ actual-archive=notification:hark + (~(got re archive.state) (add *time ~s1) bin) + (expect-eq !>(expected-archive) !>(actual-archive)) +-- diff --git a/pkg/landscape/app/hark-graph-hook.hoon b/pkg/landscape/app/hark-graph-hook.hoon index b9863bd70..7417031b2 100644 --- a/pkg/landscape/app/hark-graph-hook.hoon +++ b/pkg/landscape/app/hark-graph-hook.hoon @@ -12,6 +12,7 @@ +$ versioned-state $% state-0 state-1 + state-2 == :: +$ state-0 @@ -33,25 +34,11 @@ $: watching=(set [resource index:post]) mentions=_& watch-on-self=_& - places=(map resource place:store) + places=(jug resource place:store) == -:: -++ scry - |* [[our=@p now=@da] =mold p=path] - ?> ?=(^ p) - ~! p - ?> ?=(^ t.p) - .^(mold i.p (scot %p our) i.t.p (scot %da now) t.t.p) -:: -++ scry-notif-conversion - |= [[our=@p now=@da] desk=term =mark] - ^- $-(indexed-post:graph-store $-(cord (unit notif-kind:hook))) - %^ scry [our now] - $-(indexed-post:graph-store $-(cord (unit notif-kind:hook))) - /cf/[desk]/[mark]/notification-kind -- :: -=| state-1 +=| state-2 =* state - :: =< @@ -78,21 +65,26 @@ ^- (quip card _this) =+ !<(old=versioned-state vase) =| cards=(list card) - =. cards [watch-graph:ha cards] |- - ?: ?=(%0 -.old) - %_ $ - -.old %1 - :: - cards - :_ cards - [%pass / %agent [our dap]:bowl %poke noun+!>(%rewatch-dms)] + ?- -.old + ?(%1 %0) + %_ $ + :: + old + %* . *state-2 + watching watching.old + mentions mentions.old + watch-on-self watch-on-self.old + == == - :_ this(state old) - =. cards (flop cards) - ?: (~(has by wex.bowl) [/graph our.bowl %graph-store]) - cards - [watch-graph:ha cards] + :: + %2 + :_ this(state old) + =. cards (flop cards) + ?: (~(has by wex.bowl) [/graph our.bowl %graph-store]) + cards + [watch-graph:ha cards] + == :: ++ on-watch |= =path @@ -173,14 +165,6 @@ ++ poke-noun |= non=* [~ state] -:: ?> ?=(%rewatch-dms non) -:: =/ graphs=(list resource) -:: ~(tap in get-keys:gra) -:: %_ state -:: watching -:: %- ~(gas in watching) -:: (murn graphs |=(rid=resource ?:((should-watch:ha rid) `[rid ~] ~))) -:: == :: ++ hark-graph-hook-action |= =action:hook @@ -258,24 +242,9 @@ :: TODO: rethink this ++ remove-posts |= [rid=resource indices=(set index:graph-store)] - =/ to-remove - %- ~(gas by *(set [resource index:graph-store])) - (turn ~(tap in indices) (lead rid)) - :_ state(watching (~(dif in watching) to-remove)) - =/ convert (get-conversion:ha rid '') - %+ roll - ~(tap in indices) - |= [=index:graph-store out=(list card)] - =| =indexed-post:graph-store - =. index.p.indexed-post index - =/ notif-kind=(unit notif-kind:hook) - (convert indexed-post) - ?~ notif-kind out - =/ =place:store - (get-place rid index) - ?. ?=(%each mode.u.notif-kind) out - :_ out - (poke-hark %read-each place index) + =/ cor=(unit _handle-update:ha) (abed:handle-update:ha rid) + ?~ cor `state + abet:remove-posts:u.cor :: ++ poke-hark |= =action:store @@ -289,9 +258,14 @@ %+ skim ~(tap in watching) |= [r=resource idx=index:graph-store] =(r rid) - :_ state(watching (~(dif in watching) unwatched)) - ^- (list card) - ~ + :_ + %_ state + watching (~(dif in watching) unwatched) + places (~(del by places) rid) + == + %+ turn ~(tap in (~(get ju places) rid)) + |= =place:store + (poke-hark %del-place place) :: XX: fix :: ++ add-graph @@ -305,17 +279,16 @@ (peek-association:met %graph rid) =^ cards state (check-nodes (drop node) rid assoc) - ?. (should-watch:ha rid assoc) - [cards state] - :_ state(watching (~(put in watching) [rid ~])) - (weld cards (give:ha ~[/updates] %listen [rid ~])) + [cards state] :: ++ check-nodes |= $: nodes=(list node:graph-store) rid=resource assoc=(unit association:metadata) == - abet:check:(abed:handle-update:ha rid nodes) + =/ cor=(unit _handle-update) (abed:handle-update:ha rid) + ?~ cor `state + abet:add-nodes:u.cor -- :: ++ on-peek on-peek:def @@ -342,6 +315,12 @@ ^- path (turn index (cork (cury scot %ui) (cury rsh 4))) :: +++ get-place + |= [rid=resource =index:graph-store] + :- q.byk.bowl + %+ welp /graph/(scot %p entity.rid)/[name.rid] + (graph-index-to-path index) +:: ++ summarize |= contents=(list content:post) %+ rap 3 @@ -356,29 +335,6 @@ %mention (scot %p ship.content) == :: -++ get-place - |= [rid=resource =index:graph-store] - :- q.byk.bowl - (welp /graph/(scot %p entity.rid)/[name.rid] (graph-index-to-path index)) -:: -++ get-bin - |= [rid=resource parent=index:graph-store is-mention=?] - ^- bin:store - [?:(is-mention /mention /) (get-place rid parent)] -:: -++ get-conversion - |= [rid=resource title=cord] - ^- $-(indexed-post:graph-store (unit notif-kind:hook)) - =+ %^ scry [our now]:bowl - ,mark=(unit mark) - /gx/graph-store/graph/(scot %p entity.rid)/[name.rid]/mark/noun - ?~ mark - |=(=indexed-post:graph-store ~) - =/ f=$-(indexed-post:graph-store $-(cord (unit notif-kind:hook))) - (scry-notif-conversion [our now]:bowl q.byk.bowl u.mark) - |= =indexed-post:graph-store - ((f indexed-post) title) -:: ++ give |= [paths=(list path) =update:hook] ^- (list card) @@ -394,44 +350,44 @@ =- [%pass / %agent [our.bowl %hark-store] %poke -] hark-action+!>(action) :: -++ is-mention - |= contents=(list content:post) - ^- ? - ?. mentions %.n - ?~ contents %.n - ?. ?=(%mention -.i.contents) - $(contents t.contents) - ?: =(our.bowl ship.i.contents) - %.y - $(contents t.contents) -:: -++ should-watch - |= [rid=resource assoc=(unit association:metadata)] - ^- ? - ?~ assoc - %.y - &(watch-on-self =(our.bowl entity.rid)) +++ flatten-nodes + |= nodes=(list node:graph-store) + %+ roll nodes + |= [=node:graph-store out=(list node:graph-store)] + ^- (list node:graph-store) + %+ welp [node(children empty/~) out] + ?: ?=(%empty -.children.node) ~ + (flatten-nodes (turn (bap:orm:graph-store p.children.node) tail)) :: ++ handle-update |_ $: rid=resource :: input updates=(list node:graph-store) - mark=(unit mark) + =mark hark-pokes=(list action:store) :: output new-watches=(list index:graph-store) == ++ update-core . :: ++ abed - |= [r=resource upds=(list node:graph-store)] + |= r=resource + ^- (unit _update-core) =/ m=(unit ^mark) (get-mark:gra r) - update-core(rid r, updates upds, mark m) + ?~ m ~ + :- ~ + %_ update-core + rid r + mark u.m + == :: ++ title - ~+ title:(fall (peek-metadatum:met %graph rid) *metadatum:metadata) - :: - ++ get-conversion - ~+ (^get-conversion rid title) + ~+ ^- cord + =/ gra-met (peek-association:met %graph rid) + ?~ gra-met (crip "{(scow %p entity.rid)}/{(trip name.rid)}") + =/ grp-met (peek-association:met %groups group.u.gra-met) + =* gra-title title.metadatum.u.gra-met + ?~ grp-met gra-title + (rap 3 title.metadatum.u.grp-met ': ' gra-title ~) :: ++ abet ^- (quip card _state) @@ -447,101 +403,211 @@ ^+ update-core update-core(hark-pokes [action hark-pokes]) :: - ++ new-watch - |= [=index:graph-store =watch-for:hook =index-len:hook] - =? new-watches =(%siblings watch-for) - [(scag parent.index-len index) new-watches] - =? new-watches =(%children watch-for) - [(scag self.index-len index) new-watches] - update-core - :: - ++ check + ++ add-nodes + |= updates=(list node:graph-store) + =. updates (flatten-nodes updates) |- ^+ update-core - ?~ updates - update-core - =/ core=_update-core - (check-node i.updates) - =. updates.core t.updates - $(update-core core) + ?~ updates update-core + =/ cor=(unit _post-core) + (abed:post-core i.updates) + ?~ cor $(updates t.updates) + $(updates t.updates, update-core abet:added:u.cor) :: - ++ check-node-children - |= =node:graph-store - ^+ update-core - ?: ?=(%empty -.children.node) - update-core - =/ children=(list [=atom =node:graph-store]) - (tap:orm:graph-store p.children.node) + ++ remove-posts + |= indices=(list index:graph-store) |- ^+ update-core - ?~ children - update-core - =. update-core (check-node node.i.children) - $(children t.children) + ?~ indices update-core + =| =post:graph-store + =. index.post i.indices + =/ =node:graph-store + [&/post empty/~] + =/ cor=(unit _post-core) + (abed:post-core node) + ?~ cor $(indices t.indices) + $(indices t.indices, update-core abet:removed:u.cor) :: - ++ check-node - |= =node:graph-store - ^+ update-core - =. update-core (check-node-children node) - ?: ?=(%| -.post.node) + ++ post-core + |_ [kind=notif-kind:hook =post:graph-store] + ++ post-core . + ++ abet + =. places (~(put ju places) rid place) update-core - ::?~ mark update-core - =* pos p.post.node - =/ notif-kind=(unit notif-kind:hook) - (get-conversion [0 pos]) - ?~ notif-kind - update-core - =* not-kind u.notif-kind - =/ parent=index:post - (scag parent.index-len.not-kind index.pos) - =/ is-mention (is-mention contents.pos) - =/ =bin:store - (get-bin rid parent is-mention) - ?: =(our.bowl author.pos) - (self-post node bin u.notif-kind) - =. update-core - %^ update-unread-count u.notif-kind bin - (scag self.index-len.not-kind index.pos) - =? update-core - ?| is-mention - (~(has in watching) [rid parent]) - =(mark `%graph-validator-dm) - == - =/ link=path - (welp /(fall mark '')/(scot %p entity.rid)/[name.rid] (graph-index-to-path index.pos)) + ++ abed + |= =node:graph-store + ^- (unit _post-core) + ?: ?=(%| -.post.node) ~ + =/ not-kind (notif-kind p.post.node) + ?~ not-kind ~ + `post-core(post p.post.node, kind u.not-kind) + ++ parent-idx + (scag parent.index-len:kind index.post) + ++ self-idx + (scag self.index-len:kind index.post) + ++ is-mention + =/ contents contents.post + |- ^- ? + ?. mentions %.n + ?~ contents %.n + ?. ?=(%mention -.i.contents) + $(contents t.contents) + ?: =(our.bowl ship.i.contents) + %.y + $(contents t.contents) + :: + ++ bin + ^- bin:store + [?:(is-mention /mention /) place] + :: + ++ place + ^- place:store + (get-place rid index.post) + :: + ++ should-notify + ?| is-mention + (~(has in watching) [rid parent-idx]) + =(mark `%graph-validator-dm) + == + :: + ++ add-note + ^+ post-core + ?. should-notify post-core =/ title=(list content:store) - ?. is-mention title.not-kind + ?. is-mention title.kind ~[text/(rap 3 'You were mentioned in ' title ~)] + =/ link=path + %+ welp /[mark]/(scot %p entity.rid)/[name.rid] + (graph-index-to-path index.post) =/ =body:store - [title body.not-kind now.bowl path.bin link] - (add-unread bin body) - update-core - :: - :: - ++ update-unread-count - |= [=notif-kind:hook =bin:store =index:graph-store] - ?- mode.notif-kind - %count (hark %unread-count place.bin %.y 1) - %each (hark %unread-each place.bin /(rsh 4 (scot %ui (rear index)))) - %none update-core - == - :: - :: - ++ self-post - |= $: =node:graph-store - =bin:store - =notif-kind:hook + [title body.kind now.bowl path:bin link] + post-core(update-core (hark %add-note bin body)) + :: + ++ added-unread + ^+ post-core + %_ post-core + update-core + ?- mode.kind + %count (hark %unread-count place %.y 1) + %each (hark %unread-each place /(rsh 4 (scot %ui (rear index.post)))) + %none update-core == - ^+ update-core - ?> ?=(%& -.post.node) - =. update-core - (hark %saw-place place.bin `now.bowl) - =? update-core ?=(%count mode.notif-kind) - (hark %read-count place.bin) - =? update-core watch-on-self - (new-watch index.p.post.node [watch-for index-len]:notif-kind) - update-core + == + :: + ++ removed-unread + ^+ post-core + %_ post-core + update-core + ?- mode.kind + %count (hark %unread-count place %.n 1) + %each (hark %read-each place /(rsh 4 (scot %ui (rear index.post)))) + %none update-core + == + == + :: + ++ added + ^+ post-core + ?: =(our.bowl author.post) self-post + => added-unread + add-note + :: + :: TODO: delete notifications? + ++ removed + ^+ post-core + removed-unread + :: + ++ self-post + ^+ post-core + =. update-core + (hark %saw-place place ~) + =? update-core ?=(%count mode.kind) + (hark %read-count place.bin) + new-watch + :: + ++ new-watch + ^+ post-core + ?. watch-on-self post-core + =/ watch-for watch-for:kind + =? new-watches =(%siblings watch-for) + [parent-idx new-watches] + =? new-watches =(%children watch-for) + [self-idx new-watches] + post-core + -- + :: + ++ notif-kind + |= p=post:graph-store + ^- (unit notif-kind:hook) + |^ + ?+ mark ~ + %graph-validator-chat chat + %graph-validator-publish publish + %graph-validator-link link + %graph-validator-dm dm + == + :: + ++ chat + ?. ?=([@ ~] index.p) ~ + :- ~ + :* ~[text+(rap 3 'New messages in ' title ~)] + [ship+author.p text+': ' (hark-contents:graph-store contents.p)] + [0 1] %count %none + == + :: + ++ publish + ^- (unit notif-kind:hook) + ?+ index.p ~ + [@ %1 %1 ~] + :- ~ + :* [%text (rap 3 'New notes in ' title ~)]~ + ~[(hark-content:graph-store (snag 0 contents.p)) text+' by ' ship+author.p] + [0 1] %each %children + == + :: + [@ %2 @ %1 ~] + :- ~ + :* [%text (rap 3 'New comments in ' title ~)]~ + [ship+author.p text+': ' (hark-contents:graph-store contents.p)] + [1 3] %count %siblings + == + == + :: + ++ link + ^- (unit notif-kind:hook) + ?+ index.p ~ + [@ ~] + :- ~ + :* [text+(rap 3 'New links in ' title ~)]~ + [ship+author.p text+': ' (hark-contents:graph-store contents.p)] + [0 1] %each %children + == + :: + [@ @ %1 ~] + :- ~ + :* [text+(rap 3 'New comments on a post in ' title ~)]~ + [ship+author.p text+': ' (hark-contents:graph-store contents.p)] + [1 2] %count %siblings + == + == + :: + ++ post + =/ len (lent index.p) + =/ =mode:hook + ?:(=(1 len) %count %none) + :- ~ + :* ~[text+(rap 3 'Your post in ' title ' received replies ' ~)] + [ship+author.p text+': ' (hark-contents:graph-store contents.p)] + [(dec len) len] mode %children + == + :: + ++ dm + ?+ index.p ~ + [@ @ ~] + :- ~ + :* ~[text+'New messages from ' ship+author.p] + (hark-contents:graph-store contents.p) + [1 2] %count %none + == + == + -- :: - ++ add-unread - |= [=bin:store =body:store] - (hark %add-note bin body) -- --