From 2836cf3f08ed66b69a4ec16ecb91a1ab673496f5 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Tue, 3 Dec 2019 12:10:50 -0800 Subject: [PATCH 01/20] reworked file ingestion to not use ford --- pkg/arvo/app/publish.hoon | 1963 ++++++----------------------- pkg/arvo/lib/publish.hoon | 42 +- pkg/arvo/mar/publish/comment.hoon | 26 +- pkg/arvo/sur/publish.hoon | 15 +- 4 files changed, 378 insertions(+), 1668 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index 9dd9d9424c..0c2be5b17f 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -1,8 +1,6 @@ :: -:: /app/publish.hoon -:: /- *publish -/+ *server, *publish, default-agent, verb +/+ *server, *publish, cram, default-agent :: /= index /^ $-(json manx) @@ -33,185 +31,404 @@ /^ (map knot @) /: /===/app/publish/img /_ /png/ :: -!: |% -:: -+$ versioned-state - $% [%0 state-zero] - == -:: -+$ state-zero - $: pubs=(map @tas collection) - subs=(map [ship @tas] collection) - awaiting=(map @tas [builds=(set wire) partial=(unit delta)]) - latest=(list [who=ship coll=@tas post=@tas]) - unread=(set [who=ship coll=@tas post=@tas]) - invites=(map [who=ship coll=@tas] title=@t) - == -:: +$ card card:agent:gall :: ++$ comment + $: author=@p + date-created=@da + last-edit=@da + content=@t + == +:: ++$ note + $: author=@p + title=@t + filename=@tas + date-created=@da + last-edit=@da + file=@t + build=(each manx tang) + comments=(map @da comment) + == +:: ++$ notebook + $: title=@t + date-created=@da + last-note=@da + notes=(map @tas note) + order=(list @tas) + pinned=(set @tas) + == +:: ++$ versioned-state + $% [%1 state-one] + == +:: ++$ state-one + $: our-paths=(list path) + books=(map @tas notebook) + subs=(map [@p @tas] notebook) + recent=(list [@p @tas @tas]) + unread=(set [@p @tas @tas]) + == -- :: -=| state-zero +=| state-one =* state - ^- agent:gall =< - %+ verb | |_ bol=bowl:gall - +* this . - pub-core +> - pc ~(. pub-core bol) - def ~(. (default-agent this %|) bol) + +* this . + def ~(. (default-agent this %|) bol) + main ~(. +> bol) :: ++ on-init + ^- (quip card _this) + =/ lac [%launch-action %publish /publishtile '/~publish/tile.js'] + =/ rav [%sing %t [%da now.bol] /app/publish/notebooks] :_ this - :~ [%pass /bind/publish %arvo %e %connect [~ /'~publish'] %publish] - :* %pass /launch/publish %agent [our.bol %launch] %poke - %launch-action !>([%publish /publishtile '/~publish/tile.js']) - == + :~ [%pass /bind %arvo %e %connect [~ /'~publish'] %publish] + [%pass /tile %agent [our.bol %launch] %poke %launch-action !>(lac)] + [%pass /read/paths %arvo %c %warp our.bol q.byk.bol `rav] == + :: ++ on-save !>(state) + :: ++ on-load |= old=vase - `this(state !<(state-zero old)) + ^- (quip card _this) +:: [~ this(state !<(,[%1 state-one] old))] + [~ this(state *state-one)] :: ++ on-poke - |= [=mark =vase] + |= [mar=mark vas=vase] ^- (quip card _this) - =^ cards state - ?+ mark (on-poke:def mark vase) - %noun - (poke-noun:pc !<(* vase)) - %publish-action - (poke-publish-action:pc !<(action vase)) - %handle-http-request - =+ !<([eyre-id=@ta =inbound-request:eyre] vase) - :_ state - %+ give-simple-payload:app eyre-id - %+ require-authorization:app inbound-request - poke-handle-http-request:pc - %import - (poke-import:pc !<(* vase)) - %handle-http-cancel - [~ state] - == - [cards this] + ?+ mar (on-poke:def mar vas) + %noun + ~& state + [~ this] + :: + %handle-http-request + =+ !<([id=@ta req=inbound-request:eyre] vas) + :_ this + %+ give-simple-payload:app id + %+ require-authorization:app req + |= req=inbound-request:eyre + ^- simple-payload:http + not-found:gen + == :: ++ on-watch |= =path ^- (quip card _this) - =^ cards state - ?+ path (on-watch:def path) - [%export *] (peer-export:pc t.path) - [%publishtile *] (peer-publishtile:pc t.path) - [%primary *] (peer-primary:pc t.path) - [%collection *] (peer-collection:pc t.path) - [%http-response *] [~ state] - == - [cards this] + ?+ path (on-watch:def path) + [%http-response *] [~ this] +:: [%tile ~] + == :: ++ on-leave - |= =wire - ^- (quip card _this) - =^ cards state - (pull:pc wire) - [cards this] + |= path + `this :: - ++ on-peek on-peek:def + ++ on-peek + |= =path + ~| "unexpected scry into {} on path {}" + !! :: ++ on-agent |= [=wire =sign:agent:gall] ^- (quip card _this) - ?+ -.sign (on-agent:def wire sign) + ?- -.sign + %poke-ack + ?~ p.sign + `this + %- (slog leaf+"poke failed from {} on wire {}" u.p.sign) + `this + :: %watch-ack - =^ cards state - (reap:pc wire p.sign) - [cards this] - :: - %kick - ?. ?=([%collection *] wire) - (on-agent:def wire sign) - =^ cards state - (quit-collection:pc t.wire) - [cards this] + ?~ p.sign + `this + =/ =tank leaf+"subscribe failed from {} on wire {}" + %- (slog tank u.p.sign) + `this :: + %kick `this %fact - ?. ?=(%publish-rumor p.cage.sign) - (on-agent:def wire sign) - =^ cards state - (bake:pc !<(rumor q.cage.sign)) - [cards this] + ~| "unexpected subscription update to {} on wire {}" + ~| "with mark {}" + !! == :: ++ on-arvo - |= [=wire =sign-arvo] + |= [wir=wire sin=sign-arvo] ^- (quip card _this) - ?+ -.sign-arvo (on-arvo:def wire sign-arvo) + ?+ wir + (on-arvo:def wir sin) :: - %e - ?: ?=(%bound +<.sign-arvo) - [~ this] - (on-arvo:def wire sign-arvo) - :: - %f - ?. ?=(%made +<.sign-arvo) - (on-arvo:def wire sign-arvo) + [%read %paths ~] + ?> ?=([?(%b %c) %writ *] sin) + =/ rot=riot:clay +>.sin + ?> ?=(^ rot) =^ cards state - (made:pc wire date.sign-arvo result.sign-arvo) + (read-paths:main u.rot) [cards this] :: - %c - ?. ?=(%done +<.sign-arvo) - (on-arvo:def wire sign-arvo) - ?~ error.sign-arvo - [~ this] - ((slog tang.u.error.sign-arvo) [~ this]) + [%read %note *] + ?> ?=([?(%b %c) %writ *] sin) + =/ rot=riot:clay +>.sin + =^ cards state + (read-note:main t.t.wir rot) + [cards this] + :: + [%read %comment *] + ?> ?=([?(%b %c) %writ *] sin) + =/ rot=riot:clay +>.sin + =^ cards state + (read-comment:main t.t.wir rot) + [cards this] + :: + [%bind ~] + [~ this] == :: - ++ on-fail on-fail:def + ++ on-fail + |= [=term =tang] + %- (slog leaf+"error in {}" >term< tang) + `this -- :: |_ bol=bowl:gall -:: +our-beak: beak for this app, with case set to current invocation date +:: +++ read-paths + |= ran=rant:clay + ^- (quip card _state) + =/ rav [%next %t [%da now.bol] /app/publish/notebooks] + =/ new (filter-and-sort-paths !<((list path) q.r.ran)) + =/ dif (diff-paths our-paths new) + =^ del-moves state (del-paths del.dif) + =^ add-moves state (add-paths add.dif) + :: + =/ cards=(list card) + ;: weld + [%pass /read/paths %arvo %c %warp our.bol q.byk.bol `rav]~ + del-moves + add-moves + == + [cards state(our-paths new)] +:: +++ read-note + |= [pax=path rot=riot:clay] + ^- (quip card _state) + ?> ?=([%app %publish %notebooks @ @ %udon ~] pax) + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax + =/ book (~(get by books) book-name) + ?~ book + [~ state] + =/ old-note (~(get by notes.u.book) note-name) + ?~ old-note + [~ state] + ?~ rot + [~ state] + =/ udon !<(@t q.r.u.rot) + =/ new-note=note (form-note note-name udon) + =. date-created.new-note date-created.u.old-note + =. comments.new-note comments.u.old-note + =. notes.u.book (~(put by notes.u.book) note-name new-note) + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + :- [%pass (welp /read/note pax) %arvo %c %warp our.bol rif]~ + state(books (~(put by books) book-name u.book)) +:: +++ read-comment + |= [pax=path rot=riot:clay] + ^- (quip card _state) + ?> ?=([%app %publish %notebooks @ @ @ %publish-comment ~] pax) + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax + =/ comment-date (slaw %da i.t.t.t.t.t.pax) + ?~ comment-date + [~ state] + =/ book (~(get by books) book-name) + ?~ book + [~ state] + =/ note (~(get by notes.u.book) note-name) + ?~ note + [~ state] + =/ old-comment (~(get by comments.u.note) u.comment-date) + ?~ old-comment + [~ state] + ?~ rot + [~ state] + =/ new-comment !<(comment q.r.u.rot) + =. comments.u.note (~(put by comments.u.note) u.comment-date new-comment) + =. notes.u.book (~(put by notes.u.book) note-name u.note) + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + :- [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif]~ + state(books (~(put by books) book-name u.book)) +:: +++ filter-and-sort-paths + |= paths=(list path) + ^- (list path) + %+ sort + %+ skim paths + |= pax=path + ?| ?=([%app %publish %notebooks @ @ %udon ~] pax) + ?=([%app %publish %notebooks @ @ @ %publish-comment ~] pax) + == + |= [a=path b=path] + ^- ? + (lte (lent a) (lent b)) +:: +++ diff-paths + |= [old=(list path) new=(list path)] + ^- [del=(list path) add=(list path)] + =/ del=(list path) (skim old |=(p=path ?=(~ (find [p]~ new)))) + =/ add=(list path) (skim new |=(p=path ?=(~ (find [p]~ old)))) + [del add] +:: +++ del-paths + |= paths=(list path) + ^- (quip card _state) + %+ roll paths + |= [pax=path cad=(list card) sty=_state] + ?+ pax !! + [%app %publish %notebooks @ @ %udon ~] + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax + =/ book (~(get by books.sty) book-name) + ?~ book + [~ sty] + =. notes.u.book (~(del by notes.u.book) note-name) + :- ~ + sty(books (~(put by books) book-name u.book)) + :: + [%app %publish %notebooks @ @ @ %publish-comment ~] + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax + =/ comment-date (slaw %da i.t.t.t.t.t.pax) + ?~ comment-date + [~ sty] + =/ book (~(get by books.sty) book-name) + ?~ book + [~ sty] + =/ note (~(get by notes.u.book) note-name) + ?~ note + [~ sty] + =. comments.u.note (~(del by comments.u.note) u.comment-date) + =. notes.u.book (~(put by notes.u.book) note-name u.note) + :- ~ + sty(books (~(put by books.sty) book-name u.book)) + == +:: +++ add-paths + |= paths=(list path) + ^- (quip card _state) + %+ roll paths + |= [pax=path cad=(list card) sty=_state] + ?+ pax !! + [%app %publish %notebooks @ @ %udon ~] + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax + =/ new-note=note (scry-note pax) + =/ book=notebook + %+ fall (~(get by books.sty) book-name) + [book-name now.bol now.bol ~ [note-name]~ ~] + =/ old-note (~(get by notes.book) note-name) + ?^ old-note + =. date-created.new-note date-created.u.old-note + =. comments.new-note comments.u.old-note + =. notes.book (~(put by notes.book) note-name new-note) + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + :- [%pass (welp /read/note pax) %arvo %c %warp our.bol rif]~ + sty(books (~(put by books.sty) book-name book)) + :: + =/ comment-dir /app/publish/notebooks/[book-name]/[note-name] + =/ comment-paths .^((list path) %ct (weld our-beak comment-dir)) + =+ ^- [cards=(list card) new-comments=(map @da comment)] + %+ roll comment-paths + |= [pax=path cad=(list card) com=(map @da comment)] + ?. ?=([%app %publish %notebooks @ @ @ %publish-comment ~] pax) + [cad com] + =/ comment-name (slaw %da i.t.t.t.t.t.pax) + ?~ comment-name + [cad com] + =/ new-com .^(comment %cx (welp our-beak pax)) + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + :- [[%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] cad] + (~(put by com) u.comment-name new-com) + =. comments.new-note new-comments + =. notes.book (~(put by notes.book) note-name new-note) + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + :- [[%pass (welp /read/note pax) %arvo %c %warp our.bol rif] cards] + sty(books (~(put by books.sty) book-name book)) + :: + [%app %publish %notebooks @ @ @ %publish-comment ~] + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax + =/ comment-name (slaw %da i.t.t.t.t.t.pax) + =/ book (~(get by books.sty) book-name) + ?~ book + [~ sty] + =/ note (~(get by notes.u.book) note-name) + ?~ note + [~ sty] + ?~ comment-name + [~ sty] + =/ new-com .^(comment %cx (welp our-beak pax)) + =. comments.u.note (~(put by comments.u.note) u.comment-name new-com) + =. notes.u.book (~(put by notes.u.book) note-name u.note) + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + :- [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif]~ + sty(books (~(put by books.sty) book-name u.book)) + == +:: +++ scry-note + |= pax=path + ^- note + ?> ?=([%app %publish %notebooks @ @ %udon ~] pax) + =/ note-name i.t.t.t.t.pax + =/ udon=@t .^(@t %cx (welp our-beak pax)) + (form-note note-name udon) +:: +++ form-note + |= [note-name=@tas udon=@t] + ^- note + =/ build=(each manx tang) + %- mule |. + ^- manx + elm:(static:cram (ream udon)) + :: + =/ meta=(each (map term knot) tang) + %- mule |. + %- ~(run by inf:(static:cram (ream udon))) + |= a=dime ^- cord + ?+ (end 3 1 p.a) (scot a) + %t q.a + == + :: + =/ author=@p our.bol + =? author ?=(%.y -.meta) + %+ fall + (biff (~(get by p.meta) %author) (slat %p)) + our.bol + :: + =/ title=@t note-name + =? title ?=(%.y -.meta) + (fall (~(get by p.meta) %title) note-name) + :: + :* author + title + note-name + now.bol + now.bol + udon + build + ~ + == :: ++ our-beak /(scot %p our.bol)/[q.byk.bol]/(scot %da now.bol) :: -++ ships-to-whom - |= ships=(set @p) - ^- (set whom:clay) - %- ~(run in ships) - |= who=@p - ^- whom:clay - [%.y who] -:: -++ get-contributors - |= coll=@tas - ^- [mod=?(%white %black) who=(set @p)] - =/ pax (weld our-beak /web/publish/[coll]) - =/ pem=[r=dict:clay w=dict:clay] .^([dict:clay dict:clay] %cp pax) - :- mod.rul.w.pem - (resolve-real rul.w.pem) -:: -++ resolve-real - |= rel=real:clay - ^- (set @p) - %- ~(uni in p.who.rel) - %- (set @p) - %- ~(rep by q.who.rel) - |= [[@ta cru=crew:clay] out=(set @p)] - ^- (set @p) - (~(uni in out) cru) -:: -++ whom-to-ships - |= whoms=(set whom:clay) - ^- (set @p) - %- ~(rep in whoms) - |= [who=whom:clay out=(set @p)] - ?: ?=(%.y -.who) - (~(put in out) p.who) - out -:: ++ allowed |= [who=@p mod=?(%read %write) pax=path] ^- ? @@ -238,21 +455,20 @@ ?: =(%black mod.rul.dic) !in-list in-list -:: +write-file: write file at path :: ++ write-file =, space:userlib |= [pax=path cay=cage] ^- card =. pax (weld our-beak pax) - [%pass (weld /write-file pax) %arvo %c %info (foal pax cay)] + [%pass (weld /write pax) %arvo %c %info (foal pax cay)] :: ++ delete-file =, space:userlib |= pax=path ^- card =. pax (weld our-beak pax) - [%pass (weld /remove-file pax) %arvo %c %info (fray pax)] + [%pass (weld /delete pax) %arvo %c %info (fray pax)] :: ++ update-udon-front |= [fro=(map knot cord) udon=@t] @@ -282,1479 +498,4 @@ [' ==' ~] == :: -++ poke-noun - |= a=* - ^- (quip card _state) - ?. =(src.bol our.bol) - [~ state] - ?+ a - [~ state] - :: - %print-bowl - ~& bol - [~ state] - :: - %print-state - ~& state - [~ state] - :: - %state-surgery - =/ pubs=[broken=(list [@p @tas @tas]) new=(map @tas collection)] - %- ~(rep by pubs) - |= $: [nom=@tas col=collection] - broken=(list [@p @tas @tas]) - pubs=(map @tas collection) - == - ^- [(list [@p @tas @tas]) (map @tas collection)] - :: - =/ bad-posts=(list [@p @tas @tas]) - %- ~(rep by pos.col) - |= $: [pos=@tas dat=(each [post-info manx @t] tang)] - broken=(list [@p @tas @tas]) - == - ^- (list [@p @tas @tas]) - ?: -.dat - broken - [[our.bol nom pos] broken] - :: - =. pin.order.col - %+ skip pin.order.col - |= pos=@tas - ^- ? - ?~ (find [our.bol nom pos]~ bad-posts) - %.n - %.y - :: - =. unpin.order.col - %+ skip unpin.order.col - |= pos=@tas - ^- ? - ?~ (find [our.bol nom pos]~ bad-posts) - %.n - %.y - :: - [(welp broken bad-posts) (~(put by pubs) nom col)] - :: - =/ subs=[broken=(list [@p @tas @tas]) new=(map [@p @tas] collection)] - %- ~(rep by subs) - |= $: [[who=@p nom=@tas] col=collection] - broken=(list [@p @tas @tas]) - subs=(map [@p @tas] collection) - == - ^- [(list [@p @tas @tas]) (map [@p @tas] collection)] - :: - =/ bad-posts=(list [@p @tas @tas]) - %- ~(rep by pos.col) - |= $: [pos=@tas dat=(each [post-info manx @t] tang)] - broken=(list [@p @tas @tas]) - == - ^- (list [@p @tas @tas]) - ?: -.dat - broken - [[who nom pos] broken] - :: - :: - =. pin.order.col - %+ skip pin.order.col - |= pos=@tas - ?~ (find [who nom pos]~ bad-posts) - %.n - %.y - :: - =. unpin.order.col - %+ skip unpin.order.col - |= pos=@tas - ?~ (find [who nom pos]~ bad-posts) - %.n - %.y - :: - [(welp broken bad-posts) (~(put by subs) [who nom] col)] - :: - =/ new-latest=(list [@p @tas @tas]) - %+ skip latest - |= elm=[@p @tas @tas] - ^- ? - ?^ (find [elm]~ broken.pubs) - %.y - ?^ (find [elm]~ broken.subs) - %.y - %.n - :: - =/ new-unread=(set [@p @tas @tas]) - %- sy - %+ skip ~(tap in unread) - |= elm=[@p @tas @tas] - ^- ? - ?^ (find [elm]~ broken.pubs) - %.y - ?^ (find [elm]~ broken.subs) - %.y - %.n - :: - =/ mow=(list card) - %- ~(rep by new.pubs) - |= [[nom=@tas col=collection] out=(list card)] - ^- (list card) - =/ del=delta [%total our.bol nom col] - (welp (affection del) out) - :: - :- mow - %= state - latest new-latest - unread new-unread - pubs new.pubs - subs new.subs - == - :: - == -:: -++ da - |_ moves=(list card) - :: - ++ da-this . - :: - ++ da-done - ^- (quip card _state) - [(flop moves) state] - :: - ++ da-emit - |= mov=card - %_ da-this - moves [mov moves] - == - :: - ++ da-emil - |= mov=(list card) - %_ da-this - moves (welp (flop mov) moves) - == - :: - ++ da-change - |= del=delta - ^+ da-this - ?- -.del - :: - %collection - =/ old=(unit collection) - ?: =(our.bol who.del) - (~(get by pubs) col.del) - (~(get by subs) who.del col.del) - =/ new=collection - ?~ old - [dat.del ~ ~ [~ ~] [%white ~] ~ now.bol] - u.old(col dat.del, last-update now.bol) - =? contributors.new =(our.bol who.del) - (get-contributors col.del) - =? pubs =(our.bol who.del) - (~(put by pubs) col.del new) - =? subs !=(our.bol who.del) - (~(put by subs) [who.del col.del] new) - (da-emil (affection del)) - :: - %post - =/ old=(unit collection) - ?: =(our.bol who.del) - (~(get by pubs) col.del) - (~(get by subs) who.del col.del) - =/ new=collection - ?~ old - :* [%.n ~] (my [pos.del dat.del] ~) ~ - [~ ~] [%white ~] ~ now.bol - == - %= u.old - pos (~(put by pos.u.old) pos.del dat.del) - last-update now.bol - == - =? pubs =(our.bol who.del) - (~(put by pubs) col.del new) - =? subs !=(our.bol who.del) - (~(put by subs) [who.del col.del] new) - =. da-this - ?: -.dat.del - (da-insert who.del col.del pos.del) - (da-remove who.del col.del pos.del) - (da-emil (affection del)) - :: - %comments - =/ old=(unit collection) - ?: =(our.bol who.del) - (~(get by pubs) col.del) - (~(get by subs) who.del col.del) - =/ new=collection - ?~ old - :* [%.n ~] ~ (my [pos.del dat.del] ~) - [~ ~] [%white ~] ~ now.bol - == - %= u.old - com (~(put by com.u.old) pos.del dat.del) - last-update now.bol - == - =? pubs =(our.bol who.del) - (~(put by pubs) col.del new) - =? subs !=(our.bol who.del) - (~(put by subs) [who.del col.del] new) - (da-emil (affection del)) - :: - %total - =? contributors.dat.del =(our.bol who.del) - (get-contributors col.del) - =? pubs =(our.bol who.del) - (~(put by pubs) col.del dat.del) - =? subs !=(our.bol who.del) - (~(put by subs) [who.del col.del] dat.del(order [~ ~])) - :: - =/ posts=(list [@tas (each [post-info manx @t] tang)]) - ~(tap by pos.dat.del) - =. da-this - |- - ?~ posts - da-this - ?. +<.i.posts - %= $ - da-this (da-remove who.del col.del -.i.posts) - posts t.posts - == - %= $ - da-this (da-insert who.del col.del -.i.posts) - posts t.posts - == - (da-emil (affection del)) - :: - %remove - :: remove blog - :: - ?~ pos.del - :: collect post ids for blog, delete blog, and sent out moves - :: - =^ posts da-this - ?: =(our.bol who.del) - :: if its our blog, we must send out notifications to subscribers - :: - =/ old=(unit collection) (~(get by pubs) col.del) - ?~ old - [~ da-this] - =. pubs (~(del by pubs) col.del) - :- ~(tap in ~(key by pos.u.old)) - (da-emil (affection del)) - :: if its not our blog, we need to pull subscription - :: - =/ old=(unit collection) (~(get by subs) who.del col.del) - ?~ old - [~ da-this] - =. subs (~(del by subs) who.del col.del) - :- ~(tap in ~(key by pos.u.old)) - %- da-emil - :- [%pass /collection/[col.del] %agent [who.del %publish] %leave ~] - (affection-primary del) - :: iterate through post ids collected before, removing each from - :: secondary indices in state - :: - =. da-this - |- - ?~ posts - da-this - %= $ - da-this (da-remove who.del col.del i.posts) - posts t.posts - == - da-this - :: remove post - :: - =/ old=(unit collection) - ?: =(our.bol who.del) - (~(get by pubs) col.del) - (~(get by subs) who.del col.del) - ?~ old - da-this - ?. (~(has in ~(key by pos.u.old)) u.pos.del) - da-this - =/ new=collection - %= u.old - pos (~(del by pos.u.old) u.pos.del) - com (~(del by com.u.old) u.pos.del) - == - =. da-this (da-emil (affection del)) - ?: =(our.bol who.del) - =. pubs (~(put by pubs) col.del new) - =. da-this (da-remove who.del col.del u.pos.del) - (da-emil (affection del)) - =. subs (~(put by subs) [who.del col.del] new) - =. da-this (da-remove who.del col.del u.pos.del) - (da-emil (affection-primary del)) - :: - == - :: - ++ da-remove-unread - |= [who=@p coll=@tas post=@tas] - ^+ da-this - =. unread (~(del in unread) who coll post) - (da-emil make-tile-moves) - :: - ++ da-remove-latest - |= [who=@p coll=@tas post=@tas] - ^+ da-this - =/ ids=(list @) (fand [who coll post]~ latest) - =. latest - |- - ?~ ids - latest - %= $ - latest (oust [i.ids 1] latest) - ids t.ids - == - (da-emil make-tile-moves) - :: - ++ da-remove-order - |= [who=@p coll=@tas post=@tas] - ^+ da-this - =/ col=(unit collection) (get-coll-by-index who coll) - ?~ col - da-this - =/ new=collection u.col - =/ pin-ids=(list @) (fand [post]~ pin.order.new) - =. pin.order.new - |- - ?~ pin-ids - pin.order.new - %= $ - pin.order.new (oust [i.pin-ids 1] pin.order.new) - pin-ids t.pin-ids - == - :: - =/ unpin-ids=(list @) (fand [post]~ unpin.order.new) - =. unpin.order.new - |- - ?~ unpin-ids - unpin.order.new - %= $ - unpin.order.new (oust [i.unpin-ids 1] unpin.order.new) - unpin-ids t.unpin-ids - == - =? pubs =(who our.bol) - (~(put by pubs) coll new) - =? subs !=(who our.bol) - (~(put by subs) [who coll] new) - (da-emil make-tile-moves) - :: - ++ da-remove - |= [who=@p coll=@tas post=@tas] - ^+ da-this - =. da-this (da-remove-unread +<) - =. da-this (da-remove-latest +<) - =. da-this (da-remove-order +<) - da-this - :: - ++ da-insert-unread - |= [who=@p coll=@tas post=@tas] - ^+ da-this - :: assume we've read our own posts - :: - =? unread !=(who our.bol) - (~(put in unread) who coll post) - (da-emil make-tile-moves) - :: - ++ da-insert-latest - |= [who=@p coll=@tas post=@tas] - ^+ da-this - =/ new-date=@da date-created:(need (get-post-info-by-index who coll post)) - =/ pre=(list [@p @tas @tas]) ~ - =/ suf=(list [@p @tas @tas]) latest - =? latest =(~ (find [who coll post]~ latest)) - |- - ?~ suf - (weld pre [who coll post]~) - =/ i-date=@da date-created:(need (get-post-info-by-index i.suf)) - ?: (gte new-date i-date) - (weld pre [[who coll post] suf]) - %= $ - suf t.suf - pre (snoc pre i.suf) - == - da-this - :: - ++ da-insert-order - |= [who=@p coll=@tas post=@tas] - ^+ da-this - =/ new-post=post-info (need (get-post-info-by-index who coll post)) - =/ col=collection (need (get-coll-by-index who coll)) - :: - =/ pre=(list @tas) ~ - =/ suf=(list @tas) - ?: pinned.new-post - pin.order.col - unpin.order.col - :: - ?: ?=(^ (find [post]~ suf)) - da-this - =/ new-list=(list @tas) - |- - ?~ suf - (snoc pre post) - ?: =(post i.suf) - (weld pre suf) - =/ i-date=@da date-created:(need (get-post-info-by-index who coll i.suf)) - ?: (gte date-created.new-post i-date) - (weld pre [post suf]) - %= $ - suf t.suf - pre (snoc pre i.suf) - == - :: - =. order.col - ?: pinned.new-post - [new-list unpin.order.col] - [pin.order.col new-list] - :: - =? pubs =(our.bol who) - (~(put by pubs) coll col) - =? subs !=(our.bol who) - (~(put by subs) [who coll] col) - da-this - :: - ++ da-insert - |= [who=@p coll=@tas post=@tas] - ^+ da-this - =. da-this (da-insert-unread +<) - =. da-this (da-insert-latest +<) - =. da-this (da-insert-order +<) - da-this - -- -:: +bake: apply delta -:: -++ bake - |= del=delta - ^- (quip card _state) - da-done:(da-change:da del) -:: +affection: rumors to primary -:: -++ affection-primary - |= del=delta - ^- (list card) - [%give %fact ~[/primary] %publish-rumor !>(del)]~ -:: +affection: rumors to interested -:: -++ affection - |= del=delta - ^- (list card) - =/ wir=wire /collection/[col.del] - :~ [%give %fact ~[/primary] %publish-rumor !>(del)] - [%give %fact ~[wir] %publish-rumor !>(del)] - == -:: -++ get-post-by-index - |= [who=@p coll=@tas post=@tas] - ^- (unit (each [post-info manx @t] tang)) - =/ col=(unit collection) - ?: =(our.bol who) - (~(get by pubs) coll) - (~(get by subs) who coll) - ?~ col ~ - =/ pos=(unit (each [post-info manx @t] tang)) - (~(get by pos.u.col) post) - pos -:: -++ get-post-info-by-index - |= [who=@p coll=@tas post=@tas] - ^- (unit post-info) - =/ col=(unit collection) - ?: =(our.bol who) - (~(get by pubs) coll) - (~(get by subs) who coll) - ?~ col ~ - =/ pos=(unit (each [post-info manx @t] tang)) - (~(get by pos.u.col) post) - ?~ pos ~ - ?: ?=(%.n -.u.pos) ~ - [~ -.p.u.pos] -:: -++ get-coll-by-index - |= [who=@p coll=@tas] - ^- (unit collection) - ?: =(our.bol who) - (~(get by pubs) coll) - (~(get by subs) who coll) -:: -++ made - |= [wir=wire wen=@da mad=made-result:ford] - ^- (quip card _state) - ?+ wir - [~ state] - :: - [%collection @t ~] - =/ col=@tas i.t.wir - =/ awa (~(get by awaiting) col) - :: - =/ dat=(each collection-info tang) - ?: ?=([%incomplete *] mad) - [%.n tang.mad] - ?: ?=([%error *] build-result.mad) - [%.n message.build-result.mad] - ?> ?=(%bake +<.build-result.mad) - ?> ?=(%publish-info p.cage.build-result.mad) - [%.y (collection-info q.q.cage.build-result.mad)] - :: - ?~ awa - (bake [%collection our.bol col dat]) - =. builds.u.awa (~(del in builds.u.awa) wir) - ?~ partial.u.awa - ?~ builds.u.awa - :: one-off build, make delta and process it - :: - =. awaiting (~(del by awaiting) col) - (bake [%collection our.bol col dat]) - :: 1st part of multi-part, store partial delta and don't process it - :: - =/ del=delta - :* %total our.bol col dat - ~ ~ [~ ~] [%white ~] ~ now.bol - == - =. awaiting (~(put by awaiting) col builds.u.awa `del) - [~ state] - :: - ?~ builds.u.awa - :: last part of multipart, update partial delta and process it - :: - ?> ?=(%total -.u.partial.u.awa) - =/ del=delta - :* %total - our.bol - col - dat - pos.dat.u.partial.u.awa - com.dat.u.partial.u.awa - [~ ~] - [%white ~] - ~ - now.bol - == - =. awaiting (~(del by awaiting) col) - (bake del) - :: nth part of multi-part, update partial delta and don't process it - :: - ?> ?=(%total -.u.partial.u.awa) - =/ del=delta - :* %total - our.bol - col - dat - pos.dat.u.partial.u.awa - com.dat.u.partial.u.awa - [~ ~] - [%white ~] - ~ - now.bol - == - =. awaiting (~(put by awaiting) col builds.u.awa `del) - [~ state] - :: - [%post @t @t ~] - =/ col=@tas i.t.wir - =/ pos=@tas i.t.t.wir - =/ awa (~(get by awaiting) col) - :: - =/ dat=(each [post-info manx @t] tang) - ?: ?=([%incomplete *] mad) - [%.n tang.mad] - ?: ?=([%error *] build-result.mad) - [%.n message.build-result.mad] - ?> ?=(%bake +<.build-result.mad) - ?> ?=(%publish-post p.cage.build-result.mad) - [%.y (,[post-info manx @t] q.q.cage.build-result.mad)] - :: - ?~ awa - (bake [%post our.bol col pos dat]) - =. builds.u.awa (~(del in builds.u.awa) wir) - ?~ partial.u.awa - ?~ builds.u.awa - :: one-off build, make delta and process it - :: - =. awaiting (~(del by awaiting) col) - (bake [%post our.bol col pos dat]) - :: 1st part of multi-part, store partial delta and don't process it - :: - =/ del=delta - :* %total our.bol col [%.n ~] (my [pos dat] ~) - ~ [~ ~] [%white ~] ~ now.bol - == - =. awaiting (~(put by awaiting) col builds.u.awa `del) - [~ state] - :: - ?~ builds.u.awa - :: last part of multipart, update partial delta and process it - :: - ?> ?=(%total -.u.partial.u.awa) - =/ del=delta - :* %total - our.bol - col - col.dat.u.partial.u.awa - (~(put by pos.dat.u.partial.u.awa) pos dat) - com.dat.u.partial.u.awa - [~ ~] - [%white ~] - ~ - now.bol - == - =. awaiting (~(del by awaiting) col) - (bake del) - :: nth part of multi-part, update partial delta and don't process it - :: - ?> ?=(%total -.u.partial.u.awa) - =/ del=delta - :* %total - our.bol - col - col.dat.u.partial.u.awa - (~(put by pos.dat.u.partial.u.awa) pos dat) - com.dat.u.partial.u.awa - [~ ~] - [%white ~] - ~ - now.bol - == - =. awaiting (~(put by awaiting) col builds.u.awa `del) - [~ state] - :: - [%comments @t @t ~] - =/ col=@tas i.t.wir - =/ pos=@tas i.t.t.wir - =/ awa (~(get by awaiting) col) - :: - =/ dat=(each (list [comment-info @t]) tang) - ?: ?=([%incomplete *] mad) - [%.n tang.mad] - ?: ?=([%error *] build-result.mad) - [%.n message.build-result.mad] - ?> ?=(%bake +<.build-result.mad) - ?> ?=(%publish-comments p.cage.build-result.mad) - [%.y (,(list [comment-info @t]) q.q.cage.build-result.mad)] - :: - ?~ awa - (bake [%comments our.bol col pos dat]) - =. builds.u.awa (~(del in builds.u.awa) wir) - ?~ partial.u.awa - ?~ builds.u.awa - :: one-off build, make delta and process it - :: - =. awaiting (~(del by awaiting) col) - (bake [%comments our.bol col pos dat]) - :: 1st part of multi-part, store partial delta and don't process it - :: - =/ del=delta - :* %total our.bol col [%.n ~] ~ (my [pos dat] ~) - [~ ~] [%white ~] ~ now.bol - == - =. awaiting (~(put by awaiting) col builds.u.awa `del) - [~ state] - :: - ?~ builds.u.awa - :: last part of multipart, update partial delta and process it - :: - ?> ?=(%total -.u.partial.u.awa) - =/ del=delta - :* %total - our.bol - col - col.dat.u.partial.u.awa - pos.dat.u.partial.u.awa - (~(put by com.dat.u.partial.u.awa) pos dat) - [~ ~] - [%white ~] - ~ - now.bol - == - =. awaiting (~(del by awaiting) col) - (bake del) - :: nth part of multi-part, update partial delta and don't process it - :: - ?> ?=(%total -.u.partial.u.awa) - =/ del=delta - :* %total - our.bol - col - col.dat.u.partial.u.awa - pos.dat.u.partial.u.awa - (~(put by com.dat.u.partial.u.awa) pos dat) - [~ ~] - [%white ~] - ~ - now.bol - == - =. awaiting (~(put by awaiting) col builds.u.awa `del) - [~ state] - == -:: -++ make-kills - |= [coll=@tas post=(unit @tas)] - ^- (list card) - =/ col=(unit collection) (~(get by pubs) coll) - ?~ col - ~| [%non-existent-collection coll] !! - ?~ post - =/ kills=(list card) - %+ roll ~(tap by pos.u.col) - |= [[pos=@tas *] out=(list card)] - :* [%pass /post/[coll]/[pos] %arvo %f %kill ~] - [%pass /comments/[coll]/[pos] %arvo %f %kill ~] - out - == - [[%pass /collection/[coll] %arvo %f %kill ~] kills] - :: - :~ [%pass /post/[coll]/[u.post] %arvo %f %kill ~] - [%pass /comments/[coll]/[u.post] %arvo %f %kill ~] - == -:: -++ make-deletes - |= [coll=@tas post=(unit @tas)] - ^- (list card) - =/ files=(list path) - ?~ post - .^((list path) %ct (weld our-beak /web/publish/[coll])) - .^((list path) %ct (weld our-beak /web/publish/[coll]/[u.post])) - %+ turn files - |= pax=path - ^- card - (delete-file pax) -:: -++ mack - |= [wir=wire err=(unit tang)] - ^- (quip card _state) - ?~ err - [~ state] - %- (slog u.err) - [~ state] -:: -++ poke-publish-action - |= act=action - ^- (quip card _state) - ?- -.act - :: - %new-collection - ?. =(our.bol src.bol) - :: no one else is permitted to create blogs - :: - [~ state] - ?: (~(has by pubs) name.act) - [~ state] - :: - =/ conf=collection-info - :* our.bol - title.act - name.act - com.act - edit.act - now.bol - now.bol - == - :: - =/ blog-perms=task:able:clay - :* %perm q.byk.bol - /web/publish/[name.act] - %rw `read.perm.act `write.perm.act - == - =/ info-perms=task:able:clay - :* %perm q.byk.bol - /web/publish/[name.act]/publish-info - %rw `*rule:clay `*rule:clay - == - =/ schema=schematic:ford - :* %bake - %publish-info - *coin - [[our.bol q.byk.bol] /[name.act]/publish/web] - == - =/ pax=path /web/publish/[name.act]/publish-info - :_ state - :~ (write-file pax %publish-info !>(conf)) - [%pass /perms %arvo %c blog-perms] - [%pass /perms %arvo %c info-perms] - [%pass /collection/[name.act] %arvo %f %build %.y schema] - == - :: - %new-post - ?. =(who.act our.bol) - :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ - =/ pax=path /web/publish/[coll.act]/[name.act]/udon - ?. (allowed src.bol %write pax) - [~ state] - =/ col=(unit collection) (~(get by pubs) coll.act) - ?~ col - [~ state] - ?: (~(has by pos.u.col) name.act) - [~ state] - =. content.act (cat 3 content.act '\0a') :: XX fix udon parser - =/ front=(map knot cord) - %- my - :~ [%creator (scot %p src.bol)] - [%title title.act] - [%collection coll.act] - [%filename name.act] - [%comments com.act] - [%date-created (scot %da now.bol)] - [%last-modified (scot %da now.bol)] - [%pinned %false] - == - =/ out=@t (update-udon-front front content.act) - :: - =/ post-wir=wire /post/[coll.act]/[name.act] - =/ post-schema=schematic:ford - :* %bake - %publish-post - *coin - [[our.bol q.byk.bol] /[name.act]/[coll.act]/publish/web] - == - :: - =/ comments-wir=wire /comments/[coll.act]/[name.act] - =/ comments-schema=schematic:ford - :* %bake - %publish-comments - *coin - [[our.bol q.byk.bol] /[name.act]/[coll.act]/publish/web] - == - :: - =/ post-perms=task:able:clay - :* %perm q.byk.bol - /web/publish/[coll.act]/[name.act]/udon - %w `[%white (ships-to-whom (sy src.bol ~))] - == - =/ comment-perms=task:able:clay - :* %perm q.byk.bol - /web/publish/[coll.act]/[name.act] - %w `[%black ~] - == - :_ state - :~ (write-file pax %udon !>(out)) - [%pass /perms %arvo %c post-perms] - [%pass /perms %arvo %c comment-perms] - [%pass comments-wir %arvo %f %build %.y comments-schema] - [%pass post-wir %arvo %f %build %.y post-schema] - == - :: - %new-comment - ?. =(who.act our.bol) - :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ - =/ pax=path - /web/publish/[coll.act]/[post.act]/(scot %da now.bol)/publish-comment - ?. (allowed src.bol %write pax) - [~ state] - =/ col=(unit collection) (~(get by pubs) coll.act) - ?~ col - [~ state] - ?. (~(has by pos.u.col) post.act) - [~ state] - =/ com=comment - [[src.bol coll.act post.act now.bol now.bol] content.act] - :: - =/ comment-perms=task:able:clay [%perm q.byk.bol pax %w `[%white ~]] - :: - :_ state - :~ (write-file pax %publish-comment !>(com)) - [%pass /perms %arvo %c comment-perms] - == - :: - %delete-collection - ?. =(src.bol our.bol) - [~ state] - =/ kills (make-kills coll.act ~) - =/ deletes (make-deletes coll.act ~) - =/ del=delta [%remove our.bol coll.act ~] - =^ moves state (bake del) - :: - :- - ;: welp - kills - moves - make-tile-moves - deletes - == - %= state - awaiting (~(del by awaiting) coll.act) - == - :: - %delete-post - ?. =(src.bol our.bol) - [~ state] - =/ kills (make-kills coll.act `post.act) - =/ deletes (make-deletes coll.act `post.act) - =/ del=delta [%remove our.bol coll.act `post.act] - =^ moves state (bake del) - :: - :_ state - ;: welp - kills - moves - make-tile-moves - deletes - == - :: - %delete-comment - ?. =(src.bol our.bol) - [~ state] - :_ state - [(delete-file /web/publish/[coll.act]/[post.act]/[comment.act]/udon)]~ - :: - %edit-collection - ?. =(src.bol our.bol) - [~ state] - =/ pax=path /web/publish/[name.act]/publish-info - =/ col=(unit collection) (~(get by pubs) name.act) - ?~ col - [~ state] - ?: ?=(%.n -.col.u.col) - [~ state] - =/ out=collection-info p.col.u.col(title title.act) - :_ state - [(write-file pax %publish-info !>(out))]~ - :: - %edit-post - ?. =(who.act our.bol) - :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ - :: - =/ pax=path /web/publish/[coll.act]/[name.act]/udon - ?. (allowed src.bol %write pax) - [~ state] - =/ col=(unit collection) (~(get by pubs) coll.act) - ?~ col - [~ state] - ?. (~(has by pos.u.col) name.act) - [~ state] - :: - =/ pos=(unit (each [post-info manx @t] tang)) - (get-post-by-index who.act coll.act name.act) - ?~ pos - ~| %editing-non-existent-post !! - =/ date-created=@da - ?: ?=(%.y -.u.pos) - date-created.-.p.u.pos - now.bol - :: - =. content.act (cat 3 content.act '\0a') :: XX fix udon parser - =/ front=(map knot cord) - %- my - :~ [%creator (scot %p src.bol)] - [%title title.act] - [%collection coll.act] - [%filename name.act] - [%comments com.act] - [%date-created (scot %da date-created)] - [%last-modified (scot %da now.bol)] - [%pinned %false] - == - =/ out=@t (update-udon-front front content.act) - :: - :_ state - [(write-file pax %udon !>(out))]~ - :: - :: %invite: if the action is from us it means send invites to other people - :: if its from someone else it means we've been invited - :: - %invite - ?: =(our.bol src.bol) - =/ new-act=action [%invite coll.act title.act ~] - :_ state - %+ turn who.act - |= who=@p - ^- card - [%pass /forward %agent [who %publish] %poke %publish-action !>(new-act)] - =. invites (~(put by invites) [src.bol coll.act] title.act) - =/ upd=update [%invite %.y src.bol coll.act title.act] - :_ state - %+ welp make-tile-moves - [%give %fact ~[/primary] %publish-update !>(upd)]~ - :: - :: %reject-invite: remove invite from list, acceptance is handled by - :: %subscribe action - :: - %reject-invite - =/ title=(unit @t) (~(get by invites) [who.act coll.act]) - ?~ title - [~ state] - =. invites (~(del by invites) [who.act coll.act]) - =/ upd=update [%invite %.n who.act coll.act u.title] - :_ state - %+ welp make-tile-moves - [%give %fact ~[/primary] %publish-update !>(upd)]~ - :: - :: %serve: - :: - %serve - :: XX specialize this check for subfiles - ?. =(our.bol src.bol) - [~ state] - ?: (~(has by pubs) coll.act) - [~ state] - =/ files=(list path) - .^((list path) %ct (weld our-beak /web/publish/[coll.act])) - ?> ?=(^ (find [/web/publish/[coll.act]/publish-info]~ files)) - =/ all=[moves=(list card) builds=(set wire)] - %+ roll files - |= [pax=path out=[moves=(list card) builds=(set wire)]] - ?+ pax - out - :: - [%web %publish @tas %publish-info ~] - ?> =(coll.act i.t.t.pax) - =/ wir=wire /collection/[coll.act] - =/ schema=schematic:ford - :* %bake - %publish-info - *coin - [[our.bol q.byk.bol] /[coll.act]/publish/web] - == - %= out - builds (~(put in builds.out) wir) - :: - moves - :* [%pass wir %arvo %f %build %.y schema] - moves.out - == - == - :: - [%web %publish @tas @tas %udon ~] - ?> =(coll.act i.t.t.pax) - =/ post i.t.t.t.pax - =/ post-wir=wire /post/[coll.act]/[post] - =/ post-schema=schematic:ford - :* %bake - %publish-post - *coin - [[our.bol q.byk.bol] /[post]/[coll.act]/publish/web] - == - :: - =/ comments-wir=wire /comments/[coll.act]/[post] - =/ comments-schema=schematic:ford - :* %bake - %publish-comments - *coin - [[our.bol q.byk.bol] /[post]/[coll.act]/publish/web] - == - =/ post-perms=task:able:clay - :* %perm q.byk.bol - /web/publish/[coll.act]/[post]/udon - %w `[%white (ships-to-whom (sy src.bol ~))] - == - =/ comment-perms=task:able:clay - :* %perm q.byk.bol - /web/publish/[coll.act]/[post] - %w `[%black ~] - == - %= out - moves - :* [%pass post-wir %arvo %f %build %.y post-schema] - [%pass comments-wir %arvo %f %build %.y comments-schema] - [%pass /perms %arvo %c post-perms] - [%pass /perms %arvo %c comment-perms] - moves.out - == - :: - builds - (~(uni in builds.out) (sy post-wir comments-wir ~)) - == - :: - == - =/ blog-perms=task:able:clay - :* %perm q.byk.bol - /web/publish/[coll.act] - %rw `[%black ~] `[%white ~] - == - =/ info-perms=task:able:clay - :* %perm q.byk.bol - /web/publish/[coll.act]/publish-info - %rw `*rule:clay `*rule:clay - == - :- :* [%pass /perms %arvo %c blog-perms] - [%pass /perms %arvo %c info-perms] - moves.all - == - %= state - awaiting (~(put by awaiting) coll.act builds.all ~) - == - :: - :: %unserve: - :: - %unserve - :: XX pull subscriptions for unserved collections - :: - ?. =(our.bol src.bol) - [~ state] - =/ kills (make-kills coll.act ~) - =/ del=delta [%remove our.bol coll.act ~] - =^ moves state (bake del) - :: - :- - ;: welp - moves - make-tile-moves - kills - == - %= state - awaiting (~(del by awaiting) coll.act) - == - :: - :: %subscribe: sub to a foreign blog; remove invites for that blog - :: - %subscribe - =/ wir=wire /collection/[coll.act] - =/ title=(unit @t) (~(get by invites) [who.act coll.act]) - =. invites (~(del by invites) [who.act coll.act]) - :_ state - ;: welp - make-tile-moves - [%pass wir %agent [who.act %publish] %watch wir]~ - ?~ title ~ - =/ upd=update [%invite %.n who.act coll.act u.title] - [%give %fact ~[/primary] %publish-update !>(upd)]~ - == - :: - :: %unsubscribe: unsub from a foreign blog, delete all state related to it - :: - %unsubscribe - =/ wir=wire /collection/[coll.act] - =/ new-latest=(list [@p @tas @tas]) - %+ skim latest - |= [who=@p coll=@tas post=@tas] - ?& =(who our.bol) - =(coll coll.act) - == - :: - =. unread - ^- (set [@p @tas @tas]) - %- sy - %+ skim ~(tap in unread) - |= [who=@p coll=@tas post=@tas] - ?& =(who our.bol) - =(coll coll.act) - == - :_ %= state - subs (~(del by subs) who.act coll.act) - latest new-latest - == - :- [%pass wir %agent [who.act %publish] %leave ~] - %+ welp make-tile-moves - =/ rum=rumor [%remove who.act coll.act ~] - [%give %fact ~[/primary] %publish-rumor !>(rum)]~ - :: - :: %read: notify that we've seen a post - :: - %read - =. unread (~(del in unread) who.act coll.act post.act) - :_ state - %+ welp make-tile-moves - :: - =/ upd=update [%unread %.n (sy [who.act coll.act post.act] ~)] - [%give %fact ~[/primary] %publish-update !>(upd)]~ - :: - == -:: -++ quit-collection - |= wir=wire - ^- (quip card _state) - =/ pax=path (weld /collection wir) - :_ state - [%pass pax %agent [src.bol %publish] %watch pax]~ -:: -++ bound - |= [wir=wire success=? binding=binding:eyre] - ^- (quip card _state) - [~ state] -:: -:: +poke-handle-http-request: received on a new connection established -:: -++ poke-handle-http-request - |= =inbound-request:eyre - ^- simple-payload:http - :: - =/ request-line (parse-request-line url.request.inbound-request) - ?+ request-line - not-found:gen - :: images - :: - [[[~ %png] [%'~publish' @t ~]] ~] - =/ filename=@t i.t.site.request-line - =/ img=(unit @t) (~(get by images) filename) - ?~ img - not-found:gen - (png-response:gen (as-octs:mimes:html u.img)) - :: styling - :: - [[[~ %css] [%'~publish' %index ~]] ~] - (css-response:gen css) - :: scripting - :: - [[[~ %js] [%'~publish' %index ~]] ~] - (js-response:gen js) - :: tile js - :: - [[[~ %js] [%'~publish' %tile ~]] ~] - (js-response:gen tile-js) - :: home page; redirect to recent - :: - [[~ [%'~publish' ~]] ~] - =/ hym=manx (index (state-to-json state)) - (redirect:gen '/~publish/recent') - :: recent page - :: - [[~ [%'~publish' %recent ~]] ~] - =/ hym=manx (index (state-to-json state)) - (manx-response:gen hym) - :: subscriptions - :: - [[~ [%'~publish' %subs ~]] ~] - =/ hym=manx (index (state-to-json state)) - (manx-response:gen hym) - :: published - :: - [[~ [%'~publish' %pubs ~]] ~] - =/ hym=manx (index (state-to-json state)) - (manx-response:gen hym) - :: new post - :: - [[~ [%'~publish' %new-post ~]] ~] - =/ hym=manx (index (state-to-json state)) - (manx-response:gen hym) - :: new blog - :: - [[~ [%'~publish' %new-blog ~]] ~] - =/ hym=manx (index (state-to-json state)) - (manx-response:gen hym) - :: blog - :: - [[~ [%'~publish' @t @t ~]] ~] - =/ hym=manx (index (state-to-json state)) - (manx-response:gen hym) - :: blog post - :: - [[~ [%'~publish' @t @t @t ~]] ~] - =/ hym=manx (index (state-to-json state)) - (manx-response:gen hym) - :: - == -:: -++ state-to-json - |= sat=_state - ^- json - %- pairs:enjs:format - :~ :+ %pubs - %o - %+ roll ~(tap by pubs.sat) - |= [[nom=@tas col=collection] out=(map @t json)] - %+ ~(put by out) - nom - (total-build-to-json col) - :: - :+ %subs - %o - %- ~(rep by subs.sat) - |= $: [[who=@p nom=@tas] col=collection] - out=(map @t [%o (map @t json)]) - == - =/ shp=@t (rsh 3 1 (scot %p who)) - ?: (~(has by out) shp) - %+ ~(put by out) - shp - :- %o - %+ ~(put by +:(~(got by out) shp)) - nom - (total-build-to-json col) - %+ ~(put by out) - shp - :- %o - (my [nom (total-build-to-json col)] ~) - :: - :+ %latest - %a - %+ turn latest.sat - |= [who=@p coll=@tas post=@tas] - %- pairs:enjs:format - :~ who+(ship:enjs:format who) - coll+s+coll - post+s+post - == - :: - :+ %unread - %a - %+ turn ~(tap in unread.sat) - |= [who=@p coll=@tas post=@tas] - %- pairs:enjs:format - :~ who+(ship:enjs:format who) - coll+s+coll - post+s+post - == - :: - :+ %invites - %a - %+ turn ~(tap in invites.sat) - |= [[who=@p coll=@tas] title=@t] - %- pairs:enjs:format - :~ who+(ship:enjs:format who) - coll+s+coll - title+s+title - == - == -:: -++ make-tile-moves - ^- (list card) - [%give %fact ~[/publishtile] %json !>(make-tile-json)]~ -:: -++ make-tile-json - ^- json - %- pairs:enjs:format - :~ invites+(numb:enjs:format ~(wyt by invites)) - new+(numb:enjs:format ~(wyt in unread)) - == -:: -++ poke-import - |= i=* - ^- (quip card _state) - ?> ?=([%publish-v0 *] i) - =/ dir=publish-dir ;;(publish-dir +.i) - :: make moves to save all files to clay, and - :: make moves to call %serve for each collection - :: - =/ out=[mow=(list card) sob=soba:clay] - %+ roll ~(tap by dir) - |= [[pax=path fil=publish-file] mow=(list card) sob=soba:clay] - =/ mis=miso:clay - (feel:space:userlib (weld our-beak pax) -.fil !>(+.fil)) - ?+ pax - [mow sob] - :: - [%web %publish * %publish-info ~] - =/ col=@tas &3.pax - =/ wir=wire /collection/[col] - =/ schema=schematic:ford - :* %bake - %publish-info - *coin - [[our.bol q.byk.bol] /[col]/publish/web] - == - :- :* [%pass wir %arvo %f %build %.y schema] - mow - == - [[pax mis] sob] - :: - [%web %publish * * %udon ~] - =/ col=@tas &3.pax - =/ pos=@tas &4.pax - =/ post-wir=wire /post/[col]/[pos] - =/ post-schema=schematic:ford - :* %bake - %publish-post - *coin - [[our.bol q.byk.bol] /[pos]/[col]/publish/web] - == - =/ comment-wir=wire /comments/[col]/[pos] - =/ comment-schema=schematic:ford - :* %bake - %publish-comments - *coin - [[our.bol q.byk.bol] /[pos]/[col]/publish/web] - == - :- :* [%pass post-wir %arvo %f %build %.y post-schema] - [%pass comment-wir %arvo %f %build %.y comment-schema] - mow - == - [[pax mis] sob] - :: - [%web %publish * * * %publish-comment ~] - :- mow - [[pax mis] sob] - :: - == - :: - =/ tor=toro:clay - [q.byk.bol %.y sob.out] - :_ state - [[%pass /import %arvo %c %info tor] mow.out] -:: -++ peer-export - |= pax=path - ^- (quip card _state) - =/ pal=(list path) .^((list path) %ct (weld our-beak /web/publish)) - :: - =/ dir=publish-dir - %+ roll pal - |= [pax=path out=publish-dir] - ^- publish-dir - ?+ pax - out - :: - [%web %publish * %publish-info ~] - =/ fil=collection-info .^(collection-info %cx (welp our-beak pax)) - (~(put by out) pax [%publish-info fil]) - :: - [%web %publish * * %udon ~] - =/ fil=@t .^(@t %cx (welp our-beak pax)) - (~(put by out) pax [%udon fil]) - :: - [%web %publish * * * %publish-comment ~] - =/ fil=comment .^(comment %cx (welp our-beak pax)) - (~(put by out) pax [%publish-comment fil]) - == - :: - :_ state - [%give %fact ~ %export !>([%publish-v0 dir])]~ -:: -++ peer-publishtile - |= wir=wire - ^- (quip card _state) - :_ state - [%give %fact ~ %json !>(make-tile-json)]~ -:: -++ peer-primary - |= wir=wire - ^- (quip card _state) - ?. =(our.bol src.bol) - :: only we are allowed to subscribe on primary - :: - :_ state - [%give %kick ~ ~]~ - [~ state] -:: -++ pull - |= wir=wire - ^- (quip card _state) - ?+ wir - [~ state] - :: - [%collection @t ~] - =/ coll=@tas i.t.wir - =/ col=(unit collection) (~(get by pubs) coll) - ?~ col - [~ state] - =/ new=collection - u.col(subscribers (~(del in subscribers.u.col) src.bol)) - [~ state(pubs (~(put by pubs) coll new))] - :: - == -:: -++ peer-collection - |= wir=wire - ^- (quip card _state) - ?. ?=([@tas ~] wir) - [~ state] - =/ coll=@tas i.wir - =/ pax /web/publish/[coll] - ?> (allowed src.bol %read pax) - =/ col=collection (~(got by pubs) coll) - =/ new=collection - col(subscribers (~(put in subscribers.col) src.bol)) - =/ rum=rumor - [%total our.bol coll new] - :_ state(pubs (~(put by pubs) coll new)) - [%give %fact ~ %publish-rumor !>(rum)]~ -:: -++ reap - |= [wir=wire err=(unit tang)] - ^- (quip card _state) - ?~ err - [~ state] - ?> ?=([%collection @tas ~] wir) - =/ col=@tas i.t.wir - %- (slog [leaf+"failed to subscribe to blog: {}"] u.err) - [~ state] -:: -- diff --git a/pkg/arvo/lib/publish.hoon b/pkg/arvo/lib/publish.hoon index 339a97f996..157309a1d5 100644 --- a/pkg/arvo/lib/publish.hoon +++ b/pkg/arvo/lib/publish.hoon @@ -17,18 +17,6 @@ (rash (got %pinned) (fuss %true %false)) == :: -++ front-to-comment-info - |= fro=(map knot cord) - ^- comment-info - =/ got ~(got by fro) - ~| %invalid-frontmatter - :* (slav %p (got %creator)) - (got %collection) - (got %post) - (slav %da (got %date-created)) - (slav %da (got %last-modified)) - == -:: ++ collection-info-to-json |= con=collection-info ^- json @@ -56,17 +44,6 @@ :- %collection [%s collection.info] == :: -++ comment-info-to-json - |= info=comment-info - ^- json - %- pairs:enjs:format - :~ :- %creator [%s (scot %p creator.info)] - :- %date-created (time:enjs:format date-created.info) - :- %last-modified (time:enjs:format last-modified.info) - :- %post [%s post.info] - :- %collection [%s collection.info] - == -:: ++ tang-to-json |= tan=tang %- wall:enjs:format @@ -108,16 +85,21 @@ (tang-to-json +.bud) :: ++ comment-build-to-json - |= bud=(each (list [comment-info @t]) tang) + |= bud=(each (list comment) tang) ^- json ?: ?=(%.y -.bud) :- %a %+ turn p.bud - |= [com=comment-info bod=@t] + |= com=comment ^- json %- pairs:enjs:format - :~ info+(comment-info-to-json com) - body+s+bod + :~ :- %info + %- pairs:enjs:format + :~ :- %creator [%s (scot %p author.com)] + :- %date-created (time:enjs:format date-created.com) + :- %last-modified (time:enjs:format last-modified.com) + == + body+s+body.com == (tang-to-json +.bud) :: @@ -125,7 +107,7 @@ |= col=collection ^- json %- pairs:enjs:format - :~ info+(collection-build-to-json col.col) + :~ info+(collection-build-to-json dat.col.col) :: :+ %posts %o @@ -137,8 +119,8 @@ %+ ~(put by out) post %- pairs:enjs:format - :~ post+(post-build-to-json post-build) - comments+(comment-build-to-json comm-build) + :~ post+(post-build-to-json dat.post-build) + comments+(comment-build-to-json dat.comm-build) == :: :- %order diff --git a/pkg/arvo/mar/publish/comment.hoon b/pkg/arvo/mar/publish/comment.hoon index 15a809ba62..3329119ae4 100644 --- a/pkg/arvo/mar/publish/comment.hoon +++ b/pkg/arvo/mar/publish/comment.hoon @@ -1,5 +1,4 @@ /- publish -!: |_ com=comment:publish :: :: @@ -10,11 +9,9 @@ (as-octs:mimes:html (of-wain:format txt)) ++ txt ^- wain - :* (cat 3 'creator: ' (scot %p creator.info.com)) - (cat 3 'collection: ' collection.info.com) - (cat 3 'post: ' post.info.com) - (cat 3 'date-created: ' (scot %da date-created.info.com)) - (cat 3 'last-modified: ' (scot %da last-modified.info.com)) + :* (cat 3 'author: ' (scot %p author.com)) + (cat 3 'date-created: ' (scot %da date-created.com)) + (cat 3 'last-modified: ' (scot %da last-modified.com)) '-----' (to-wain:format body.com) == @@ -29,25 +26,17 @@ ^- comment:publish :: TODO: putting ~ instead of * breaks this but shouldn't :: - ?> ?= $: creator=@t - collection=@t - post=@t + ?> ?= $: author=@t date-created=@t last-modified=@t line=@t body=* == txs - :_ (of-wain:format (wain body.txs)) + ?> =(line.txs '-----') :: - :* %+ rash creator.txs - ;~(pfix (jest 'creator: ~') fed:ag) - :: - %+ rash collection.txs - ;~(pfix (jest 'collection: ') (cook crip (star next))) - :: - %+ rash post.txs - ;~(pfix (jest 'post: ') (cook crip (star next))) + :* %+ rash author.txs + ;~(pfix (jest 'author: ~') fed:ag) :: %+ rash date-created.txs ;~ pfix @@ -61,6 +50,7 @@ (cook year when:so) == :: + (of-wain:format (wain body.txs)) == ++ noun comment:publish -- diff --git a/pkg/arvo/sur/publish.hoon b/pkg/arvo/sur/publish.hoon index 15ceea26c5..7630116a05 100644 --- a/pkg/arvo/sur/publish.hoon +++ b/pkg/arvo/sur/publish.hoon @@ -70,16 +70,13 @@ pinned=? == :: -+$ comment-info - $: creator=@p - collection=@tas - post=@tas ++$ comment + $: author=@p date-created=@da last-modified=@da + body=@t == :: -+$ comment [info=comment-info body=@t] -:: +$ perm-config [read=rule:clay write=rule:clay] :: +$ comment-config $?(%open %closed %none) @@ -97,9 +94,9 @@ == :: +$ collection - $: col=(each collection-info tang) - pos=(map @tas dat=(each [post-info manx @t] tang)) - com=(map @tas dat=(each (list [comment-info @t]) tang)) + $: col=[=bone dat=(each collection-info tang)] + pos=(map @tas [=bone dat=(each [post-info manx @t] tang)]) + com=(map @tas [=bone dat=(each (list comment) tang)]) order=[pin=(list @tas) unpin=(list @tas)] contributors=[mod=?(%white %black) who=(set @p)] subscribers=(set @p) From 504b9b289c0c4ed30d55a00149d1cb7ec874effc Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Thu, 5 Dec 2019 15:42:38 -0800 Subject: [PATCH 02/20] group and permissions creation on %new-book action --- pkg/arvo/app/publish.hoon | 279 ++++++++++++++++++++++++++---- pkg/arvo/mar/publish/action2.hoon | 13 ++ pkg/arvo/sur/publish.hoon | 23 +++ 3 files changed, 283 insertions(+), 32 deletions(-) create mode 100644 pkg/arvo/mar/publish/action2.hoon diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index 0c2be5b17f..d7c3121100 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -1,5 +1,5 @@ :: -/- *publish +/- *publish, *group-store, *permission-hook, *permission-group-hook /+ *server, *publish, cram, default-agent :: /= index @@ -59,6 +59,8 @@ notes=(map @tas note) order=(list @tas) pinned=(set @tas) + participants=path + subscribers=path == :: +$ versioned-state @@ -91,6 +93,10 @@ :~ [%pass /bind %arvo %e %connect [~ /'~publish'] %publish] [%pass /tile %agent [our.bol %launch] %poke %launch-action !>(lac)] [%pass /read/paths %arvo %c %warp our.bol q.byk.bol `rav] + [%pass /permissions %agent [our.bol %permission-store] %watch /updates] + :* %pass /invites %agent [our.bol %invite-store] %watch + /invitatory/publish + == == :: ++ on-save !>(state) @@ -117,14 +123,25 @@ |= req=inbound-request:eyre ^- simple-payload:http not-found:gen + :: + %publish-action2 + =^ cards state + (poke-publish-action-2:main !<(action-2 vas)) + [cards this] == :: ++ on-watch - |= =path + |= pax=path ^- (quip card _this) - ?+ path (on-watch:def path) - [%http-response *] [~ this] -:: [%tile ~] + ?+ pax (on-watch:def pax) + [%http-response *] [~ this] + :: + [%notebook @ ~] + =/ book-name i.t.pax + =/ book (~(get by books) book-name) + !! + :: + [%tile ~] !! == :: ++ on-leave @@ -137,27 +154,26 @@ !! :: ++ on-agent - |= [=wire =sign:agent:gall] + |= [wir=wire sin=sign:agent:gall] ^- (quip card _this) - ?- -.sign - %poke-ack - ?~ p.sign - `this - %- (slog leaf+"poke failed from {} on wire {}" u.p.sign) - `this + ?- -.sin + %poke-ack (on-agent:def wir sin) :: - %watch-ack - ?~ p.sign - `this - =/ =tank leaf+"subscribe failed from {} on wire {}" - %- (slog tank u.p.sign) - `this + %watch-ack (on-agent:def wir sin) + :: + %kick (on-agent:def wir sin) :: - %kick `this %fact - ~| "unexpected subscription update to {} on wire {}" - ~| "with mark {}" - !! + ?+ wir (on-agent:def wir sin) + [%subscribe @ @ ~] + =/ who=@p (slav %p i.t.wir) + =/ book-name i.t.t.wir + !! + :: + [%permissions ~] !! + :: + [%invites ~] !! + == == :: ++ on-arvo @@ -204,6 +220,7 @@ |= ran=rant:clay ^- (quip card _state) =/ rav [%next %t [%da now.bol] /app/publish/notebooks] + ~& new-path-list+!<((list path) q.r.ran) =/ new (filter-and-sort-paths !<((list path) q.r.ran)) =/ dif (diff-paths our-paths new) =^ del-moves state (del-paths del.dif) @@ -331,17 +348,28 @@ =/ book-name i.t.t.t.pax =/ note-name i.t.t.t.t.pax =/ new-note=note (scry-note pax) - =/ book=notebook - %+ fall (~(get by books.sty) book-name) - [book-name now.bol now.bol ~ [note-name]~ ~] - =/ old-note (~(get by notes.book) note-name) + =/ old-book (~(get by books.sty) book-name) + =+ ^- [cards=(list card) new-book=notebook] + ?~ old-book + :- ~ + :* book-name + now.bol + now.bol + ~ + [note-name]~ + ~ + /publish/[book-name]/participants + /publish/[book-name]/subscribers + == + [~ u.old-book] + =/ old-note (~(get by notes.new-book) note-name) ?^ old-note =. date-created.new-note date-created.u.old-note =. comments.new-note comments.u.old-note - =. notes.book (~(put by notes.book) note-name new-note) + =. notes.new-book (~(put by notes.new-book) note-name new-note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] :- [%pass (welp /read/note pax) %arvo %c %warp our.bol rif]~ - sty(books (~(put by books.sty) book-name book)) + sty(books (~(put by books.sty) book-name new-book)) :: =/ comment-dir /app/publish/notebooks/[book-name]/[note-name] =/ comment-paths .^((list path) %ct (weld our-beak comment-dir)) @@ -358,10 +386,10 @@ :- [[%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] cad] (~(put by com) u.comment-name new-com) =. comments.new-note new-comments - =. notes.book (~(put by notes.book) note-name new-note) + =. notes.new-book (~(put by notes.new-book) note-name new-note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] :- [[%pass (welp /read/note pax) %arvo %c %warp our.bol rif] cards] - sty(books (~(put by books.sty) book-name book)) + sty(books (~(put by books.sty) book-name new-book)) :: [%app %publish %notebooks @ @ @ %publish-comment ~] =/ book-name i.t.t.t.pax @@ -470,7 +498,18 @@ =. pax (weld our-beak pax) [%pass (weld /delete pax) %arvo %c %info (fray pax)] :: -++ update-udon-front +++ delete-dir + |= pax=path + ^- card + =/ nor=nori:clay + :- %& + %+ turn .^((list path) %ct (weld our-beak pax)) + |= pax=path + ^- [path miso:clay] + [pax %del ~] + [%pass (weld /delete pax) %arvo %c %info q.byk.bol nor] +:: +++ add-front-matter |= [fro=(map knot cord) udon=@t] ^- @t %- of-wain:format @@ -478,7 +517,7 @@ =/ id (find ";>" tum) ?~ id %+ weld (front-to-wain fro) - (to-wain:format (crip (weld ";>\0a" tum))) + (to-wain:format (crip :(weld ";>\0a" tum))) %+ weld (front-to-wain fro) (to-wain:format (crip (slag u.id tum))) :: @@ -498,4 +537,180 @@ [' ==' ~] == :: +++ group-poke + |= act=group-action + ^- card + [%pass / %agent [our.bol %group-store] %poke %group-action !>(act)] +:: +++ perm-hook-poke + |= act=permission-hook-action + ^- card + :* %pass + / + %agent + [our.bol %permission-hook] + %poke + %permission-hook-action + !>(act) + == +:: +++ perm-group-hook-poke + |= act=permission-group-hook-action + ^- card + :* %pass + / + %agent + [our.bol %permission-group-hook] + %poke + %permission-group-hook-action + !>(act) + == +:: +++ create-security + |= [par=path sub=path sec=rw-security] + ^- (list card) + =+ ^- [par-type=?(%black %white) sub-type=?(%black %white)] + ?- sec + %channel [%black %black] + %village [%white %white] + %journal [%black %white] + %mailbox [%white %black] + == + :~ (perm-group-hook-poke [%associate par [[par par-type] ~ ~]]) + (perm-group-hook-poke [%associate sub [[sub sub-type] ~ ~]]) + == +:: +++ poke-publish-action-2 + |= act=action-2 + ^- (quip card _state) + ?- -.act + %new-book + ?> (team:title our.bol src.bol) + =+ ^- [cards=(list card) par-path=path sub-path=path] + ?- -.group.act + %old [~ par.group.act sub.group.act] + %new + =/ par-path /publish/[book.act]/participants + =/ sub-path /publish/[book.act]/subscribers + :_ [par-path sub-path] + ;: weld + :~ (group-poke [%bundle par-path]) + (group-poke [%bundle sub-path]) + (group-poke [%add par.group.act par-path]) + (group-poke [%add sub.group.act sub-path]) + == + (create-security par-path sub-path sec.group.act) + :~ (perm-hook-poke [%add-owned par-path par-path]) + (perm-hook-poke [%add-owned sub-path sub-path]) + == + == + == + =/ new-book=notebook [title.act now.bol now.bol ~ ~ ~ par-path sub-path] + :- cards + state(books (~(put by books) book.act new-book)) + :: + %new-note + =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon + =/ front=(map knot cord) + %- my + :~ title+title.act + author+(scot %p src.bol) + == + =. body.act (cat 3 body.act '\0a') + =/ file=@t (add-front-matter front body.act) + :_ state + [(write-file pax %udon !>(file))]~ + :: + %new-comment + =/ pax=path + %+ weld /app/publish/notebooks + /[book.act]/[note.act]/(scot %da now.bol)/publish-comment + =/ new-comment=comment + :* author=src.bol + date-created=now.bol + last-edit=now.bol + content=body.act + == + :_ state + [(write-file pax %publish-comment !>(new-comment))]~ + :: + %edit-book + ?> (team:title our.bol src.bol) + =/ book (~(got by books) book.act) + =? title.book ?=(^ new-title.act) + u.new-title.act + =+ ^- [cards=(list card) par-path=path sub-path=path] + ?~ new-group.act + [~ participants.book subscribers.book] + ?- -.u.new-group.act + %old [~ par.u.new-group.act sub.u.new-group.act] + %new + =/ par-path /publish/[book.act]/participants + =/ sub-path /publish/[book.act]/subscribers + :_ [par-path sub-path] + %+ weld + :~ (group-poke [%bundle par-path]) + (group-poke [%bundle sub-path]) + (group-poke [%add par.u.new-group.act par-path]) + (group-poke [%add sub.u.new-group.act sub-path]) + (perm-hook-poke [%add-owned par-path par-path]) + (perm-hook-poke [%add-owned sub-path sub-path]) + == + (create-security par-path sub-path sec.u.new-group.act) + == + =. participants.book par-path + =. subscribers.book sub-path + [~ state(books (~(put by books) book.act book))] + :: + %edit-note + =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon + =/ front=(map knot cord) + %- my + :~ title+new-title.act + author+(scot %p src.bol) + == + =. new-body.act (cat 3 new-body.act '\0a') + =/ file=@t (add-front-matter front new-body.act) + :_ state + [(write-file pax %udon !>(file))]~ + :: + %edit-comment + =/ pax=path + %+ weld /app/publish/notebooks + /[book.act]/[note.act]/[comment.act]/publish-comment + =/ comment .^(comment %cx (weld our-beak pax)) + =. content.comment new-body.act + =. last-edit.comment now.bol + :_ state + [(write-file pax %publish-comment !>(comment))]~ + :: + %del-book + ?> (team:title our.bol src.bol) + =/ pax=path /app/publish/notebooks/[book.act] + :_ state(books (~(del by books) book.act)) + [(delete-dir pax)]~ + :: + %del-note + =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon + :_ state + [(delete-file pax)]~ + :: + %del-comment + =/ pax=path + %+ weld /app/publish/notebooks + /[book.act]/[note.act]/[comment.act]/publish-comment + :_ state + [(delete-file pax)]~ + :: + %subscribe + =/ wir=wire /subscribe/(scot %p who.act)/[book.act] + :_ state + [%pass wir %agent [who.act %publish] %watch /notebook/[book.act]]~ + :: + %unsubscribe + =/ wir=wire /subscribe/(scot %p who.act)/[book.act] + :_ state(subs (~(del by subs) who.act book.act)) + [%pass wir %agent [who.act %publish] %leave ~]~ + == +:: -- diff --git a/pkg/arvo/mar/publish/action2.hoon b/pkg/arvo/mar/publish/action2.hoon new file mode 100644 index 0000000000..3f063ca1a7 --- /dev/null +++ b/pkg/arvo/mar/publish/action2.hoon @@ -0,0 +1,13 @@ +:: +:::: /hoon/action/publish/mar + :: +/- *publish +=, format +:: +|_ act=action-2 +:: +++ grab + |% + ++ noun action-2 + -- +-- diff --git a/pkg/arvo/sur/publish.hoon b/pkg/arvo/sur/publish.hoon index 7630116a05..efaabc3404 100644 --- a/pkg/arvo/sur/publish.hoon +++ b/pkg/arvo/sur/publish.hoon @@ -1,3 +1,4 @@ +/- *rw-security |% :: +$ action @@ -49,6 +50,28 @@ [%read who=@p coll=@tas post=@tas] == :: ++$ group-info + $% [%old par=path sub=path] + [%new par=(set ship) sub=(set ship) sec=rw-security] + == +:: ++$ action-2 + $% [%new-book book=@tas title=@t group=group-info] + [%new-note who=@p book=@tas note=@tas title=@t body=@t] + [%new-comment who=@p book=@tas note=@tas body=@t] + :: + [%edit-book book=@tas new-title=(unit @t) new-group=(unit group-info)] + [%edit-note who=@p book=@tas note=@tas new-title=@t new-body=@t] + [%edit-comment who=@p book=@tas note=@tas comment=@tas new-body=@t] + :: + [%del-book book=@tas] + [%del-note who=@p book=@tas note=@tas] + [%del-comment who=@p book=@tas note=@tas comment=@tas] + :: + [%subscribe who=@p book=@tas] + [%unsubscribe who=@p book=@tas] + == +:: +$ collection-info $: owner=@p title=@t From dcec0315aefeaa38f40dd3f23f9c69dd3ea583cb Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Mon, 9 Dec 2019 09:10:03 -0800 Subject: [PATCH 03/20] sending updates to subscribers --- pkg/arvo/app/publish.hoon | 151 +++++++++++++++++++++++++------------- pkg/arvo/lib/publish.hoon | 125 ------------------------------- pkg/arvo/sur/publish.hoon | 134 ++++++++------------------------- 3 files changed, 127 insertions(+), 283 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index d7c3121100..cb8df6b5d8 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -34,35 +34,6 @@ |% +$ card card:agent:gall :: -+$ comment - $: author=@p - date-created=@da - last-edit=@da - content=@t - == -:: -+$ note - $: author=@p - title=@t - filename=@tas - date-created=@da - last-edit=@da - file=@t - build=(each manx tang) - comments=(map @da comment) - == -:: -+$ notebook - $: title=@t - date-created=@da - last-note=@da - notes=(map @tas note) - order=(list @tas) - pinned=(set @tas) - participants=path - subscribers=path - == -:: +$ versioned-state $% [%1 state-one] == @@ -120,13 +91,11 @@ :_ this %+ give-simple-payload:app id %+ require-authorization:app req - |= req=inbound-request:eyre - ^- simple-payload:http - not-found:gen + handle-http-request:main :: %publish-action2 =^ cards state - (poke-publish-action-2:main !<(action-2 vas)) + (poke-publish-action:main !<(action vas)) [cards this] == :: @@ -138,8 +107,11 @@ :: [%notebook @ ~] =/ book-name i.t.pax - =/ book (~(get by books) book-name) - !! + =/ book (~(got by books) book-name) + :_ this + [%give %fact ~ %publish-book-update !>([%full book-name book])]~ + :: + [%primary ~] [~ this] :: [%tile ~] !! == @@ -168,7 +140,8 @@ [%subscribe @ @ ~] =/ who=@p (slav %p i.t.wir) =/ book-name i.t.t.wir - !! + ?> ?=(%publish-book-update p.cage.sin) + (handle-notebook-delta:main !<(notebook-delta q.cage.sin)) :: [%permissions ~] !! :: @@ -254,8 +227,11 @@ =. comments.new-note comments.u.old-note =. notes.u.book (~(put by notes.u.book) note-name new-note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - :- [%pass (welp /read/note pax) %arvo %c %warp our.bol rif]~ - state(books (~(put by books) book-name u.book)) + =/ fac=notebook-delta [%note book-name note-name new-note] + :_ state(books (~(put by books) book-name u.book)) + :~ [%pass (welp /read/note pax) %arvo %c %warp our.bol rif] + [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] + == :: ++ read-comment |= [pax=path rot=riot:clay] @@ -281,8 +257,12 @@ =. comments.u.note (~(put by comments.u.note) u.comment-date new-comment) =. notes.u.book (~(put by notes.u.book) note-name u.note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - :- [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif]~ - state(books (~(put by books) book-name u.book)) + =/ fac=notebook-delta + [%comment book-name note-name u.comment-date new-comment] + :_ state(books (~(put by books) book-name u.book)) + :~ [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] + [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] + == :: ++ filter-and-sort-paths |= paths=(list path) @@ -317,8 +297,9 @@ ?~ book [~ sty] =. notes.u.book (~(del by notes.u.book) note-name) - :- ~ - sty(books (~(put by books) book-name u.book)) + =/ fac=notebook-delta [%del-note book-name note-name] + :_ sty(books (~(put by books) book-name u.book)) + [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)]~ :: [%app %publish %notebooks @ @ @ %publish-comment ~] =/ book-name i.t.t.t.pax @@ -334,8 +315,9 @@ [~ sty] =. comments.u.note (~(del by comments.u.note) u.comment-date) =. notes.u.book (~(put by notes.u.book) note-name u.note) - :- ~ - sty(books (~(put by books.sty) book-name u.book)) + =/ fac=notebook-delta [%del-comment book-name note-name u.comment-date] + :_ sty(books (~(put by books.sty) book-name u.book)) + [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)]~ == :: ++ add-paths @@ -368,8 +350,11 @@ =. comments.new-note comments.u.old-note =. notes.new-book (~(put by notes.new-book) note-name new-note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - :- [%pass (welp /read/note pax) %arvo %c %warp our.bol rif]~ - sty(books (~(put by books.sty) book-name new-book)) + =/ fac=notebook-delta [%note book-name note-name new-note] + :_ sty(books (~(put by books.sty) book-name new-book)) + :~ [%pass (welp /read/note pax) %arvo %c %warp our.bol rif] + [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] + == :: =/ comment-dir /app/publish/notebooks/[book-name]/[note-name] =/ comment-paths .^((list path) %ct (weld our-beak comment-dir)) @@ -388,8 +373,12 @@ =. comments.new-note new-comments =. notes.new-book (~(put by notes.new-book) note-name new-note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - :- [[%pass (welp /read/note pax) %arvo %c %warp our.bol rif] cards] - sty(books (~(put by books.sty) book-name new-book)) + =/ fac=notebook-delta [%note book-name note-name new-note] + :_ sty(books (~(put by books.sty) book-name new-book)) + :* [%pass (welp /read/note pax) %arvo %c %warp our.bol rif] + [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] + cards + == :: [%app %publish %notebooks @ @ @ %publish-comment ~] =/ book-name i.t.t.t.pax @@ -407,8 +396,12 @@ =. comments.u.note (~(put by comments.u.note) u.comment-name new-com) =. notes.u.book (~(put by notes.u.book) note-name u.note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - :- [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif]~ - sty(books (~(put by books.sty) book-name u.book)) + =/ fac=notebook-delta + [%comment book-name note-name u.comment-name new-com] + :_ sty(books (~(put by books.sty) book-name u.book)) + :~ [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] + [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] + == == :: ++ scry-note @@ -580,8 +573,8 @@ (perm-group-hook-poke [%associate sub [[sub sub-type] ~ ~]]) == :: -++ poke-publish-action-2 - |= act=action-2 +++ poke-publish-action + |= act=action ^- (quip card _state) ?- -.act %new-book @@ -660,7 +653,10 @@ == =. participants.book par-path =. subscribers.book sub-path - [~ state(books (~(put by books) book.act book))] + :_ state(books (~(put by books) book.act book)) + ?~ new-title.act ~ + =/ fac=notebook-delta [%book-meta book.act u.new-title.act] + [%give %fact `/notebook/[book.act] %publish-book-update !>(fac)]~ :: %edit-note =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon @@ -713,4 +709,53 @@ [%pass wir %agent [who.act %publish] %leave ~]~ == :: +++ handle-notebook-delta + |= del=notebook-delta + ^- (quip card _state) + ?- -.del + %book + :_ state(books (~(put by books) book.del data.del)) + ~ + :: + %book-meta + =/ book (~(got by books) book.del) + =. title.book title.del + :_ state(books (~(put by books) book.del data.del)) + ~ + :: + %note + =/ book (~(got by books) book.del) + =. notes.book (~(put by notes.book) note.del data.del) + :_ state(books (~(put by books) book.del data.del)) + ~ + :: + %comment + =/ book (~(got by books) book.del) + =/ note (~(got by notes.book) note.del) + =. comments.note (~(put by comments.note) comment-date.del data.del) + =. notes.book (~(put by notes.book) note.del note) + :_ state(books (~(put by books) book.del data.del)) + ~ + :: + %del-book !! + :: + %del-note + =/ book (~(got by books) book.del) + =. notes.book (~(del by notes.book) note.del) + :_ state(books (~(put by books) book.del data.del)) + ~ + :: + %del-comment + =/ book (~(got by books) book.del) + =/ note (~(got by notes.book) note.del) + =. comments.note (~(del by comments.note) comment-date.del) + =. notes.book (~(put by notes.book) note.del note) + :_ state(books (~(put by books) book.del data.del)) + ~ + == +:: +++ handle-http-request + |= req=inbound-request:eyre + ^- simple-payload:http + not-found:gen -- diff --git a/pkg/arvo/lib/publish.hoon b/pkg/arvo/lib/publish.hoon index 157309a1d5..02ca605b05 100644 --- a/pkg/arvo/lib/publish.hoon +++ b/pkg/arvo/lib/publish.hoon @@ -2,48 +2,6 @@ /+ elem-to-react-json |% :: -++ front-to-post-info - |= fro=(map knot cord) - ^- post-info - =/ got ~(got by fro) - ~| %invalid-frontmatter - :* (slav %p (got %creator)) - (got %title) - (got %collection) - (got %filename) - (comment-config (got %comments)) - (slav %da (got %date-created)) - (slav %da (got %last-modified)) - (rash (got %pinned) (fuss %true %false)) - == -:: -++ collection-info-to-json - |= con=collection-info - ^- json - %- pairs:enjs:format - :~ :- %owner [%s (scot %p owner.con)] - :- %title [%s title.con] - :- %comments [%s comments.con] - :- %allow-edit [%s allow-edit.con] - :- %date-created (time:enjs:format date-created.con) - :- %last-modified (time:enjs:format last-modified.con) - :- %filename [%s filename.con] - == -:: -++ post-info-to-json - |= info=post-info - ^- json - %- pairs:enjs:format - :~ :- %creator [%s (scot %p creator.info)] - :- %title [%s title.info] - :- %comments [%s comments.info] - :- %date-created (time:enjs:format date-created.info) - :- %last-modified (time:enjs:format last-modified.info) - :- %pinned [%b pinned.info] - :- %filename [%s filename.info] - :- %collection [%s collection.info] - == -:: ++ tang-to-json |= tan=tang %- wall:enjs:format @@ -65,87 +23,4 @@ ?: &((gte a 'A') (lte a 'Z')) (add 32 a) '-' -:: -++ collection-build-to-json - |= bud=(each collection-info tang) - ^- json - ?: ?=(%.y -.bud) - (collection-info-to-json +.bud) - (tang-to-json +.bud) -:: -++ post-build-to-json - |= bud=(each [post-info manx @t] tang) - ^- json - ?: ?=(%.y -.bud) - %- pairs:enjs:format - :~ info+(post-info-to-json +<.bud) - body+(elem-to-react-json +>-.bud) - raw+[%s +>+.bud] - == - (tang-to-json +.bud) -:: -++ comment-build-to-json - |= bud=(each (list comment) tang) - ^- json - ?: ?=(%.y -.bud) - :- %a - %+ turn p.bud - |= com=comment - ^- json - %- pairs:enjs:format - :~ :- %info - %- pairs:enjs:format - :~ :- %creator [%s (scot %p author.com)] - :- %date-created (time:enjs:format date-created.com) - :- %last-modified (time:enjs:format last-modified.com) - == - body+s+body.com - == - (tang-to-json +.bud) -:: -++ total-build-to-json - |= col=collection - ^- json - %- pairs:enjs:format - :~ info+(collection-build-to-json dat.col.col) - :: - :+ %posts - %o - %+ roll ~(tap in ~(key by pos.col)) - |= [post=@tas out=(map @t json)] - =/ post-build (~(got by pos.col) post) - =/ comm-build (~(got by com.col) post) - - %+ ~(put by out) - post - %- pairs:enjs:format - :~ post+(post-build-to-json dat.post-build) - comments+(comment-build-to-json dat.comm-build) - == - :: - :- %order - %- pairs:enjs:format - :~ pin+a+(turn pin.order.col |=(s=@tas [%s s])) - unpin+a+(turn unpin.order.col |=(s=@tas [%s s])) - == - :: - :- %contributors - %- pairs:enjs:format - :~ mod+s+mod.contributors.col - :+ %who - %a - %+ turn ~(tap in who.contributors.col) - |= who=@p - (ship:enjs:format who) - == - :: - :+ %subscribers - %a - %+ turn ~(tap in subscribers.col) - |= who=@p - ^- json - (ship:enjs:format who) - :: - [%last-update (time:enjs:format last-update.col)] - == -- diff --git a/pkg/arvo/sur/publish.hoon b/pkg/arvo/sur/publish.hoon index efaabc3404..985d9c49d0 100644 --- a/pkg/arvo/sur/publish.hoon +++ b/pkg/arvo/sur/publish.hoon @@ -1,61 +1,12 @@ /- *rw-security |% :: -+$ action - $% $: %new-collection - name=@tas - title=@t - com=comment-config - edit=edit-config - perm=perm-config - == - :: - $: %new-post - who=@p - coll=@tas - name=@tas - title=@t - com=comment-config - perm=perm-config - content=@t - == - :: - [%new-comment who=@p coll=@tas post=@tas content=@t] - :: - [%delete-collection coll=@tas] - [%delete-post coll=@tas post=@tas] - [%delete-comment coll=@tas post=@tas comment=@tas] - :: - [%edit-collection name=@tas title=@t] - :: - $: %edit-post - who=@p - coll=@tas - name=@tas - title=@t - com=comment-config - perm=perm-config - content=@t - == - :: - [%invite coll=@tas title=@t who=(list ship)] - [%reject-invite who=@p coll=@tas] - :: - [%serve coll=@tas] - [%unserve coll=@tas] - :: - [%subscribe who=@p coll=@tas] - [%unsubscribe who=@p coll=@tas] - :: - [%read who=@p coll=@tas post=@tas] - == -:: +$ group-info $% [%old par=path sub=path] [%new par=(set ship) sub=(set ship) sec=rw-security] == :: -+$ action-2 ++$ action $% [%new-book book=@tas title=@t group=group-info] [%new-note who=@p book=@tas note=@tas title=@t body=@t] [%new-comment who=@p book=@tas note=@tas body=@t] @@ -72,70 +23,43 @@ [%unsubscribe who=@p book=@tas] == :: -+$ collection-info - $: owner=@p - title=@t - filename=@tas - comments=comment-config - allow-edit=edit-config - date-created=@da - last-modified=@da - == -:: -+$ post-info - $: creator=@p - title=@t - collection=@tas - filename=@tas - comments=comment-config - date-created=@da - last-modified=@da - pinned=? - == -:: +$ comment $: author=@p date-created=@da - last-modified=@da - body=@t + last-edit=@da + content=@t == :: -+$ perm-config [read=rule:clay write=rule:clay] -:: -+$ comment-config $?(%open %closed %none) -:: -+$ edit-config $?(%post %comment %all %none) -:: -+$ rumor delta -:: -+$ publish-dir (map path publish-file) -:: -+$ publish-file - $% [%udon @t] - [%publish-info collection-info] - [%publish-comment comment] ++$ note + $: author=@p + title=@t + filename=@tas + date-created=@da + last-edit=@da + file=@t + build=(each manx tang) + comments=(map @da comment) == :: -+$ collection - $: col=[=bone dat=(each collection-info tang)] - pos=(map @tas [=bone dat=(each [post-info manx @t] tang)]) - com=(map @tas [=bone dat=(each (list comment) tang)]) - order=[pin=(list @tas) unpin=(list @tas)] - contributors=[mod=?(%white %black) who=(set @p)] - subscribers=(set @p) - last-update=@da ++$ notebook + $: title=@t + date-created=@da + notes=(map @tas note) + order=(list @tas) + pinned=(set @tas) + participants=path + subscribers=path == :: -+$ delta - $% [%collection who=@p col=@tas dat=(each collection-info tang)] - [%post who=@p col=@tas pos=@tas dat=(each [post-info manx @t] tang)] - [%comments who=@p col=@tas pos=@tas dat=(each (list comment) tang)] - [%total who=@p col=@tas dat=collection] - [%remove who=@p col=@tas pos=(unit @tas)] ++$ notebook-delta + $% [%book book=@tas data=notebook] + [%book-meta book=@tas title=@t] + [%note book=@tas note=@tas data=note] + [%comment book=@tas note=@tas comment-date=@da data=comment] + [%del-book book=@tas] + [%del-note book=@tas note=@tas] + [%del-comment book=@tas note=@tas comment=@da] == :: -+$ update - $% [%invite add=? who=@p col=@tas title=@t] - [%unread add=? keys=(set [who=@p coll=@tas post=@tas])] - == ++$ primary-delta !! -- From e807e6c223a5f932c34ebd035f94c7cded080ac3 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Fri, 13 Dec 2019 14:27:37 -0800 Subject: [PATCH 04/20] paginated frontend api --- pkg/arvo/app/publish.hoon | 687 ++++++++++++++++------- pkg/arvo/lib/publish.hoon | 136 +++++ pkg/arvo/mar/publish/action2.hoon | 108 +++- pkg/arvo/mar/publish/comment.hoon | 10 +- pkg/arvo/mar/publish/info.hoon | 75 +-- pkg/arvo/mar/publish/notebook-delta.hoon | 13 + pkg/arvo/mar/publish/primary-delta.hoon | 70 +++ pkg/arvo/sur/publish.hoon | 47 +- 8 files changed, 863 insertions(+), 283 deletions(-) create mode 100644 pkg/arvo/mar/publish/notebook-delta.hoon create mode 100644 pkg/arvo/mar/publish/primary-delta.hoon diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index cb8df6b5d8..8d597a6b3f 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -42,7 +42,6 @@ $: our-paths=(list path) books=(map @tas notebook) subs=(map [@p @tas] notebook) - recent=(list [@p @tas @tas]) unread=(set [@p @tas @tas]) == -- @@ -58,7 +57,7 @@ :: ++ on-init ^- (quip card _this) - =/ lac [%launch-action %publish /publishtile '/~publish/tile.js'] + =/ lac [%publish /publishtile '/~publish/tile.js'] =/ rav [%sing %t [%da now.bol] /app/publish/notebooks] :_ this :~ [%pass /bind %arvo %e %connect [~ /'~publish'] %publish] @@ -75,8 +74,8 @@ ++ on-load |= old=vase ^- (quip card _this) -:: [~ this(state !<(,[%1 state-one] old))] - [~ this(state *state-one)] + [~ this(state !<(,[%1 state-one] old))] +:: [~ this(state *state-one)] :: ++ on-poke |= [mar=mark vas=vase] @@ -108,17 +107,17 @@ [%notebook @ ~] =/ book-name i.t.pax =/ book (~(got by books) book-name) + =/ delta=notebook-delta + [%add-book our.bol book-name book] :_ this - [%give %fact ~ %publish-book-update !>([%full book-name book])]~ + [%give %fact ~ %publish-notebook-delta !>(delta)]~ :: [%primary ~] [~ this] :: [%tile ~] !! == :: - ++ on-leave - |= path - `this + ++ on-leave on-leave:def :: ++ on-peek |= =path @@ -140,8 +139,10 @@ [%subscribe @ @ ~] =/ who=@p (slav %p i.t.wir) =/ book-name i.t.t.wir - ?> ?=(%publish-book-update p.cage.sin) - (handle-notebook-delta:main !<(notebook-delta q.cage.sin)) + ?> ?=(%publish-notebook-delta p.cage.sin) + =^ cards state + (handle-notebook-delta:main !<(notebook-delta q.cage.sin)) + [cards this] :: [%permissions ~] !! :: @@ -162,6 +163,13 @@ =^ cards state (read-paths:main u.rot) [cards this] + :: + [%read %info *] + ?> ?=([?(%b %c) %writ *] sin) + =/ rot=riot:clay +>.sin + =^ cards state + (read-info:main t.t.wir rot) + [cards this] :: [%read %note *] ?> ?=([?(%b %c) %writ *] sin) @@ -181,10 +189,7 @@ [~ this] == :: - ++ on-fail - |= [=term =tang] - %- (slog leaf+"error in {}" >term< tang) - `this + ++ on-fail on-fail:def -- :: |_ bol=bowl:gall @@ -193,7 +198,6 @@ |= ran=rant:clay ^- (quip card _state) =/ rav [%next %t [%da now.bol] /app/publish/notebooks] - ~& new-path-list+!<((list path) q.r.ran) =/ new (filter-and-sort-paths !<((list path) q.r.ran)) =/ dif (diff-paths our-paths new) =^ del-moves state (del-paths del.dif) @@ -207,6 +211,33 @@ == [cards state(our-paths new)] :: +++ read-info + |= [pax=path rot=riot:clay] + ^- (quip card _state) + ?> ?=([%app %publish %notebooks @ %publish-info ~] pax) + =/ book-name i.t.t.t.pax + ?~ rot + [~ state] + =/ info=notebook-info !<(notebook-info q.r.u.rot) + =/ new-book=notebook + :* title.info + description.info + comments.info + writers.info + subscribers.info + now.bol + ~ ~ ~ + == + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + =/ delta=notebook-delta + [%edit-book our.bol book-name new-book] + =^ cards state + (handle-notebook-delta delta) + :_ state + :* [%pass (welp /read/info pax) %arvo %c %warp our.bol rif] + cards + == +:: ++ read-note |= [pax=path rot=riot:clay] ^- (quip card _state) @@ -223,45 +254,36 @@ [~ state] =/ udon !<(@t q.r.u.rot) =/ new-note=note (form-note note-name udon) - =. date-created.new-note date-created.u.old-note - =. comments.new-note comments.u.old-note - =. notes.u.book (~(put by notes.u.book) note-name new-note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - =/ fac=notebook-delta [%note book-name note-name new-note] - :_ state(books (~(put by books) book-name u.book)) - :~ [%pass (welp /read/note pax) %arvo %c %warp our.bol rif] - [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] + =/ delta=notebook-delta + [%edit-note our.bol book-name note-name new-note] + =^ cards state + (handle-notebook-delta delta) + :_ state + :* [%pass (welp /read/note pax) %arvo %c %warp our.bol rif] + cards == :: ++ read-comment |= [pax=path rot=riot:clay] ^- (quip card _state) ?> ?=([%app %publish %notebooks @ @ @ %publish-comment ~] pax) - =/ book-name i.t.t.t.pax - =/ note-name i.t.t.t.t.pax + ?~ rot + [~ state] =/ comment-date (slaw %da i.t.t.t.t.t.pax) ?~ comment-date [~ state] - =/ book (~(get by books) book-name) - ?~ book - [~ state] - =/ note (~(get by notes.u.book) note-name) - ?~ note - [~ state] - =/ old-comment (~(get by comments.u.note) u.comment-date) - ?~ old-comment - [~ state] - ?~ rot - [~ state] + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax =/ new-comment !<(comment q.r.u.rot) - =. comments.u.note (~(put by comments.u.note) u.comment-date new-comment) - =. notes.u.book (~(put by notes.u.book) note-name u.note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - =/ fac=notebook-delta - [%comment book-name note-name u.comment-date new-comment] - :_ state(books (~(put by books) book-name u.book)) - :~ [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] - [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] + =/ delta=notebook-delta + [%edit-comment our.bol book-name note-name u.comment-date new-comment] + =^ cards state + (handle-notebook-delta delta) + :_ state + :* [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] + cards == :: ++ filter-and-sort-paths @@ -270,7 +292,8 @@ %+ sort %+ skim paths |= pax=path - ?| ?=([%app %publish %notebooks @ @ %udon ~] pax) + ?| ?=([%app %publish %notebooks @ %publish-info ~] pax) + ?=([%app %publish %notebooks @ @ %udon ~] pax) ?=([%app %publish %notebooks @ @ @ %publish-comment ~] pax) == |= [a=path b=path] @@ -290,6 +313,11 @@ %+ roll paths |= [pax=path cad=(list card) sty=_state] ?+ pax !! + [%app %publish %notebooks @ %publish-info ~] + =/ book-name i.t.t.t.pax + =/ delta=notebook-delta [%del-book our.bol book-name] + (handle-notebook-delta delta) + :: [%app %publish %notebooks @ @ %udon ~] =/ book-name i.t.t.t.pax =/ note-name i.t.t.t.t.pax @@ -297,9 +325,8 @@ ?~ book [~ sty] =. notes.u.book (~(del by notes.u.book) note-name) - =/ fac=notebook-delta [%del-note book-name note-name] - :_ sty(books (~(put by books) book-name u.book)) - [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)]~ + =/ delta=notebook-delta [%del-note our.bol book-name note-name] + (handle-notebook-delta delta) :: [%app %publish %notebooks @ @ @ %publish-comment ~] =/ book-name i.t.t.t.pax @@ -307,17 +334,32 @@ =/ comment-date (slaw %da i.t.t.t.t.t.pax) ?~ comment-date [~ sty] - =/ book (~(get by books.sty) book-name) - ?~ book - [~ sty] - =/ note (~(get by notes.u.book) note-name) - ?~ note - [~ sty] - =. comments.u.note (~(del by comments.u.note) u.comment-date) - =. notes.u.book (~(put by notes.u.book) note-name u.note) - =/ fac=notebook-delta [%del-comment book-name note-name u.comment-date] - :_ sty(books (~(put by books.sty) book-name u.book)) - [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)]~ + =/ delta=notebook-delta + [%del-comment our.bol book-name note-name u.comment-date] + (handle-notebook-delta delta) + == +:: +++ make-groups + |= [book-name=@tas group=group-info] + ^- [(list card) path path] + ?- -.group + %old [~ writers.group subscribers.group] + %new + =/ writers-path /~/publish/[book-name]/writers + =/ subscribers-path /~/publish/[book-name]/subscribers + ^- [(list card) path path] + :_ [writers-path subscribers-path] + ;: weld + :~ (group-poke [%bundle writers-path]) + (group-poke [%bundle subscribers-path]) + (group-poke [%add writers.group writers-path]) + (group-poke [%add subscribers.group subscribers-path]) + == + (create-security writers-path subscribers-path sec.group) + :~ (perm-hook-poke [%add-owned writers-path writers-path]) + (perm-hook-poke [%add-owned subscribers-path subscribers-path]) + == + == == :: ++ add-paths @@ -325,85 +367,108 @@ ^- (quip card _state) %+ roll paths |= [pax=path cad=(list card) sty=_state] + ^- (quip card _state) ?+ pax !! + [%app %publish %notebooks @ %publish-info ~] + =/ book-name i.t.t.t.pax + =/ info=notebook-info .^(notebook-info %cx (welp our-beak pax)) + =/ new-book=notebook + :* title.info + description.info + comments.info + writers.info + subscribers.info + now.bol + ~ ~ ~ + == + =+ ^- [read-cards=(list card) notes=(map @tas note)] + (watch-notes /app/publish/notebooks/[book-name]) + =. notes.new-book notes + =/ delta=notebook-delta [%add-book our.bol book-name new-book] + :: + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + =^ update-cards sty (handle-notebook-delta delta) + :_ sty + ;: weld + [%pass (welp /read/info pax) %arvo %c %warp our.bol rif]~ + read-cards + update-cards + == + :: [%app %publish %notebooks @ @ %udon ~] =/ book-name i.t.t.t.pax =/ note-name i.t.t.t.t.pax =/ new-note=note (scry-note pax) - =/ old-book (~(get by books.sty) book-name) - =+ ^- [cards=(list card) new-book=notebook] - ?~ old-book - :- ~ - :* book-name - now.bol - now.bol - ~ - [note-name]~ - ~ - /publish/[book-name]/participants - /publish/[book-name]/subscribers - == - [~ u.old-book] - =/ old-note (~(get by notes.new-book) note-name) - ?^ old-note - =. date-created.new-note date-created.u.old-note - =. comments.new-note comments.u.old-note - =. notes.new-book (~(put by notes.new-book) note-name new-note) - =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - =/ fac=notebook-delta [%note book-name note-name new-note] - :_ sty(books (~(put by books.sty) book-name new-book)) - :~ [%pass (welp /read/note pax) %arvo %c %warp our.bol rif] - [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] - == - :: - =/ comment-dir /app/publish/notebooks/[book-name]/[note-name] - =/ comment-paths .^((list path) %ct (weld our-beak comment-dir)) - =+ ^- [cards=(list card) new-comments=(map @da comment)] - %+ roll comment-paths - |= [pax=path cad=(list card) com=(map @da comment)] - ?. ?=([%app %publish %notebooks @ @ @ %publish-comment ~] pax) - [cad com] - =/ comment-name (slaw %da i.t.t.t.t.t.pax) - ?~ comment-name - [cad com] - =/ new-com .^(comment %cx (welp our-beak pax)) - =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - :- [[%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] cad] - (~(put by com) u.comment-name new-com) - =. comments.new-note new-comments - =. notes.new-book (~(put by notes.new-book) note-name new-note) + =+ ^- [read-cards=(list card) comments=(map @da comment)] + (watch-comments /app/publish/notebooks/[book-name]/[note-name]) + =. comments.new-note comments =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - =/ fac=notebook-delta [%note book-name note-name new-note] - :_ sty(books (~(put by books.sty) book-name new-book)) - :* [%pass (welp /read/note pax) %arvo %c %warp our.bol rif] - [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] - cards + =/ delta=notebook-delta + [%add-note our.bol book-name note-name new-note] + =^ update-cards sty (handle-notebook-delta delta) + :_ sty + ;: weld + [%pass (welp /read/note pax) %arvo %c %warp our.bol rif]~ + read-cards + update-cards == :: [%app %publish %notebooks @ @ @ %publish-comment ~] =/ book-name i.t.t.t.pax =/ note-name i.t.t.t.t.pax =/ comment-name (slaw %da i.t.t.t.t.t.pax) - =/ book (~(get by books.sty) book-name) - ?~ book - [~ sty] - =/ note (~(get by notes.u.book) note-name) - ?~ note - [~ sty] ?~ comment-name [~ sty] =/ new-com .^(comment %cx (welp our-beak pax)) - =. comments.u.note (~(put by comments.u.note) u.comment-name new-com) - =. notes.u.book (~(put by notes.u.book) note-name u.note) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - =/ fac=notebook-delta - [%comment book-name note-name u.comment-name new-com] - :_ sty(books (~(put by books.sty) book-name u.book)) - :~ [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] - [%give %fact `/notebook/[book-name] %publish-book-update !>(fac)] + :: + =/ delta=notebook-delta + [%add-comment our.bol book-name note-name u.comment-name new-com] + =^ update-cards sty (handle-notebook-delta delta) + :_ sty + ;: weld + [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif]~ + update-cards == == :: +++ watch-notes + |= pax=path + ^- [(list card) (map @tas note)] + =/ paths .^((list path) %ct (weld our-beak pax)) + %+ roll paths + |= [pax=path cards=(list card) notes=(map @tas note)] + ?. ?=([%app %publish %notebooks @ @ %udon ~] pax) + [cards notes] + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax + =/ new-note (scry-note pax) + =^ comment-cards comments.new-note + (watch-comments /app/publish/notebooks/[book-name]/[note-name]) + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + :_ (~(put by notes) note-name new-note) + ;: weld + [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif]~ + comment-cards + cards + == +:: +++ watch-comments + |= pax=path + ^- [(list card) (map @da comment)] + =/ paths .^((list path) %ct (weld our-beak pax)) + %+ roll paths + |= [pax=path cards=(list card) comments=(map @da comment)] + ?. ?=([%app %publish %notebooks @ @ @ %publish-comment ~] pax) + [cards comments] + =/ comment-name (slaw %da i.t.t.t.t.t.pax) + ?~ comment-name + [cards comments] + =/ new-com .^(comment %cx (welp our-beak pax)) + =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] + :_ (~(put by comments) u.comment-name new-com) + [[%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] cards] +:: ++ scry-note |= pax=path ^- note @@ -459,7 +524,6 @@ %read (allowed-by who -.pem) %write (allowed-by who +.pem) == -:: +allowed-by: checks if ship :who is allowed by the permission rules in :dic :: ++ allowed-by |= [who=@p dic=dict:clay] @@ -478,18 +542,16 @@ in-list :: ++ write-file - =, space:userlib |= [pax=path cay=cage] ^- card =. pax (weld our-beak pax) - [%pass (weld /write pax) %arvo %c %info (foal pax cay)] + [%pass (weld /write pax) %arvo %c %info (foal:space:userlib pax cay)] :: ++ delete-file - =, space:userlib |= pax=path ^- card =. pax (weld our-beak pax) - [%pass (weld /delete pax) %arvo %c %info (fray pax)] + [%pass (weld /delete pax) %arvo %c %info (fray:space:userlib pax)] :: ++ delete-dir |= pax=path @@ -573,36 +635,30 @@ (perm-group-hook-poke [%associate sub [[sub sub-type] ~ ~]]) == :: +:: ++ poke-publish-action |= act=action ^- (quip card _state) ?- -.act %new-book ?> (team:title our.bol src.bol) - =+ ^- [cards=(list card) par-path=path sub-path=path] - ?- -.group.act - %old [~ par.group.act sub.group.act] - %new - =/ par-path /publish/[book.act]/participants - =/ sub-path /publish/[book.act]/subscribers - :_ [par-path sub-path] - ;: weld - :~ (group-poke [%bundle par-path]) - (group-poke [%bundle sub-path]) - (group-poke [%add par.group.act par-path]) - (group-poke [%add sub.group.act sub-path]) - == - (create-security par-path sub-path sec.group.act) - :~ (perm-hook-poke [%add-owned par-path par-path]) - (perm-hook-poke [%add-owned sub-path sub-path]) - == - == + =+ ^- [cards=(list card) writers-path=path subscribers-path=path] + (make-groups book.act group.act) + =/ new-book=notebook-info + :* title.act + about.act + coms.act + writers-path + subscribers-path == - =/ new-book=notebook [title.act now.bol now.bol ~ ~ ~ par-path sub-path] - :- cards - state(books (~(put by books) book.act new-book)) + =/ pax=path /app/publish/notebooks/[book.act]/publish-info + :_ state + [(write-file pax %publish-info !>(new-book)) cards] :: %new-note + ?: &(=(src.bol our.bol) !=(our.bol who.act)) + :_ state + [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon =/ front=(map knot cord) %- my @@ -615,13 +671,15 @@ [(write-file pax %udon !>(file))]~ :: %new-comment + ?: &(=(src.bol our.bol) !=(our.bol who.act)) + :_ state + [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ =/ pax=path %+ weld /app/publish/notebooks /[book.act]/[note.act]/(scot %da now.bol)/publish-comment =/ new-comment=comment :* author=src.bol date-created=now.bol - last-edit=now.bol content=body.act == :_ state @@ -629,56 +687,50 @@ :: %edit-book ?> (team:title our.bol src.bol) - =/ book (~(got by books) book.act) - =? title.book ?=(^ new-title.act) - u.new-title.act - =+ ^- [cards=(list card) par-path=path sub-path=path] - ?~ new-group.act - [~ participants.book subscribers.book] - ?- -.u.new-group.act - %old [~ par.u.new-group.act sub.u.new-group.act] - %new - =/ par-path /publish/[book.act]/participants - =/ sub-path /publish/[book.act]/subscribers - :_ [par-path sub-path] - %+ weld - :~ (group-poke [%bundle par-path]) - (group-poke [%bundle sub-path]) - (group-poke [%add par.u.new-group.act par-path]) - (group-poke [%add sub.u.new-group.act sub-path]) - (perm-hook-poke [%add-owned par-path par-path]) - (perm-hook-poke [%add-owned sub-path sub-path]) - == - (create-security par-path sub-path sec.u.new-group.act) + =/ book (~(get by books) book.act) + ?~ book + [~ state] + =+ ^- [cards=(list card) writers-path=path subscribers-path=path] + ?~ group.act + [~ writers.u.book subscribers.u.book] + (make-groups book.act u.group.act) + =/ new-info=notebook-info + :* title.act + about.act + coms.act + writers-path + subscribers-path == - =. participants.book par-path - =. subscribers.book sub-path - :_ state(books (~(put by books) book.act book)) - ?~ new-title.act ~ - =/ fac=notebook-delta [%book-meta book.act u.new-title.act] - [%give %fact `/notebook/[book.act] %publish-book-update !>(fac)]~ + =/ pax=path /app/publish/notebooks/[book.act] + :_ state + [(write-file pax %publish-info !>(notebook-info)) cards] :: %edit-note + ?: &(=(src.bol our.bol) !=(our.bol who.act)) + :_ state + [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon =/ front=(map knot cord) %- my - :~ title+new-title.act + :~ title+title.act author+(scot %p src.bol) == - =. new-body.act (cat 3 new-body.act '\0a') - =/ file=@t (add-front-matter front new-body.act) + =. body.act (cat 3 body.act '\0a') + =/ file=@t (add-front-matter front body.act) :_ state [(write-file pax %udon !>(file))]~ :: %edit-comment + ?: &(=(src.bol our.bol) !=(our.bol who.act)) + :_ state + [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ =/ pax=path %+ weld /app/publish/notebooks /[book.act]/[note.act]/[comment.act]/publish-comment - =/ comment .^(comment %cx (weld our-beak pax)) - =. content.comment new-body.act - =. last-edit.comment now.bol + =/ new-comment .^(comment %cx (weld our-beak pax)) + =. content.new-comment body.act :_ state - [(write-file pax %publish-comment !>(comment))]~ + [(write-file pax %publish-comment !>(new-comment))]~ :: %del-book ?> (team:title our.bol src.bol) @@ -687,11 +739,17 @@ [(delete-dir pax)]~ :: %del-note + ?: &(=(src.bol our.bol) !=(our.bol who.act)) + :_ state + [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon :_ state [(delete-file pax)]~ :: %del-comment + ?: &(=(src.bol our.bol) !=(our.bol who.act)) + :_ state + [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ =/ pax=path %+ weld /app/publish/notebooks /[book.act]/[note.act]/[comment.act]/publish-comment @@ -699,63 +757,272 @@ [(delete-file pax)]~ :: %subscribe + ?> (team:title our.bol src.bol) =/ wir=wire /subscribe/(scot %p who.act)/[book.act] :_ state [%pass wir %agent [who.act %publish] %watch /notebook/[book.act]]~ :: %unsubscribe + ?> (team:title our.bol src.bol) =/ wir=wire /subscribe/(scot %p who.act)/[book.act] :_ state(subs (~(del by subs) who.act book.act)) [%pass wir %agent [who.act %publish] %leave ~]~ == :: +++ get-notebook + |= [host=@p book-name=@tas] + ^- (unit notebook) + ?: =(our.bol host) + (~(get by books) book-name) + (~(get by subs) host book-name) +:: +++ emit-updates-and-state + |= [host=@p book-name=@tas book=notebook del=notebook-delta] + ^- (quip card _state) + ?: =(our.bol host) + :_ state(books (~(put by books) book-name book)) + :~ [%give %fact `/notebook/[book-name] %publish-notebook-delta !>(del)] + [%give %fact `/primary %publish-primary-delta !>(del)] + == + :_ state(subs (~(put by subs) [host book-name] book)) + [%give %fact `/primary %publish-primary-delta !>(del)]~ +:: ++ handle-notebook-delta |= del=notebook-delta ^- (quip card _state) ?- -.del - %book - :_ state(books (~(put by books) book.del data.del)) - ~ + %add-book + (emit-updates-and-state host.del book.del data.del del) :: - %book-meta - =/ book (~(got by books) book.del) - =. title.book title.del - :_ state(books (~(put by books) book.del data.del)) - ~ + %add-note + =/ book=(unit notebook) + (get-notebook host.del book.del) + ?~ book + [~ state] + =. notes.u.book (~(put by notes.u.book) note.del data.del) + (emit-updates-and-state host.del book.del u.book del) :: - %note - =/ book (~(got by books) book.del) - =. notes.book (~(put by notes.book) note.del data.del) - :_ state(books (~(put by books) book.del data.del)) - ~ + %add-comment + =/ book=(unit notebook) + (get-notebook host.del book.del) + ?~ book + [~ state] + =/ note (~(get by notes.u.book) note.del) + ?~ note + [~ state] + =. comments.u.note (~(put by comments.u.note) comment-date.del data.del) + =. notes.u.book (~(put by notes.u.book) note.del u.note) + (emit-updates-and-state host.del book.del u.book del) :: - %comment - =/ book (~(got by books) book.del) - =/ note (~(got by notes.book) note.del) - =. comments.note (~(put by comments.note) comment-date.del data.del) - =. notes.book (~(put by notes.book) note.del note) - :_ state(books (~(put by books) book.del data.del)) - ~ + %edit-book + =/ old-book=(unit notebook) + (get-notebook host.del book.del) + ?~ old-book + [~ state] + =/ new-book=notebook + %= data.del + date-created date-created.u.old-book + notes notes.u.old-book + order order.u.old-book + pinned pinned.u.old-book + == + (emit-updates-and-state host.del book.del new-book del) :: - %del-book !! + %edit-note + =/ book=(unit notebook) + (get-notebook host.del book.del) + ?~ book + [~ state] + =/ old-note (~(get by notes.u.book) note.del) + ?~ old-note + [~ state] + =/ new-note=note + %= data.del + date-created date-created.u.old-note + comments comments.u.old-note + == + =. notes.u.book (~(put by notes.u.book) note.del new-note) + (emit-updates-and-state host.del book.del u.book del) + :: + %edit-comment + =/ book=(unit notebook) + (get-notebook host.del book.del) + ?~ book + [~ state] + =/ note (~(get by notes.u.book) note.del) + ?~ note + [~ state] + =. comments.u.note (~(put by comments.u.note) comment-date.del data.del) + =. notes.u.book (~(put by notes.u.book) note.del u.note) + (emit-updates-and-state host.del book.del u.book del) + :: + %del-book + ?: =(our.bol host.del) + :_ state(books (~(del by books) book.del)) + :~ [%give %fact `/notebook/[book.del] %publish-notebook-delta !>(del)] + [%give %fact `/primary %publish-primary-delta !>(del)] + == + :_ state(subs (~(del by subs) host.del book.del)) + [%give %fact `/primary %publish-primary-delta !>(del)]~ :: %del-note - =/ book (~(got by books) book.del) - =. notes.book (~(del by notes.book) note.del) - :_ state(books (~(put by books) book.del data.del)) - ~ + =/ book=(unit notebook) + (get-notebook host.del book.del) + ?~ book + [~ state] + =. notes.u.book (~(del by notes.u.book) note.del) + (emit-updates-and-state host.del book.del u.book del) :: %del-comment - =/ book (~(got by books) book.del) - =/ note (~(got by notes.book) note.del) - =. comments.note (~(del by comments.note) comment-date.del) - =. notes.book (~(put by notes.book) note.del note) - :_ state(books (~(put by books) book.del data.del)) - ~ + =/ book=(unit notebook) + (get-notebook host.del book.del) + ?~ book + [~ state] + =/ note (~(get by notes.u.book) note.del) + ?~ note + [~ state] + =. comments.u.note (~(del by comments.u.note) comment.del) + =. notes.u.book (~(put by notes.u.book) note.del u.note) + (emit-updates-and-state host.del book.del u.book del) == :: ++ handle-http-request |= req=inbound-request:eyre ^- simple-payload:http - not-found:gen + =/ url (parse-request-line url.request.req) + ?+ url + not-found:gen + :: + [[[~ %png] [%'~publish' @t ~]] ~] + =/ filename=@t i.t.site.url + =/ img=(unit @t) (~(get by images) filename) + ?~ img + not-found:gen + (png-response:gen (as-octs:mimes:html u.img)) + :: + [[[~ %css] [%'~publish' %index ~]] ~] + (css-response:gen css) + :: + [[[~ %js] [%'~publish' %index ~]] ~] + (js-response:gen js) + :: + [[[~ %js] [%'~publish' %tile ~]] ~] + (js-response:gen tile-js) + :: + :: pagination endpoints + :: + :: all notebooks, short form + [[[~ %json] [%'~publish' %notebooks ~]] ~] + %- json-response:gen + %- json-to-octs + (notebooks-list-json our.bol books subs) + :: + :: notes pagination + [[[~ %json] [%'~publish' %notes @ @ @ @ ~]] ~] + =/ host=(unit @p) (slaw %p i.t.t.site.url) + ?~ host + not-found:gen + =/ book-name i.t.t.t.site.url + =/ book=(unit notebook) + ?: =(our.bol u.host) + (~(get by books) book-name) + (~(get by subs) u.host book-name) + ?~ book + not-found:gen + =/ start (rush i.t.t.t.t.site.url dem) + ?~ start + not-found:gen + =/ length (rush i.t.t.t.t.t.site.url dem) + ?~ length + not-found:gen + %- json-response:gen + %- json-to-octs + (notes-page notes.u.book u.start u.length) + :: + :: comments pagination + [[[~ %json] [%'~publish' %comments @ @ @ @ @ ~]] ~] + =/ host=(unit @p) (slaw %p i.t.t.site.url) + ?~ host + not-found:gen + =/ book-name i.t.t.t.site.url + =/ book=(unit notebook) + ?: =(our.bol u.host) + (~(get by books) book-name) + (~(get by subs) u.host book-name) + ?~ book + not-found:gen + =/ note-name i.t.t.t.t.site.url + =/ note=(unit note) (~(get by notes.u.book) note-name) + ?~ note + not-found:gen + =/ start (rush i.t.t.t.t.t.site.url dem) + ?~ start + not-found:gen + =/ length (rush i.t.t.t.t.t.t.site.url dem) + ?~ length + not-found:gen + %- json-response:gen + %- json-to-octs + (comments-page comments.u.note u.start u.length) + :: + :: presentation endpoints + :: + :: all notebooks, short form, wrapped in html + [[~ [%'~publish' ~]] ~] + =, enjs:format + =/ jon=json + %- pairs + :~ notebooks+(notebooks-list-json our.bol books subs) + == + (manx-response:gen (index jon)) + :: + :: single notebook, with initial 50 notes in short form, wrapped in html + [[~ [%'~publish' @ @ ~]] ~] + =, enjs:format + =/ host=(unit @p) (slaw %p i.t.site.url) + ?~ host + not-found:gen + =/ book-name i.t.t.site.url + =/ book=(unit notebook) + ?: =(our.bol u.host) + (~(get by books) book-name) + (~(get by subs) u.host book-name) + ?~ book + not-found:gen + =/ jon=json + %- pairs + :~ notebooks+(notebooks-list-json our.bol books subs) + notebook+(notebook-full-json u.host book-name u.book) + notes+(notes-page notes.u.book 0 50) + == + (manx-response:gen (index jon)) + :: + :: single note, with initial 50 comments, wrapped in html + [[~ [%'~publish' @ @ @ ~]] ~] + =, enjs:format + =/ host=(unit @p) (slaw %p i.t.site.url) + ?~ host + not-found:gen + =/ book-name i.t.t.site.url + =/ book=(unit notebook) + ?: =(our.bol u.host) + (~(get by books) book-name) + (~(get by subs) u.host book-name) + ?~ book + not-found:gen + =/ note-name i.t.t.t.site.url + =/ note=(unit note) (~(get by notes.u.book) note-name) + ?~ note + not-found:gen + =/ jon=json + %- pairs + :~ notebooks+(notebooks-list-json our.bol books subs) + notebook+(notebook-full-json u.host book-name u.book) + notes+(notes-page notes.u.book 0 50) + note+(note-full-json u.host book-name note-name u.note) + comments+(comments-page comments.u.note 0 50) + == + (manx-response:gen (index jon)) + == +:: -- diff --git a/pkg/arvo/lib/publish.hoon b/pkg/arvo/lib/publish.hoon index 02ca605b05..103a9f6ea2 100644 --- a/pkg/arvo/lib/publish.hoon +++ b/pkg/arvo/lib/publish.hoon @@ -23,4 +23,140 @@ ?: &((gte a 'A') (lte a 'Z')) (add 32 a) '-' +:: +++ note-build-to-json + |= build=(each manx tang) + ^- json + ?: ?=(%.y -.build) + %- pairs:enjs:format + :~ success+b+%.y + result+(elem-to-react-json p.build) + == + %- pairs:enjs:format + :~ success+b+%.n + result+(tang-to-json p.build) + == +:: +++ notebooks-list-json + |= [our=@p books=(map @tas notebook) subs=(map [@p @tas] notebook)] + ^- json + =, enjs:format + :- %a + %+ weld + %+ turn ~(tap by books) + |= [name=@tas book=notebook] + (notebook-short-json our name book) + %+ turn ~(tap by subs) + |= [[host=@p name=@tas] book=notebook] + (notebook-short-json host name book) +:: +++ notebook-short-json + |= [host=@p book-name=@tas book=notebook] + ^- json + =, enjs:format + %- pairs + :~ host+(ship host) + id+s+book-name + title+s+title.book + date-created+(time date-created.book) + num-notes+(numb ~(wyt by notes.book)) + == +:: +++ notebook-full-json + |= [host=@p name=@tas book=notebook] + ^- json + =, enjs:format + %- pairs + :~ host+(ship host) + id+s+name + title+s+title.book + date-created+(time date-created.book) + :: subscribers + :: notes + == +:: +++ note-short-json + |= [host=@p book-name=@tas note-name=@tas =note] + ^- json + =, enjs:format + %- pairs + :~ host+(ship host) + book-id+s+book-name + note-id+s+note-name + author+(ship author.note) + title+s+title.note + date-created+(time date-created.note) + num-comments+(numb ~(wyt by comments.note)) + == +:: +++ note-full-json + |= [host=@p book-name=@tas note-name=@tas =note] + ^- json + =, enjs:format + %- pairs + :~ host+(ship host) + book-id+s+book-name + note-id+s+note-name + author+(ship author.note) + title+s+title.note + date-created+(time date-created.note) + build+(note-build-to-json build.note) + file+s+file.note + == +:: +++ notes-page + |= [notes=(map @tas note) start=@ud length=@ud] + ^- json + =/ notes-list=(list [@tas note]) + %+ sort ~(tap by notes) + |= [[@tas n1=note] [@tas n2=note]] + (gte date-created.n1 date-created.n2) + %- notes-list-json + (scag length (slag start notes-list)) +:: +++ notes-list-json + |= notes=(list [@tas note]) + ^- json + =, enjs:format + :- %a + %+ turn notes + |= [note-name=@tas =note] + ^- json + %- pairs + :~ note-id+s+note-name + author+(ship author.note) + title+s+title.note + date-created+(time date-created.note) + num-comments+(numb ~(wyt by comments.note)) + :: snippet + == +:: +++ comments-page + |= [comments=(map @da comment) start=@ud end=@ud] + ^- json + =/ coms=(list [@da comment]) + %+ sort ~(tap by comments) + |= [[d1=@da comment] [d2=@da comment]] + (gte d1 d2) + %- comments-list-json + (scag end (slag start coms)) +:: +++ comments-list-json + |= comments=(list [@da comment]) + ^- json + =, enjs:format + :- %a + (turn comments comment-json) +:: +++ comment-json + |= [date=@da com=comment] + ^- json + =, enjs:format + %+ frond:enjs:format + (scot %da date) + %- pairs + :~ author+(ship author.com) + date-created+(time date-created.com) + content+s+content.com + == -- diff --git a/pkg/arvo/mar/publish/action2.hoon b/pkg/arvo/mar/publish/action2.hoon index 3f063ca1a7..01aa6de618 100644 --- a/pkg/arvo/mar/publish/action2.hoon +++ b/pkg/arvo/mar/publish/action2.hoon @@ -4,10 +4,114 @@ /- *publish =, format :: -|_ act=action-2 +|_ act=action +:: +++ grow + |% + ++ tank >act< + -- :: ++ grab |% - ++ noun action-2 + ++ noun action + ++ json + |= jon=^json + =, dejs:format + ;; action + |^ %- of + :~ new-book+new-book + new-note+new-note + new-comment+new-comment + edit-book+edit-book + edit-note+edit-note + edit-comment+edit-comment + del-book+del-book + del-note+del-note + del-comment+del-comment + subscribe+subscribe + unsubscribe+unsubscribe + == + :: + ++ new-book + %- ot + :~ book+so + title+so + about+so + coms+bo + group+group-info + == + :: + ++ new-note + %- ot + :~ who+(su fed:ag) + book+so + note+so + title+so + body+so + == + :: + ++ new-comment + %- ot + :~ who+(su fed:ag) + book+so + note+so + body+so + == + :: + ++ edit-book + %- ot + :~ book+so + title+so + about+so + coms+bo + group+(mu group-info) + == + :: + ++ edit-note + %- ot + :~ who+(su fed:ag) + book+so + note+so + title+so + body+so + == + :: + ++ edit-comment + %- ot + :~ who+(su fed:ag) + book+so + note+so + comment+(su ;~(pfix sig (cook year when:^so))) + body+so + == + :: + ++ del-book (ot book+so ~) + :: + ++ del-note (ot who+(su fed:ag) book+so note+so ~) + :: + ++ del-comment + %- ot + :~ who+(su fed:ag) + book+so + note+so + comment+(su ;~(pfix sig (cook year when:^so))) + == + ++ subscribe + %- ot + :~ who+(su fed:ag) + book+so + == + ++ unsubscribe + %- ot + :~ who+(su fed:ag) + book+so + == + ++ group-info + %- of + :~ old+(ot writers+pa subscribers+pa ~) + new+(ot writers+set-ship subscribers+set-ship sec+so ~) + == + ++ set-ship (ar (su fed:ag)) + -- -- -- diff --git a/pkg/arvo/mar/publish/comment.hoon b/pkg/arvo/mar/publish/comment.hoon index 3329119ae4..b67bab1e42 100644 --- a/pkg/arvo/mar/publish/comment.hoon +++ b/pkg/arvo/mar/publish/comment.hoon @@ -11,9 +11,8 @@ ^- wain :* (cat 3 'author: ' (scot %p author.com)) (cat 3 'date-created: ' (scot %da date-created.com)) - (cat 3 'last-modified: ' (scot %da last-modified.com)) '-----' - (to-wain:format body.com) + (to-wain:format content.com) == -- ++ grab @@ -28,7 +27,6 @@ :: ?> ?= $: author=@t date-created=@t - last-modified=@t line=@t body=* == @@ -43,12 +41,6 @@ (jest 'date-created: ~') (cook year when:so) == - :: - %+ rash last-modified.txs - ;~ pfix - (jest 'last-modified: ~') - (cook year when:so) - == :: (of-wain:format (wain body.txs)) == diff --git a/pkg/arvo/mar/publish/info.hoon b/pkg/arvo/mar/publish/info.hoon index 3cd60d0743..e221092605 100644 --- a/pkg/arvo/mar/publish/info.hoon +++ b/pkg/arvo/mar/publish/info.hoon @@ -1,9 +1,9 @@ :: :::: /hoon/info/publish/mar :: -/- publish +/- *publish !: -|_ con=collection-info:publish +|_ info=notebook-info :: :: ++ grow @@ -13,13 +13,11 @@ (as-octs:mimes:html (of-wain:format txt)) ++ txt ^- wain - :~ (cat 3 'owner: ' (scot %p owner.con)) - (cat 3 'title: ' title.con) - (cat 3 'filename: ' filename.con) - (cat 3 'comments: ' comments.con) - (cat 3 'allow-edit: ' allow-edit.con) - (cat 3 'date-created: ' (scot %da date-created.con)) - (cat 3 'last-modified: ' (scot %da last-modified.con)) + :~ (cat 3 'title: ' title.info) + (cat 3 'description: ' description.info) + (cat 3 'comments: ' ?:(comments.info 'on' 'off')) + (cat 3 'writers: ' (spat writers.info)) + (cat 3 'subscribers: ' (spat subscribers.info)) == -- ++ grab @@ -29,56 +27,41 @@ (txt (to-wain:format q.p)) ++ txt |= txs=(pole @t) - ^- collection-info:publish + ^- notebook-info :: TODO: putting ~ instead of * breaks this but shouldn't :: - ?> ?= $: owner=@t - title=@t - filename=@t + ?> ?= $: title=@t + description=@t comments=@t - allow-edit=@t - date-created=@t - last-modified=@t + writers=@t + subscribers=@t * == txs :: - :* %+ rash owner.txs - ;~(pfix (jest 'owner: ~') fed:ag) - :: - %+ rash title.txs + :* %+ rash title.txs ;~(pfix (jest 'title: ') (cook crip (star next))) :: - %+ rash filename.txs - ;~(pfix (jest 'filename: ') (cook crip (star next))) + %+ rash description.txs + ;~(pfix (jest 'description: ') (cook crip (star next))) :: - %+ rash comments.txs - ;~ pfix - (jest 'comments: ') - %+ cook comment-config:publish - ;~(pose (jest %open) (jest %closed) (jest %none)) - == + %+ rash comments.txs + ;~ pfix + (jest 'comments: ') + %+ cook + |= val=@t + ^- ? + =(val %on) + ;~(pose (jest %on) (jest %off)) + == :: - %+ rash allow-edit.txs - ;~ pfix - (jest 'allow-edit: ') - %+ cook edit-config:publish - ;~(pose (jest %post) (jest %comment) (jest %all) (jest %none)) - == + %+ rash writers.txs + ;~(pfix (jest 'writers: ') ;~(pfix net (more net urs:ab))) :: - %+ rash date-created.txs - ;~ pfix - (jest 'date-created: ~') - (cook year when:so) - == - :: - %+ rash last-modified.txs - ;~ pfix - (jest 'last-modified: ~') - (cook year when:so) - == + %+ rash subscribers.txs + ;~(pfix (jest 'subscribers: ') ;~(pfix net (more net urs:ab))) == - ++ noun collection-info:publish + ++ noun notebook-info -- ++ grad %mime -- diff --git a/pkg/arvo/mar/publish/notebook-delta.hoon b/pkg/arvo/mar/publish/notebook-delta.hoon new file mode 100644 index 0000000000..76d693efc0 --- /dev/null +++ b/pkg/arvo/mar/publish/notebook-delta.hoon @@ -0,0 +1,13 @@ +:: +:::: /hoon/action/publish/mar + :: +/- *publish +=, format +:: +|_ del=notebook-delta +:: +++ grab + |% + ++ noun notebook-delta + -- +-- diff --git a/pkg/arvo/mar/publish/primary-delta.hoon b/pkg/arvo/mar/publish/primary-delta.hoon new file mode 100644 index 0000000000..53e5649929 --- /dev/null +++ b/pkg/arvo/mar/publish/primary-delta.hoon @@ -0,0 +1,70 @@ +:: +:::: /hoon/action/publish/mar + :: +/- *publish +=, format +:: +|_ del=primary-delta +:: +++ grab + |% + ++ noun primary-delta + -- +++ grow + |% + ++ json + =, enjs:format + %+ frond -.del + ?- -.del + %add-book + (notebook-short-json host.del book.del data.del) + :: + %add-note + (note-short-json host.del book.del note.del data.del) + :: + %add-comment + %- pairs:enjs:format + :~ host+(ship host.del) + book+s+book.del + note+s+note.del + comment+s+(scot %da comment-date.del) + data+(comment-json data.del) + == + %edit-book + (notebook-short-json host.del book.del data.del) + :: + %edit-note + (note-short-json host.del book.del note.del data.del) + :: + %edit-comment + %- pairs:enjs:format + :~ host+(ship host.del) + book+s+book.del + note+s+note.del + comment+s+(scot %da comment-date.del) + comment+(comment-json data.del) + == + :: + %del-book + %- pairs:enjs:format + :~ host+(ship host.del) + book+s+book.del + == + :: + %del-note + %- pairs:enjs:format + :~ host+(ship host.del) + book+s+book.del + note+s+note.del + == + :: + %del-comment + %- pairs:enjs:format + :~ host+(ship host.del) + book+s+book.del + note+s+note.del + comment+s+(scot %da date-created.del) + == + -- + -- +-- diff --git a/pkg/arvo/sur/publish.hoon b/pkg/arvo/sur/publish.hoon index 985d9c49d0..2591048977 100644 --- a/pkg/arvo/sur/publish.hoon +++ b/pkg/arvo/sur/publish.hoon @@ -2,18 +2,18 @@ |% :: +$ group-info - $% [%old par=path sub=path] - [%new par=(set ship) sub=(set ship) sec=rw-security] + $% [%old writers=path subscribers=path] + [%new writers=(set ship) subscribers=(set ship) sec=rw-security] == :: +$ action - $% [%new-book book=@tas title=@t group=group-info] + $% [%new-book book=@tas title=@t about=@t coms=? group=group-info] [%new-note who=@p book=@tas note=@tas title=@t body=@t] [%new-comment who=@p book=@tas note=@tas body=@t] :: - [%edit-book book=@tas new-title=(unit @t) new-group=(unit group-info)] - [%edit-note who=@p book=@tas note=@tas new-title=@t new-body=@t] - [%edit-comment who=@p book=@tas note=@tas comment=@tas new-body=@t] + [%edit-book book=@tas title=@t about=@t coms=? group=(unit group-info)] + [%edit-note who=@p book=@tas note=@tas title=@t body=@t] + [%edit-comment who=@p book=@tas note=@tas comment=@tas body=@t] :: [%del-book book=@tas] [%del-note who=@p book=@tas note=@tas] @@ -26,7 +26,6 @@ +$ comment $: author=@p date-created=@da - last-edit=@da content=@t == :: @@ -43,23 +42,39 @@ :: +$ notebook $: title=@t + description=@t + comments=? + writers=path + subscribers=path date-created=@da notes=(map @tas note) order=(list @tas) pinned=(set @tas) - participants=path + == +:: ++$ notebook-info + $: title=@t + description=@t + comments=? + writers=path subscribers=path == :: +$ notebook-delta - $% [%book book=@tas data=notebook] - [%book-meta book=@tas title=@t] - [%note book=@tas note=@tas data=note] - [%comment book=@tas note=@tas comment-date=@da data=comment] - [%del-book book=@tas] - [%del-note book=@tas note=@tas] - [%del-comment book=@tas note=@tas comment=@da] + $% [%add-book host=@p book=@tas data=notebook] + [%add-note host=@p book=@tas note=@tas data=note] + [%add-comment host=@p book=@tas note=@tas comment-date=@da data=comment] + :: + [%edit-book host=@p book=@tas data=notebook] + [%edit-note host=@p book=@tas note=@tas data=note] + [%edit-comment host=@p book=@tas note=@tas comment-date=@da data=comment] + :: + [%del-book host=@p book=@tas] + [%del-note host=@p book=@tas note=@tas] + [%del-comment host=@p book=@tas note=@tas comment=@da] == :: -+$ primary-delta !! ++$ primary-delta + $% notebook-delta + == -- From d4ae9dbcc8a3f10694e0b2c9e44ec8ea64ce4972 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Wed, 18 Dec 2019 14:45:37 -0800 Subject: [PATCH 05/20] added js reducers --- pkg/arvo/app/publish.hoon | 106 ++++-- pkg/arvo/lib/publish.hoon | 175 ++++++--- pkg/arvo/mar/publish/primary-delta.hoon | 42 ++- pkg/arvo/sur/publish.hoon | 3 +- pkg/interface/publish/src/js/api.js | 77 ++++ .../publish/src/js/reducers/initial.js | 7 + .../publish/src/js/reducers/primary.js | 213 +++++++++++ .../publish/src/js/reducers/response.js | 167 +++++++++ .../publish/src/js/reducers/rumor.js | 336 ------------------ .../publish/src/js/reducers/spinner.js | 14 - .../publish/src/js/reducers/update.js | 36 -- pkg/interface/publish/src/js/store.js | 28 +- 12 files changed, 712 insertions(+), 492 deletions(-) create mode 100644 pkg/interface/publish/src/js/reducers/initial.js create mode 100644 pkg/interface/publish/src/js/reducers/primary.js create mode 100644 pkg/interface/publish/src/js/reducers/response.js delete mode 100644 pkg/interface/publish/src/js/reducers/rumor.js delete mode 100644 pkg/interface/publish/src/js/reducers/spinner.js delete mode 100644 pkg/interface/publish/src/js/reducers/update.js diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index 8d597a6b3f..2c7bdd57b5 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -42,7 +42,6 @@ $: our-paths=(list path) books=(map @tas notebook) subs=(map [@p @tas] notebook) - unread=(set [@p @tas @tas]) == -- :: @@ -273,9 +272,9 @@ =/ comment-date (slaw %da i.t.t.t.t.t.pax) ?~ comment-date [~ state] - =/ book-name i.t.t.t.pax - =/ note-name i.t.t.t.t.pax - =/ new-comment !<(comment q.r.u.rot) + =/ book-name i.t.t.t.pax + =/ note-name i.t.t.t.t.pax + =/ new-comment !<(comment q.r.u.rot) =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] =/ delta=notebook-delta [%edit-comment our.bol book-name note-name u.comment-date new-comment] @@ -508,6 +507,7 @@ note-name now.bol now.bol + %.n udon build ~ @@ -701,9 +701,9 @@ writers-path subscribers-path == - =/ pax=path /app/publish/notebooks/[book.act] + =/ pax=path /app/publish/notebooks/[book.act]/publish-info :_ state - [(write-file pax %publish-info !>(notebook-info)) cards] + [(write-file pax %publish-info !>(new-info)) cards] :: %edit-note ?: &(=(src.bol our.bol) !=(our.bol who.act)) @@ -765,8 +765,11 @@ %unsubscribe ?> (team:title our.bol src.bol) =/ wir=wire /subscribe/(scot %p who.act)/[book.act] + =/ del=primary-delta [%del-book who.act book.act] :_ state(subs (~(del by subs) who.act book.act)) - [%pass wir %agent [who.act %publish] %leave ~]~ + :~ [%pass wir %agent [who.act %publish] %leave ~] + [%give %fact `/primary %publish-primary-delta !>(del)] + == == :: ++ get-notebook @@ -799,6 +802,7 @@ (get-notebook host.del book.del) ?~ book [~ state] + =. read.data.del =(our.bol author.data.del) =. notes.u.book (~(put by notes.u.book) note.del data.del) (emit-updates-and-state host.del book.del u.book del) :: @@ -824,7 +828,6 @@ date-created date-created.u.old-book notes notes.u.old-book order order.u.old-book - pinned pinned.u.old-book == (emit-updates-and-state host.del book.del new-book del) :: @@ -840,6 +843,7 @@ %= data.del date-created date-created.u.old-note comments comments.u.old-note + read read.u.old-note == =. notes.u.book (~(put by notes.u.book) note.del new-note) (emit-updates-and-state host.del book.del u.book del) @@ -915,7 +919,7 @@ [[[~ %json] [%'~publish' %notebooks ~]] ~] %- json-response:gen %- json-to-octs - (notebooks-list-json our.bol books subs) + (notebooks-map-json our.bol books subs) :: :: notes pagination [[[~ %json] [%'~publish' %notes @ @ @ @ ~]] ~] @@ -937,6 +941,7 @@ not-found:gen %- json-response:gen %- json-to-octs + :- %o (notes-page notes.u.book u.start u.length) :: :: comments pagination @@ -965,15 +970,52 @@ %- json-to-octs (comments-page comments.u.note u.start u.length) :: + :: single notebook with initial 50 notes in short form, as json + [[[~ %json] [%'~publish' @ @ ~]] ~] + =, enjs:format + =/ host=(unit @p) (slaw %p i.t.site.url) + ?~ host + not-found:gen + =/ book-name i.t.t.site.url + =/ book=(unit notebook) + ?: =(our.bol u.host) + (~(get by books) book-name) + (~(get by subs) u.host book-name) + ?~ book + not-found:gen + =/ notebook-json (notebook-full-json u.host book-name u.book) + ?> ?=(%o -.notebook-json) + =. p.notebook-json + (~(uni by p.notebook-json) (notes-page notes.u.book 0 50)) + =/ jon=json (pairs notebook+notebook-json ~) + (json-response:gen (json-to-octs jon)) + :: + :: single note, with initial 50 comments, as json + [[[~ %json] [%'~publish' @ @ @ ~]] ~] + =, enjs:format + =/ host=(unit @p) (slaw %p i.t.site.url) + ?~ host + not-found:gen + =/ book-name i.t.t.site.url + =/ book=(unit notebook) + ?: =(our.bol u.host) + (~(get by books) book-name) + (~(get by subs) u.host book-name) + ?~ book + not-found:gen + =/ note-name i.t.t.t.site.url + =/ note=(unit note) (~(get by notes.u.book) note-name) + ?~ note + not-found:gen + =/ jon=json o+(note-presentation-json u.book note-name u.note) + (json-response:gen (json-to-octs jon)) + :: :: presentation endpoints :: :: all notebooks, short form, wrapped in html [[~ [%'~publish' ~]] ~] =, enjs:format - =/ jon=json - %- pairs - :~ notebooks+(notebooks-list-json our.bol books subs) - == + =/ jon=json (pairs notebooks+(notebooks-map-json our.bol books subs) ~) (manx-response:gen (index jon)) :: :: single notebook, with initial 50 notes in short form, wrapped in html @@ -989,12 +1031,18 @@ (~(get by subs) u.host book-name) ?~ book not-found:gen - =/ jon=json - %- pairs - :~ notebooks+(notebooks-list-json our.bol books subs) - notebook+(notebook-full-json u.host book-name u.book) - notes+(notes-page notes.u.book 0 50) - == + =/ notebook-json (notebook-full-json u.host book-name u.book) + ?> ?=(%o -.notebook-json) + =. p.notebook-json + (~(uni by p.notebook-json) (notes-page notes.u.book 0 50)) + =/ notebooks-json (notebooks-map-json our.bol books subs) + ?> ?=(%o -.notebooks-json) + =/ host-books-json (~(got by p.notebooks-json) (scot %p u.host)) + ?> ?=(%o -.host-books-json) + =. p.host-books-json (~(put by p.host-books-json) book-name notebook-json) + =. p.notebooks-json + (~(put by p.notebooks-json) (scot %p u.host) host-books-json) + =/ jon=json (pairs notebooks+notebooks-json ~) (manx-response:gen (index jon)) :: :: single note, with initial 50 comments, wrapped in html @@ -1014,14 +1062,18 @@ =/ note=(unit note) (~(get by notes.u.book) note-name) ?~ note not-found:gen - =/ jon=json - %- pairs - :~ notebooks+(notebooks-list-json our.bol books subs) - notebook+(notebook-full-json u.host book-name u.book) - notes+(notes-page notes.u.book 0 50) - note+(note-full-json u.host book-name note-name u.note) - comments+(comments-page comments.u.note 0 50) - == + =/ notebook-json (notebook-full-json u.host book-name u.book) + ?> ?=(%o -.notebook-json) + =/ note-json (note-presentation-json u.book note-name u.note) + =. p.notebook-json (~(uni by p.notebook-json) note-json) + =/ notebooks-json (notebooks-map-json our.bol books subs) + ?> ?=(%o -.notebooks-json) + =/ host-books-json (~(got by p.notebooks-json) (scot %p u.host)) + ?> ?=(%o -.host-books-json) + =. p.host-books-json (~(put by p.host-books-json) book-name notebook-json) + =. p.notebooks-json + (~(put by p.notebooks-json) (scot %p u.host) host-books-json) + =/ jon=json (pairs notebooks+notebooks-json ~) (manx-response:gen (index jon)) == :: diff --git a/pkg/arvo/lib/publish.hoon b/pkg/arvo/lib/publish.hoon index 103a9f6ea2..cc8add231b 100644 --- a/pkg/arvo/lib/publish.hoon +++ b/pkg/arvo/lib/publish.hoon @@ -37,6 +37,15 @@ result+(tang-to-json p.build) == :: +++ count-unread + |= notes=(map @tas note) + ^- @ud + %- ~(rep by notes) + |= [[key=@tas val=note] count=@ud] + ?: read.val + count + +(count) +:: ++ notebooks-list-json |= [our=@p books=(map @tas notebook) subs=(map [@p @tas] notebook)] ^- json @@ -45,92 +54,164 @@ %+ weld %+ turn ~(tap by books) |= [name=@tas book=notebook] - (notebook-short-json our name book) + (notebook-short-json book) %+ turn ~(tap by subs) |= [[host=@p name=@tas] book=notebook] - (notebook-short-json host name book) + (notebook-short-json book) +:: +++ notebooks-map-json + |= [our=@p books=(map @tas notebook) subs=(map [@p @tas] notebook)] + ^- json + =, enjs:format + =/ subs-notebooks-map=json + %- ~(rep by subs) + |= [[[host=@p book-name=@tas] book=notebook] out=json] + ^- json + =/ host-ta (scot %p host) + ?~ out + (frond host-ta (frond book-name (notebook-short-json book))) + ?> ?=(%o -.out) + =/ books (~(get by p.out) host-ta) + ?~ books + :- %o + (~(put by p.out) host-ta (frond book-name (notebook-short-json book))) + ?> ?=(%o -.u.books) + =. p.u.books (~(put by p.u.books) book-name (notebook-short-json book)) + :- %o + (~(put by p.out) host-ta u.books) + =? subs-notebooks-map ?=(~ subs-notebooks-map) + [%o ~] + =/ our-notebooks-map=json + %- ~(rep by books) + |= [[book-name=@tas book=notebook] out=json] + ^- json + ?~ out + (frond book-name (notebook-short-json book)) + ?> ?=(%o -.out) + :- %o + (~(put by p.out) book-name (notebook-short-json book)) + ?~ our-notebooks-map + subs-notebooks-map + ?> ?=(%o -.subs-notebooks-map) + :- %o + (~(put by p.subs-notebooks-map) (scot %p our) our-notebooks-map) :: ++ notebook-short-json + |= book=notebook + ^- json + =, enjs:format + %- pairs + :~ title+s+title.book + date-created+(time date-created.book) + num-notes+(numb ~(wyt by notes.book)) + num-unread+(numb (count-unread notes.book)) + == +:: +++ notebook-full-json |= [host=@p book-name=@tas book=notebook] ^- json =, enjs:format %- pairs - :~ host+(ship host) - id+s+book-name - title+s+title.book + :~ title+s+title.book date-created+(time date-created.book) num-notes+(numb ~(wyt by notes.book)) + num-unread+(numb (count-unread notes.book)) + notes-by-date+(notes-by-date notes.book) + :: XX settings stuff, subscribers == :: -++ notebook-full-json - |= [host=@p name=@tas book=notebook] - ^- json +++ note-presentation-json + |= [book=notebook note-name=@tas not=note] + ^- (map @t json) =, enjs:format - %- pairs - :~ host+(ship host) - id+s+name - title+s+title.book - date-created+(time date-created.book) - :: subscribers - :: notes - == -:: -++ note-short-json - |= [host=@p book-name=@tas note-name=@tas =note] - ^- json - =, enjs:format - %- pairs - :~ host+(ship host) - book-id+s+book-name - note-id+s+note-name - author+(ship author.note) - title+s+title.note - date-created+(time date-created.note) - num-comments+(numb ~(wyt by comments.note)) + =/ notes-list=(list [@tas note]) + %+ sort ~(tap by notes.book) + |= [[@tas n1=note] [@tas n2=note]] + (gte date-created.n1 date-created.n2) + =/ idx=@ (need (find [note-name not]~ notes-list)) + =/ next=(unit [name=@tas not=note]) + ?: =(idx 0) ~ + `(snag (dec idx) notes-list) + =/ prev=(unit [name=@tas not=note]) + ?: =(+(idx) (lent notes-list)) ~ + `(snag +(idx) notes-list) + =/ current=json (note-full-json note-name not) + ?> ?=(%o -.current) + =. p.current (~(put by p.current) %prev-note ?~(prev ~ s+name.u.prev)) + =. p.current (~(put by p.current) %next-note ?~(next ~ s+name.u.next)) + =/ notes=(list [@t json]) [note-name current]~ + =? notes ?=(^ prev) + [[name.u.prev (note-short-json name.u.prev not.u.prev)] notes] + =? notes ?=(^ next) + [[name.u.next (note-short-json name.u.next not.u.next)] notes] + %- my + :~ notes+(pairs notes) + notes-by-date+a+(turn notes-list |=([name=@tas *] s+name)) == :: ++ note-full-json - |= [host=@p book-name=@tas note-name=@tas =note] + |= [note-name=@tas =note] ^- json =, enjs:format %- pairs - :~ host+(ship host) - book-id+s+book-name - note-id+s+note-name - author+(ship author.note) + :~ note-id+s+note-name + author+s+(scot %p author.note) title+s+title.note date-created+(time date-created.note) build+(note-build-to-json build.note) file+s+file.note + num-comments+(numb ~(wyt by comments.note)) + comments+(comments-page comments.note 0 50) + read+b+read.note == :: -++ notes-page - |= [notes=(map @tas note) start=@ud length=@ud] +++ notes-by-date + |= notes=(map @tas note) ^- json =/ notes-list=(list [@tas note]) %+ sort ~(tap by notes) |= [[@tas n1=note] [@tas n2=note]] (gte date-created.n1 date-created.n2) - %- notes-list-json - (scag length (slag start notes-list)) -:: -++ notes-list-json - |= notes=(list [@tas note]) - ^- json - =, enjs:format :- %a - %+ turn notes + %+ turn notes-list + |= [name=@tas note] + ^- json + [%s name] +:: +++ note-short-json |= [note-name=@tas =note] ^- json + =, enjs:format %- pairs :~ note-id+s+note-name - author+(ship author.note) + author+s+(scot %p author.note) title+s+title.note date-created+(time date-created.note) num-comments+(numb ~(wyt by comments.note)) - :: snippet + read+b+read.note + :: XX snippet == :: +++ notes-page + |= [notes=(map @tas note) start=@ud length=@ud] + ^- (map @t json) + =/ notes-list=(list [@tas note]) + %+ sort ~(tap by notes) + |= [[@tas n1=note] [@tas n2=note]] + (gte date-created.n1 date-created.n2) + %- my + :~ notes-by-date+a+(turn notes-list |=([name=@tas *] s+name)) + notes+o+(notes-list-json (scag length (slag start notes-list))) + == +:: +++ notes-list-json + |= notes=(list [@tas note]) + ^- (map @t json) + %+ roll notes + |= [[name=@tas not=note] out-map=(map @t json)] + ^- (map @t json) + (~(put by out-map) name (note-short-json name not)) +:: ++ comments-page |= [comments=(map @da comment) start=@ud end=@ud] ^- json @@ -155,7 +236,7 @@ %+ frond:enjs:format (scot %da date) %- pairs - :~ author+(ship author.com) + :~ author+s+(scot %p author.com) date-created+(time date-created.com) content+s+content.com == diff --git a/pkg/arvo/mar/publish/primary-delta.hoon b/pkg/arvo/mar/publish/primary-delta.hoon index 53e5649929..f411e737ff 100644 --- a/pkg/arvo/mar/publish/primary-delta.hoon +++ b/pkg/arvo/mar/publish/primary-delta.hoon @@ -2,7 +2,7 @@ :::: /hoon/action/publish/mar :: /- *publish -=, format +/+ *publish :: |_ del=primary-delta :: @@ -13,58 +13,64 @@ ++ grow |% ++ json - =, enjs:format - %+ frond -.del + %+ frond:enjs:format -.del ?- -.del %add-book - (notebook-short-json host.del book.del data.del) + %+ frond:enjs:format (scot %p host.del) + %+ frond:enjs:format book.del + (notebook-short-json data.del) :: %add-note - (note-short-json host.del book.del note.del data.del) + %+ frond:enjs:format (scot %p host.del) + %+ frond:enjs:format book.del + (note-full-json note.del data.del) :: %add-comment %- pairs:enjs:format - :~ host+(ship host.del) + :~ host+s+(scot %p host.del) book+s+book.del note+s+note.del - comment+s+(scot %da comment-date.del) - data+(comment-json data.del) + comment+(comment-json comment-date.del data.del) == + :: %edit-book - (notebook-short-json host.del book.del data.del) + %+ frond:enjs:format (scot %p host.del) + %+ frond:enjs:format book.del + (notebook-short-json data.del) :: %edit-note - (note-short-json host.del book.del note.del data.del) + %+ frond:enjs:format (scot %p host.del) + %+ frond:enjs:format book.del + (note-full-json note.del data.del) :: %edit-comment %- pairs:enjs:format - :~ host+(ship host.del) + :~ host+s+(scot %p host.del) book+s+book.del note+s+note.del - comment+s+(scot %da comment-date.del) - comment+(comment-json data.del) + comment+(comment-json comment-date.del data.del) == :: %del-book %- pairs:enjs:format - :~ host+(ship host.del) + :~ host+s+(scot %p host.del) book+s+book.del == :: %del-note %- pairs:enjs:format - :~ host+(ship host.del) + :~ host+s+(scot %p host.del) book+s+book.del note+s+note.del == :: %del-comment %- pairs:enjs:format - :~ host+(ship host.del) + :~ host+s+(scot %p host.del) book+s+book.del note+s+note.del - comment+s+(scot %da date-created.del) + comment+s+(scot %da comment.del) == - -- + == -- -- diff --git a/pkg/arvo/sur/publish.hoon b/pkg/arvo/sur/publish.hoon index 2591048977..9e3ea2eb3f 100644 --- a/pkg/arvo/sur/publish.hoon +++ b/pkg/arvo/sur/publish.hoon @@ -35,6 +35,7 @@ filename=@tas date-created=@da last-edit=@da + read=? file=@t build=(each manx tang) comments=(map @da comment) @@ -49,7 +50,7 @@ date-created=@da notes=(map @tas note) order=(list @tas) - pinned=(set @tas) + unread=(set @tas) == :: +$ notebook-info diff --git a/pkg/interface/publish/src/js/api.js b/pkg/interface/publish/src/js/api.js index 252f7b6bf2..bf430b847d 100644 --- a/pkg/interface/publish/src/js/api.js +++ b/pkg/interface/publish/src/js/api.js @@ -42,6 +42,83 @@ class UrbitApi { }); }); } + + // TODO add error handling + + handleErrors(response) { + if (!response.ok) throw Error(response.status); + return response; + } + + fetchNotebooks() { + fetch('/~publish/notebooks.json') + .then((response) => response.json()) + .then((json) => { + store.handleEvent({ + type: 'notebooks', + data: json, + }); + }); + } + + fetchNotebook(host, book) { + fetch(`/~publish/${host}/${book}.json`) + .then((response) => response.json()) + .then((json) => { + store.handleEvent({ + type: 'notebook', + data: json, + host: host, + notebook: book, + }); + }); + } + + fetchNote(host, book, note) { + fetch(`/~publish/${host}/${book}/${note}.json`) + .then((response) => response.json()) + .then((json) => { + store.handleEvent({ + type: 'note', + data: json, + host: host, + notebook: book, + note: note, + }); + }); + } + + fetchNotesPage(host, book, start, length) { + fetch(`/~publish/notes/${host}/${book}/${start}/${length}.json`) + .then((response) => response.json()) + .then((json) => { + store.handleEvent({ + type: 'notes-page', + data: json, + host: host, + notebook: book, + startIndex: start, + length: length, + }); + }); + } + + fetchCommentsPage(host, book, note, start, length) { + fetch(`/~publish/comments/${host}/${book}/${note}/${start}/${length}.json`) + .then((response) => response.json()) + .then((json) => { + store.handleEvent({ + type: 'comments-page', + data: json, + host: host, + notebook: book, + note: note, + startIndex: start, + length: length, + }); + }); + } + } export let api = new UrbitApi(); diff --git a/pkg/interface/publish/src/js/reducers/initial.js b/pkg/interface/publish/src/js/reducers/initial.js new file mode 100644 index 0000000000..4264836ac2 --- /dev/null +++ b/pkg/interface/publish/src/js/reducers/initial.js @@ -0,0 +1,7 @@ +import _ from 'lodash'; + +export class InitialReducer { + reduce(json, state) { + state.notebooks = json.notebooks || null; + } +} diff --git a/pkg/interface/publish/src/js/reducers/primary.js b/pkg/interface/publish/src/js/reducers/primary.js new file mode 100644 index 0000000000..23cdd01871 --- /dev/null +++ b/pkg/interface/publish/src/js/reducers/primary.js @@ -0,0 +1,213 @@ +import _ from 'lodash'; + +export class PrimaryReducer { + reduce(json, state){ + console.log("primaryReducer", json); + switch(Object.keys(json)[0]){ + case "add-book": + this.addBook(json["add-book"], state); + break; + case "add-note": + this.addNote(json["add-note"], state); + break; + case "add-comment": + this.addComment(json["add-comment"], state); + break; + case "edit-book": + this.editBook(json["edit-book"], state); + break; + case "edit-note": + this.editNote(json["edit-note"], state); + break; + case "edit-comment": + this.editComment(json["edit-comment"], state); + break; + case "del-book": + this.delBook(json["del-book"], state); + break; + case "del-note": + this.delNote(json["del-note"], state); + break; + case "del-comment": + this.delComment(json["del-comment"], state); + break; + default: + break; + } + } + + addBook(json, state) { + let host = Object.keys(json)[0]; + let book = Object.keys(json[host])[0]; + if (state.notebooks[host]) { + state.notebooks[host][book] = json[host][book]; + } else { + state.notebooks[host] = json[host]; + } + } + + addNote(json, state) { + let host = Object.keys(json)[0]; + let book = Object.keys(json[host])[0]; + let noteId = json[host][book]["note-id"]; + if (state.notebooks[host] && state.notebooks[host][book]) { + if (state.notebooks[host][book]["notes-by-date"]) { + state.notebooks[host][book]["notes-by-date"].unshift(noteId); + } else { + state.notebooks[host][book]["notes-by-date"] = [noteId]; + } + + if (state.notebooks[host][book].notes) { + state.notebooks[host][book].notes[noteId] = json[host][book]; + } else { + state.notebooks[host][book].notes = {[noteId]: json[host][book]}; + } + + state.notebooks[host][book]["num-notes"] += 1; + if (!json[host][book].read) { + state.notebooks[host][book]["num-unread"] += 1; + } + let prevNoteId = state.notebooks[host][book]["notes-by-date"][1] || null; + state.notebooks[host][book].notes[noteId]["prev-note"] = prevNoteId + state.notebooks[host][book].notes[noteId]["next-note"] = null; + + if (state.notebooks[host][book].notes[prevNoteId]) { + state.notebooks[host][book].notes[prevNoteId]["next-note"] = noteId; + } + } + } + + addComment(json, state) { + let host = json.host + let book = json.book + let note = json.note + let comment = json.comment; + if (state.notebooks[host] && + state.notebooks[host][book] && + state.notebooks[host][book].notes && + state.notebooks[host][book].notes[note]) + { + state.notebooks[host][book].notes[note]["num-comments"] += 1; + if (state.notebooks[host][book].notes[note].comments) { + state.notebooks[host][book].notes[note].comments.unshift(comment); + } else if (state.notebooks[host][book].notes[note]["num-comments"] === 1) { + state.notebooks[host][book].notes[note].comments = [comment]; + } + } + } + + editBook(json, state) { + let host = Object.keys(json)[0]; + let book = Object.keys(json[host])[0]; + if (state.notebooks[host] && state.notebooks[host][book]) { + state.notebooks[host][book]["date-created"] = json[host][book]["date-created"]; + state.notebooks[host][book]["num-notes"] = json[host][book]["num-notes"]; + state.notebooks[host][book]["num-unread"] = json[host][book]["num-unread"]; + state.notebooks[host][book]["title"] = json[host][book]["title"]; + } + } + + editNote(json, state) { + let host = Object.keys(json)[0]; + let book = Object.keys(json[host])[0]; + let noteId = json[host][book]["note-id"]; + let note = json[host][book]; + if (state.notebooks[host] && + state.notebooks[host][book] && + state.notebooks[host][book].notes && + state.notebooks[host][book].notes[noteId]) + { + state.notebooks[host][book].notes[noteId]["author"] = note["author"]; + state.notebooks[host][book].notes[noteId]["build"] = note["build"]; + state.notebooks[host][book].notes[noteId]["file"] = note["file"]; + state.notebooks[host][book].notes[noteId]["title"] = note["title"]; + } + } + + editComment(json, state) { + let host = json.host + let book = json.book + let note = json.note + let comment = json.comment; + let commentId = Object.keys(comment)[0] + if (state.notebooks[host] && + state.notebooks[host][book] && + state.notebooks[host][book].notes && + state.notebooks[host][book].notes[note] && + state.notebooks[host][book].notes[note].comments) + { + let keys = state.notebooks[host][book].notes[note].comments.map((com) => { + return Object.keys(com)[0]; + }); + let index = keys.indexOf(commentId); + if (index > -1) { + state.notebooks[host][book].notes[note].comments[index] = comment; + } + } + } + + delBook(json, state) { + let host = json.host; + let book = json.book; + if (state.notebooks[host]) { + if (state.notebooks[host][book]) { + delete state.notebooks[host][book]; + } + if (Object.keys(state.notebooks[host]).length === 0) { + delete state.notebooks[host]; + } + } + } + + delNote(json, state) { + let host = json.host; + let book = json.book; + let note = json.note; + if (state.notebooks[host] && + state.notebooks[host][book] && + state.notebooks[host][book].notes) + { + if (state.notebooks[host][book].notes[note]) { + state.notebooks[host][book]["num-notes"] -= 1; + if (!state.notebooks[host][book].notes[note].read) { + state.notebooks[host][book]["num-unread"] -= 1; + } + + delete state.notebooks[host][book].notes[note]; + let index = state.notebooks[host][book]["notes-by-date"].indexOf(note); + if (index > -1) { + state.notebooks[host][book]["notes-by-date"].splice(index, 1); + } + + } + if (Object.keys(state.notebooks[host][book].notes).length === 0) { + delete state.notebooks[host][book].notes; + delete state.notebooks[host][book]["notes-by-date"]; + } + } + } + + delComment(json, state) { + let host = json.host + let book = json.book + let note = json.note + let comment = json.comment; + if (state.notebooks[host] && + state.notebooks[host][book] && + state.notebooks[host][book].notes && + state.notebooks[host][book].notes[note]) + { + state.notebooks[host][book].notes[note]["num-comments"] -= 1; + if (state.notebooks[host][book].notes[note].comments) { + let keys = state.notebooks[host][book].notes[note].comments.map((com) => { + return Object.keys(com)[0]; + }); + + let index = keys.indexOf(comment); + if (index > -1) { + state.notebooks[host][book].notes[note].comments.splice(index, 1); + } + } + } + } +} diff --git a/pkg/interface/publish/src/js/reducers/response.js b/pkg/interface/publish/src/js/reducers/response.js new file mode 100644 index 0000000000..3afe5a8841 --- /dev/null +++ b/pkg/interface/publish/src/js/reducers/response.js @@ -0,0 +1,167 @@ +import _ from 'lodash'; + +export class ResponseReducer { + reduce(json, state) { + console.log("responseReducer", json); + switch(json.type) { + case "notebooks": + this.handleNotebooks(json, state); + break; + case "notebook": + this.handleNotebook(json, state); + break; + case "note": + this.handleNote(json, state); + break; + case "notes-page": + this.handleNotesPage(json, state); + break; + case "comments-page": + this.handleCommentsPage(json, state); + break; + default: + break; + } + } + + handleNotebooks(json, state) { + for (var host in state.notebooks) { + if (json.data[host]) { + for (var book in state.notebooks[host]) { + if (!json.data[host][book]) { + delete state.notebooks[host][book]; + } + } + } else { + delete state.notebooks[host]; + } + } + + for (var host in json.data) { + if (state.notebooks[host]) { + for (var book in json.data[host]) { + if (state.notebooks[host][book]) { + state.notebooks[host][book]["title"] = json.data[host][book]["title"]; + state.notebooks[host][book]["date-created"] = + json.data[host][book]["date-created"]; + state.notebooks[host][book]["num-notes"] = + json.data[host][book]["num-notes"]; + state.notebooks[host][book]["num-unread"] = + json.data[host][book]["num-unread"]; + } else { + state.notebooks[host][book] = json.data[host][book]; + } + } + } else { + state.notebooks[host] = json.data[host]; + } + } + } + + handleNotebook(json, state) { + if (state.notebooks[json.host]) { + if (state.notebooks[json.host][json.notebook]) { + state.notebooks[json.host][json.notebook]["notes-by-date"] = + json.data.notebook["notes-by-date"]; + if (state.notebooks[json.host][json.notebook].notes) { + for (var key in json.data.notebook.notes) { + let oldNote = state.notebooks[json.host][json.notebook].notes[key]; + if (!(oldNote)) { + state.notebooks[json.host][json.notebook].notes[key] = + json.data.notebook.notes[key]; + } else if (!(oldNote.build)) { + state.notebooks[json.host][json.notebook].notes[key]["author"] = + json.data.notebook.notes[key]["author"]; + state.notebooks[json.host][json.notebook].notes[key]["date-created"] = + json.data.notebook.notes[key]["date-created"]; + state.notebooks[json.host][json.notebook].notes[key]["note-id"] = + json.data.notebook.notes[key]["note-id"]; + state.notebooks[json.host][json.notebook].notes[key]["num-comments"] = + json.data.notebook.notes[key]["num-comments"]; + state.notebooks[json.host][json.notebook].notes[key]["title"] = + json.data.notebook.notes[key]["title"]; + } + } + } else { + state.notebooks[json.host][json.notebook].notes = + json.data.notebook.notes; + } + } else { + state.notebooks[json.host][json.notebook] = json.data.notebook; + } + } else { + state.notebooks[json.host] = {[json.notebook]: json.data.notebook}; + } + } + + handleNote(json, state) { + if (state.notebooks[json.host] && + state.notebooks[json.host][json.notebook]) { + state.notebooks[json.host][json.notebook]["notes-by-date"] = + json.data["notes-by-date"]; + if (state.notebooks[json.host][json.notebook].notes) { + for (var key in json.data.notes) { + let oldNote = state.notebooks[json.host][json.notebook].notes[key]; + if (!(oldNote && oldNote.build && key !== json.note)) { + state.notebooks[json.host][json.notebook].notes[key] = + json.data.notes[key]; + } + } + } else { + state.notebooks[json.host][json.notebook].notes = json.data.notes; + } + } else { + throw Error("tried to fetch note, but we don't have the notebook"); + } + } + + handleNotesPage(json, state) { + if (state.notebooks[json.host] && state.notebooks[json.host][json.notebook]) { + state.notebooks[json.host][json.notebook]["notes-by-date"] = + json.data["notes-by-date"]; + if (state.notebooks[json.host][json.notebook].notes) { + for (var key in json.data.notes) { + let oldNote = state.notebooks[json.host][json.notebook].notes[key]; + if (!(oldNote)) { + state.notebooks[json.host][json.notebook].notes[key] = + json.data.notes[key]; + } else if (!(oldNote.build)) { + state.notebooks[json.host][json.notebook].notes[key]["author"] = + json.data.notes[key]["author"]; + state.notebooks[json.host][json.notebook].notes[key]["date-created"] = + json.data.notes[key]["date-created"]; + state.notebooks[json.host][json.notebook].notes[key]["note-id"] = + json.data.notes[key]["note-id"]; + state.notebooks[json.host][json.notebook].notes[key]["num-comments"] = + json.data.notes[key]["num-comments"]; + state.notebooks[json.host][json.notebook].notes[key]["title"] = + json.data.notes[key]["title"]; + } + } + } else { + state.notebooks[json.host][json.notebook].notes = + json.data.notes; + } + } else { + throw Error("tried to fetch paginated notes, but we don't have the notebook"); + } + } + + handleCommentsPage(json, state) { + if (state.notebooks[json.host] && + state.notebooks[json.host][json.notebook] && + state.notebooks[json.host][json.notebook].notes[json.note]) + { + if (state.notebooks[json.host][json.notebook].notes[json.note].comments) { + state.notebooks[json.host][json.notebook].notes[json.note].comments + .concat(json.data); + } else { + state.notebooks[json.host][json.notebook].notes[json.note].comments = + json.data; + } + } else { + throw Error("tried to fetch paginated comments, but we don't have the note"); + } + } + +} diff --git a/pkg/interface/publish/src/js/reducers/rumor.js b/pkg/interface/publish/src/js/reducers/rumor.js deleted file mode 100644 index 97fa99966d..0000000000 --- a/pkg/interface/publish/src/js/reducers/rumor.js +++ /dev/null @@ -1,336 +0,0 @@ -export class RumorReducer { - reduce(json, state){ - if (json.collection) { - this.reduceCollection(json.collection, state); - } - if (json.post) { - this.reducePost(json, state); - } - if (json.comments) { - this.reduceComments(json, state); - } - if (json.total) { - this.reduceTotal(json, state); - } - if (json.remove) { - this.reduceRemove(json.remove, state); - } - } - - reduceRemove(json, state) { - if (json.who === window.ship) { - if (json.post) { - this.removePost(json, state); - delete state.pubs[json.coll].posts[json.post]; - } else { - - let postIds = Object.keys(state.pubs[json.coll].posts); - postIds.forEach((postId) => { - this.removePost({ - who: json.who, - coll: json.coll, - post: postId, - }, state); - }); - delete state.pubs[json.coll]; - - } - } else { - if (json.post) { - this.removePost(json, state); - delete state.subs[json.who][json.coll].posts[json.post]; - } else { - let postIds = Object.keys(state.subs[json.who][json.coll].posts); - postIds.forEach((postId) => { - this.removePost({ - who: json.who, - coll: json.coll, - post: postId, - }, state); - }); - delete state.subs[json.who][json.coll]; - } - } - } - - removePost(json, state) { - this.removeLatest(json, state); - this.removeOrder(json, state); - this.removeUnread(json, state); - } - - removeLatest(json, state) { - let idx = _.findIndex(state.latest, json); - _.pullAt(state.latest, [idx]); - } - - removeUnread(json, state) { - let idx = _.findIndex(state.latest, json); - _.pullAt(state.latest, [idx]); - } - - removeOrder(json, state) { - if (json.who === window.ship) { - if (state.pubs[json.coll]) { - let pinIdx = state.pubs[json.coll].order.pin.indexOf(json.post); - let unpinIdx = state.pubs[json.coll].order.unpin.indexOf(json.post); - - if (pinIdx != -1) { - _.pullAt(state.pubs[json.coll].order.pin, [pinIdx]); - } - if (unpinIdx != -1) { - _.pullAt(state.pubs[json.coll].order.unpin, [unpinIdx]); - } - } - } else { - if (state.subs[json.who][json.coll]) { - let pinIdx = - state.subs[json.who][json.coll].order.pin.indexOf(json.post); - let unpinIdx = - state.subs[json.who][json.coll].order.unpin.indexOf(json.post); - - if (pinIdx != -1) { - _.pullAt(state.subs[json.who][json.coll].order.pin, [pinIdx]); - } - if (unpinIdx != -1) { - _.pullAt(state.subs[json.who][json.coll].order.unpin, [unpinIdx]); - } - } - } - } - - reduceCollection(json, state) { - if (json.who === window.ship) { - if (state.pubs[json.coll]) { - state.pubs[json.coll].info = json.data; - } else { - state.pubs[json.coll] = { - info: json.data, - order: { pin: [], unpin: [] }, - posts: {}, - } - } - } else { - if (state.subs[json.who]) { - if (state.subs[json.who][json.coll]) { - state.subs[json.who][json.coll].info = json.data; - } else { - state.subs[json.who][json.coll] = { - info: json.data, - order: { pin: [], unpin: [] }, - posts: {}, - } - } - } else { - state.subs[json.who] = { - [json.coll]: { - info: json.data, - order: { pin: [], unpin: [] }, - posts: {}, - } - } - } - } - } - - reducePost(json, state) { - let who = json.post.who; - let coll = json.post.coll; - let post = json.post.post; - let data = json.post.data; - - if (who === window.ship) { - if (state.pubs[coll].posts[post]) { - state.pubs[coll].posts[post].post = data; - } else { - state.pubs[coll].posts[post] = { - post: data, - comments: [], - }; - } - } else { - if (state.subs[who][coll].posts[post]) { - state.subs[who][coll].posts[post].post = data; - } else { - state.subs[who][coll].posts[post] = { - post: data, - comments: [], - }; - } - } - - this.insertPost(json, state); - } - - insertPost(json, state) { - if (typeof(json.post.data) === 'string') { - return; - } - - this.insertLatest(json, state); - this.insertUnread(json, state); - this.insertOrder(json, state); - } - - insertLatest(json, state) { - let newIndex = { - post: json.post.post, - coll: json.post.coll, - who: json.post.who, - } - let newDate = json.post.data.info["date-created"]; - - if (state.latest.length == 0) { - state.latest.push(newIndex); - return; - } - - if (state.latest.indexOf(newIndex) != -1) { - return; - } - - for (var i=0; i= idate) { - state.latest.splice(i, 0, newIndex); - break; - } else if (i == (state.latest.length - 1)) { - state.latest.push(newIndex); - break; - } - } - } - - insertUnread(json, state) { - if (json.post.who != window.ship) { - state.unread.push({ - post: json.post.post, - coll: json.post.coll, - who: json.post.who, - }); - } - } - - insertOrder(json, state) { - let blogId = json.post.coll; - let ship = json.post.who; - let blog = this.retrieveColl(state, blogId, ship); - let list = json.post.data.info.pinned - ? blog.order.pin - : blog.order.unpin; - let newDate = json.post.data.info["date-created"]; - - if (list.length == 0) { - list.push(json.post.post); - } - - if (list.indexOf(json.post.post) != -1) { - return; - } - - for (var i=0; i= idate) { - list.splice(i, 0, json.post.post); - break; - } else if (i == (state.latest.length - 1)) { - list.push(json.post.post); - break; - } - } - - if (window.ship == ship) { - state.pubs[blogId].order = json.post.data.info.pinned - ? {pin: list, unpin: blog.order.unpin} - : {pin: blog.order.pin, unpin: list}; - } else { - state.subs[ship][blogId].order = json.post.data.info.pinned - ? {pin: list, unpin: blog.order.unpin} - : {pin: blog.order.pin, unpin: list}; - } - } - - retrieveColl(state, coll, who) { - if (who === window.ship) { - return state.pubs[coll]; - } else { - return state.subs[who][coll]; - } - } - - retrievePost(state, coll, post, who) { - if (who === window.ship) { - return state.pubs[coll].posts[post].post; - } else { - return state.subs[who][coll].posts[post].post; - } - } - - reduceComments(json, state) { - let who = json.comments.who; - let coll = json.comments.coll; - let post = json.comments.post; - let data = json.comments.data; - - if (who === window.ship) { - if (state.pubs[coll].posts[post]) { - state.pubs[coll].posts[post].comments = data; - } else { - state.pubs[coll].posts[post] = { - post: null, - comments: data, - }; - } - } else { - if (state.subs[who][coll].posts[post]) { - state.subs[who][coll].posts[post].comments = data; - } else { - state.subs[who][coll].posts[post] = { - post: null, - comments: data, - }; - } - } - } - - reduceTotal(json, state) { - if (json.total.who == window.ship) { - state.pubs[json.total.coll] = json.total.data - } else { - if (state.subs[json.total.who]) { - state.subs[json.total.who][json.total.coll] = json.total.data; - } else { - state.subs[json.total.who] = { - [json.total.coll] : json.total.data - } - } - } - let posts = Object.keys(json.total.data.posts); - for (var i=0; i { - return _.findIndex(state.unread, val); - }); - _.pullAt(state.unread, idx); - } - } -} diff --git a/pkg/interface/publish/src/js/store.js b/pkg/interface/publish/src/js/store.js index 96c03cbf9c..7623627f4a 100644 --- a/pkg/interface/publish/src/js/store.js +++ b/pkg/interface/publish/src/js/store.js @@ -1,31 +1,33 @@ -import { UpdateReducer } from '/reducers/update'; -import { RumorReducer } from '/reducers/rumor'; -import { SpinnerReducer } from '/reducers/spinner'; +import { InitialReducer } from '/reducers/initial'; +import { PrimaryReducer } from '/reducers/primary'; +import { ResponseReducer } from '/reducers/response'; class Store { constructor() { this.state = { - spinner: false, - ...window.injectedState, + notebooks: {}, } - this.updateReducer = new UpdateReducer(); - this.rumorReducer = new RumorReducer(); - this.spinnerReducer = new SpinnerReducer(); + this.initialReducer = new InitialReducer(); + this.primaryReducer = new PrimaryReducer(); + this.responseReducer = new ResponseReducer(); this.setState = () => {}; + + this.initialReducer.reduce(window.injectedState, this.state); } setStateHandler(setState) { this.setState = setState; } - handleEvent(data) { - this.updateReducer.reduce(data.data, this.state); - this.rumorReducer.reduce(data.data, this.state); - this.spinnerReducer.reduce(data.data, this.state); + handleEvent(evt) { + if (evt.from && evt.from.path === '/primary'){ + this.primaryReducer.reduce(evt.data, this.state); + } else if (evt.type) { + this.responseReducer.reduce(evt, this.state); + } this.setState(this.state); } - } export let store = new Store(); From 97f820a2c6896ccfeb78e8c915384900016ce863 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Wed, 8 Jan 2020 10:45:16 -0800 Subject: [PATCH 06/20] fixed group and invite bugs --- pkg/arvo/app/publish.hoon | 237 +++++++++++++++++++------- pkg/interface/publish/src/js/store.js | 5 + 2 files changed, 180 insertions(+), 62 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index 2c7bdd57b5..0f862e1929 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -1,5 +1,10 @@ :: -/- *publish, *group-store, *permission-hook, *permission-group-hook +/- *publish, + *group-store, + *permission-hook, + *permission-group-hook, + *permission-store, + *invite-store /+ *server, *publish, cram, default-agent :: /= index @@ -105,6 +110,8 @@ :: [%notebook @ ~] =/ book-name i.t.pax + ?. (allowed src.bol %read book-name) + ~|("not permitted" !!) =/ book (~(got by books) book-name) =/ delta=notebook-delta [%add-book our.bol book-name book] @@ -117,11 +124,7 @@ == :: ++ on-leave on-leave:def - :: - ++ on-peek - |= =path - ~| "unexpected scry into {} on path {}" - !! + ++ on-peek on-peek:def :: ++ on-agent |= [wir=wire sin=sign:agent:gall] @@ -143,9 +146,15 @@ (handle-notebook-delta:main !<(notebook-delta q.cage.sin)) [cards this] :: - [%permissions ~] !! + [%permissions ~] + =^ cards state + (handle-permission-update:main !<(permission-update q.cage.sin)) + [cards this] :: - [%invites ~] !! + [%invites ~] + =^ cards state + (handle-invite-update:main !<(invite-update q.cage.sin)) + [cards this] == == :: @@ -338,29 +347,6 @@ (handle-notebook-delta delta) == :: -++ make-groups - |= [book-name=@tas group=group-info] - ^- [(list card) path path] - ?- -.group - %old [~ writers.group subscribers.group] - %new - =/ writers-path /~/publish/[book-name]/writers - =/ subscribers-path /~/publish/[book-name]/subscribers - ^- [(list card) path path] - :_ [writers-path subscribers-path] - ;: weld - :~ (group-poke [%bundle writers-path]) - (group-poke [%bundle subscribers-path]) - (group-poke [%add writers.group writers-path]) - (group-poke [%add subscribers.group subscribers-path]) - == - (create-security writers-path subscribers-path sec.group) - :~ (perm-hook-poke [%add-owned writers-path writers-path]) - (perm-hook-poke [%add-owned subscribers-path subscribers-path]) - == - == - == -:: ++ add-paths |= paths=(list path) ^- (quip card _state) @@ -513,33 +499,55 @@ ~ == :: +++ handle-permission-update + |= upd=permission-update + ^- (quip card _state) + ?. ?=(?(%add %remove) -.upd) + [~ state] + =/ book=@tas + %- need + %+ roll ~(tap by books) + |= [[nom=@tas book=notebook] out=(unit @tas)] + ?: =(path.upd subscribers.book) + `nom + out + :_ state + %- zing + %+ turn ~(tap in who.upd) + |= who=@p + ?: (allowed who %read book) + ~ + [%give %kick `/notebook/[book] `who]~ +:: +++ handle-invite-update + |= upd=invite-update + ^- (quip card _state) + ?. ?=(%accepted -.upd) + [~ state] + =/ wir=wire (weld /subscribe/(scot %p ship.invite.upd) path.upd) + :_ state + :_ ~ + :* %pass + wir + %agent + [ship.invite.upd %publish] + %watch + (weld /notebook path.upd) + == +:: ++ our-beak /(scot %p our.bol)/[q.byk.bol]/(scot %da now.bol) :: ++ allowed - |= [who=@p mod=?(%read %write) pax=path] + |= [who=@p mod=?(%read %write) book=@tas] ^- ? - =. pax (weld our-beak pax) - =/ pem=[dict:clay dict:clay] .^([dict:clay dict:clay] %cp pax) - ?- mod - %read (allowed-by who -.pem) - %write (allowed-by who +.pem) - == -:: -++ allowed-by - |= [who=@p dic=dict:clay] - ^- ? - ?: =(who our.bol) & - =/ in-list=? - ?| (~(has in p.who.rul.dic) who) - :: - %- ~(rep by q.who.rul.dic) - |= [[@ta cru=crew:clay] out=_|] - ?: out & - (~(has in cru) who) - == - ?: =(%black mod.rul.dic) - !in-list - in-list + =/ scry-bek /(scot %p our.bol)/permission-store/(scot %da now.bol) + =/ book=notebook (~(got by books) book) + =/ scry-pax + ?: =(%read mod) + subscribers.book + writers.book + =/ full-pax :(weld scry-bek /permitted/(scot %p who) scry-pax) + .^(? %gx full-pax) :: ++ write-file |= [pax=path cay=cage] @@ -622,26 +630,51 @@ == :: ++ create-security - |= [par=path sub=path sec=rw-security] + |= [read=path write=path sec=rw-security] ^- (list card) - =+ ^- [par-type=?(%black %white) sub-type=?(%black %white)] + =+ ^- [read-type=?(%black %white) write-type=?(%black %white)] ?- sec %channel [%black %black] %village [%white %white] %journal [%black %white] %mailbox [%white %black] == - :~ (perm-group-hook-poke [%associate par [[par par-type] ~ ~]]) - (perm-group-hook-poke [%associate sub [[sub sub-type] ~ ~]]) + :~ (perm-group-hook-poke [%associate read [[read read-type] ~ ~]]) + (perm-group-hook-poke [%associate write [[write write-type] ~ ~]]) == :: +++ make-groups + |= [book-name=@tas group=group-info] + ^- [(list card) path path] + ?- -.group + %old [~ writers.group subscribers.group] + %new + =/ writers-path /~/publish/[book-name]/writers + =/ subscribers-path /~/publish/[book-name]/subscribers + ^- [(list card) path path] + :_ [writers-path subscribers-path] + ;: weld + :~ (group-poke [%bundle writers-path]) + (group-poke [%bundle subscribers-path]) + (group-poke [%add writers.group writers-path]) + (group-poke [%add subscribers.group subscribers-path]) + == + (create-security subscribers-path writers-path sec.group) + :~ (perm-hook-poke [%add-owned writers-path writers-path]) + (perm-hook-poke [%add-owned subscribers-path subscribers-path]) + == + == + == :: ++ poke-publish-action |= act=action ^- (quip card _state) ?- -.act %new-book - ?> (team:title our.bol src.bol) + ?. (team:title our.bol src.bol) + ~|("action not permitted" !!) + ?: (~(has by books) book.act) + ~|("notebook already exists: {}" !!) =+ ^- [cards=(list card) writers-path=path subscribers-path=path] (make-groups book.act group.act) =/ new-book=notebook-info @@ -659,6 +692,15 @@ ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + =/ book=(unit notebook) (~(get by books) book.act) + ?~ book + ~|("nonexistent notebook {}" !!) + ?: (~(has by notes.u.book) note.act) + ~|("note already exists: {}" !!) + ?. ?| (team:title our.bol src.bol) + (allowed src.bol %write book.act) + == + ~|("action not permitted" !!) =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon =/ front=(map knot cord) %- my @@ -674,6 +716,17 @@ ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + =/ book=(unit notebook) (~(get by books) book.act) + ?~ book + ~|("nonexistent notebook {}" !!) + ?. (~(has by notes.u.book) note.act) + ~|("nonexistent note {}" !!) + ?. ?& ?| (team:title our.bol src.bol) + (allowed src.bol %read book.act) + == + comments.u.book + == + ~|("action not permitted" !!) =/ pax=path %+ weld /app/publish/notebooks /[book.act]/[note.act]/(scot %da now.bol)/publish-comment @@ -686,10 +739,11 @@ [(write-file pax %publish-comment !>(new-comment))]~ :: %edit-book - ?> (team:title our.bol src.bol) + ?. (team:title our.bol src.bol) + ~|("action not permitted" !!) =/ book (~(get by books) book.act) ?~ book - [~ state] + ~|("nonexistent notebook" !!) =+ ^- [cards=(list card) writers-path=path subscribers-path=path] ?~ group.act [~ writers.u.book subscribers.u.book] @@ -709,6 +763,18 @@ ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + =/ book=(unit notebook) (~(get by books) book.act) + ?~ book + ~|("nonexistent notebook {}" !!) + =/ note=(unit note) (~(get by notes.u.book) note.act) + ?~ note + ~|("nonexistent note: {}" !!) + ?. ?| (team:title our.bol src.bol) + ?& =(author.u.note src.bol) + (allowed src.bol %write book.act) + == + == + ~|("action not permitted" !!) =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon =/ front=(map knot cord) %- my @@ -724,6 +790,22 @@ ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + =/ book=(unit notebook) (~(get by books) book.act) + ?~ book + ~|("nonexistent notebook {}" !!) + =/ not=(unit note) (~(get by notes.u.book) note.act) + ?~ not + ~|("nonexistent note {}" !!) + =/ com=(unit comment) + (~(get by comments.u.not) (slav %da comment.act)) + ?~ com + ~|("nonexistent comment {}" !!) + ?. ?| (team:title our.bol src.bol) + ?& =(author.u.com src.bol) + (allowed src.bol %read book.act) + == + == + ~|("action not permitted" !!) =/ pax=path %+ weld /app/publish/notebooks /[book.act]/[note.act]/[comment.act]/publish-comment @@ -733,7 +815,10 @@ [(write-file pax %publish-comment !>(new-comment))]~ :: %del-book - ?> (team:title our.bol src.bol) + ?. (team:title our.bol src.bol) + ~|("action not permitted" !!) + ?. (~(has by books) book.act) + ~|("nonexistent notebook {}" !!) =/ pax=path /app/publish/notebooks/[book.act] :_ state(books (~(del by books) book.act)) [(delete-dir pax)]~ @@ -742,6 +827,18 @@ ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + =/ book=(unit notebook) (~(get by books) book.act) + ?~ book + ~|("nonexistent notebook {}" !!) + =/ note=(unit note) (~(get by notes.u.book) note.act) + ?~ note + ~|("nonexistent note: {}" !!) + ?. ?| (team:title our.bol src.bol) + ?& =(author.u.note src.bol) + (allowed src.bol %write book.act) + == + == + ~|("action not permitted" !!) =/ pax=path /app/publish/notebooks/[book.act]/[note.act]/udon :_ state [(delete-file pax)]~ @@ -750,6 +847,22 @@ ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + =/ book=(unit notebook) (~(get by books) book.act) + ?~ book + ~|("nonexistent notebook {}" !!) + =/ note=(unit note) (~(get by notes.u.book) note.act) + ?~ note + ~|("nonexistent note {}" !!) + =/ comment=(unit comment) + (~(get by comments.u.note) (slav %da comment.act)) + ?~ comment + ~|("nonexistent comment {}" !!) + ?. ?| (team:title our.bol src.bol) + ?& =(author.u.comment src.bol) + (allowed src.bol %read book.act) + == + == + ~|("action not permitted" !!) =/ pax=path %+ weld /app/publish/notebooks /[book.act]/[note.act]/[comment.act]/publish-comment diff --git a/pkg/interface/publish/src/js/store.js b/pkg/interface/publish/src/js/store.js index 7623627f4a..fc88e520be 100644 --- a/pkg/interface/publish/src/js/store.js +++ b/pkg/interface/publish/src/js/store.js @@ -6,6 +6,11 @@ class Store { constructor() { this.state = { notebooks: {}, + groups: {}, + permissions: {}, + invites: {}, + spinner: false, + sidebarShown: false, } this.initialReducer = new InitialReducer(); From 041900dc26cadd61cf746bde432fda5055fbfc8b Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Wed, 8 Jan 2020 15:13:42 -0800 Subject: [PATCH 07/20] handle marking posts as read --- pkg/arvo/app/publish.hoon | 59 +++-- pkg/arvo/mar/publish/action.hoon | 234 +++++++----------- pkg/arvo/mar/publish/action2.hoon | 117 --------- pkg/arvo/mar/publish/primary-delta.hoon | 7 + pkg/arvo/mar/publish/rumor.hoon | 55 ---- pkg/arvo/mar/publish/update.hoon | 41 --- pkg/arvo/sur/publish.hoon | 3 + .../publish/src/js/reducers/primary.js | 16 ++ 8 files changed, 152 insertions(+), 380 deletions(-) delete mode 100644 pkg/arvo/mar/publish/action2.hoon delete mode 100644 pkg/arvo/mar/publish/rumor.hoon delete mode 100644 pkg/arvo/mar/publish/update.hoon diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index 0f862e1929..c5fbdedb72 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -96,7 +96,7 @@ %+ require-authorization:app req handle-http-request:main :: - %publish-action2 + %publish-action =^ cards state (poke-publish-action:main !<(action vas)) [cards this] @@ -109,14 +109,9 @@ [%http-response *] [~ this] :: [%notebook @ ~] - =/ book-name i.t.pax - ?. (allowed src.bol %read book-name) - ~|("not permitted" !!) - =/ book (~(got by books) book-name) - =/ delta=notebook-delta - [%add-book our.bol book-name book] - :_ this - [%give %fact ~ %publish-notebook-delta !>(delta)]~ + =^ cards state + (watch-notebook:main pax) + [cards this] :: [%primary ~] [~ this] :: @@ -535,6 +530,18 @@ (weld /notebook path.upd) == :: +++ watch-notebook + |= pax=path + ?> ?=([%notebook @ ~] pax) + =/ book-name i.t.pax + ?. (allowed src.bol %read book-name) + ~|("not permitted" !!) + =/ book (~(got by books) book-name) + =/ delta=notebook-delta + [%add-book our.bol book-name book] + :_ state + [%give %fact ~ %publish-notebook-delta !>(delta)]~ +:: ++ our-beak /(scot %p our.bol)/[q.byk.bol]/(scot %da now.bol) :: ++ allowed @@ -546,7 +553,7 @@ ?: =(%read mod) subscribers.book writers.book - =/ full-pax :(weld scry-bek /permitted/(scot %p who) scry-pax) + =/ full-pax :(weld scry-bek /permitted/(scot %p who) scry-pax /noun) .^(? %gx full-pax) :: ++ write-file @@ -691,7 +698,7 @@ %new-note ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ =/ book=(unit notebook) (~(get by books) book.act) ?~ book ~|("nonexistent notebook {}" !!) @@ -715,7 +722,7 @@ %new-comment ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ =/ book=(unit notebook) (~(get by books) book.act) ?~ book ~|("nonexistent notebook {}" !!) @@ -762,7 +769,7 @@ %edit-note ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ =/ book=(unit notebook) (~(get by books) book.act) ?~ book ~|("nonexistent notebook {}" !!) @@ -789,7 +796,7 @@ %edit-comment ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ =/ book=(unit notebook) (~(get by books) book.act) ?~ book ~|("nonexistent notebook {}" !!) @@ -826,7 +833,7 @@ %del-note ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ =/ book=(unit notebook) (~(get by books) book.act) ?~ book ~|("nonexistent notebook {}" !!) @@ -846,7 +853,7 @@ %del-comment ?: &(=(src.bol our.bol) !=(our.bol who.act)) :_ state - [%pass /forward %agent [who.act %publish] %poke %publish-action2 !>(act)]~ + [%pass /forward %agent [who.act %publish] %poke %publish-action !>(act)]~ =/ book=(unit notebook) (~(get by books) book.act) ?~ book ~|("nonexistent notebook {}" !!) @@ -883,6 +890,26 @@ :~ [%pass wir %agent [who.act %publish] %leave ~] [%give %fact `/primary %publish-primary-delta !>(del)] == + :: + %read + ?> (team:title our.bol src.bol) + =/ book=(unit notebook) + ?: =(our.bol who.act) + (~(get by books) book.act) + (~(get by subs) who.act book.act) + ?~ book + ~|("nonexistent notebook: {}" !!) + =/ not=(unit note) (~(get by notes.u.book) note.act) + ?~ not + ~|("nonexistent note: {}" !!) + =. read.u.not %.y + =. notes.u.book (~(put by notes.u.book) note.act u.not) + =? books =(our.bol who.act) + (~(put by books) book.act u.book) + =? subs !=(our.bol who.act) + (~(put by subs) [who.act book.act] u.book) + :_ state + [%give %fact `/primary %publish-primary-delta !>(act)]~ == :: ++ get-notebook diff --git a/pkg/arvo/mar/publish/action.hoon b/pkg/arvo/mar/publish/action.hoon index 4bb9dc4de8..c771c903f1 100644 --- a/pkg/arvo/mar/publish/action.hoon +++ b/pkg/arvo/mar/publish/action.hoon @@ -1,11 +1,10 @@ :: :::: /hoon/action/publish/mar :: -/? 309 -/- publish +/- *publish =, format :: -|_ act=action:publish +|_ act=action :: ++ grow |% @@ -14,179 +13,112 @@ :: ++ grab |% - ++ noun action:publish + ++ noun action ++ json |= jon=^json - %- action:publish - =< (action jon) - |% - ++ action - %- of:dejs - :~ new-collection+new-collection - new-post+new-post - new-comment+new-comment - :: - delete-collection+delete-collection - delete-post+delete-post - delete-comment+delete-comment - :: - edit-collection+edit-collection - edit-post+edit-post - :: - invite+invite - reject-invite+reject-invite - :: - serve+serve - unserve+unserve - :: - subscribe+subscribe - unsubscribe+unsubscribe - :: - read+read + =, dejs:format + ;; action + |^ %- of + :~ new-book+new-book + new-note+new-note + new-comment+new-comment + edit-book+edit-book + edit-note+edit-note + edit-comment+edit-comment + del-book+del-book + del-note+del-note + del-comment+del-comment + subscribe+subscribe + unsubscribe+unsubscribe + read+read + == + :: + ++ new-book + %- ot + :~ book+so + title+so + about+so + coms+bo + group+group-info == :: - ++ new-collection - %- ot:dejs - :~ name+so:dejs - title+so:dejs - comments+comment-config - allow-edit+edit-config - perm+perm-config - == - :: - ++ new-post - %- ot:dejs - :~ who+(su:dejs fed:ag) - coll+so:dejs - name+so:dejs - title+so:dejs - comments+comment-config - perm+perm-config - content+so:dejs + ++ new-note + %- ot + :~ who+(su fed:ag) + book+so + note+so + title+so + body+so == :: ++ new-comment - %- ot:dejs - :~ who+(su:dejs fed:ag) - coll+so:dejs - name+(su:dejs sym) - content+so:dejs + %- ot + :~ who+(su fed:ag) + book+so + note+so + body+so == :: - ++ delete-collection - %- ot:dejs - :~ coll+so:dejs + ++ edit-book + %- ot + :~ book+so + title+so + about+so + coms+bo + group+(mu group-info) == :: - ++ delete-post - %- ot:dejs - :~ coll+so:dejs - post+so:dejs - == - :: - ++ delete-comment - %- ot:dejs - :~ coll+so:dejs - post+so:dejs - comment+so:dejs - == - :: - ++ edit-collection - %- ot:dejs - :~ name+so:dejs - title+so:dejs - == - :: - ++ edit-post - %- ot:dejs - :~ who+(su:dejs fed:ag) - coll+so:dejs - name+so:dejs - title+so:dejs - comments+comment-config - perm+perm-config - content+so:dejs + ++ edit-note + %- ot + :~ who+(su fed:ag) + book+so + note+so + title+so + body+so == :: ++ edit-comment - %- ot:dejs - :~ coll+so:dejs - name+so:dejs - id+so:dejs - content+so:dejs + %- ot + :~ who+(su fed:ag) + book+so + note+so + comment+(su ;~(pfix sig (cook year when:^so))) + body+so == :: - ++ comment-config - %- su:dejs - ;~(pose (jest %open) (jest %closed) (jest %none)) + ++ del-book (ot book+so ~) :: - ++ edit-config - %- su:dejs - ;~(pose (jest %post) (jest %comment) (jest %all) (jest %none)) + ++ del-note (ot who+(su fed:ag) book+so note+so ~) :: - ++ perm-config - %- ot:dejs - :~ :- %read - %- ot:dejs - :~ mod+(su:dejs ;~(pose (jest %black) (jest %white))) - who+whoms - == - :- %write - %- ot:dejs - :~ mod+(su:dejs ;~(pose (jest %black) (jest %white))) - who+whoms - == == - :: - ++ whoms - |= jon=^json - ^- (set whom:clay) - =/ x ((ar:dejs (su:dejs fed:ag)) jon) - %- (set whom:clay) - %- ~(run in (sy x)) - |=(w=@ [& w]) - :: - ++ invite - %- ot:dejs - :~ coll+so:dejs - title+so:dejs - who+(ar:dejs (su:dejs fed:ag)) + ++ del-comment + %- ot + :~ who+(su fed:ag) + book+so + note+so + comment+(su ;~(pfix sig (cook year when:^so))) == - :: - ++ reject-invite - %- ot:dejs - :~ who+(su:dejs fed:ag) - coll+so:dejs - == - :: - ++ serve - %- ot:dejs - :~ coll+so:dejs - == - :: - ++ unserve - %- ot:dejs - :~ coll+so:dejs - == - :: ++ subscribe - %- ot:dejs - :~ who+(su:dejs fed:ag) - coll+so:dejs + %- ot + :~ who+(su fed:ag) + book+so == - :: ++ unsubscribe - %- ot:dejs - :~ who+(su:dejs fed:ag) - coll+so:dejs + %- ot + :~ who+(su fed:ag) + book+so == - :: ++ read - %- ot:dejs - :~ who+(su:dejs fed:ag) - coll+so:dejs - post+so:dejs + %- ot + :~ who+(su fed:ag) + book+so + note+so == - :: + ++ group-info + %- of + :~ old+(ot writers+pa subscribers+pa ~) + new+(ot writers+set-ship subscribers+set-ship sec+so ~) + == + ++ set-ship (ar (su fed:ag)) -- -- -- diff --git a/pkg/arvo/mar/publish/action2.hoon b/pkg/arvo/mar/publish/action2.hoon deleted file mode 100644 index 01aa6de618..0000000000 --- a/pkg/arvo/mar/publish/action2.hoon +++ /dev/null @@ -1,117 +0,0 @@ -:: -:::: /hoon/action/publish/mar - :: -/- *publish -=, format -:: -|_ act=action -:: -++ grow - |% - ++ tank >act< - -- -:: -++ grab - |% - ++ noun action - ++ json - |= jon=^json - =, dejs:format - ;; action - |^ %- of - :~ new-book+new-book - new-note+new-note - new-comment+new-comment - edit-book+edit-book - edit-note+edit-note - edit-comment+edit-comment - del-book+del-book - del-note+del-note - del-comment+del-comment - subscribe+subscribe - unsubscribe+unsubscribe - == - :: - ++ new-book - %- ot - :~ book+so - title+so - about+so - coms+bo - group+group-info - == - :: - ++ new-note - %- ot - :~ who+(su fed:ag) - book+so - note+so - title+so - body+so - == - :: - ++ new-comment - %- ot - :~ who+(su fed:ag) - book+so - note+so - body+so - == - :: - ++ edit-book - %- ot - :~ book+so - title+so - about+so - coms+bo - group+(mu group-info) - == - :: - ++ edit-note - %- ot - :~ who+(su fed:ag) - book+so - note+so - title+so - body+so - == - :: - ++ edit-comment - %- ot - :~ who+(su fed:ag) - book+so - note+so - comment+(su ;~(pfix sig (cook year when:^so))) - body+so - == - :: - ++ del-book (ot book+so ~) - :: - ++ del-note (ot who+(su fed:ag) book+so note+so ~) - :: - ++ del-comment - %- ot - :~ who+(su fed:ag) - book+so - note+so - comment+(su ;~(pfix sig (cook year when:^so))) - == - ++ subscribe - %- ot - :~ who+(su fed:ag) - book+so - == - ++ unsubscribe - %- ot - :~ who+(su fed:ag) - book+so - == - ++ group-info - %- of - :~ old+(ot writers+pa subscribers+pa ~) - new+(ot writers+set-ship subscribers+set-ship sec+so ~) - == - ++ set-ship (ar (su fed:ag)) - -- - -- --- diff --git a/pkg/arvo/mar/publish/primary-delta.hoon b/pkg/arvo/mar/publish/primary-delta.hoon index f411e737ff..b0d45ef20a 100644 --- a/pkg/arvo/mar/publish/primary-delta.hoon +++ b/pkg/arvo/mar/publish/primary-delta.hoon @@ -71,6 +71,13 @@ note+s+note.del comment+s+(scot %da comment.del) == + :: + %read + %- pairs:enjs:format + :~ host+s+(scot %p who.del) + book+s+book.del + note+s+note.del + == == -- -- diff --git a/pkg/arvo/mar/publish/rumor.hoon b/pkg/arvo/mar/publish/rumor.hoon deleted file mode 100644 index 895368f202..0000000000 --- a/pkg/arvo/mar/publish/rumor.hoon +++ /dev/null @@ -1,55 +0,0 @@ -/- *publish -/+ *publish -|_ rum=rumor -++ grab - |% - ++ noun rumor - -- -++ grow - |% - ++ noun rum - ++ json - =, enjs:format - %+ frond -.rum - ?- -.rum - %collection - %- pairs - :~ [%coll s+col.rum] - [%who (ship who.rum)] - [%data (collection-build-to-json dat.rum)] - == - :: - %post - %- pairs - :~ [%coll s+col.rum] - [%post s+pos.rum] - [%who (ship who.rum)] - [%data (post-build-to-json dat.rum)] - == - :: - %comments - %- pairs - :~ [%coll s+col.rum] - [%post s+pos.rum] - [%who (ship who.rum)] - [%data (comment-build-to-json dat.rum)] - == - :: - %total - %- pairs - :~ [%coll s+col.rum] - [%who (ship who.rum)] - [%data (total-build-to-json dat.rum)] - == - :: - %remove - %- pairs - :~ [%who (ship who.rum)] - [%coll s+col.rum] - [%post ?~(pos.rum ~ s+u.pos.rum)] - == - :: - == - :: - -- --- diff --git a/pkg/arvo/mar/publish/update.hoon b/pkg/arvo/mar/publish/update.hoon deleted file mode 100644 index fde715fd76..0000000000 --- a/pkg/arvo/mar/publish/update.hoon +++ /dev/null @@ -1,41 +0,0 @@ -/- *publish -|_ upd=update -++ grab - |% - ++ noun update - -- -++ grow - |% - ++ noun upd - ++ json - =, enjs:format - %+ frond -.upd - :: - ?- -.upd - %invite - %- pairs - :~ [%who (ship who.upd)] - [%add b+add.upd] - [%coll s+col.upd] - [%title s+title.upd] - == - :: - %unread - %- pairs - :~ [%add b+add.upd] - :+ %posts - %a - %+ turn ~(tap in keys.upd) - |= [who=@p coll=@tas post=@tas] - ^- ^json - %- pairs - :~ [%who (ship who)] - [%coll s+coll] - [%post s+post] - == - == - :: - == - :: - -- --- diff --git a/pkg/arvo/sur/publish.hoon b/pkg/arvo/sur/publish.hoon index 9e3ea2eb3f..24c8b3505e 100644 --- a/pkg/arvo/sur/publish.hoon +++ b/pkg/arvo/sur/publish.hoon @@ -21,6 +21,8 @@ :: [%subscribe who=@p book=@tas] [%unsubscribe who=@p book=@tas] + :: + [%read who=@p book=@tas note=@tas] == :: +$ comment @@ -77,5 +79,6 @@ :: +$ primary-delta $% notebook-delta + [%read who=@p book=@tas note=@tas] == -- diff --git a/pkg/interface/publish/src/js/reducers/primary.js b/pkg/interface/publish/src/js/reducers/primary.js index 23cdd01871..79640bac52 100644 --- a/pkg/interface/publish/src/js/reducers/primary.js +++ b/pkg/interface/publish/src/js/reducers/primary.js @@ -31,6 +31,9 @@ export class PrimaryReducer { case "del-comment": this.delComment(json["del-comment"], state); break; + case "read": + this.read(json["read"], state); + break; default: break; } @@ -210,4 +213,17 @@ export class PrimaryReducer { } } } + + read(json, state){ + let host = json.host; + let book = json.book; + let noteId = json.note + if (state.notebooks[host] && + state.notebooks[host][book] && + state.notebooks[host][book].notes && + state.notebooks[host][book].notes[noteId]) + { + state.notebooks[host][book].notes[noteId]["read"] = true; + } + } } From 366772c5599d66f6e238540c65738b51a4d8c0b2 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Thu, 9 Jan 2020 17:11:06 -0800 Subject: [PATCH 08/20] store, update, send tile notification number --- pkg/arvo/app/publish.hoon | 114 +++++++++++++++++++++++------ pkg/interface/publish/tile/tile.js | 28 +------ 2 files changed, 94 insertions(+), 48 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index c5fbdedb72..bf1bc9cf55 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -47,6 +47,7 @@ $: our-paths=(list path) books=(map @tas notebook) subs=(map [@p @tas] notebook) + tile-num=@ud == -- :: @@ -68,6 +69,7 @@ [%pass /tile %agent [our.bol %launch] %poke %launch-action !>(lac)] [%pass /read/paths %arvo %c %warp our.bol q.byk.bol `rav] [%pass /permissions %agent [our.bol %permission-store] %watch /updates] + (invite-poke:main [%create /publish]) :* %pass /invites %agent [our.bol %invite-store] %watch /invitatory/publish == @@ -115,7 +117,11 @@ :: [%primary ~] [~ this] :: - [%tile ~] !! + [%publishtile ~] + =/ jon=json + (frond:enjs:format %notifications (numb:enjs:format tile-num)) + :_ this + [%give %fact ~ %json !>(jon)]~ == :: ++ on-leave on-leave:def @@ -497,7 +503,7 @@ ++ handle-permission-update |= upd=permission-update ^- (quip card _state) - ?. ?=(?(%add %remove) -.upd) + ?. ?=(%remove -.upd) [~ state] =/ book=@tas %- need @@ -512,22 +518,47 @@ |= who=@p ?: (allowed who %read book) ~ - [%give %kick `/notebook/[book] `who]~ + [%give %kick [/notebook/[book]]~ `who]~ :: ++ handle-invite-update |= upd=invite-update ^- (quip card _state) - ?. ?=(%accepted -.upd) + ?+ -.upd [~ state] - =/ wir=wire (weld /subscribe/(scot %p ship.invite.upd) path.upd) - :_ state - :_ ~ - :* %pass - wir - %agent - [ship.invite.upd %publish] - %watch - (weld /notebook path.upd) + :: + %delete + =/ scry-pax + /(scot %p our.bol)/invite-store/(scot %da now.bol)/invitatory/publish/noun + =/ inv=(unit invitatory) .^((unit invitatory) %gx scry-pax) + ?~ inv + [~ state] + =. tile-num (sub tile-num ~(wyt by u.inv)) + =/ jon=json (frond:enjs:format %notifications (numb:enjs:format tile-num)) + :_ state + [%give %fact [/publishtile]~ %json !>(jon)]~ + :: + %invite + =. tile-num +(tile-num) + =/ jon=json (frond:enjs:format %notifications (numb:enjs:format tile-num)) + :_ state + [%give %fact [/publishtile]~ %json !>(jon)]~ + :: + %decline + =. tile-num (dec tile-num) + =/ jon=json (frond:enjs:format %notifications (numb:enjs:format tile-num)) + :_ state + [%give %fact [/publishtile]~ %json !>(jon)]~ + :: + %accepted + ?> ?=([%notebook @ ~] path.invite.upd) + =/ book i.t.path.invite.upd + =/ wir=wire /subscribe/(scot %p ship.invite.upd)/[book] + =. tile-num (dec tile-num) + =/ jon=json (frond:enjs:format %notifications (numb:enjs:format tile-num)) + :_ state + :~ [%pass wir %agent [ship.invite.upd %publish] %watch path.invite.upd] + [%give %fact [/publishtile]~ %json !>(jon)] + == == :: ++ watch-notebook @@ -624,6 +655,11 @@ !>(act) == :: +++ invite-poke + |= act=invite-action + ^- card + [%pass / %agent [our.bol %invite-store] %poke %invite-action !>(act)] +:: ++ perm-group-hook-poke |= act=permission-group-hook-action ^- card @@ -827,7 +863,7 @@ ?. (~(has by books) book.act) ~|("nonexistent notebook {}" !!) =/ pax=path /app/publish/notebooks/[book.act] - :_ state(books (~(del by books) book.act)) + :_ state [(delete-dir pax)]~ :: %del-note @@ -887,8 +923,8 @@ =/ wir=wire /subscribe/(scot %p who.act)/[book.act] =/ del=primary-delta [%del-book who.act book.act] :_ state(subs (~(del by subs) who.act book.act)) - :~ [%pass wir %agent [who.act %publish] %leave ~] - [%give %fact `/primary %publish-primary-delta !>(del)] + :~ `card`[%pass wir %agent [who.act %publish] %leave ~] + `card`[%give %fact [/primary]~ %publish-primary-delta !>(del)] == :: %read @@ -902,14 +938,20 @@ =/ not=(unit note) (~(get by notes.u.book) note.act) ?~ not ~|("nonexistent note: {}" !!) + =? tile-num !read.u.not + (dec tile-num) =. read.u.not %.y =. notes.u.book (~(put by notes.u.book) note.act u.not) =? books =(our.bol who.act) (~(put by books) book.act u.book) =? subs !=(our.bol who.act) (~(put by subs) [who.act book.act] u.book) + =/ jon=json + (frond:enjs:format %notifications (numb:enjs:format tile-num)) :_ state - [%give %fact `/primary %publish-primary-delta !>(act)]~ + :~ [%give %fact [/primary]~ %publish-primary-delta !>(act)] + [%give %fact [/publishtile]~ %json !>(jon)] + == == :: ++ get-notebook @@ -919,22 +961,36 @@ (~(get by books) book-name) (~(get by subs) host book-name) :: +++ get-unread + |= book=notebook + ^- @ud + %+ roll ~(tap by notes.book) + |= [[nom=@tas not=note] out=@ud] + ?: read.not + out + +(out) +:: ++ emit-updates-and-state |= [host=@p book-name=@tas book=notebook del=notebook-delta] ^- (quip card _state) ?: =(our.bol host) :_ state(books (~(put by books) book-name book)) - :~ [%give %fact `/notebook/[book-name] %publish-notebook-delta !>(del)] - [%give %fact `/primary %publish-primary-delta !>(del)] + :~ [%give %fact [/notebook/[book-name]]~ %publish-notebook-delta !>(del)] + [%give %fact [/primary]~ %publish-primary-delta !>(del)] == + =/ jon=json + (frond:enjs:format %notifications (numb:enjs:format tile-num)) :_ state(subs (~(put by subs) [host book-name] book)) - [%give %fact `/primary %publish-primary-delta !>(del)]~ + :~ [%give %fact [/primary]~ %publish-primary-delta !>(del)] + [%give %fact [/publishtile]~ %json !>(jon)] + == :: ++ handle-notebook-delta |= del=notebook-delta ^- (quip card _state) ?- -.del %add-book + =. tile-num (add tile-num (get-unread data.del)) (emit-updates-and-state host.del book.del data.del del) :: %add-note @@ -943,6 +999,8 @@ ?~ book [~ state] =. read.data.del =(our.bol author.data.del) + =? tile-num !read.data.del + +(tile-num) =. notes.u.book (~(put by notes.u.book) note.del data.del) (emit-updates-and-state host.del book.del u.book del) :: @@ -1001,19 +1059,29 @@ (emit-updates-and-state host.del book.del u.book del) :: %del-book + =. tile-num + %+ sub tile-num + (get-unread (~(got by books) book.del)) ?: =(our.bol host.del) :_ state(books (~(del by books) book.del)) - :~ [%give %fact `/notebook/[book.del] %publish-notebook-delta !>(del)] - [%give %fact `/primary %publish-primary-delta !>(del)] + :~ [%give %fact [/notebook/[book.del]]~ %publish-notebook-delta !>(del)] + [%give %fact [/primary]~ %publish-primary-delta !>(del)] == + =/ jon=json + (frond:enjs:format %notifications (numb:enjs:format tile-num)) :_ state(subs (~(del by subs) host.del book.del)) - [%give %fact `/primary %publish-primary-delta !>(del)]~ + :~ [%give %fact [/primary]~ %publish-primary-delta !>(del)] + [%give %fact [/publishtile]~ %json !>(jon)] + == :: %del-note =/ book=(unit notebook) (get-notebook host.del book.del) ?~ book [~ state] + =/ not=note (~(got by notes.u.book) note.del) + =? tile-num !read.not + (dec tile-num) =. notes.u.book (~(del by notes.u.book) note.del) (emit-updates-and-state host.del book.del u.book del) :: diff --git a/pkg/interface/publish/tile/tile.js b/pkg/interface/publish/tile/tile.js index 94ffbf019f..eb12eaa9be 100644 --- a/pkg/interface/publish/tile/tile.js +++ b/pkg/interface/publish/tile/tile.js @@ -5,33 +5,11 @@ import classnames from 'classnames'; export default class PublishTile extends Component { constructor(props){ super(props); + console.log("publish-tile", this.props); } - render(){ - let info = []; - if (this.props.data.invites > 0) { - let text = (this.props.data.invites == 1) - ? "Invite" - : "Invites" - info.push( -

- {this.props.data.invites} - {text} -

- ); - } - if (this.props.data.new > 0) { - let text = (this.props.data.new == 1) - ? "New Post" - : "New Posts" - info.push( -

- {this.props.data.new} - {text} -

- ); - } + render(){ return ( From 9a8f1bec90380fa225abf8b4b601cd8b706b0bca Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Tue, 21 Jan 2020 10:48:22 -0800 Subject: [PATCH 09/20] made publish marks backward compatible --- pkg/arvo/mar/publish/comment.hoon | 60 ++++++++++++------------ pkg/arvo/mar/publish/info.hoon | 76 ++++++++++++++++--------------- 2 files changed, 72 insertions(+), 64 deletions(-) diff --git a/pkg/arvo/mar/publish/comment.hoon b/pkg/arvo/mar/publish/comment.hoon index b67bab1e42..c2a40cae5e 100644 --- a/pkg/arvo/mar/publish/comment.hoon +++ b/pkg/arvo/mar/publish/comment.hoon @@ -1,5 +1,5 @@ -/- publish -|_ com=comment:publish +/- *publish +|_ com=comment :: :: ++ grow @@ -19,32 +19,36 @@ |% ++ mime |= [mite:eyre p=octs:eyre] - (txt (to-wain:format q.p)) - ++ txt - |= txs=(pole @t) - ^- comment:publish - :: TODO: putting ~ instead of * breaks this but shouldn't - :: - ?> ?= $: author=@t - date-created=@t - line=@t - body=* - == - txs - ?> =(line.txs '-----') - :: - :* %+ rash author.txs - ;~(pfix (jest 'author: ~') fed:ag) - :: - %+ rash date-created.txs - ;~ pfix - (jest 'date-created: ~') - (cook year when:so) - == - :: - (of-wain:format (wain body.txs)) - == - ++ noun comment:publish + |^ (rash q.p both-parser) + ++ key-val + |* [key=rule val=rule] + ;~(sfix ;~(pfix key val) gaq) + ++ old-parser + ;~ plug + (key-val (jest 'creator: ~') fed:ag) + (key-val (jest 'collection: ') sym) + (key-val (jest 'post: ') sym) + (key-val (jest 'date-created: ~') (cook year when:so)) + (key-val (jest 'last-modified: ~') (cook year when:so)) + ;~(pfix (jest (cat 3 '-----' 10)) (cook crip (star next))) + == + ++ new-parser + ;~ plug + (key-val (jest 'author: ~') fed:ag) + (key-val (jest 'date-created: ~') (cook year when:so)) + ;~(pfix (jest (cat 3 '-----' 10)) (cook crip (star next))) + == + ++ both-parser + ;~ pose + new-parser + %+ cook + |= [author=@ @ @ date-created=@da @ content=@t] + ^- comment + [author date-created content] + old-parser + == + -- + ++ noun comment -- ++ grad %mime -- diff --git a/pkg/arvo/mar/publish/info.hoon b/pkg/arvo/mar/publish/info.hoon index e221092605..731e6e568e 100644 --- a/pkg/arvo/mar/publish/info.hoon +++ b/pkg/arvo/mar/publish/info.hoon @@ -24,43 +24,47 @@ |% ++ mime |= [mite:eyre p=octs:eyre] - (txt (to-wain:format q.p)) - ++ txt - |= txs=(pole @t) - ^- notebook-info - :: TODO: putting ~ instead of * breaks this but shouldn't - :: - ?> ?= $: title=@t - description=@t - comments=@t - writers=@t - subscribers=@t - * - == - txs - :: - :* %+ rash title.txs - ;~(pfix (jest 'title: ') (cook crip (star next))) - :: - %+ rash description.txs - ;~(pfix (jest 'description: ') (cook crip (star next))) - :: - %+ rash comments.txs - ;~ pfix - (jest 'comments: ') - %+ cook - |= val=@t - ^- ? - =(val %on) - ;~(pose (jest %on) (jest %off)) + |^ (rash q.p both-parser) + ++ key-val + |* [key=rule val=rule] + ;~(sfix ;~(pfix key val) gaq) + ++ old-parser + ;~ plug + (key-val (jest 'owner: ~') fed:ag) + (key-val (jest 'title: ') (cook crip (star qit))) + (key-val (jest 'filename: ') sym) + %+ key-val (jest 'comments: ') + ;~(pose (jest %open) (jest %closed) (jest %none)) + %+ key-val (jest 'allow-edit: ') + ;~(pose (jest %post) (jest %comment) (jest %all) (jest %none)) + (key-val (jest 'date-created: ~') (cook year when:so)) + ;~ pose + (key-val (jest 'last-modified: ~') (cook year when:so)) + ;~(pfix (jest 'last-modified: ~') (cook year when:so)) == - :: - %+ rash writers.txs - ;~(pfix (jest 'writers: ') ;~(pfix net (more net urs:ab))) - :: - %+ rash subscribers.txs - ;~(pfix (jest 'subscribers: ') ;~(pfix net (more net urs:ab))) - == + == + ++ new-parser + ;~ plug + (key-val (jest 'title: ') (cook crip (star qit))) + (key-val (jest 'description: ') (cook crip (star qit))) + %+ key-val (jest 'comments: ') + (cook |=(a=@ =(%on a)) ;~(pose (jest %on) (jest %off))) + (key-val (jest 'writers: ') ;~(pfix net (more net urs:ab))) + ;~ pose + (key-val (jest 'subscribers: ') ;~(pfix net (more net urs:ab))) + ;~(pfix (jest 'subscribers: ') ;~(pfix net (more net urs:ab))) + == + == + ++ both-parser + ;~ pose + new-parser + %+ cook + |= [@ title=@t @ comments=@ *] + ^- notebook-info + [title '' =('open' comments) / /] + old-parser + == + -- ++ noun notebook-info -- ++ grad %mime From 1fde0913cb8faa914dacbe70d93cd653520fd111 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Tue, 21 Jan 2020 10:48:52 -0800 Subject: [PATCH 10/20] wrote on-load arm for state transitions &c --- pkg/arvo/app/publish.hoon | 150 ++++++++++++++++++++++++++++++++++++-- 1 file changed, 145 insertions(+), 5 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index bf1bc9cf55..3e4487090a 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -39,8 +39,11 @@ |% +$ card card:agent:gall :: -+$ versioned-state - $% [%1 state-one] ++$ collection-zero [* pos=(map @tas *) *] +:: ++$ state-zero + $: pubs=(map @tas collection-zero) + * == :: +$ state-one @@ -49,9 +52,14 @@ subs=(map [@p @tas] notebook) tile-num=@ud == +:: ++$ versioned-state + $% [%1 state-one] + == +:: -- :: -=| state-one +=| versioned-state =* state - ^- agent:gall =< @@ -80,8 +88,140 @@ ++ on-load |= old=vase ^- (quip card _this) - [~ this(state !<(,[%1 state-one] old))] -:: [~ this(state *state-one)] + =/ old-state=(each versioned-state tang) + (mule |.(!<(versioned-state old))) + ?: ?=(%& -.old-state) + [~ this(state p.old-state)] + =/ zero !<(state-zero old) + :: unsubscribe from all foreign notebooks + :: kill all ford builds + :: flush all state + :: detect files in /web/publish + :: move to /app/publish/notebooks + :: for each notebook + :: kick all subscribers + :: make a group for it + :: send invites to all previously subscribed ships + :: + |^ + =/ rav [%sing %t [%da now.bol] /app/publish/notebooks] + =/ tile-json + (frond:enjs:format %notifications (numb:enjs:format 0)) + =/ init-cards=(list card) + :~ [%pass /read/paths %arvo %c %warp our.bol q.byk.bol `rav] + :* %pass /permissions %agent [our.bol %permission-store] %watch + /updates + == + (invite-poke:main [%create /publish]) + :* %pass /invites %agent [our.bol %invite-store] %watch + /invitatory/publish + == + [%give %fact [/publishtile]~ %json !>(tile-json)] + == + =+ ^- [kick-cards=(list card) old-subs=(jug @tas @p)] kick-subs + :_ this(state [%1 *state-one]) + ;: weld + leave-subs + kick-cards + kill-builds + init-cards + (move-files old-subs) + == + :: + ++ leave-subs + ^- (list card) + %+ turn ~(tap by wex.bol) + |= [[wir=wire who=@p @] ? path] + ^- card + [%pass wir %agent [who %publish] %leave ~] + :: + ++ kick-subs + ^- [(list card) (jug @tas @p)] + =+ ^- [paths=(list path) subs=(jug @tas @p)] + %+ roll ~(tap by sup.bol) + |= [[duct [who=@p pax=path]] paths=(list path) subs=(jug @tas @p)] + ^- [(list path) (jug @tas @p)] + ?. ?=([%collection @ ~] pax) + [paths subs] + =/ book-name i.t.pax + :- [pax paths] + (~(put ju subs) book-name who) + [[%give %kick paths ~]~ subs] + :: + ++ kill-builds + ^- (list card) + %- zing + %+ turn ~(tap by pubs.zero) + |= [col-name=@tas col-data=collection-zero] + ^- (list card) + :- [%pass /collection/[col-name] %arvo %f %kill ~] + %- zing + %+ turn ~(tap by pos.col-data) + |= [pos-name=@tas *] + :~ [%pass /post/[col-name]/[pos-name] %arvo %f %kill ~] + [%pass /comments/[col-name]/[pos-name] %arvo %f %kill ~] + == + :: + ++ send-invites + |= [book=@tas subscribers=(set @p)] + ^- (list card) + %+ turn ~(tap in subscribers) + |= who=@p + ^- card + =/ uid (sham %publish who book eny.bol) + =/ inv=invite + :* our.bol %publish /notebook/[book] who + 'invite for notebook {}/{}' + == + =/ act=invite-action [%invite /publish uid inv] + [%pass /invite %agent [who %invite-hook] %poke %invite-action !>(act)] + :: + ++ move-files + |= old-subs=(jug @tas @p) + ^- (list card) + =+ ^- [cards=(list card) sob=soba:clay] + %+ roll .^((list path) %ct (weld our-beak /web/publish)) + |= [pax=path car=(list card) sob=soba:clay] + ^- [(list card) soba:clay] + ?+ pax + [car sob] + :: + [%web %publish @ %publish-info ~] + =/ book-name i.t.t.pax + =/ book=notebook-info .^(notebook-info %cx (welp our-beak pax)) + =+ ^- [grp-car=(list card) writers-path=path subscribers-path=path] + (make-groups book-name [%new ~ ~ %journal]) + =. writers.book writers-path + =. subscribers.book subscribers-path + =/ inv-car (send-invites book-name (~(get ju old-subs) book-name)) + :- :(weld car grp-car inv-car) + ^- soba:clay + :+ [pax %del ~] + :- /app/publish/notebooks/[book-name]/publish-info + [%ins %publish-info !>(book)] + sob + :: + [%web %publish @ @ %udon ~] + =/ book i.t.t.pax + =/ note i.t.t.t.pax + :- car + :+ [pax %del ~] + :- /app/publish/notebooks/[book]/[note]/udon + [%ins %udon !>(.^(@t %cx (welp our-beak pax)))] + sob + :: + [%web %publish @ @ @ %publish-comment ~] + =/ book i.t.t.pax + =/ note i.t.t.t.pax + =/ comm i.t.t.t.t.pax + :- car + :+ [pax %del ~] + :- /app/publish/notebooks/[book]/[note]/[comm]/publish-comment + [%ins %publish-comment !>(.^(comment %cx (welp our-beak pax)))] + sob + == + [[%pass /move-files %arvo %c %info q.byk.bol %& sob] cards] + -- :: ++ on-poke |= [mar=mark vas=vase] From e9452bfa721380e9604a3035a7a85a839ff50ae8 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Wed, 22 Jan 2020 12:47:00 -0800 Subject: [PATCH 11/20] don't send null kick if subscribers list is empty scry old files into the correct structure --- pkg/arvo/app/publish.hoon | 16 +++++++++++----- pkg/arvo/sur/publish.hoon | 19 +++++++++++++++++++ 2 files changed, 30 insertions(+), 5 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index 3e4487090a..32eb4b4417 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -121,9 +121,9 @@ =+ ^- [kick-cards=(list card) old-subs=(jug @tas @p)] kick-subs :_ this(state [%1 *state-one]) ;: weld + kill-builds leave-subs kick-cards - kill-builds init-cards (move-files old-subs) == @@ -146,6 +146,8 @@ =/ book-name i.t.pax :- [pax paths] (~(put ju subs) book-name who) + ?~ paths + [~ subs] [[%give %kick paths ~]~ subs] :: ++ kill-builds @@ -180,7 +182,7 @@ |= old-subs=(jug @tas @p) ^- (list card) =+ ^- [cards=(list card) sob=soba:clay] - %+ roll .^((list path) %ct (weld our-beak /web/publish)) + %+ roll .^((list path) %ct (weld our-beak:main /web/publish)) |= [pax=path car=(list card) sob=soba:clay] ^- [(list card) soba:clay] ?+ pax @@ -188,7 +190,8 @@ :: [%web %publish @ %publish-info ~] =/ book-name i.t.t.pax - =/ book=notebook-info .^(notebook-info %cx (welp our-beak pax)) + =/ old=old-info .^(old-info %cx (welp our-beak:main pax)) + =/ book=notebook-info [title.old '' =(%open comments.old) / /] =+ ^- [grp-car=(list card) writers-path=path subscribers-path=path] (make-groups book-name [%new ~ ~ %journal]) =. writers.book writers-path @@ -207,17 +210,20 @@ :- car :+ [pax %del ~] :- /app/publish/notebooks/[book]/[note]/udon - [%ins %udon !>(.^(@t %cx (welp our-beak pax)))] + [%ins %udon !>(.^(@t %cx (welp our-beak:main pax)))] sob :: [%web %publish @ @ @ %publish-comment ~] =/ book i.t.t.pax =/ note i.t.t.t.pax =/ comm i.t.t.t.t.pax + =/ old=old-comment .^(old-comment %cx (welp our-beak:main pax)) + =/ new=comment [creator.old date-created.old content.old] :- car + :+ [pax %del ~] :- /app/publish/notebooks/[book]/[note]/[comm]/publish-comment - [%ins %publish-comment !>(.^(comment %cx (welp our-beak pax)))] + [%ins %publish-comment !>(new)] sob == [[%pass /move-files %arvo %c %info q.byk.bol %& sob] cards] diff --git a/pkg/arvo/sur/publish.hoon b/pkg/arvo/sur/publish.hoon index 24c8b3505e..ec46afc245 100644 --- a/pkg/arvo/sur/publish.hoon +++ b/pkg/arvo/sur/publish.hoon @@ -63,6 +63,25 @@ subscribers=path == :: ++$ old-info + $: owner=@p + title=@t + filename=@tas + comments=?(%open %closed %none) + allow-edit=?(%post %comment %all %none) + date-created=@da + last-modified=@da + == ++$ old-comment + $: $: creator=@p + collection=@tas + post=@tas + date-created=@da + last-modified=@da + == + content=@t + == +:: +$ notebook-delta $% [%add-book host=@p book=@tas data=notebook] [%add-note host=@p book=@tas note=@tas data=note] From f49e97a5c3fe9e19f528ffb407c458ccb2439ece Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Thu, 23 Jan 2020 10:52:09 -0800 Subject: [PATCH 12/20] fix publish-action mark --- pkg/arvo/mar/publish/action.hoon | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/pkg/arvo/mar/publish/action.hoon b/pkg/arvo/mar/publish/action.hoon index c771c903f1..c23d8e8b80 100644 --- a/pkg/arvo/mar/publish/action.hoon +++ b/pkg/arvo/mar/publish/action.hoon @@ -18,7 +18,8 @@ |= jon=^json =, dejs:format ;; action - |^ %- of + |^ %. jon + %- of :~ new-book+new-book new-note+new-note new-comment+new-comment From 3c4933690fbe50ff4f62f6f4e0c94e07c33fe083 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Fri, 24 Jan 2020 10:58:18 -0800 Subject: [PATCH 13/20] added new url routes added subscriber data to notebooks --- pkg/arvo/app/publish.hoon | 155 ++++++++++++++++++++++++++------------ pkg/arvo/lib/publish.hoon | 4 +- 2 files changed, 109 insertions(+), 50 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index 32eb4b4417..036bcfa76d 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -234,7 +234,12 @@ ^- (quip card _this) ?+ mar (on-poke:def mar vas) %noun - ~& state + ?: =(%print-state q.vas) + ~& state + [~ this] + ?: =(%print-bowl q.vas) + ~& bol + [~ this] [~ this] :: %handle-http-request @@ -1244,6 +1249,68 @@ (emit-updates-and-state host.del book.del u.book del) == :: +++ get-subscribers-json + |= book=@tas + ^- json + :- %a + %+ roll ~(val by sup.bol) + |= [[who=@p pax=path] out=(list json)] + ^- (list json) + ?. ?=([%notebook @ ~] pax) out + ?. =(book i.t.pax) out + [[%s (scot %p who)] out] +:: +++ get-notebook-json + |= [host=@p book-name=@tas] + ^- (unit json) + =, enjs:format + =/ book=(unit notebook) + ?: =(our.bol host) + (~(get by books) book-name) + (~(get by subs) host book-name) + ?~ book + ~ + =/ notebook-json (notebook-full-json host book-name u.book) + ?> ?=(%o -.notebook-json) + =. p.notebook-json + (~(uni by p.notebook-json) (notes-page notes.u.book 0 50)) + =. p.notebook-json + (~(put by p.notebook-json) %subscribers (get-subscribers-json book-name)) + =/ notebooks-json (notebooks-map-json our.bol books subs) + ?> ?=(%o -.notebooks-json) + =/ host-books-json (~(got by p.notebooks-json) (scot %p host)) + ?> ?=(%o -.host-books-json) + =. p.host-books-json (~(put by p.host-books-json) book-name notebook-json) + =. p.notebooks-json + (~(put by p.notebooks-json) (scot %p host) host-books-json) + `(pairs notebooks+notebooks-json ~) +:: +++ get-note-json + |= [host=@p book-name=@tas note-name=@tas] + ^- (unit json) + =, enjs:format + =/ book=(unit notebook) + ?: =(our.bol host) + (~(get by books) book-name) + (~(get by subs) host book-name) + ?~ book + ~ + =/ note=(unit note) (~(get by notes.u.book) note-name) + ?~ note + ~ + =/ notebook-json (notebook-full-json host book-name u.book) + ?> ?=(%o -.notebook-json) + =/ note-json (note-presentation-json u.book note-name u.note) + =. p.notebook-json (~(uni by p.notebook-json) note-json) + =/ notebooks-json (notebooks-map-json our.bol books subs) + ?> ?=(%o -.notebooks-json) + =/ host-books-json (~(got by p.notebooks-json) (scot %p host)) + ?> ?=(%o -.host-books-json) + =. p.host-books-json (~(put by p.host-books-json) book-name notebook-json) + =. p.notebooks-json + (~(put by p.notebooks-json) (scot %p host) host-books-json) + `(pairs notebooks+notebooks-json ~) +:: ++ handle-http-request |= req=inbound-request:eyre ^- simple-payload:http @@ -1341,6 +1408,8 @@ ?> ?=(%o -.notebook-json) =. p.notebook-json (~(uni by p.notebook-json) (notes-page notes.u.book 0 50)) + =. p.notebook-json + (~(put by p.notebook-json) %subscribers (get-subscribers-json book-name)) =/ jon=json (pairs notebook+notebook-json ~) (json-response:gen (json-to-octs jon)) :: @@ -1367,68 +1436,56 @@ :: presentation endpoints :: :: all notebooks, short form, wrapped in html - [[~ [%'~publish' ~]] ~] + [[~ [%'~publish' ?(~ [%join ~] [%new ~])]] ~] =, enjs:format =/ jon=json (pairs notebooks+(notebooks-map-json our.bol books subs) ~) (manx-response:gen (index jon)) :: :: single notebook, with initial 50 notes in short form, wrapped in html - [[~ [%'~publish' @ @ ~]] ~] - =, enjs:format - =/ host=(unit @p) (slaw %p i.t.site.url) + [[~ [%'~publish' %notebook @ @ *]] ~] + =/ host=(unit @p) (slaw %p i.t.t.site.url) ?~ host not-found:gen - =/ book-name i.t.t.site.url - =/ book=(unit notebook) - ?: =(our.bol u.host) - (~(get by books) book-name) - (~(get by subs) u.host book-name) - ?~ book + =/ book-name i.t.t.t.site.url + =/ book-json=(unit json) (get-notebook-json u.host book-name) + ?~ book-json not-found:gen - =/ notebook-json (notebook-full-json u.host book-name u.book) - ?> ?=(%o -.notebook-json) - =. p.notebook-json - (~(uni by p.notebook-json) (notes-page notes.u.book 0 50)) - =/ notebooks-json (notebooks-map-json our.bol books subs) - ?> ?=(%o -.notebooks-json) - =/ host-books-json (~(got by p.notebooks-json) (scot %p u.host)) - ?> ?=(%o -.host-books-json) - =. p.host-books-json (~(put by p.host-books-json) book-name notebook-json) - =. p.notebooks-json - (~(put by p.notebooks-json) (scot %p u.host) host-books-json) - =/ jon=json (pairs notebooks+notebooks-json ~) - (manx-response:gen (index jon)) + (manx-response:gen (index u.book-json)) + :: + :: single notebook, with initial 50 notes in short form, wrapped in html + [[~ [%'~publish' %popout %notebook @ @ *]] ~] + =/ host=(unit @p) (slaw %p i.t.t.t.site.url) + ?~ host + not-found:gen + =/ book-name i.t.t.t.t.site.url + =/ book-json=(unit json) (get-notebook-json u.host book-name) + ?~ book-json + not-found:gen + (manx-response:gen (index u.book-json)) :: :: single note, with initial 50 comments, wrapped in html - [[~ [%'~publish' @ @ @ ~]] ~] - =, enjs:format - =/ host=(unit @p) (slaw %p i.t.site.url) + [[~ [%'~publish' %note @ @ @ ~]] ~] + =/ host=(unit @p) (slaw %p i.t.t.site.url) ?~ host not-found:gen - =/ book-name i.t.t.site.url - =/ book=(unit notebook) - ?: =(our.bol u.host) - (~(get by books) book-name) - (~(get by subs) u.host book-name) - ?~ book + =/ book-name i.t.t.t.site.url + =/ note-name i.t.t.t.t.site.url + =/ note-json=(unit json) (get-note-json u.host book-name note-name) + ?~ note-json not-found:gen - =/ note-name i.t.t.t.site.url - =/ note=(unit note) (~(get by notes.u.book) note-name) - ?~ note + (manx-response:gen (index u.note-json)) + :: + :: single note, with initial 50 comments, wrapped in html + [[~ [%'~publish' %popout %note @ @ @ ~]] ~] + =/ host=(unit @p) (slaw %p i.t.t.t.site.url) + ?~ host not-found:gen - =/ notebook-json (notebook-full-json u.host book-name u.book) - ?> ?=(%o -.notebook-json) - =/ note-json (note-presentation-json u.book note-name u.note) - =. p.notebook-json (~(uni by p.notebook-json) note-json) - =/ notebooks-json (notebooks-map-json our.bol books subs) - ?> ?=(%o -.notebooks-json) - =/ host-books-json (~(got by p.notebooks-json) (scot %p u.host)) - ?> ?=(%o -.host-books-json) - =. p.host-books-json (~(put by p.host-books-json) book-name notebook-json) - =. p.notebooks-json - (~(put by p.notebooks-json) (scot %p u.host) host-books-json) - =/ jon=json (pairs notebooks+notebooks-json ~) - (manx-response:gen (index jon)) + =/ book-name i.t.t.t.t.site.url + =/ note-name i.t.t.t.t.t.site.url + =/ note-json=(unit json) (get-note-json u.host book-name note-name) + ?~ note-json + not-found:gen + (manx-response:gen (index u.note-json)) == :: -- diff --git a/pkg/arvo/lib/publish.hoon b/pkg/arvo/lib/publish.hoon index cc8add231b..6bb3cc60db 100644 --- a/pkg/arvo/lib/publish.hoon +++ b/pkg/arvo/lib/publish.hoon @@ -117,7 +117,9 @@ num-notes+(numb ~(wyt by notes.book)) num-unread+(numb (count-unread notes.book)) notes-by-date+(notes-by-date notes.book) - :: XX settings stuff, subscribers + comments+b+comments.book + writers-group-path+s+(spat writers.book) + subscribers-group-path+s+(spat subscribers.book) == :: ++ note-presentation-json From 7c057099d510dc94ab1ec82fc42ea22d5c325f91 Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Fri, 24 Jan 2020 13:42:47 -0800 Subject: [PATCH 14/20] thread state through properly in the case of importing many files --- pkg/arvo/app/publish.hoon | 96 +++++++++++++++++++-------------------- 1 file changed, 48 insertions(+), 48 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index 036bcfa76d..c7d0917894 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -295,7 +295,7 @@ =/ book-name i.t.t.wir ?> ?=(%publish-notebook-delta p.cage.sin) =^ cards state - (handle-notebook-delta:main !<(notebook-delta q.cage.sin)) + (handle-notebook-delta:main !<(notebook-delta q.cage.sin) state) [cards this] :: [%permissions ~] @@ -392,7 +392,7 @@ =/ delta=notebook-delta [%edit-book our.bol book-name new-book] =^ cards state - (handle-notebook-delta delta) + (handle-notebook-delta delta state) :_ state :* [%pass (welp /read/info pax) %arvo %c %warp our.bol rif] cards @@ -418,7 +418,7 @@ =/ delta=notebook-delta [%edit-note our.bol book-name note-name new-note] =^ cards state - (handle-notebook-delta delta) + (handle-notebook-delta delta state) :_ state :* [%pass (welp /read/note pax) %arvo %c %warp our.bol rif] cards @@ -440,7 +440,7 @@ =/ delta=notebook-delta [%edit-comment our.bol book-name note-name u.comment-date new-comment] =^ cards state - (handle-notebook-delta delta) + (handle-notebook-delta delta state) :_ state :* [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif] cards @@ -476,7 +476,7 @@ [%app %publish %notebooks @ %publish-info ~] =/ book-name i.t.t.t.pax =/ delta=notebook-delta [%del-book our.bol book-name] - (handle-notebook-delta delta) + (handle-notebook-delta delta sty) :: [%app %publish %notebooks @ @ %udon ~] =/ book-name i.t.t.t.pax @@ -486,7 +486,7 @@ [~ sty] =. notes.u.book (~(del by notes.u.book) note-name) =/ delta=notebook-delta [%del-note our.bol book-name note-name] - (handle-notebook-delta delta) + (handle-notebook-delta delta sty) :: [%app %publish %notebooks @ @ @ %publish-comment ~] =/ book-name i.t.t.t.pax @@ -496,7 +496,7 @@ [~ sty] =/ delta=notebook-delta [%del-comment our.bol book-name note-name u.comment-date] - (handle-notebook-delta delta) + (handle-notebook-delta delta sty) == :: ++ add-paths @@ -524,7 +524,7 @@ =/ delta=notebook-delta [%add-book our.bol book-name new-book] :: =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] - =^ update-cards sty (handle-notebook-delta delta) + =^ update-cards sty (handle-notebook-delta delta sty) :_ sty ;: weld [%pass (welp /read/info pax) %arvo %c %warp our.bol rif]~ @@ -542,7 +542,7 @@ =/ rif=riff:clay [q.byk.bol `[%next %x [%da now.bol] pax]] =/ delta=notebook-delta [%add-note our.bol book-name note-name new-note] - =^ update-cards sty (handle-notebook-delta delta) + =^ update-cards sty (handle-notebook-delta delta sty) :_ sty ;: weld [%pass (welp /read/note pax) %arvo %c %warp our.bol rif]~ @@ -561,7 +561,7 @@ :: =/ delta=notebook-delta [%add-comment our.bol book-name note-name u.comment-name new-com] - =^ update-cards sty (handle-notebook-delta delta) + =^ update-cards sty (handle-notebook-delta delta sty) :_ sty ;: weld [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif]~ @@ -1106,11 +1106,11 @@ == :: ++ get-notebook - |= [host=@p book-name=@tas] + |= [host=@p book-name=@tas sty=_state] ^- (unit notebook) ?: =(our.bol host) - (~(get by books) book-name) - (~(get by subs) host book-name) + (~(get by books.sty) book-name) + (~(get by subs.sty) host book-name) :: ++ get-unread |= book=notebook @@ -1122,72 +1122,72 @@ +(out) :: ++ emit-updates-and-state - |= [host=@p book-name=@tas book=notebook del=notebook-delta] + |= [host=@p book-name=@tas book=notebook del=notebook-delta sty=_state] ^- (quip card _state) ?: =(our.bol host) - :_ state(books (~(put by books) book-name book)) + :_ sty(books (~(put by books.sty) book-name book)) :~ [%give %fact [/notebook/[book-name]]~ %publish-notebook-delta !>(del)] [%give %fact [/primary]~ %publish-primary-delta !>(del)] == =/ jon=json (frond:enjs:format %notifications (numb:enjs:format tile-num)) - :_ state(subs (~(put by subs) [host book-name] book)) + :_ sty(subs (~(put by subs.sty) [host book-name] book)) :~ [%give %fact [/primary]~ %publish-primary-delta !>(del)] [%give %fact [/publishtile]~ %json !>(jon)] == :: ++ handle-notebook-delta - |= del=notebook-delta + |= [del=notebook-delta sty=_state] ^- (quip card _state) ?- -.del %add-book =. tile-num (add tile-num (get-unread data.del)) - (emit-updates-and-state host.del book.del data.del del) + (emit-updates-and-state host.del book.del data.del del sty) :: %add-note =/ book=(unit notebook) - (get-notebook host.del book.del) + (get-notebook host.del book.del sty) ?~ book - [~ state] + [~ sty] =. read.data.del =(our.bol author.data.del) - =? tile-num !read.data.del - +(tile-num) + =? tile-num.sty !read.data.del + +(tile-num.sty) =. notes.u.book (~(put by notes.u.book) note.del data.del) - (emit-updates-and-state host.del book.del u.book del) + (emit-updates-and-state host.del book.del u.book del sty) :: %add-comment =/ book=(unit notebook) - (get-notebook host.del book.del) + (get-notebook host.del book.del sty) ?~ book - [~ state] + [~ sty] =/ note (~(get by notes.u.book) note.del) ?~ note - [~ state] + [~ sty] =. comments.u.note (~(put by comments.u.note) comment-date.del data.del) =. notes.u.book (~(put by notes.u.book) note.del u.note) - (emit-updates-and-state host.del book.del u.book del) + (emit-updates-and-state host.del book.del u.book del sty) :: %edit-book =/ old-book=(unit notebook) - (get-notebook host.del book.del) + (get-notebook host.del book.del sty) ?~ old-book - [~ state] + [~ sty] =/ new-book=notebook %= data.del date-created date-created.u.old-book notes notes.u.old-book order order.u.old-book == - (emit-updates-and-state host.del book.del new-book del) + (emit-updates-and-state host.del book.del new-book del sty) :: %edit-note =/ book=(unit notebook) - (get-notebook host.del book.del) + (get-notebook host.del book.del sty) ?~ book - [~ state] + [~ sty] =/ old-note (~(get by notes.u.book) note.del) ?~ old-note - [~ state] + [~ sty] =/ new-note=note %= data.del date-created date-created.u.old-note @@ -1195,58 +1195,58 @@ read read.u.old-note == =. notes.u.book (~(put by notes.u.book) note.del new-note) - (emit-updates-and-state host.del book.del u.book del) + (emit-updates-and-state host.del book.del u.book del sty) :: %edit-comment =/ book=(unit notebook) - (get-notebook host.del book.del) + (get-notebook host.del book.del sty) ?~ book - [~ state] + [~ sty] =/ note (~(get by notes.u.book) note.del) ?~ note - [~ state] + [~ sty] =. comments.u.note (~(put by comments.u.note) comment-date.del data.del) =. notes.u.book (~(put by notes.u.book) note.del u.note) - (emit-updates-and-state host.del book.del u.book del) + (emit-updates-and-state host.del book.del u.book del sty) :: %del-book =. tile-num %+ sub tile-num (get-unread (~(got by books) book.del)) ?: =(our.bol host.del) - :_ state(books (~(del by books) book.del)) + :_ sty(books (~(del by books.sty) book.del)) :~ [%give %fact [/notebook/[book.del]]~ %publish-notebook-delta !>(del)] [%give %fact [/primary]~ %publish-primary-delta !>(del)] == =/ jon=json - (frond:enjs:format %notifications (numb:enjs:format tile-num)) - :_ state(subs (~(del by subs) host.del book.del)) + (frond:enjs:format %notifications (numb:enjs:format tile-num.sty)) + :_ sty(subs (~(del by subs.sty) host.del book.del)) :~ [%give %fact [/primary]~ %publish-primary-delta !>(del)] [%give %fact [/publishtile]~ %json !>(jon)] == :: %del-note =/ book=(unit notebook) - (get-notebook host.del book.del) + (get-notebook host.del book.del sty) ?~ book - [~ state] + [~ sty] =/ not=note (~(got by notes.u.book) note.del) =? tile-num !read.not (dec tile-num) =. notes.u.book (~(del by notes.u.book) note.del) - (emit-updates-and-state host.del book.del u.book del) + (emit-updates-and-state host.del book.del u.book del sty) :: %del-comment =/ book=(unit notebook) - (get-notebook host.del book.del) + (get-notebook host.del book.del sty) ?~ book - [~ state] + [~ sty] =/ note (~(get by notes.u.book) note.del) ?~ note - [~ state] + [~ sty] =. comments.u.note (~(del by comments.u.note) comment.del) =. notes.u.book (~(put by notes.u.book) note.del u.note) - (emit-updates-and-state host.del book.del u.book del) + (emit-updates-and-state host.del book.del u.book del sty) == :: ++ get-subscribers-json From b4e99b7f046939ae8af73bbddb8bb61b382743cb Mon Sep 17 00:00:00 2001 From: Isaac Visintainer Date: Mon, 27 Jan 2020 09:23:20 -0800 Subject: [PATCH 15/20] fix group creation in the case of notebook import --- pkg/arvo/app/publish.hoon | 17 ++++++++++++++--- 1 file changed, 14 insertions(+), 3 deletions(-) diff --git a/pkg/arvo/app/publish.hoon b/pkg/arvo/app/publish.hoon index c7d0917894..70b3892b3d 100644 --- a/pkg/arvo/app/publish.hoon +++ b/pkg/arvo/app/publish.hoon @@ -476,7 +476,8 @@ [%app %publish %notebooks @ %publish-info ~] =/ book-name i.t.t.t.pax =/ delta=notebook-delta [%del-book our.bol book-name] - (handle-notebook-delta delta sty) + =^ cards sty (handle-notebook-delta delta sty) + [(weld cards cad) sty] :: [%app %publish %notebooks @ @ %udon ~] =/ book-name i.t.t.t.pax @@ -486,7 +487,8 @@ [~ sty] =. notes.u.book (~(del by notes.u.book) note-name) =/ delta=notebook-delta [%del-note our.bol book-name note-name] - (handle-notebook-delta delta sty) + =^ cards sty (handle-notebook-delta delta sty) + [(weld cards cad) sty] :: [%app %publish %notebooks @ @ @ %publish-comment ~] =/ book-name i.t.t.t.pax @@ -496,7 +498,8 @@ [~ sty] =/ delta=notebook-delta [%del-comment our.bol book-name note-name u.comment-date] - (handle-notebook-delta delta sty) + =^ cards sty (handle-notebook-delta delta sty) + [(weld cards cad) sty] == :: ++ add-paths @@ -518,6 +521,10 @@ now.bol ~ ~ ~ == + =+ ^- [grp-car=(list card) writers-path=path subscribers-path=path] + (make-groups book-name [%new ~ ~ %journal]) + =. writers.new-book writers-path + =. subscribers.new-book subscribers-path =+ ^- [read-cards=(list card) notes=(map @tas note)] (watch-notes /app/publish/notebooks/[book-name]) =. notes.new-book notes @@ -527,9 +534,11 @@ =^ update-cards sty (handle-notebook-delta delta sty) :_ sty ;: weld + grp-car [%pass (welp /read/info pax) %arvo %c %warp our.bol rif]~ read-cards update-cards + cad == :: [%app %publish %notebooks @ @ %udon ~] @@ -548,6 +557,7 @@ [%pass (welp /read/note pax) %arvo %c %warp our.bol rif]~ read-cards update-cards + cad == :: [%app %publish %notebooks @ @ @ %publish-comment ~] @@ -566,6 +576,7 @@ ;: weld [%pass (welp /read/comment pax) %arvo %c %warp our.bol rif]~ update-cards + cad == == :: From 0d732e4092dcff8439562c634ae5f051493dc8c5 Mon Sep 17 00:00:00 2001 From: Matilde Park Date: Thu, 23 Jan 2020 00:49:42 -0500 Subject: [PATCH 16/20] publish: initial fe scaffold --- pkg/arvo/app/publish/css/index.css | 3 +- pkg/arvo/app/publish/img/Home.png | Bin 0 -> 679 bytes pkg/arvo/app/publish/img/SwitcherClosed.png | Bin 0 -> 1377 bytes pkg/arvo/app/publish/img/SwitcherOpen.png | Bin 0 -> 1406 bytes pkg/arvo/app/publish/img/arrow.png | Bin 245 -> 0 bytes pkg/arvo/app/publish/img/popout.png | Bin 0 -> 1480 bytes pkg/arvo/app/publish/index.hoon | 3 +- pkg/arvo/app/publish/js/index.js | 49187 +++++++++++++++- pkg/arvo/app/publish/js/tile.js | 2164 +- pkg/interface/publish/package-lock.json | 41 +- pkg/interface/publish/src/css/custom.css | 305 +- .../publish/src/css/indigo-static.css | 1 + pkg/interface/publish/src/css/tachyons.css | 2 - pkg/interface/publish/src/index.css | 2 +- pkg/interface/publish/src/index.js | 20 +- pkg/interface/publish/src/js/api.js | 14 + .../publish/src/js/components/blog.js | 373 - .../src/js/components/lib/blog-data.js | 90 - .../src/js/components/lib/blog-notes.js | 50 - .../src/js/components/lib/blog-settings.js | 122 - .../src/js/components/lib/blog-subs.js | 140 - .../src/js/components/lib/comment-box.js | 78 - .../publish/src/js/components/lib/comment.js | 59 - .../publish/src/js/components/lib/comments.js | 112 - .../src/js/components/lib/header-bar.js | 59 +- .../src/js/components/lib/header-menu.js | 78 - .../publish/src/js/components/lib/icon.js | 74 - .../src/js/components/lib/icons/icon-check.js | 11 - .../js/components/lib/icons/icon-comment.js | 17 - .../src/js/components/lib/icons/icon-cross.js | 11 - .../js/components/lib/icons/icon-decline.js | 13 - .../src/js/components/lib/icons/icon-home.js | 3 +- .../src/js/components/lib/icons/icon-inbox.js | 11 - .../lib/icons/icon-sidebar-switch.js | 34 + .../src/js/components/lib/icons/icon-sig.js | 11 - .../js/components/lib/icons/icon-spinner.js | 9 - .../src/js/components/lib/icons/icon-user.js | 9 - .../src/js/components/lib/icons/sigil.js | 16 +- .../src/js/components/lib/next-prev.js | 130 - .../src/js/components/lib/path-control.js | 104 - .../src/js/components/lib/post-body.js | 108 - .../src/js/components/lib/post-preview.js | 61 - .../src/js/components/lib/post-snippet.js | 26 - .../src/js/components/lib/publish-create.js | 54 - .../src/js/components/lib/recent-preview.js | 72 - .../src/js/components/lib/seal-dict.js | 106 - .../publish/src/js/components/lib/sidebar.js | 46 + .../src/js/components/lib/title-snippet.js | 30 - .../publish/src/js/components/new-blog.js | 267 - .../publish/src/js/components/new-post.js | 311 - .../publish/src/js/components/not-found.js | 33 - .../publish/src/js/components/post.js | 546 - .../publish/src/js/components/pubs.js | 109 - .../publish/src/js/components/recent.js | 180 - .../publish/src/js/components/root.js | 152 +- .../publish/src/js/components/skeleton.js | 44 +- .../publish/src/js/components/subs.js | 200 - .../publish/src/js/reducers/local.js | 17 + .../publish/src/js/reducers/response.js | 9 + 59 files changed, 51637 insertions(+), 4090 deletions(-) create mode 100644 pkg/arvo/app/publish/img/Home.png create mode 100644 pkg/arvo/app/publish/img/SwitcherClosed.png create mode 100644 pkg/arvo/app/publish/img/SwitcherOpen.png delete mode 100644 pkg/arvo/app/publish/img/arrow.png create mode 100644 pkg/arvo/app/publish/img/popout.png create mode 100644 pkg/interface/publish/src/css/indigo-static.css delete mode 100644 pkg/interface/publish/src/css/tachyons.css delete mode 100644 pkg/interface/publish/src/js/components/blog.js delete mode 100644 pkg/interface/publish/src/js/components/lib/blog-data.js delete mode 100644 pkg/interface/publish/src/js/components/lib/blog-notes.js delete mode 100644 pkg/interface/publish/src/js/components/lib/blog-settings.js delete mode 100644 pkg/interface/publish/src/js/components/lib/blog-subs.js delete mode 100644 pkg/interface/publish/src/js/components/lib/comment-box.js delete mode 100644 pkg/interface/publish/src/js/components/lib/comment.js delete mode 100644 pkg/interface/publish/src/js/components/lib/comments.js delete mode 100644 pkg/interface/publish/src/js/components/lib/header-menu.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icon.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-check.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-comment.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-cross.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-decline.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-inbox.js create mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-sidebar-switch.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-sig.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-spinner.js delete mode 100644 pkg/interface/publish/src/js/components/lib/icons/icon-user.js delete mode 100644 pkg/interface/publish/src/js/components/lib/next-prev.js delete mode 100644 pkg/interface/publish/src/js/components/lib/path-control.js delete mode 100644 pkg/interface/publish/src/js/components/lib/post-body.js delete mode 100644 pkg/interface/publish/src/js/components/lib/post-preview.js delete mode 100644 pkg/interface/publish/src/js/components/lib/post-snippet.js delete mode 100644 pkg/interface/publish/src/js/components/lib/publish-create.js delete mode 100644 pkg/interface/publish/src/js/components/lib/recent-preview.js delete mode 100644 pkg/interface/publish/src/js/components/lib/seal-dict.js create mode 100644 pkg/interface/publish/src/js/components/lib/sidebar.js delete mode 100644 pkg/interface/publish/src/js/components/lib/title-snippet.js delete mode 100644 pkg/interface/publish/src/js/components/new-blog.js delete mode 100644 pkg/interface/publish/src/js/components/new-post.js delete mode 100644 pkg/interface/publish/src/js/components/not-found.js delete mode 100644 pkg/interface/publish/src/js/components/post.js delete mode 100644 pkg/interface/publish/src/js/components/pubs.js delete mode 100644 pkg/interface/publish/src/js/components/recent.js delete mode 100644 pkg/interface/publish/src/js/components/subs.js create mode 100644 pkg/interface/publish/src/js/reducers/local.js diff --git a/pkg/arvo/app/publish/css/index.css b/pkg/arvo/app/publish/css/index.css index 2d8ae035e9..3bf28d43a0 100644 --- a/pkg/arvo/app/publish/css/index.css +++ b/pkg/arvo/app/publish/css/index.css @@ -1,2 +1 @@ -/*! TACHYONS v4.11.2 | http://tachyons.io */ -/*! normalize.css v8.0.0 | MIT License | github.com/necolas/normalize.css */html{line-height:1.15;-webkit-text-size-adjust:100%}body{margin:0}h1{font-size:2em;margin:.67em 0}hr{box-sizing:content-box;height:0;overflow:visible}pre{font-family:monospace,monospace;font-size:1em}a{background-color:transparent}abbr[title]{border-bottom:none;text-decoration:underline;-webkit-text-decoration:underline dotted;text-decoration:underline dotted}b,strong{font-weight:bolder}code,kbd,samp{font-family:monospace,monospace;font-size:1em}small{font-size:80%}sub,sup{font-size:75%;line-height:0;position:relative;vertical-align:baseline}sub{bottom:-.25em}sup{top:-.5em}img{border-style:none}button,input,optgroup,select,textarea{font-family:inherit;font-size:100%;line-height:1.15;margin:0}button,input{overflow:visible}button,select{text-transform:none}[type=button],[type=reset],[type=submit],button{-webkit-appearance:button}[type=button]::-moz-focus-inner,[type=reset]::-moz-focus-inner,[type=submit]::-moz-focus-inner,button::-moz-focus-inner{border-style:none;padding:0}[type=button]:-moz-focusring,[type=reset]:-moz-focusring,[type=submit]:-moz-focusring,button:-moz-focusring{outline:1px dotted ButtonText}fieldset{padding:.35em .75em .625em}legend{box-sizing:border-box;color:inherit;display:table;max-width:100%;padding:0;white-space:normal}progress{vertical-align:baseline}textarea{overflow:auto}[type=checkbox],[type=radio]{box-sizing:border-box;padding:0}[type=number]::-webkit-inner-spin-button,[type=number]::-webkit-outer-spin-button{height:auto}[type=search]{-webkit-appearance:textfield;outline-offset:-2px}[type=search]::-webkit-search-decoration{-webkit-appearance:none}::-webkit-file-upload-button{-webkit-appearance:button;font:inherit}details{display:block}summary{display:list-item}[hidden],template{display:none}.border-box,a,article,aside,blockquote,body,code,dd,div,dl,dt,fieldset,figcaption,figure,footer,form,h1,h2,h3,h4,h5,h6,header,html,input[type=email],input[type=number],input[type=password],input[type=tel],input[type=text],input[type=url],legend,li,main,nav,ol,p,pre,section,table,td,textarea,th,tr,ul{box-sizing:border-box}.aspect-ratio{height:0;position:relative}.aspect-ratio--16x9{padding-bottom:56.25%}.aspect-ratio--9x16{padding-bottom:177.77%}.aspect-ratio--4x3{padding-bottom:75%}.aspect-ratio--3x4{padding-bottom:133.33%}.aspect-ratio--6x4{padding-bottom:66.6%}.aspect-ratio--4x6{padding-bottom:150%}.aspect-ratio--8x5{padding-bottom:62.5%}.aspect-ratio--5x8{padding-bottom:160%}.aspect-ratio--7x5{padding-bottom:71.42%}.aspect-ratio--5x7{padding-bottom:140%}.aspect-ratio--1x1{padding-bottom:100%}.aspect-ratio--object{position:absolute;top:0;right:0;bottom:0;left:0;width:100%;height:100%;z-index:100}img{max-width:100%}.cover{background-size:cover!important}.contain{background-size:contain!important}.bg-center{background-position:50%}.bg-center,.bg-top{background-repeat:no-repeat}.bg-top{background-position:top}.bg-right{background-position:100%}.bg-bottom,.bg-right{background-repeat:no-repeat}.bg-bottom{background-position:bottom}.bg-left{background-repeat:no-repeat;background-position:0}.outline{outline:1px solid}.outline-transparent{outline:1px solid transparent}.outline-0{outline:0}.ba{border-style:solid;border-width:1px}.bt{border-top-style:solid;border-top-width:1px}.br{border-right-style:solid;border-right-width:1px}.bb{border-bottom-style:solid;border-bottom-width:1px}.bl{border-left-style:solid;border-left-width:1px}.bn{border-style:none;border-width:0}.b--black{border-color:#000}.b--near-black{border-color:#111}.b--dark-gray{border-color:#333}.b--mid-gray{border-color:#555}.b--gray{border-color:#777}.b--silver{border-color:#999}.b--light-silver{border-color:#aaa}.b--moon-gray{border-color:#ccc}.b--light-gray{border-color:#eee}.b--near-white{border-color:#f4f4f4}.b--white{border-color:#fff}.b--white-90{border-color:hsla(0,0%,100%,.9)}.b--white-80{border-color:hsla(0,0%,100%,.8)}.b--white-70{border-color:hsla(0,0%,100%,.7)}.b--white-60{border-color:hsla(0,0%,100%,.6)}.b--white-50{border-color:hsla(0,0%,100%,.5)}.b--white-40{border-color:hsla(0,0%,100%,.4)}.b--white-30{border-color:hsla(0,0%,100%,.3)}.b--white-20{border-color:hsla(0,0%,100%,.2)}.b--white-10{border-color:hsla(0,0%,100%,.1)}.b--white-05{border-color:hsla(0,0%,100%,.05)}.b--white-025{border-color:hsla(0,0%,100%,.025)}.b--white-0125{border-color:hsla(0,0%,100%,.0125)}.b--black-90{border-color:rgba(0,0,0,.9)}.b--black-80{border-color:rgba(0,0,0,.8)}.b--black-70{border-color:rgba(0,0,0,.7)}.b--black-60{border-color:rgba(0,0,0,.6)}.b--black-50{border-color:rgba(0,0,0,.5)}.b--black-40{border-color:rgba(0,0,0,.4)}.b--black-30{border-color:rgba(0,0,0,.3)}.b--black-20{border-color:rgba(0,0,0,.2)}.b--black-10{border-color:rgba(0,0,0,.1)}.b--black-05{border-color:rgba(0,0,0,.05)}.b--black-025{border-color:rgba(0,0,0,.025)}.b--black-0125{border-color:rgba(0,0,0,.0125)}.b--dark-red{border-color:#e7040f}.b--red{border-color:#ff4136}.b--light-red{border-color:#ff725c}.b--orange{border-color:#ff6300}.b--gold{border-color:#ffb700}.b--yellow{border-color:gold}.b--light-yellow{border-color:#fbf1a9}.b--purple{border-color:#5e2ca5}.b--light-purple{border-color:#a463f2}.b--dark-pink{border-color:#d5008f}.b--hot-pink{border-color:#ff41b4}.b--pink{border-color:#ff80cc}.b--light-pink{border-color:#ffa3d7}.b--dark-green{border-color:#137752}.b--green{border-color:#19a974}.b--light-green{border-color:#9eebcf}.b--navy{border-color:#001b44}.b--dark-blue{border-color:#00449e}.b--blue{border-color:#357edd}.b--light-blue{border-color:#96ccff}.b--lightest-blue{border-color:#cdecff}.b--washed-blue{border-color:#f6fffe}.b--washed-green{border-color:#e8fdf5}.b--washed-yellow{border-color:#fffceb}.b--washed-red{border-color:#ffdfdf}.b--transparent{border-color:transparent}.b--inherit{border-color:inherit}.br0{border-radius:0}.br1{border-radius:.125rem}.br2{border-radius:.25rem}.br3{border-radius:.5rem}.br4{border-radius:1rem}.br-100{border-radius:100%}.br-pill{border-radius:9999px}.br--bottom{border-top-left-radius:0;border-top-right-radius:0}.br--top{border-bottom-right-radius:0}.br--right,.br--top{border-bottom-left-radius:0}.br--right{border-top-left-radius:0}.br--left{border-top-right-radius:0;border-bottom-right-radius:0}.b--dotted{border-style:dotted}.b--dashed{border-style:dashed}.b--solid{border-style:solid}.b--none{border-style:none}.bw0{border-width:0}.bw1{border-width:.125rem}.bw2{border-width:.25rem}.bw3{border-width:.5rem}.bw4{border-width:1rem}.bw5{border-width:2rem}.bt-0{border-top-width:0}.br-0{border-right-width:0}.bb-0{border-bottom-width:0}.bl-0{border-left-width:0}.shadow-1{box-shadow:0 0 4px 2px rgba(0,0,0,.2)}.shadow-2{box-shadow:0 0 8px 2px rgba(0,0,0,.2)}.shadow-3{box-shadow:2px 2px 4px 2px rgba(0,0,0,.2)}.shadow-4{box-shadow:2px 2px 8px 0 rgba(0,0,0,.2)}.shadow-5{box-shadow:4px 4px 8px 0 rgba(0,0,0,.2)}.pre{overflow-x:auto;overflow-y:hidden;overflow:scroll}.top-0{top:0}.right-0{right:0}.bottom-0{bottom:0}.left-0{left:0}.top-1{top:1rem}.right-1{right:1rem}.bottom-1{bottom:1rem}.left-1{left:1rem}.top-2{top:2rem}.right-2{right:2rem}.bottom-2{bottom:2rem}.left-2{left:2rem}.top--1{top:-1rem}.right--1{right:-1rem}.bottom--1{bottom:-1rem}.left--1{left:-1rem}.top--2{top:-2rem}.right--2{right:-2rem}.bottom--2{bottom:-2rem}.left--2{left:-2rem}.absolute--fill{top:0;right:0;bottom:0;left:0}.cf:after,.cf:before{content:" ";display:table}.cf:after{clear:both}.cf{*zoom:1}.cl{clear:left}.cr{clear:right}.cb{clear:both}.cn{clear:none}.dn{display:none}.di{display:inline}.db{display:block}.dib{display:inline-block}.dit{display:inline-table}.dt{display:table}.dtc{display:table-cell}.dt-row{display:table-row}.dt-row-group{display:table-row-group}.dt-column{display:table-column}.dt-column-group{display:table-column-group}.dt--fixed{table-layout:fixed;width:100%}.flex{display:flex}.inline-flex{display:inline-flex}.flex-auto{flex:1 1 auto;min-width:0;min-height:0}.flex-none{flex:none}.flex-column{flex-direction:column}.flex-row{flex-direction:row}.flex-wrap{flex-wrap:wrap}.flex-nowrap{flex-wrap:nowrap}.flex-wrap-reverse{flex-wrap:wrap-reverse}.flex-column-reverse{flex-direction:column-reverse}.flex-row-reverse{flex-direction:row-reverse}.items-start{align-items:flex-start}.items-end{align-items:flex-end}.items-center{align-items:center}.items-baseline{align-items:baseline}.items-stretch{align-items:stretch}.self-start{align-self:flex-start}.self-end{align-self:flex-end}.self-center{align-self:center}.self-baseline{align-self:baseline}.self-stretch{align-self:stretch}.justify-start{justify-content:flex-start}.justify-end{justify-content:flex-end}.justify-center{justify-content:center}.justify-between{justify-content:space-between}.justify-around{justify-content:space-around}.content-start{align-content:flex-start}.content-end{align-content:flex-end}.content-center{align-content:center}.content-between{align-content:space-between}.content-around{align-content:space-around}.content-stretch{align-content:stretch}.order-0{order:0}.order-1{order:1}.order-2{order:2}.order-3{order:3}.order-4{order:4}.order-5{order:5}.order-6{order:6}.order-7{order:7}.order-8{order:8}.order-last{order:99999}.flex-grow-0{flex-grow:0}.flex-grow-1{flex-grow:1}.flex-shrink-0{flex-shrink:0}.flex-shrink-1{flex-shrink:1}.fl{float:left}.fl,.fr{_display:inline}.fr{float:right}.fn{float:none}.sans-serif{font-family:-apple-system,BlinkMacSystemFont,avenir next,avenir,helvetica neue,helvetica,ubuntu,roboto,noto,segoe ui,arial,sans-serif}.serif{font-family:georgia,times,serif}.system-sans-serif{font-family:sans-serif}.system-serif{font-family:serif}.code,code{font-family:Consolas,monaco,monospace}.courier{font-family:Courier Next,courier,monospace}.helvetica{font-family:helvetica neue,helvetica,sans-serif}.avenir{font-family:avenir next,avenir,sans-serif}.athelas{font-family:athelas,georgia,serif}.georgia{font-family:georgia,serif}.times{font-family:times,serif}.bodoni{font-family:Bodoni MT,serif}.calisto{font-family:Calisto MT,serif}.garamond{font-family:garamond,serif}.baskerville{font-family:baskerville,serif}.i{font-style:italic}.fs-normal{font-style:normal}.normal{font-weight:400}.b{font-weight:700}.fw1{font-weight:100}.fw2{font-weight:200}.fw3{font-weight:300}.fw4{font-weight:400}.fw5{font-weight:500}.fw6{font-weight:600}.fw7{font-weight:700}.fw8{font-weight:800}.fw9{font-weight:900}.input-reset{-webkit-appearance:none;-moz-appearance:none}.button-reset::-moz-focus-inner,.input-reset::-moz-focus-inner{border:0;padding:0}.h1{height:1rem}.h2{height:2rem}.h3{height:4rem}.h4{height:8rem}.h5{height:16rem}.h-25{height:25%}.h-50{height:50%}.h-75{height:75%}.h-100{height:100%}.min-h-100{min-height:100%}.vh-25{height:25vh}.vh-50{height:50vh}.vh-75{height:75vh}.vh-100{height:100vh}.min-vh-100{min-height:100vh}.h-auto{height:auto}.h-inherit{height:inherit}.tracked{letter-spacing:.1em}.tracked-tight{letter-spacing:-.05em}.tracked-mega{letter-spacing:.25em}.lh-solid{line-height:1}.lh-title{line-height:1.25}.lh-copy{line-height:1.5}.link{text-decoration:none}.link,.link:active,.link:focus,.link:hover,.link:link,.link:visited{transition:color .15s ease-in}.link:focus{outline:1px dotted currentColor}.list{list-style-type:none}.mw-100{max-width:100%}.mw1{max-width:1rem}.mw2{max-width:2rem}.mw3{max-width:4rem}.mw4{max-width:8rem}.mw5{max-width:16rem}.mw6{max-width:32rem}.mw7{max-width:48rem}.mw8{max-width:64rem}.mw9{max-width:96rem}.mw-none{max-width:none}.w1{width:1rem}.w2{width:2rem}.w3{width:4rem}.w4{width:8rem}.w5{width:16rem}.w-10{width:10%}.w-20{width:20%}.w-25{width:25%}.w-30{width:30%}.w-33{width:33%}.w-34{width:34%}.w-40{width:40%}.w-50{width:50%}.w-60{width:60%}.w-70{width:70%}.w-75{width:75%}.w-80{width:80%}.w-90{width:90%}.w-100{width:100%}.w-third{width:33.33333%}.w-two-thirds{width:66.66667%}.w-auto{width:auto}.overflow-visible{overflow:visible}.overflow-hidden{overflow:hidden}.overflow-scroll{overflow:scroll}.overflow-auto{overflow:auto}.overflow-x-visible{overflow-x:visible}.overflow-x-hidden{overflow-x:hidden}.overflow-x-scroll{overflow-x:scroll}.overflow-x-auto{overflow-x:auto}.overflow-y-visible{overflow-y:visible}.overflow-y-hidden{overflow-y:hidden}.overflow-y-scroll{overflow-y:scroll}.overflow-y-auto{overflow-y:auto}.static{position:static}.relative{position:relative}.absolute{position:absolute}.fixed{position:fixed}.o-100{opacity:1}.o-90{opacity:.9}.o-80{opacity:.8}.o-70{opacity:.7}.o-60{opacity:.6}.o-50{opacity:.5}.o-40{opacity:.4}.o-30{opacity:.3}.o-20{opacity:.2}.o-10{opacity:.1}.o-05{opacity:.05}.o-025{opacity:.025}.o-0{opacity:0}.rotate-45{-webkit-transform:rotate(45deg);transform:rotate(45deg)}.rotate-90{-webkit-transform:rotate(90deg);transform:rotate(90deg)}.rotate-135{-webkit-transform:rotate(135deg);transform:rotate(135deg)}.rotate-180{-webkit-transform:rotate(180deg);transform:rotate(180deg)}.rotate-225{-webkit-transform:rotate(225deg);transform:rotate(225deg)}.rotate-270{-webkit-transform:rotate(270deg);transform:rotate(270deg)}.rotate-315{-webkit-transform:rotate(315deg);transform:rotate(315deg)}.black-90{color:rgba(0,0,0,.9)}.black-80{color:rgba(0,0,0,.8)}.black-70{color:rgba(0,0,0,.7)}.black-60{color:rgba(0,0,0,.6)}.black-50{color:rgba(0,0,0,.5)}.black-40{color:rgba(0,0,0,.4)}.black-30{color:rgba(0,0,0,.3)}.black-20{color:rgba(0,0,0,.2)}.black-10{color:rgba(0,0,0,.1)}.black-05{color:rgba(0,0,0,.05)}.white-90{color:hsla(0,0%,100%,.9)}.white-80{color:hsla(0,0%,100%,.8)}.white-70{color:hsla(0,0%,100%,.7)}.white-60{color:hsla(0,0%,100%,.6)}.white-50{color:hsla(0,0%,100%,.5)}.white-40{color:hsla(0,0%,100%,.4)}.white-30{color:hsla(0,0%,100%,.3)}.white-20{color:hsla(0,0%,100%,.2)}.white-10{color:hsla(0,0%,100%,.1)}.black{color:#000}.near-black{color:#111}.dark-gray{color:#333}.mid-gray{color:#555}.gray{color:#777}.silver{color:#999}.light-silver{color:#aaa}.moon-gray{color:#ccc}.light-gray{color:#eee}.near-white{color:#f4f4f4}.white{color:#fff}.dark-red{color:#e7040f}.red{color:#ff4136}.light-red{color:#ff725c}.orange{color:#ff6300}.gold{color:#ffb700}.yellow{color:gold}.light-yellow{color:#fbf1a9}.purple{color:#5e2ca5}.light-purple{color:#a463f2}.dark-pink{color:#d5008f}.hot-pink{color:#ff41b4}.pink{color:#ff80cc}.light-pink{color:#ffa3d7}.dark-green{color:#137752}.green{color:#19a974}.light-green{color:#9eebcf}.navy{color:#001b44}.dark-blue{color:#00449e}.blue{color:#357edd}.light-blue{color:#96ccff}.lightest-blue{color:#cdecff}.washed-blue{color:#f6fffe}.washed-green{color:#e8fdf5}.washed-yellow{color:#fffceb}.washed-red{color:#ffdfdf}.color-inherit{color:inherit}.bg-black-90{background-color:rgba(0,0,0,.9)}.bg-black-80{background-color:rgba(0,0,0,.8)}.bg-black-70{background-color:rgba(0,0,0,.7)}.bg-black-60{background-color:rgba(0,0,0,.6)}.bg-black-50{background-color:rgba(0,0,0,.5)}.bg-black-40{background-color:rgba(0,0,0,.4)}.bg-black-30{background-color:rgba(0,0,0,.3)}.bg-black-20{background-color:rgba(0,0,0,.2)}.bg-black-10{background-color:rgba(0,0,0,.1)}.bg-black-05{background-color:rgba(0,0,0,.05)}.bg-white-90{background-color:hsla(0,0%,100%,.9)}.bg-white-80{background-color:hsla(0,0%,100%,.8)}.bg-white-70{background-color:hsla(0,0%,100%,.7)}.bg-white-60{background-color:hsla(0,0%,100%,.6)}.bg-white-50{background-color:hsla(0,0%,100%,.5)}.bg-white-40{background-color:hsla(0,0%,100%,.4)}.bg-white-30{background-color:hsla(0,0%,100%,.3)}.bg-white-20{background-color:hsla(0,0%,100%,.2)}.bg-white-10{background-color:hsla(0,0%,100%,.1)}.bg-black{background-color:#000}.bg-near-black{background-color:#111}.bg-dark-gray{background-color:#333}.bg-mid-gray{background-color:#555}.bg-gray{background-color:#777}.bg-silver{background-color:#999}.bg-light-silver{background-color:#aaa}.bg-moon-gray{background-color:#ccc}.bg-light-gray{background-color:#eee}.bg-near-white{background-color:#f4f4f4}.bg-white{background-color:#fff}.bg-transparent{background-color:transparent}.bg-dark-red{background-color:#e7040f}.bg-red{background-color:#ff4136}.bg-light-red{background-color:#ff725c}.bg-orange{background-color:#ff6300}.bg-gold{background-color:#ffb700}.bg-yellow{background-color:gold}.bg-light-yellow{background-color:#fbf1a9}.bg-purple{background-color:#5e2ca5}.bg-light-purple{background-color:#a463f2}.bg-dark-pink{background-color:#d5008f}.bg-hot-pink{background-color:#ff41b4}.bg-pink{background-color:#ff80cc}.bg-light-pink{background-color:#ffa3d7}.bg-dark-green{background-color:#137752}.bg-green{background-color:#19a974}.bg-light-green{background-color:#9eebcf}.bg-navy{background-color:#001b44}.bg-dark-blue{background-color:#00449e}.bg-blue{background-color:#357edd}.bg-light-blue{background-color:#96ccff}.bg-lightest-blue{background-color:#cdecff}.bg-washed-blue{background-color:#f6fffe}.bg-washed-green{background-color:#e8fdf5}.bg-washed-yellow{background-color:#fffceb}.bg-washed-red{background-color:#ffdfdf}.bg-inherit{background-color:inherit}.hover-black:focus,.hover-black:hover{color:#000}.hover-near-black:focus,.hover-near-black:hover{color:#111}.hover-dark-gray:focus,.hover-dark-gray:hover{color:#333}.hover-mid-gray:focus,.hover-mid-gray:hover{color:#555}.hover-gray:focus,.hover-gray:hover{color:#777}.hover-silver:focus,.hover-silver:hover{color:#999}.hover-light-silver:focus,.hover-light-silver:hover{color:#aaa}.hover-moon-gray:focus,.hover-moon-gray:hover{color:#ccc}.hover-light-gray:focus,.hover-light-gray:hover{color:#eee}.hover-near-white:focus,.hover-near-white:hover{color:#f4f4f4}.hover-white:focus,.hover-white:hover{color:#fff}.hover-black-90:focus,.hover-black-90:hover{color:rgba(0,0,0,.9)}.hover-black-80:focus,.hover-black-80:hover{color:rgba(0,0,0,.8)}.hover-black-70:focus,.hover-black-70:hover{color:rgba(0,0,0,.7)}.hover-black-60:focus,.hover-black-60:hover{color:rgba(0,0,0,.6)}.hover-black-50:focus,.hover-black-50:hover{color:rgba(0,0,0,.5)}.hover-black-40:focus,.hover-black-40:hover{color:rgba(0,0,0,.4)}.hover-black-30:focus,.hover-black-30:hover{color:rgba(0,0,0,.3)}.hover-black-20:focus,.hover-black-20:hover{color:rgba(0,0,0,.2)}.hover-black-10:focus,.hover-black-10:hover{color:rgba(0,0,0,.1)}.hover-white-90:focus,.hover-white-90:hover{color:hsla(0,0%,100%,.9)}.hover-white-80:focus,.hover-white-80:hover{color:hsla(0,0%,100%,.8)}.hover-white-70:focus,.hover-white-70:hover{color:hsla(0,0%,100%,.7)}.hover-white-60:focus,.hover-white-60:hover{color:hsla(0,0%,100%,.6)}.hover-white-50:focus,.hover-white-50:hover{color:hsla(0,0%,100%,.5)}.hover-white-40:focus,.hover-white-40:hover{color:hsla(0,0%,100%,.4)}.hover-white-30:focus,.hover-white-30:hover{color:hsla(0,0%,100%,.3)}.hover-white-20:focus,.hover-white-20:hover{color:hsla(0,0%,100%,.2)}.hover-white-10:focus,.hover-white-10:hover{color:hsla(0,0%,100%,.1)}.hover-inherit:focus,.hover-inherit:hover{color:inherit}.hover-bg-black:focus,.hover-bg-black:hover{background-color:#000}.hover-bg-near-black:focus,.hover-bg-near-black:hover{background-color:#111}.hover-bg-dark-gray:focus,.hover-bg-dark-gray:hover{background-color:#333}.hover-bg-mid-gray:focus,.hover-bg-mid-gray:hover{background-color:#555}.hover-bg-gray:focus,.hover-bg-gray:hover{background-color:#777}.hover-bg-silver:focus,.hover-bg-silver:hover{background-color:#999}.hover-bg-light-silver:focus,.hover-bg-light-silver:hover{background-color:#aaa}.hover-bg-moon-gray:focus,.hover-bg-moon-gray:hover{background-color:#ccc}.hover-bg-light-gray:focus,.hover-bg-light-gray:hover{background-color:#eee}.hover-bg-near-white:focus,.hover-bg-near-white:hover{background-color:#f4f4f4}.hover-bg-white:focus,.hover-bg-white:hover{background-color:#fff}.hover-bg-transparent:focus,.hover-bg-transparent:hover{background-color:transparent}.hover-bg-black-90:focus,.hover-bg-black-90:hover{background-color:rgba(0,0,0,.9)}.hover-bg-black-80:focus,.hover-bg-black-80:hover{background-color:rgba(0,0,0,.8)}.hover-bg-black-70:focus,.hover-bg-black-70:hover{background-color:rgba(0,0,0,.7)}.hover-bg-black-60:focus,.hover-bg-black-60:hover{background-color:rgba(0,0,0,.6)}.hover-bg-black-50:focus,.hover-bg-black-50:hover{background-color:rgba(0,0,0,.5)}.hover-bg-black-40:focus,.hover-bg-black-40:hover{background-color:rgba(0,0,0,.4)}.hover-bg-black-30:focus,.hover-bg-black-30:hover{background-color:rgba(0,0,0,.3)}.hover-bg-black-20:focus,.hover-bg-black-20:hover{background-color:rgba(0,0,0,.2)}.hover-bg-black-10:focus,.hover-bg-black-10:hover{background-color:rgba(0,0,0,.1)}.hover-bg-white-90:focus,.hover-bg-white-90:hover{background-color:hsla(0,0%,100%,.9)}.hover-bg-white-80:focus,.hover-bg-white-80:hover{background-color:hsla(0,0%,100%,.8)}.hover-bg-white-70:focus,.hover-bg-white-70:hover{background-color:hsla(0,0%,100%,.7)}.hover-bg-white-60:focus,.hover-bg-white-60:hover{background-color:hsla(0,0%,100%,.6)}.hover-bg-white-50:focus,.hover-bg-white-50:hover{background-color:hsla(0,0%,100%,.5)}.hover-bg-white-40:focus,.hover-bg-white-40:hover{background-color:hsla(0,0%,100%,.4)}.hover-bg-white-30:focus,.hover-bg-white-30:hover{background-color:hsla(0,0%,100%,.3)}.hover-bg-white-20:focus,.hover-bg-white-20:hover{background-color:hsla(0,0%,100%,.2)}.hover-bg-white-10:focus,.hover-bg-white-10:hover{background-color:hsla(0,0%,100%,.1)}.hover-dark-red:focus,.hover-dark-red:hover{color:#e7040f}.hover-red:focus,.hover-red:hover{color:#ff4136}.hover-light-red:focus,.hover-light-red:hover{color:#ff725c}.hover-orange:focus,.hover-orange:hover{color:#ff6300}.hover-gold:focus,.hover-gold:hover{color:#ffb700}.hover-yellow:focus,.hover-yellow:hover{color:gold}.hover-light-yellow:focus,.hover-light-yellow:hover{color:#fbf1a9}.hover-purple:focus,.hover-purple:hover{color:#5e2ca5}.hover-light-purple:focus,.hover-light-purple:hover{color:#a463f2}.hover-dark-pink:focus,.hover-dark-pink:hover{color:#d5008f}.hover-hot-pink:focus,.hover-hot-pink:hover{color:#ff41b4}.hover-pink:focus,.hover-pink:hover{color:#ff80cc}.hover-light-pink:focus,.hover-light-pink:hover{color:#ffa3d7}.hover-dark-green:focus,.hover-dark-green:hover{color:#137752}.hover-green:focus,.hover-green:hover{color:#19a974}.hover-light-green:focus,.hover-light-green:hover{color:#9eebcf}.hover-navy:focus,.hover-navy:hover{color:#001b44}.hover-dark-blue:focus,.hover-dark-blue:hover{color:#00449e}.hover-blue:focus,.hover-blue:hover{color:#357edd}.hover-light-blue:focus,.hover-light-blue:hover{color:#96ccff}.hover-lightest-blue:focus,.hover-lightest-blue:hover{color:#cdecff}.hover-washed-blue:focus,.hover-washed-blue:hover{color:#f6fffe}.hover-washed-green:focus,.hover-washed-green:hover{color:#e8fdf5}.hover-washed-yellow:focus,.hover-washed-yellow:hover{color:#fffceb}.hover-washed-red:focus,.hover-washed-red:hover{color:#ffdfdf}.hover-bg-dark-red:focus,.hover-bg-dark-red:hover{background-color:#e7040f}.hover-bg-red:focus,.hover-bg-red:hover{background-color:#ff4136}.hover-bg-light-red:focus,.hover-bg-light-red:hover{background-color:#ff725c}.hover-bg-orange:focus,.hover-bg-orange:hover{background-color:#ff6300}.hover-bg-gold:focus,.hover-bg-gold:hover{background-color:#ffb700}.hover-bg-yellow:focus,.hover-bg-yellow:hover{background-color:gold}.hover-bg-light-yellow:focus,.hover-bg-light-yellow:hover{background-color:#fbf1a9}.hover-bg-purple:focus,.hover-bg-purple:hover{background-color:#5e2ca5}.hover-bg-light-purple:focus,.hover-bg-light-purple:hover{background-color:#a463f2}.hover-bg-dark-pink:focus,.hover-bg-dark-pink:hover{background-color:#d5008f}.hover-bg-hot-pink:focus,.hover-bg-hot-pink:hover{background-color:#ff41b4}.hover-bg-pink:focus,.hover-bg-pink:hover{background-color:#ff80cc}.hover-bg-light-pink:focus,.hover-bg-light-pink:hover{background-color:#ffa3d7}.hover-bg-dark-green:focus,.hover-bg-dark-green:hover{background-color:#137752}.hover-bg-green:focus,.hover-bg-green:hover{background-color:#19a974}.hover-bg-light-green:focus,.hover-bg-light-green:hover{background-color:#9eebcf}.hover-bg-navy:focus,.hover-bg-navy:hover{background-color:#001b44}.hover-bg-dark-blue:focus,.hover-bg-dark-blue:hover{background-color:#00449e}.hover-bg-blue:focus,.hover-bg-blue:hover{background-color:#357edd}.hover-bg-light-blue:focus,.hover-bg-light-blue:hover{background-color:#96ccff}.hover-bg-lightest-blue:focus,.hover-bg-lightest-blue:hover{background-color:#cdecff}.hover-bg-washed-blue:focus,.hover-bg-washed-blue:hover{background-color:#f6fffe}.hover-bg-washed-green:focus,.hover-bg-washed-green:hover{background-color:#e8fdf5}.hover-bg-washed-yellow:focus,.hover-bg-washed-yellow:hover{background-color:#fffceb}.hover-bg-washed-red:focus,.hover-bg-washed-red:hover{background-color:#ffdfdf}.hover-bg-inherit:focus,.hover-bg-inherit:hover{background-color:inherit}.pa0{padding:0}.pa1{padding:.25rem}.pa2{padding:.5rem}.pa3{padding:1rem}.pa4{padding:2rem}.pa5{padding:4rem}.pa6{padding:8rem}.pa7{padding:16rem}.pl0{padding-left:0}.pl1{padding-left:.25rem}.pl2{padding-left:.5rem}.pl3{padding-left:1rem}.pl4{padding-left:2rem}.pl5{padding-left:4rem}.pl6{padding-left:8rem}.pl7{padding-left:16rem}.pr0{padding-right:0}.pr1{padding-right:.25rem}.pr2{padding-right:.5rem}.pr3{padding-right:1rem}.pr4{padding-right:2rem}.pr5{padding-right:4rem}.pr6{padding-right:8rem}.pr7{padding-right:16rem}.pb0{padding-bottom:0}.pb1{padding-bottom:.25rem}.pb2{padding-bottom:.5rem}.pb3{padding-bottom:1rem}.pb4{padding-bottom:2rem}.pb5{padding-bottom:4rem}.pb6{padding-bottom:8rem}.pb7{padding-bottom:16rem}.pt0{padding-top:0}.pt1{padding-top:.25rem}.pt2{padding-top:.5rem}.pt3{padding-top:1rem}.pt4{padding-top:2rem}.pt5{padding-top:4rem}.pt6{padding-top:8rem}.pt7{padding-top:16rem}.pv0{padding-top:0;padding-bottom:0}.pv1{padding-top:.25rem;padding-bottom:.25rem}.pv2{padding-top:.5rem;padding-bottom:.5rem}.pv3{padding-top:1rem;padding-bottom:1rem}.pv4{padding-top:2rem;padding-bottom:2rem}.pv5{padding-top:4rem;padding-bottom:4rem}.pv6{padding-top:8rem;padding-bottom:8rem}.pv7{padding-top:16rem;padding-bottom:16rem}.ph0{padding-left:0;padding-right:0}.ph1{padding-left:.25rem;padding-right:.25rem}.ph2{padding-left:.5rem;padding-right:.5rem}.ph3{padding-left:1rem;padding-right:1rem}.ph4{padding-left:2rem;padding-right:2rem}.ph5{padding-left:4rem;padding-right:4rem}.ph6{padding-left:8rem;padding-right:8rem}.ph7{padding-left:16rem;padding-right:16rem}.ma0{margin:0}.ma1{margin:.25rem}.ma2{margin:.5rem}.ma3{margin:1rem}.ma4{margin:2rem}.ma5{margin:4rem}.ma6{margin:8rem}.ma7{margin:16rem}.ml0{margin-left:0}.ml1{margin-left:.25rem}.ml2{margin-left:.5rem}.ml3{margin-left:1rem}.ml4{margin-left:2rem}.ml5{margin-left:4rem}.ml6{margin-left:8rem}.ml7{margin-left:16rem}.mr0{margin-right:0}.mr1{margin-right:.25rem}.mr2{margin-right:.5rem}.mr3{margin-right:1rem}.mr4{margin-right:2rem}.mr5{margin-right:4rem}.mr6{margin-right:8rem}.mr7{margin-right:16rem}.mb0{margin-bottom:0}.mb1{margin-bottom:.25rem}.mb2{margin-bottom:.5rem}.mb3{margin-bottom:1rem}.mb4{margin-bottom:2rem}.mb5{margin-bottom:4rem}.mb6{margin-bottom:8rem}.mb7{margin-bottom:16rem}.mt0{margin-top:0}.mt1{margin-top:.25rem}.mt2{margin-top:.5rem}.mt3{margin-top:1rem}.mt4{margin-top:2rem}.mt5{margin-top:4rem}.mt6{margin-top:8rem}.mt7{margin-top:16rem}.mv0{margin-top:0;margin-bottom:0}.mv1{margin-top:.25rem;margin-bottom:.25rem}.mv2{margin-top:.5rem;margin-bottom:.5rem}.mv3{margin-top:1rem;margin-bottom:1rem}.mv4{margin-top:2rem;margin-bottom:2rem}.mv5{margin-top:4rem;margin-bottom:4rem}.mv6{margin-top:8rem;margin-bottom:8rem}.mv7{margin-top:16rem;margin-bottom:16rem}.mh0{margin-left:0;margin-right:0}.mh1{margin-left:.25rem;margin-right:.25rem}.mh2{margin-left:.5rem;margin-right:.5rem}.mh3{margin-left:1rem;margin-right:1rem}.mh4{margin-left:2rem;margin-right:2rem}.mh5{margin-left:4rem;margin-right:4rem}.mh6{margin-left:8rem;margin-right:8rem}.mh7{margin-left:16rem;margin-right:16rem}.na1{margin:-.25rem}.na2{margin:-.5rem}.na3{margin:-1rem}.na4{margin:-2rem}.na5{margin:-4rem}.na6{margin:-8rem}.na7{margin:-16rem}.nl1{margin-left:-.25rem}.nl2{margin-left:-.5rem}.nl3{margin-left:-1rem}.nl4{margin-left:-2rem}.nl5{margin-left:-4rem}.nl6{margin-left:-8rem}.nl7{margin-left:-16rem}.nr1{margin-right:-.25rem}.nr2{margin-right:-.5rem}.nr3{margin-right:-1rem}.nr4{margin-right:-2rem}.nr5{margin-right:-4rem}.nr6{margin-right:-8rem}.nr7{margin-right:-16rem}.nb1{margin-bottom:-.25rem}.nb2{margin-bottom:-.5rem}.nb3{margin-bottom:-1rem}.nb4{margin-bottom:-2rem}.nb5{margin-bottom:-4rem}.nb6{margin-bottom:-8rem}.nb7{margin-bottom:-16rem}.nt1{margin-top:-.25rem}.nt2{margin-top:-.5rem}.nt3{margin-top:-1rem}.nt4{margin-top:-2rem}.nt5{margin-top:-4rem}.nt6{margin-top:-8rem}.nt7{margin-top:-16rem}.collapse{border-collapse:collapse;border-spacing:0}.striped--light-silver:nth-child(odd){background-color:#aaa}.striped--moon-gray:nth-child(odd){background-color:#ccc}.striped--light-gray:nth-child(odd){background-color:#eee}.striped--near-white:nth-child(odd){background-color:#f4f4f4}.stripe-light:nth-child(odd){background-color:hsla(0,0%,100%,.1)}.stripe-dark:nth-child(odd){background-color:rgba(0,0,0,.1)}.strike{text-decoration:line-through}.underline{text-decoration:underline}.no-underline{text-decoration:none}.tl{text-align:left}.tr{text-align:right}.tc{text-align:center}.tj{text-align:justify}.ttc{text-transform:capitalize}.ttl{text-transform:lowercase}.ttu{text-transform:uppercase}.ttn{text-transform:none}.f-6,.f-headline{font-size:6rem}.f-5,.f-subheadline{font-size:5rem}.f1{font-size:3rem}.f2{font-size:2.25rem}.f3{font-size:1.5rem}.f4{font-size:1.25rem}.f5{font-size:1rem}.f6{font-size:.875rem}.f7{font-size:.75rem}.measure{max-width:30em}.measure-wide{max-width:34em}.measure-narrow{max-width:20em}.indent{text-indent:1em;margin-top:0;margin-bottom:0}.small-caps{font-variant:small-caps}.truncate{white-space:nowrap;overflow:hidden;text-overflow:ellipsis}.overflow-container{overflow-y:scroll}.center{margin-left:auto}.center,.mr-auto{margin-right:auto}.ml-auto{margin-left:auto}.clip{position:fixed!important;_position:absolute!important;clip:rect(1px 1px 1px 1px);clip:rect(1px,1px,1px,1px)}.ws-normal{white-space:normal}.nowrap{white-space:nowrap}.pre{white-space:pre}.v-base{vertical-align:baseline}.v-mid{vertical-align:middle}.v-top{vertical-align:top}.v-btm{vertical-align:bottom}.dim{opacity:1}.dim,.dim:focus,.dim:hover{transition:opacity .15s ease-in}.dim:focus,.dim:hover{opacity:.5}.dim:active{opacity:.8;transition:opacity .15s ease-out}.glow,.glow:focus,.glow:hover{transition:opacity .15s ease-in}.glow:focus,.glow:hover{opacity:1}.hide-child .child{opacity:0;transition:opacity .15s ease-in}.hide-child:active .child,.hide-child:focus .child,.hide-child:hover .child{opacity:1;transition:opacity .15s ease-in}.underline-hover:focus,.underline-hover:hover{text-decoration:underline}.grow{-moz-osx-font-smoothing:grayscale;-webkit-backface-visibility:hidden;backface-visibility:hidden;-webkit-transform:translateZ(0);transform:translateZ(0);transition:-webkit-transform .25s ease-out;transition:transform .25s ease-out;transition:transform .25s ease-out,-webkit-transform .25s ease-out}.grow:focus,.grow:hover{-webkit-transform:scale(1.05);transform:scale(1.05)}.grow:active{-webkit-transform:scale(.9);transform:scale(.9)}.grow-large{-moz-osx-font-smoothing:grayscale;-webkit-backface-visibility:hidden;backface-visibility:hidden;-webkit-transform:translateZ(0);transform:translateZ(0);transition:-webkit-transform .25s ease-in-out;transition:transform .25s ease-in-out;transition:transform .25s ease-in-out,-webkit-transform .25s ease-in-out}.grow-large:focus,.grow-large:hover{-webkit-transform:scale(1.2);transform:scale(1.2)}.grow-large:active{-webkit-transform:scale(.95);transform:scale(.95)}.pointer:hover,.shadow-hover{cursor:pointer}.shadow-hover{position:relative;transition:all .5s cubic-bezier(.165,.84,.44,1)}.shadow-hover:after{content:"";box-shadow:0 0 16px 2px rgba(0,0,0,.2);border-radius:inherit;opacity:0;position:absolute;top:0;left:0;width:100%;height:100%;z-index:-1;transition:opacity .5s cubic-bezier(.165,.84,.44,1)}.shadow-hover:focus:after,.shadow-hover:hover:after{opacity:1}.bg-animate,.bg-animate:focus,.bg-animate:hover{transition:background-color .15s ease-in-out}.z-0{z-index:0}.z-1{z-index:1}.z-2{z-index:2}.z-3{z-index:3}.z-4{z-index:4}.z-5{z-index:5}.z-999{z-index:999}.z-9999{z-index:9999}.z-max{z-index:2147483647}.z-inherit{z-index:inherit}.z-initial{z-index:auto}.z-unset{z-index:unset}.nested-copy-line-height ol,.nested-copy-line-height p,.nested-copy-line-height ul{line-height:1.5}.nested-headline-line-height h1,.nested-headline-line-height h2,.nested-headline-line-height h3,.nested-headline-line-height h4,.nested-headline-line-height h5,.nested-headline-line-height h6{line-height:1.25}.nested-list-reset ol,.nested-list-reset ul{padding-left:0;margin-left:0;list-style-type:none}.nested-copy-indent p+p{text-indent:1em;margin-top:0;margin-bottom:0}.nested-copy-separator p+p{margin-top:1.5em}.nested-img img{width:100%;max-width:100%;display:block}.nested-links a{color:#357edd;transition:color .15s ease-in}.nested-links a:focus,.nested-links a:hover{color:#96ccff;transition:color .15s ease-in}.debug *{outline:1px solid gold}.debug-white *{outline:1px solid #fff}.debug-black *{outline:1px solid #000}.debug-grid{background:transparent url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAICAYAAADED76LAAAAFElEQVR4AWPAC97/9x0eCsAEPgwAVLshdpENIxcAAAAASUVORK5CYII=) repeat 0 0}.debug-grid-16{background:transparent url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAABAAAAAQCAYAAAAf8/9hAAAAMklEQVR4AWOgCLz/b0epAa6UGuBOqQHOQHLUgFEDnAbcBZ4UGwDOkiCnkIhdgNgNxAYAiYlD+8sEuo8AAAAASUVORK5CYII=) repeat 0 0}.debug-grid-8-solid{background:#fff url(data:image/gif;base64,R0lGODdhCAAIAPEAAADw/wDx/////wAAACwAAAAACAAIAAACDZQvgaeb/lxbAIKA8y0AOw==) repeat 0 0}.debug-grid-16-solid{background:#fff url(data:image/gif;base64,R0lGODdhEAAQAPEAAADw/wDx/xXy/////ywAAAAAEAAQAAACIZyPKckYDQFsb6ZqD85jZ2+BkwiRFKehhqQCQgDHcgwEBQA7) repeat 0 0}@media screen and (min-width:30em){.aspect-ratio-ns{height:0;position:relative}.aspect-ratio--16x9-ns{padding-bottom:56.25%}.aspect-ratio--9x16-ns{padding-bottom:177.77%}.aspect-ratio--4x3-ns{padding-bottom:75%}.aspect-ratio--3x4-ns{padding-bottom:133.33%}.aspect-ratio--6x4-ns{padding-bottom:66.6%}.aspect-ratio--4x6-ns{padding-bottom:150%}.aspect-ratio--8x5-ns{padding-bottom:62.5%}.aspect-ratio--5x8-ns{padding-bottom:160%}.aspect-ratio--7x5-ns{padding-bottom:71.42%}.aspect-ratio--5x7-ns{padding-bottom:140%}.aspect-ratio--1x1-ns{padding-bottom:100%}.aspect-ratio--object-ns{position:absolute;top:0;right:0;bottom:0;left:0;width:100%;height:100%;z-index:100}.cover-ns{background-size:cover!important}.contain-ns{background-size:contain!important}.bg-center-ns{background-position:50%}.bg-center-ns,.bg-top-ns{background-repeat:no-repeat}.bg-top-ns{background-position:top}.bg-right-ns{background-position:100%}.bg-bottom-ns,.bg-right-ns{background-repeat:no-repeat}.bg-bottom-ns{background-position:bottom}.bg-left-ns{background-repeat:no-repeat;background-position:0}.outline-ns{outline:1px solid}.outline-transparent-ns{outline:1px solid transparent}.outline-0-ns{outline:0}.ba-ns{border-style:solid;border-width:1px}.bt-ns{border-top-style:solid;border-top-width:1px}.br-ns{border-right-style:solid;border-right-width:1px}.bb-ns{border-bottom-style:solid;border-bottom-width:1px}.bl-ns{border-left-style:solid;border-left-width:1px}.bn-ns{border-style:none;border-width:0}.br0-ns{border-radius:0}.br1-ns{border-radius:.125rem}.br2-ns{border-radius:.25rem}.br3-ns{border-radius:.5rem}.br4-ns{border-radius:1rem}.br-100-ns{border-radius:100%}.br-pill-ns{border-radius:9999px}.br--bottom-ns{border-top-left-radius:0;border-top-right-radius:0}.br--top-ns{border-bottom-right-radius:0}.br--right-ns,.br--top-ns{border-bottom-left-radius:0}.br--right-ns{border-top-left-radius:0}.br--left-ns{border-top-right-radius:0;border-bottom-right-radius:0}.b--dotted-ns{border-style:dotted}.b--dashed-ns{border-style:dashed}.b--solid-ns{border-style:solid}.b--none-ns{border-style:none}.bw0-ns{border-width:0}.bw1-ns{border-width:.125rem}.bw2-ns{border-width:.25rem}.bw3-ns{border-width:.5rem}.bw4-ns{border-width:1rem}.bw5-ns{border-width:2rem}.bt-0-ns{border-top-width:0}.br-0-ns{border-right-width:0}.bb-0-ns{border-bottom-width:0}.bl-0-ns{border-left-width:0}.shadow-1-ns{box-shadow:0 0 4px 2px rgba(0,0,0,.2)}.shadow-2-ns{box-shadow:0 0 8px 2px rgba(0,0,0,.2)}.shadow-3-ns{box-shadow:2px 2px 4px 2px rgba(0,0,0,.2)}.shadow-4-ns{box-shadow:2px 2px 8px 0 rgba(0,0,0,.2)}.shadow-5-ns{box-shadow:4px 4px 8px 0 rgba(0,0,0,.2)}.top-0-ns{top:0}.left-0-ns{left:0}.right-0-ns{right:0}.bottom-0-ns{bottom:0}.top-1-ns{top:1rem}.left-1-ns{left:1rem}.right-1-ns{right:1rem}.bottom-1-ns{bottom:1rem}.top-2-ns{top:2rem}.left-2-ns{left:2rem}.right-2-ns{right:2rem}.bottom-2-ns{bottom:2rem}.top--1-ns{top:-1rem}.right--1-ns{right:-1rem}.bottom--1-ns{bottom:-1rem}.left--1-ns{left:-1rem}.top--2-ns{top:-2rem}.right--2-ns{right:-2rem}.bottom--2-ns{bottom:-2rem}.left--2-ns{left:-2rem}.absolute--fill-ns{top:0;right:0;bottom:0;left:0}.cl-ns{clear:left}.cr-ns{clear:right}.cb-ns{clear:both}.cn-ns{clear:none}.dn-ns{display:none}.di-ns{display:inline}.db-ns{display:block}.dib-ns{display:inline-block}.dit-ns{display:inline-table}.dt-ns{display:table}.dtc-ns{display:table-cell}.dt-row-ns{display:table-row}.dt-row-group-ns{display:table-row-group}.dt-column-ns{display:table-column}.dt-column-group-ns{display:table-column-group}.dt--fixed-ns{table-layout:fixed;width:100%}.flex-ns{display:flex}.inline-flex-ns{display:inline-flex}.flex-auto-ns{flex:1 1 auto;min-width:0;min-height:0}.flex-none-ns{flex:none}.flex-column-ns{flex-direction:column}.flex-row-ns{flex-direction:row}.flex-wrap-ns{flex-wrap:wrap}.flex-nowrap-ns{flex-wrap:nowrap}.flex-wrap-reverse-ns{flex-wrap:wrap-reverse}.flex-column-reverse-ns{flex-direction:column-reverse}.flex-row-reverse-ns{flex-direction:row-reverse}.items-start-ns{align-items:flex-start}.items-end-ns{align-items:flex-end}.items-center-ns{align-items:center}.items-baseline-ns{align-items:baseline}.items-stretch-ns{align-items:stretch}.self-start-ns{align-self:flex-start}.self-end-ns{align-self:flex-end}.self-center-ns{align-self:center}.self-baseline-ns{align-self:baseline}.self-stretch-ns{align-self:stretch}.justify-start-ns{justify-content:flex-start}.justify-end-ns{justify-content:flex-end}.justify-center-ns{justify-content:center}.justify-between-ns{justify-content:space-between}.justify-around-ns{justify-content:space-around}.content-start-ns{align-content:flex-start}.content-end-ns{align-content:flex-end}.content-center-ns{align-content:center}.content-between-ns{align-content:space-between}.content-around-ns{align-content:space-around}.content-stretch-ns{align-content:stretch}.order-0-ns{order:0}.order-1-ns{order:1}.order-2-ns{order:2}.order-3-ns{order:3}.order-4-ns{order:4}.order-5-ns{order:5}.order-6-ns{order:6}.order-7-ns{order:7}.order-8-ns{order:8}.order-last-ns{order:99999}.flex-grow-0-ns{flex-grow:0}.flex-grow-1-ns{flex-grow:1}.flex-shrink-0-ns{flex-shrink:0}.flex-shrink-1-ns{flex-shrink:1}.fl-ns{float:left}.fl-ns,.fr-ns{_display:inline}.fr-ns{float:right}.fn-ns{float:none}.i-ns{font-style:italic}.fs-normal-ns{font-style:normal}.normal-ns{font-weight:400}.b-ns{font-weight:700}.fw1-ns{font-weight:100}.fw2-ns{font-weight:200}.fw3-ns{font-weight:300}.fw4-ns{font-weight:400}.fw5-ns{font-weight:500}.fw6-ns{font-weight:600}.fw7-ns{font-weight:700}.fw8-ns{font-weight:800}.fw9-ns{font-weight:900}.h1-ns{height:1rem}.h2-ns{height:2rem}.h3-ns{height:4rem}.h4-ns{height:8rem}.h5-ns{height:16rem}.h-25-ns{height:25%}.h-50-ns{height:50%}.h-75-ns{height:75%}.h-100-ns{height:100%}.min-h-100-ns{min-height:100%}.vh-25-ns{height:25vh}.vh-50-ns{height:50vh}.vh-75-ns{height:75vh}.vh-100-ns{height:100vh}.min-vh-100-ns{min-height:100vh}.h-auto-ns{height:auto}.h-inherit-ns{height:inherit}.tracked-ns{letter-spacing:.1em}.tracked-tight-ns{letter-spacing:-.05em}.tracked-mega-ns{letter-spacing:.25em}.lh-solid-ns{line-height:1}.lh-title-ns{line-height:1.25}.lh-copy-ns{line-height:1.5}.mw-100-ns{max-width:100%}.mw1-ns{max-width:1rem}.mw2-ns{max-width:2rem}.mw3-ns{max-width:4rem}.mw4-ns{max-width:8rem}.mw5-ns{max-width:16rem}.mw6-ns{max-width:32rem}.mw7-ns{max-width:48rem}.mw8-ns{max-width:64rem}.mw9-ns{max-width:96rem}.mw-none-ns{max-width:none}.w1-ns{width:1rem}.w2-ns{width:2rem}.w3-ns{width:4rem}.w4-ns{width:8rem}.w5-ns{width:16rem}.w-10-ns{width:10%}.w-20-ns{width:20%}.w-25-ns{width:25%}.w-30-ns{width:30%}.w-33-ns{width:33%}.w-34-ns{width:34%}.w-40-ns{width:40%}.w-50-ns{width:50%}.w-60-ns{width:60%}.w-70-ns{width:70%}.w-75-ns{width:75%}.w-80-ns{width:80%}.w-90-ns{width:90%}.w-100-ns{width:100%}.w-third-ns{width:33.33333%}.w-two-thirds-ns{width:66.66667%}.w-auto-ns{width:auto}.overflow-visible-ns{overflow:visible}.overflow-hidden-ns{overflow:hidden}.overflow-scroll-ns{overflow:scroll}.overflow-auto-ns{overflow:auto}.overflow-x-visible-ns{overflow-x:visible}.overflow-x-hidden-ns{overflow-x:hidden}.overflow-x-scroll-ns{overflow-x:scroll}.overflow-x-auto-ns{overflow-x:auto}.overflow-y-visible-ns{overflow-y:visible}.overflow-y-hidden-ns{overflow-y:hidden}.overflow-y-scroll-ns{overflow-y:scroll}.overflow-y-auto-ns{overflow-y:auto}.static-ns{position:static}.relative-ns{position:relative}.absolute-ns{position:absolute}.fixed-ns{position:fixed}.rotate-45-ns{-webkit-transform:rotate(45deg);transform:rotate(45deg)}.rotate-90-ns{-webkit-transform:rotate(90deg);transform:rotate(90deg)}.rotate-135-ns{-webkit-transform:rotate(135deg);transform:rotate(135deg)}.rotate-180-ns{-webkit-transform:rotate(180deg);transform:rotate(180deg)}.rotate-225-ns{-webkit-transform:rotate(225deg);transform:rotate(225deg)}.rotate-270-ns{-webkit-transform:rotate(270deg);transform:rotate(270deg)}.rotate-315-ns{-webkit-transform:rotate(315deg);transform:rotate(315deg)}.pa0-ns{padding:0}.pa1-ns{padding:.25rem}.pa2-ns{padding:.5rem}.pa3-ns{padding:1rem}.pa4-ns{padding:2rem}.pa5-ns{padding:4rem}.pa6-ns{padding:8rem}.pa7-ns{padding:16rem}.pl0-ns{padding-left:0}.pl1-ns{padding-left:.25rem}.pl2-ns{padding-left:.5rem}.pl3-ns{padding-left:1rem}.pl4-ns{padding-left:2rem}.pl5-ns{padding-left:4rem}.pl6-ns{padding-left:8rem}.pl7-ns{padding-left:16rem}.pr0-ns{padding-right:0}.pr1-ns{padding-right:.25rem}.pr2-ns{padding-right:.5rem}.pr3-ns{padding-right:1rem}.pr4-ns{padding-right:2rem}.pr5-ns{padding-right:4rem}.pr6-ns{padding-right:8rem}.pr7-ns{padding-right:16rem}.pb0-ns{padding-bottom:0}.pb1-ns{padding-bottom:.25rem}.pb2-ns{padding-bottom:.5rem}.pb3-ns{padding-bottom:1rem}.pb4-ns{padding-bottom:2rem}.pb5-ns{padding-bottom:4rem}.pb6-ns{padding-bottom:8rem}.pb7-ns{padding-bottom:16rem}.pt0-ns{padding-top:0}.pt1-ns{padding-top:.25rem}.pt2-ns{padding-top:.5rem}.pt3-ns{padding-top:1rem}.pt4-ns{padding-top:2rem}.pt5-ns{padding-top:4rem}.pt6-ns{padding-top:8rem}.pt7-ns{padding-top:16rem}.pv0-ns{padding-top:0;padding-bottom:0}.pv1-ns{padding-top:.25rem;padding-bottom:.25rem}.pv2-ns{padding-top:.5rem;padding-bottom:.5rem}.pv3-ns{padding-top:1rem;padding-bottom:1rem}.pv4-ns{padding-top:2rem;padding-bottom:2rem}.pv5-ns{padding-top:4rem;padding-bottom:4rem}.pv6-ns{padding-top:8rem;padding-bottom:8rem}.pv7-ns{padding-top:16rem;padding-bottom:16rem}.ph0-ns{padding-left:0;padding-right:0}.ph1-ns{padding-left:.25rem;padding-right:.25rem}.ph2-ns{padding-left:.5rem;padding-right:.5rem}.ph3-ns{padding-left:1rem;padding-right:1rem}.ph4-ns{padding-left:2rem;padding-right:2rem}.ph5-ns{padding-left:4rem;padding-right:4rem}.ph6-ns{padding-left:8rem;padding-right:8rem}.ph7-ns{padding-left:16rem;padding-right:16rem}.ma0-ns{margin:0}.ma1-ns{margin:.25rem}.ma2-ns{margin:.5rem}.ma3-ns{margin:1rem}.ma4-ns{margin:2rem}.ma5-ns{margin:4rem}.ma6-ns{margin:8rem}.ma7-ns{margin:16rem}.ml0-ns{margin-left:0}.ml1-ns{margin-left:.25rem}.ml2-ns{margin-left:.5rem}.ml3-ns{margin-left:1rem}.ml4-ns{margin-left:2rem}.ml5-ns{margin-left:4rem}.ml6-ns{margin-left:8rem}.ml7-ns{margin-left:16rem}.mr0-ns{margin-right:0}.mr1-ns{margin-right:.25rem}.mr2-ns{margin-right:.5rem}.mr3-ns{margin-right:1rem}.mr4-ns{margin-right:2rem}.mr5-ns{margin-right:4rem}.mr6-ns{margin-right:8rem}.mr7-ns{margin-right:16rem}.mb0-ns{margin-bottom:0}.mb1-ns{margin-bottom:.25rem}.mb2-ns{margin-bottom:.5rem}.mb3-ns{margin-bottom:1rem}.mb4-ns{margin-bottom:2rem}.mb5-ns{margin-bottom:4rem}.mb6-ns{margin-bottom:8rem}.mb7-ns{margin-bottom:16rem}.mt0-ns{margin-top:0}.mt1-ns{margin-top:.25rem}.mt2-ns{margin-top:.5rem}.mt3-ns{margin-top:1rem}.mt4-ns{margin-top:2rem}.mt5-ns{margin-top:4rem}.mt6-ns{margin-top:8rem}.mt7-ns{margin-top:16rem}.mv0-ns{margin-top:0;margin-bottom:0}.mv1-ns{margin-top:.25rem;margin-bottom:.25rem}.mv2-ns{margin-top:.5rem;margin-bottom:.5rem}.mv3-ns{margin-top:1rem;margin-bottom:1rem}.mv4-ns{margin-top:2rem;margin-bottom:2rem}.mv5-ns{margin-top:4rem;margin-bottom:4rem}.mv6-ns{margin-top:8rem;margin-bottom:8rem}.mv7-ns{margin-top:16rem;margin-bottom:16rem}.mh0-ns{margin-left:0;margin-right:0}.mh1-ns{margin-left:.25rem;margin-right:.25rem}.mh2-ns{margin-left:.5rem;margin-right:.5rem}.mh3-ns{margin-left:1rem;margin-right:1rem}.mh4-ns{margin-left:2rem;margin-right:2rem}.mh5-ns{margin-left:4rem;margin-right:4rem}.mh6-ns{margin-left:8rem;margin-right:8rem}.mh7-ns{margin-left:16rem;margin-right:16rem}.na1-ns{margin:-.25rem}.na2-ns{margin:-.5rem}.na3-ns{margin:-1rem}.na4-ns{margin:-2rem}.na5-ns{margin:-4rem}.na6-ns{margin:-8rem}.na7-ns{margin:-16rem}.nl1-ns{margin-left:-.25rem}.nl2-ns{margin-left:-.5rem}.nl3-ns{margin-left:-1rem}.nl4-ns{margin-left:-2rem}.nl5-ns{margin-left:-4rem}.nl6-ns{margin-left:-8rem}.nl7-ns{margin-left:-16rem}.nr1-ns{margin-right:-.25rem}.nr2-ns{margin-right:-.5rem}.nr3-ns{margin-right:-1rem}.nr4-ns{margin-right:-2rem}.nr5-ns{margin-right:-4rem}.nr6-ns{margin-right:-8rem}.nr7-ns{margin-right:-16rem}.nb1-ns{margin-bottom:-.25rem}.nb2-ns{margin-bottom:-.5rem}.nb3-ns{margin-bottom:-1rem}.nb4-ns{margin-bottom:-2rem}.nb5-ns{margin-bottom:-4rem}.nb6-ns{margin-bottom:-8rem}.nb7-ns{margin-bottom:-16rem}.nt1-ns{margin-top:-.25rem}.nt2-ns{margin-top:-.5rem}.nt3-ns{margin-top:-1rem}.nt4-ns{margin-top:-2rem}.nt5-ns{margin-top:-4rem}.nt6-ns{margin-top:-8rem}.nt7-ns{margin-top:-16rem}.strike-ns{text-decoration:line-through}.underline-ns{text-decoration:underline}.no-underline-ns{text-decoration:none}.tl-ns{text-align:left}.tr-ns{text-align:right}.tc-ns{text-align:center}.tj-ns{text-align:justify}.ttc-ns{text-transform:capitalize}.ttl-ns{text-transform:lowercase}.ttu-ns{text-transform:uppercase}.ttn-ns{text-transform:none}.f-6-ns,.f-headline-ns{font-size:6rem}.f-5-ns,.f-subheadline-ns{font-size:5rem}.f1-ns{font-size:3rem}.f2-ns{font-size:2.25rem}.f3-ns{font-size:1.5rem}.f4-ns{font-size:1.25rem}.f5-ns{font-size:1rem}.f6-ns{font-size:.875rem}.f7-ns{font-size:.75rem}.measure-ns{max-width:30em}.measure-wide-ns{max-width:34em}.measure-narrow-ns{max-width:20em}.indent-ns{text-indent:1em;margin-top:0;margin-bottom:0}.small-caps-ns{font-variant:small-caps}.truncate-ns{white-space:nowrap;overflow:hidden;text-overflow:ellipsis}.center-ns{margin-left:auto}.center-ns,.mr-auto-ns{margin-right:auto}.ml-auto-ns{margin-left:auto}.clip-ns{position:fixed!important;_position:absolute!important;clip:rect(1px 1px 1px 1px);clip:rect(1px,1px,1px,1px)}.ws-normal-ns{white-space:normal}.nowrap-ns{white-space:nowrap}.pre-ns{white-space:pre}.v-base-ns{vertical-align:baseline}.v-mid-ns{vertical-align:middle}.v-top-ns{vertical-align:top}.v-btm-ns{vertical-align:bottom}}@media screen and (min-width:30em) and (max-width:60em){.aspect-ratio-m{height:0;position:relative}.aspect-ratio--16x9-m{padding-bottom:56.25%}.aspect-ratio--9x16-m{padding-bottom:177.77%}.aspect-ratio--4x3-m{padding-bottom:75%}.aspect-ratio--3x4-m{padding-bottom:133.33%}.aspect-ratio--6x4-m{padding-bottom:66.6%}.aspect-ratio--4x6-m{padding-bottom:150%}.aspect-ratio--8x5-m{padding-bottom:62.5%}.aspect-ratio--5x8-m{padding-bottom:160%}.aspect-ratio--7x5-m{padding-bottom:71.42%}.aspect-ratio--5x7-m{padding-bottom:140%}.aspect-ratio--1x1-m{padding-bottom:100%}.aspect-ratio--object-m{position:absolute;top:0;right:0;bottom:0;left:0;width:100%;height:100%;z-index:100}.cover-m{background-size:cover!important}.contain-m{background-size:contain!important}.bg-center-m{background-position:50%}.bg-center-m,.bg-top-m{background-repeat:no-repeat}.bg-top-m{background-position:top}.bg-right-m{background-position:100%}.bg-bottom-m,.bg-right-m{background-repeat:no-repeat}.bg-bottom-m{background-position:bottom}.bg-left-m{background-repeat:no-repeat;background-position:0}.outline-m{outline:1px solid}.outline-transparent-m{outline:1px solid transparent}.outline-0-m{outline:0}.ba-m{border-style:solid;border-width:1px}.bt-m{border-top-style:solid;border-top-width:1px}.br-m{border-right-style:solid;border-right-width:1px}.bb-m{border-bottom-style:solid;border-bottom-width:1px}.bl-m{border-left-style:solid;border-left-width:1px}.bn-m{border-style:none;border-width:0}.br0-m{border-radius:0}.br1-m{border-radius:.125rem}.br2-m{border-radius:.25rem}.br3-m{border-radius:.5rem}.br4-m{border-radius:1rem}.br-100-m{border-radius:100%}.br-pill-m{border-radius:9999px}.br--bottom-m{border-top-left-radius:0;border-top-right-radius:0}.br--top-m{border-bottom-right-radius:0}.br--right-m,.br--top-m{border-bottom-left-radius:0}.br--right-m{border-top-left-radius:0}.br--left-m{border-top-right-radius:0;border-bottom-right-radius:0}.b--dotted-m{border-style:dotted}.b--dashed-m{border-style:dashed}.b--solid-m{border-style:solid}.b--none-m{border-style:none}.bw0-m{border-width:0}.bw1-m{border-width:.125rem}.bw2-m{border-width:.25rem}.bw3-m{border-width:.5rem}.bw4-m{border-width:1rem}.bw5-m{border-width:2rem}.bt-0-m{border-top-width:0}.br-0-m{border-right-width:0}.bb-0-m{border-bottom-width:0}.bl-0-m{border-left-width:0}.shadow-1-m{box-shadow:0 0 4px 2px rgba(0,0,0,.2)}.shadow-2-m{box-shadow:0 0 8px 2px rgba(0,0,0,.2)}.shadow-3-m{box-shadow:2px 2px 4px 2px rgba(0,0,0,.2)}.shadow-4-m{box-shadow:2px 2px 8px 0 rgba(0,0,0,.2)}.shadow-5-m{box-shadow:4px 4px 8px 0 rgba(0,0,0,.2)}.top-0-m{top:0}.left-0-m{left:0}.right-0-m{right:0}.bottom-0-m{bottom:0}.top-1-m{top:1rem}.left-1-m{left:1rem}.right-1-m{right:1rem}.bottom-1-m{bottom:1rem}.top-2-m{top:2rem}.left-2-m{left:2rem}.right-2-m{right:2rem}.bottom-2-m{bottom:2rem}.top--1-m{top:-1rem}.right--1-m{right:-1rem}.bottom--1-m{bottom:-1rem}.left--1-m{left:-1rem}.top--2-m{top:-2rem}.right--2-m{right:-2rem}.bottom--2-m{bottom:-2rem}.left--2-m{left:-2rem}.absolute--fill-m{top:0;right:0;bottom:0;left:0}.cl-m{clear:left}.cr-m{clear:right}.cb-m{clear:both}.cn-m{clear:none}.dn-m{display:none}.di-m{display:inline}.db-m{display:block}.dib-m{display:inline-block}.dit-m{display:inline-table}.dt-m{display:table}.dtc-m{display:table-cell}.dt-row-m{display:table-row}.dt-row-group-m{display:table-row-group}.dt-column-m{display:table-column}.dt-column-group-m{display:table-column-group}.dt--fixed-m{table-layout:fixed;width:100%}.flex-m{display:flex}.inline-flex-m{display:inline-flex}.flex-auto-m{flex:1 1 auto;min-width:0;min-height:0}.flex-none-m{flex:none}.flex-column-m{flex-direction:column}.flex-row-m{flex-direction:row}.flex-wrap-m{flex-wrap:wrap}.flex-nowrap-m{flex-wrap:nowrap}.flex-wrap-reverse-m{flex-wrap:wrap-reverse}.flex-column-reverse-m{flex-direction:column-reverse}.flex-row-reverse-m{flex-direction:row-reverse}.items-start-m{align-items:flex-start}.items-end-m{align-items:flex-end}.items-center-m{align-items:center}.items-baseline-m{align-items:baseline}.items-stretch-m{align-items:stretch}.self-start-m{align-self:flex-start}.self-end-m{align-self:flex-end}.self-center-m{align-self:center}.self-baseline-m{align-self:baseline}.self-stretch-m{align-self:stretch}.justify-start-m{justify-content:flex-start}.justify-end-m{justify-content:flex-end}.justify-center-m{justify-content:center}.justify-between-m{justify-content:space-between}.justify-around-m{justify-content:space-around}.content-start-m{align-content:flex-start}.content-end-m{align-content:flex-end}.content-center-m{align-content:center}.content-between-m{align-content:space-between}.content-around-m{align-content:space-around}.content-stretch-m{align-content:stretch}.order-0-m{order:0}.order-1-m{order:1}.order-2-m{order:2}.order-3-m{order:3}.order-4-m{order:4}.order-5-m{order:5}.order-6-m{order:6}.order-7-m{order:7}.order-8-m{order:8}.order-last-m{order:99999}.flex-grow-0-m{flex-grow:0}.flex-grow-1-m{flex-grow:1}.flex-shrink-0-m{flex-shrink:0}.flex-shrink-1-m{flex-shrink:1}.fl-m{float:left}.fl-m,.fr-m{_display:inline}.fr-m{float:right}.fn-m{float:none}.i-m{font-style:italic}.fs-normal-m{font-style:normal}.normal-m{font-weight:400}.b-m{font-weight:700}.fw1-m{font-weight:100}.fw2-m{font-weight:200}.fw3-m{font-weight:300}.fw4-m{font-weight:400}.fw5-m{font-weight:500}.fw6-m{font-weight:600}.fw7-m{font-weight:700}.fw8-m{font-weight:800}.fw9-m{font-weight:900}.h1-m{height:1rem}.h2-m{height:2rem}.h3-m{height:4rem}.h4-m{height:8rem}.h5-m{height:16rem}.h-25-m{height:25%}.h-50-m{height:50%}.h-75-m{height:75%}.h-100-m{height:100%}.min-h-100-m{min-height:100%}.vh-25-m{height:25vh}.vh-50-m{height:50vh}.vh-75-m{height:75vh}.vh-100-m{height:100vh}.min-vh-100-m{min-height:100vh}.h-auto-m{height:auto}.h-inherit-m{height:inherit}.tracked-m{letter-spacing:.1em}.tracked-tight-m{letter-spacing:-.05em}.tracked-mega-m{letter-spacing:.25em}.lh-solid-m{line-height:1}.lh-title-m{line-height:1.25}.lh-copy-m{line-height:1.5}.mw-100-m{max-width:100%}.mw1-m{max-width:1rem}.mw2-m{max-width:2rem}.mw3-m{max-width:4rem}.mw4-m{max-width:8rem}.mw5-m{max-width:16rem}.mw6-m{max-width:32rem}.mw7-m{max-width:48rem}.mw8-m{max-width:64rem}.mw9-m{max-width:96rem}.mw-none-m{max-width:none}.w1-m{width:1rem}.w2-m{width:2rem}.w3-m{width:4rem}.w4-m{width:8rem}.w5-m{width:16rem}.w-10-m{width:10%}.w-20-m{width:20%}.w-25-m{width:25%}.w-30-m{width:30%}.w-33-m{width:33%}.w-34-m{width:34%}.w-40-m{width:40%}.w-50-m{width:50%}.w-60-m{width:60%}.w-70-m{width:70%}.w-75-m{width:75%}.w-80-m{width:80%}.w-90-m{width:90%}.w-100-m{width:100%}.w-third-m{width:33.33333%}.w-two-thirds-m{width:66.66667%}.w-auto-m{width:auto}.overflow-visible-m{overflow:visible}.overflow-hidden-m{overflow:hidden}.overflow-scroll-m{overflow:scroll}.overflow-auto-m{overflow:auto}.overflow-x-visible-m{overflow-x:visible}.overflow-x-hidden-m{overflow-x:hidden}.overflow-x-scroll-m{overflow-x:scroll}.overflow-x-auto-m{overflow-x:auto}.overflow-y-visible-m{overflow-y:visible}.overflow-y-hidden-m{overflow-y:hidden}.overflow-y-scroll-m{overflow-y:scroll}.overflow-y-auto-m{overflow-y:auto}.static-m{position:static}.relative-m{position:relative}.absolute-m{position:absolute}.fixed-m{position:fixed}.rotate-45-m{-webkit-transform:rotate(45deg);transform:rotate(45deg)}.rotate-90-m{-webkit-transform:rotate(90deg);transform:rotate(90deg)}.rotate-135-m{-webkit-transform:rotate(135deg);transform:rotate(135deg)}.rotate-180-m{-webkit-transform:rotate(180deg);transform:rotate(180deg)}.rotate-225-m{-webkit-transform:rotate(225deg);transform:rotate(225deg)}.rotate-270-m{-webkit-transform:rotate(270deg);transform:rotate(270deg)}.rotate-315-m{-webkit-transform:rotate(315deg);transform:rotate(315deg)}.pa0-m{padding:0}.pa1-m{padding:.25rem}.pa2-m{padding:.5rem}.pa3-m{padding:1rem}.pa4-m{padding:2rem}.pa5-m{padding:4rem}.pa6-m{padding:8rem}.pa7-m{padding:16rem}.pl0-m{padding-left:0}.pl1-m{padding-left:.25rem}.pl2-m{padding-left:.5rem}.pl3-m{padding-left:1rem}.pl4-m{padding-left:2rem}.pl5-m{padding-left:4rem}.pl6-m{padding-left:8rem}.pl7-m{padding-left:16rem}.pr0-m{padding-right:0}.pr1-m{padding-right:.25rem}.pr2-m{padding-right:.5rem}.pr3-m{padding-right:1rem}.pr4-m{padding-right:2rem}.pr5-m{padding-right:4rem}.pr6-m{padding-right:8rem}.pr7-m{padding-right:16rem}.pb0-m{padding-bottom:0}.pb1-m{padding-bottom:.25rem}.pb2-m{padding-bottom:.5rem}.pb3-m{padding-bottom:1rem}.pb4-m{padding-bottom:2rem}.pb5-m{padding-bottom:4rem}.pb6-m{padding-bottom:8rem}.pb7-m{padding-bottom:16rem}.pt0-m{padding-top:0}.pt1-m{padding-top:.25rem}.pt2-m{padding-top:.5rem}.pt3-m{padding-top:1rem}.pt4-m{padding-top:2rem}.pt5-m{padding-top:4rem}.pt6-m{padding-top:8rem}.pt7-m{padding-top:16rem}.pv0-m{padding-top:0;padding-bottom:0}.pv1-m{padding-top:.25rem;padding-bottom:.25rem}.pv2-m{padding-top:.5rem;padding-bottom:.5rem}.pv3-m{padding-top:1rem;padding-bottom:1rem}.pv4-m{padding-top:2rem;padding-bottom:2rem}.pv5-m{padding-top:4rem;padding-bottom:4rem}.pv6-m{padding-top:8rem;padding-bottom:8rem}.pv7-m{padding-top:16rem;padding-bottom:16rem}.ph0-m{padding-left:0;padding-right:0}.ph1-m{padding-left:.25rem;padding-right:.25rem}.ph2-m{padding-left:.5rem;padding-right:.5rem}.ph3-m{padding-left:1rem;padding-right:1rem}.ph4-m{padding-left:2rem;padding-right:2rem}.ph5-m{padding-left:4rem;padding-right:4rem}.ph6-m{padding-left:8rem;padding-right:8rem}.ph7-m{padding-left:16rem;padding-right:16rem}.ma0-m{margin:0}.ma1-m{margin:.25rem}.ma2-m{margin:.5rem}.ma3-m{margin:1rem}.ma4-m{margin:2rem}.ma5-m{margin:4rem}.ma6-m{margin:8rem}.ma7-m{margin:16rem}.ml0-m{margin-left:0}.ml1-m{margin-left:.25rem}.ml2-m{margin-left:.5rem}.ml3-m{margin-left:1rem}.ml4-m{margin-left:2rem}.ml5-m{margin-left:4rem}.ml6-m{margin-left:8rem}.ml7-m{margin-left:16rem}.mr0-m{margin-right:0}.mr1-m{margin-right:.25rem}.mr2-m{margin-right:.5rem}.mr3-m{margin-right:1rem}.mr4-m{margin-right:2rem}.mr5-m{margin-right:4rem}.mr6-m{margin-right:8rem}.mr7-m{margin-right:16rem}.mb0-m{margin-bottom:0}.mb1-m{margin-bottom:.25rem}.mb2-m{margin-bottom:.5rem}.mb3-m{margin-bottom:1rem}.mb4-m{margin-bottom:2rem}.mb5-m{margin-bottom:4rem}.mb6-m{margin-bottom:8rem}.mb7-m{margin-bottom:16rem}.mt0-m{margin-top:0}.mt1-m{margin-top:.25rem}.mt2-m{margin-top:.5rem}.mt3-m{margin-top:1rem}.mt4-m{margin-top:2rem}.mt5-m{margin-top:4rem}.mt6-m{margin-top:8rem}.mt7-m{margin-top:16rem}.mv0-m{margin-top:0;margin-bottom:0}.mv1-m{margin-top:.25rem;margin-bottom:.25rem}.mv2-m{margin-top:.5rem;margin-bottom:.5rem}.mv3-m{margin-top:1rem;margin-bottom:1rem}.mv4-m{margin-top:2rem;margin-bottom:2rem}.mv5-m{margin-top:4rem;margin-bottom:4rem}.mv6-m{margin-top:8rem;margin-bottom:8rem}.mv7-m{margin-top:16rem;margin-bottom:16rem}.mh0-m{margin-left:0;margin-right:0}.mh1-m{margin-left:.25rem;margin-right:.25rem}.mh2-m{margin-left:.5rem;margin-right:.5rem}.mh3-m{margin-left:1rem;margin-right:1rem}.mh4-m{margin-left:2rem;margin-right:2rem}.mh5-m{margin-left:4rem;margin-right:4rem}.mh6-m{margin-left:8rem;margin-right:8rem}.mh7-m{margin-left:16rem;margin-right:16rem}.na1-m{margin:-.25rem}.na2-m{margin:-.5rem}.na3-m{margin:-1rem}.na4-m{margin:-2rem}.na5-m{margin:-4rem}.na6-m{margin:-8rem}.na7-m{margin:-16rem}.nl1-m{margin-left:-.25rem}.nl2-m{margin-left:-.5rem}.nl3-m{margin-left:-1rem}.nl4-m{margin-left:-2rem}.nl5-m{margin-left:-4rem}.nl6-m{margin-left:-8rem}.nl7-m{margin-left:-16rem}.nr1-m{margin-right:-.25rem}.nr2-m{margin-right:-.5rem}.nr3-m{margin-right:-1rem}.nr4-m{margin-right:-2rem}.nr5-m{margin-right:-4rem}.nr6-m{margin-right:-8rem}.nr7-m{margin-right:-16rem}.nb1-m{margin-bottom:-.25rem}.nb2-m{margin-bottom:-.5rem}.nb3-m{margin-bottom:-1rem}.nb4-m{margin-bottom:-2rem}.nb5-m{margin-bottom:-4rem}.nb6-m{margin-bottom:-8rem}.nb7-m{margin-bottom:-16rem}.nt1-m{margin-top:-.25rem}.nt2-m{margin-top:-.5rem}.nt3-m{margin-top:-1rem}.nt4-m{margin-top:-2rem}.nt5-m{margin-top:-4rem}.nt6-m{margin-top:-8rem}.nt7-m{margin-top:-16rem}.strike-m{text-decoration:line-through}.underline-m{text-decoration:underline}.no-underline-m{text-decoration:none}.tl-m{text-align:left}.tr-m{text-align:right}.tc-m{text-align:center}.tj-m{text-align:justify}.ttc-m{text-transform:capitalize}.ttl-m{text-transform:lowercase}.ttu-m{text-transform:uppercase}.ttn-m{text-transform:none}.f-6-m,.f-headline-m{font-size:6rem}.f-5-m,.f-subheadline-m{font-size:5rem}.f1-m{font-size:3rem}.f2-m{font-size:2.25rem}.f3-m{font-size:1.5rem}.f4-m{font-size:1.25rem}.f5-m{font-size:1rem}.f6-m{font-size:.875rem}.f7-m{font-size:.75rem}.measure-m{max-width:30em}.measure-wide-m{max-width:34em}.measure-narrow-m{max-width:20em}.indent-m{text-indent:1em;margin-top:0;margin-bottom:0}.small-caps-m{font-variant:small-caps}.truncate-m{white-space:nowrap;overflow:hidden;text-overflow:ellipsis}.center-m{margin-left:auto}.center-m,.mr-auto-m{margin-right:auto}.ml-auto-m{margin-left:auto}.clip-m{position:fixed!important;_position:absolute!important;clip:rect(1px 1px 1px 1px);clip:rect(1px,1px,1px,1px)}.ws-normal-m{white-space:normal}.nowrap-m{white-space:nowrap}.pre-m{white-space:pre}.v-base-m{vertical-align:baseline}.v-mid-m{vertical-align:middle}.v-top-m{vertical-align:top}.v-btm-m{vertical-align:bottom}}@media screen and (min-width:60em){.aspect-ratio-l{height:0;position:relative}.aspect-ratio--16x9-l{padding-bottom:56.25%}.aspect-ratio--9x16-l{padding-bottom:177.77%}.aspect-ratio--4x3-l{padding-bottom:75%}.aspect-ratio--3x4-l{padding-bottom:133.33%}.aspect-ratio--6x4-l{padding-bottom:66.6%}.aspect-ratio--4x6-l{padding-bottom:150%}.aspect-ratio--8x5-l{padding-bottom:62.5%}.aspect-ratio--5x8-l{padding-bottom:160%}.aspect-ratio--7x5-l{padding-bottom:71.42%}.aspect-ratio--5x7-l{padding-bottom:140%}.aspect-ratio--1x1-l{padding-bottom:100%}.aspect-ratio--object-l{position:absolute;top:0;right:0;bottom:0;left:0;width:100%;height:100%;z-index:100}.cover-l{background-size:cover!important}.contain-l{background-size:contain!important}.bg-center-l{background-position:50%}.bg-center-l,.bg-top-l{background-repeat:no-repeat}.bg-top-l{background-position:top}.bg-right-l{background-position:100%}.bg-bottom-l,.bg-right-l{background-repeat:no-repeat}.bg-bottom-l{background-position:bottom}.bg-left-l{background-repeat:no-repeat;background-position:0}.outline-l{outline:1px solid}.outline-transparent-l{outline:1px solid transparent}.outline-0-l{outline:0}.ba-l{border-style:solid;border-width:1px}.bt-l{border-top-style:solid;border-top-width:1px}.br-l{border-right-style:solid;border-right-width:1px}.bb-l{border-bottom-style:solid;border-bottom-width:1px}.bl-l{border-left-style:solid;border-left-width:1px}.bn-l{border-style:none;border-width:0}.br0-l{border-radius:0}.br1-l{border-radius:.125rem}.br2-l{border-radius:.25rem}.br3-l{border-radius:.5rem}.br4-l{border-radius:1rem}.br-100-l{border-radius:100%}.br-pill-l{border-radius:9999px}.br--bottom-l{border-top-left-radius:0;border-top-right-radius:0}.br--top-l{border-bottom-right-radius:0}.br--right-l,.br--top-l{border-bottom-left-radius:0}.br--right-l{border-top-left-radius:0}.br--left-l{border-top-right-radius:0;border-bottom-right-radius:0}.b--dotted-l{border-style:dotted}.b--dashed-l{border-style:dashed}.b--solid-l{border-style:solid}.b--none-l{border-style:none}.bw0-l{border-width:0}.bw1-l{border-width:.125rem}.bw2-l{border-width:.25rem}.bw3-l{border-width:.5rem}.bw4-l{border-width:1rem}.bw5-l{border-width:2rem}.bt-0-l{border-top-width:0}.br-0-l{border-right-width:0}.bb-0-l{border-bottom-width:0}.bl-0-l{border-left-width:0}.shadow-1-l{box-shadow:0 0 4px 2px rgba(0,0,0,.2)}.shadow-2-l{box-shadow:0 0 8px 2px rgba(0,0,0,.2)}.shadow-3-l{box-shadow:2px 2px 4px 2px rgba(0,0,0,.2)}.shadow-4-l{box-shadow:2px 2px 8px 0 rgba(0,0,0,.2)}.shadow-5-l{box-shadow:4px 4px 8px 0 rgba(0,0,0,.2)}.top-0-l{top:0}.left-0-l{left:0}.right-0-l{right:0}.bottom-0-l{bottom:0}.top-1-l{top:1rem}.left-1-l{left:1rem}.right-1-l{right:1rem}.bottom-1-l{bottom:1rem}.top-2-l{top:2rem}.left-2-l{left:2rem}.right-2-l{right:2rem}.bottom-2-l{bottom:2rem}.top--1-l{top:-1rem}.right--1-l{right:-1rem}.bottom--1-l{bottom:-1rem}.left--1-l{left:-1rem}.top--2-l{top:-2rem}.right--2-l{right:-2rem}.bottom--2-l{bottom:-2rem}.left--2-l{left:-2rem}.absolute--fill-l{top:0;right:0;bottom:0;left:0}.cl-l{clear:left}.cr-l{clear:right}.cb-l{clear:both}.cn-l{clear:none}.dn-l{display:none}.di-l{display:inline}.db-l{display:block}.dib-l{display:inline-block}.dit-l{display:inline-table}.dt-l{display:table}.dtc-l{display:table-cell}.dt-row-l{display:table-row}.dt-row-group-l{display:table-row-group}.dt-column-l{display:table-column}.dt-column-group-l{display:table-column-group}.dt--fixed-l{table-layout:fixed;width:100%}.flex-l{display:flex}.inline-flex-l{display:inline-flex}.flex-auto-l{flex:1 1 auto;min-width:0;min-height:0}.flex-none-l{flex:none}.flex-column-l{flex-direction:column}.flex-row-l{flex-direction:row}.flex-wrap-l{flex-wrap:wrap}.flex-nowrap-l{flex-wrap:nowrap}.flex-wrap-reverse-l{flex-wrap:wrap-reverse}.flex-column-reverse-l{flex-direction:column-reverse}.flex-row-reverse-l{flex-direction:row-reverse}.items-start-l{align-items:flex-start}.items-end-l{align-items:flex-end}.items-center-l{align-items:center}.items-baseline-l{align-items:baseline}.items-stretch-l{align-items:stretch}.self-start-l{align-self:flex-start}.self-end-l{align-self:flex-end}.self-center-l{align-self:center}.self-baseline-l{align-self:baseline}.self-stretch-l{align-self:stretch}.justify-start-l{justify-content:flex-start}.justify-end-l{justify-content:flex-end}.justify-center-l{justify-content:center}.justify-between-l{justify-content:space-between}.justify-around-l{justify-content:space-around}.content-start-l{align-content:flex-start}.content-end-l{align-content:flex-end}.content-center-l{align-content:center}.content-between-l{align-content:space-between}.content-around-l{align-content:space-around}.content-stretch-l{align-content:stretch}.order-0-l{order:0}.order-1-l{order:1}.order-2-l{order:2}.order-3-l{order:3}.order-4-l{order:4}.order-5-l{order:5}.order-6-l{order:6}.order-7-l{order:7}.order-8-l{order:8}.order-last-l{order:99999}.flex-grow-0-l{flex-grow:0}.flex-grow-1-l{flex-grow:1}.flex-shrink-0-l{flex-shrink:0}.flex-shrink-1-l{flex-shrink:1}.fl-l{float:left}.fl-l,.fr-l{_display:inline}.fr-l{float:right}.fn-l{float:none}.i-l{font-style:italic}.fs-normal-l{font-style:normal}.normal-l{font-weight:400}.b-l{font-weight:700}.fw1-l{font-weight:100}.fw2-l{font-weight:200}.fw3-l{font-weight:300}.fw4-l{font-weight:400}.fw5-l{font-weight:500}.fw6-l{font-weight:600}.fw7-l{font-weight:700}.fw8-l{font-weight:800}.fw9-l{font-weight:900}.h1-l{height:1rem}.h2-l{height:2rem}.h3-l{height:4rem}.h4-l{height:8rem}.h5-l{height:16rem}.h-25-l{height:25%}.h-50-l{height:50%}.h-75-l{height:75%}.h-100-l{height:100%}.min-h-100-l{min-height:100%}.vh-25-l{height:25vh}.vh-50-l{height:50vh}.vh-75-l{height:75vh}.vh-100-l{height:100vh}.min-vh-100-l{min-height:100vh}.h-auto-l{height:auto}.h-inherit-l{height:inherit}.tracked-l{letter-spacing:.1em}.tracked-tight-l{letter-spacing:-.05em}.tracked-mega-l{letter-spacing:.25em}.lh-solid-l{line-height:1}.lh-title-l{line-height:1.25}.lh-copy-l{line-height:1.5}.mw-100-l{max-width:100%}.mw1-l{max-width:1rem}.mw2-l{max-width:2rem}.mw3-l{max-width:4rem}.mw4-l{max-width:8rem}.mw5-l{max-width:16rem}.mw6-l{max-width:32rem}.mw7-l{max-width:48rem}.mw8-l{max-width:64rem}.mw9-l{max-width:96rem}.mw-none-l{max-width:none}.w1-l{width:1rem}.w2-l{width:2rem}.w3-l{width:4rem}.w4-l{width:8rem}.w5-l{width:16rem}.w-10-l{width:10%}.w-20-l{width:20%}.w-25-l{width:25%}.w-30-l{width:30%}.w-33-l{width:33%}.w-34-l{width:34%}.w-40-l{width:40%}.w-50-l{width:50%}.w-60-l{width:60%}.w-70-l{width:70%}.w-75-l{width:75%}.w-80-l{width:80%}.w-90-l{width:90%}.w-100-l{width:100%}.w-third-l{width:33.33333%}.w-two-thirds-l{width:66.66667%}.w-auto-l{width:auto}.overflow-visible-l{overflow:visible}.overflow-hidden-l{overflow:hidden}.overflow-scroll-l{overflow:scroll}.overflow-auto-l{overflow:auto}.overflow-x-visible-l{overflow-x:visible}.overflow-x-hidden-l{overflow-x:hidden}.overflow-x-scroll-l{overflow-x:scroll}.overflow-x-auto-l{overflow-x:auto}.overflow-y-visible-l{overflow-y:visible}.overflow-y-hidden-l{overflow-y:hidden}.overflow-y-scroll-l{overflow-y:scroll}.overflow-y-auto-l{overflow-y:auto}.static-l{position:static}.relative-l{position:relative}.absolute-l{position:absolute}.fixed-l{position:fixed}.rotate-45-l{-webkit-transform:rotate(45deg);transform:rotate(45deg)}.rotate-90-l{-webkit-transform:rotate(90deg);transform:rotate(90deg)}.rotate-135-l{-webkit-transform:rotate(135deg);transform:rotate(135deg)}.rotate-180-l{-webkit-transform:rotate(180deg);transform:rotate(180deg)}.rotate-225-l{-webkit-transform:rotate(225deg);transform:rotate(225deg)}.rotate-270-l{-webkit-transform:rotate(270deg);transform:rotate(270deg)}.rotate-315-l{-webkit-transform:rotate(315deg);transform:rotate(315deg)}.pa0-l{padding:0}.pa1-l{padding:.25rem}.pa2-l{padding:.5rem}.pa3-l{padding:1rem}.pa4-l{padding:2rem}.pa5-l{padding:4rem}.pa6-l{padding:8rem}.pa7-l{padding:16rem}.pl0-l{padding-left:0}.pl1-l{padding-left:.25rem}.pl2-l{padding-left:.5rem}.pl3-l{padding-left:1rem}.pl4-l{padding-left:2rem}.pl5-l{padding-left:4rem}.pl6-l{padding-left:8rem}.pl7-l{padding-left:16rem}.pr0-l{padding-right:0}.pr1-l{padding-right:.25rem}.pr2-l{padding-right:.5rem}.pr3-l{padding-right:1rem}.pr4-l{padding-right:2rem}.pr5-l{padding-right:4rem}.pr6-l{padding-right:8rem}.pr7-l{padding-right:16rem}.pb0-l{padding-bottom:0}.pb1-l{padding-bottom:.25rem}.pb2-l{padding-bottom:.5rem}.pb3-l{padding-bottom:1rem}.pb4-l{padding-bottom:2rem}.pb5-l{padding-bottom:4rem}.pb6-l{padding-bottom:8rem}.pb7-l{padding-bottom:16rem}.pt0-l{padding-top:0}.pt1-l{padding-top:.25rem}.pt2-l{padding-top:.5rem}.pt3-l{padding-top:1rem}.pt4-l{padding-top:2rem}.pt5-l{padding-top:4rem}.pt6-l{padding-top:8rem}.pt7-l{padding-top:16rem}.pv0-l{padding-top:0;padding-bottom:0}.pv1-l{padding-top:.25rem;padding-bottom:.25rem}.pv2-l{padding-top:.5rem;padding-bottom:.5rem}.pv3-l{padding-top:1rem;padding-bottom:1rem}.pv4-l{padding-top:2rem;padding-bottom:2rem}.pv5-l{padding-top:4rem;padding-bottom:4rem}.pv6-l{padding-top:8rem;padding-bottom:8rem}.pv7-l{padding-top:16rem;padding-bottom:16rem}.ph0-l{padding-left:0;padding-right:0}.ph1-l{padding-left:.25rem;padding-right:.25rem}.ph2-l{padding-left:.5rem;padding-right:.5rem}.ph3-l{padding-left:1rem;padding-right:1rem}.ph4-l{padding-left:2rem;padding-right:2rem}.ph5-l{padding-left:4rem;padding-right:4rem}.ph6-l{padding-left:8rem;padding-right:8rem}.ph7-l{padding-left:16rem;padding-right:16rem}.ma0-l{margin:0}.ma1-l{margin:.25rem}.ma2-l{margin:.5rem}.ma3-l{margin:1rem}.ma4-l{margin:2rem}.ma5-l{margin:4rem}.ma6-l{margin:8rem}.ma7-l{margin:16rem}.ml0-l{margin-left:0}.ml1-l{margin-left:.25rem}.ml2-l{margin-left:.5rem}.ml3-l{margin-left:1rem}.ml4-l{margin-left:2rem}.ml5-l{margin-left:4rem}.ml6-l{margin-left:8rem}.ml7-l{margin-left:16rem}.mr0-l{margin-right:0}.mr1-l{margin-right:.25rem}.mr2-l{margin-right:.5rem}.mr3-l{margin-right:1rem}.mr4-l{margin-right:2rem}.mr5-l{margin-right:4rem}.mr6-l{margin-right:8rem}.mr7-l{margin-right:16rem}.mb0-l{margin-bottom:0}.mb1-l{margin-bottom:.25rem}.mb2-l{margin-bottom:.5rem}.mb3-l{margin-bottom:1rem}.mb4-l{margin-bottom:2rem}.mb5-l{margin-bottom:4rem}.mb6-l{margin-bottom:8rem}.mb7-l{margin-bottom:16rem}.mt0-l{margin-top:0}.mt1-l{margin-top:.25rem}.mt2-l{margin-top:.5rem}.mt3-l{margin-top:1rem}.mt4-l{margin-top:2rem}.mt5-l{margin-top:4rem}.mt6-l{margin-top:8rem}.mt7-l{margin-top:16rem}.mv0-l{margin-top:0;margin-bottom:0}.mv1-l{margin-top:.25rem;margin-bottom:.25rem}.mv2-l{margin-top:.5rem;margin-bottom:.5rem}.mv3-l{margin-top:1rem;margin-bottom:1rem}.mv4-l{margin-top:2rem;margin-bottom:2rem}.mv5-l{margin-top:4rem;margin-bottom:4rem}.mv6-l{margin-top:8rem;margin-bottom:8rem}.mv7-l{margin-top:16rem;margin-bottom:16rem}.mh0-l{margin-left:0;margin-right:0}.mh1-l{margin-left:.25rem;margin-right:.25rem}.mh2-l{margin-left:.5rem;margin-right:.5rem}.mh3-l{margin-left:1rem;margin-right:1rem}.mh4-l{margin-left:2rem;margin-right:2rem}.mh5-l{margin-left:4rem;margin-right:4rem}.mh6-l{margin-left:8rem;margin-right:8rem}.mh7-l{margin-left:16rem;margin-right:16rem}.na1-l{margin:-.25rem}.na2-l{margin:-.5rem}.na3-l{margin:-1rem}.na4-l{margin:-2rem}.na5-l{margin:-4rem}.na6-l{margin:-8rem}.na7-l{margin:-16rem}.nl1-l{margin-left:-.25rem}.nl2-l{margin-left:-.5rem}.nl3-l{margin-left:-1rem}.nl4-l{margin-left:-2rem}.nl5-l{margin-left:-4rem}.nl6-l{margin-left:-8rem}.nl7-l{margin-left:-16rem}.nr1-l{margin-right:-.25rem}.nr2-l{margin-right:-.5rem}.nr3-l{margin-right:-1rem}.nr4-l{margin-right:-2rem}.nr5-l{margin-right:-4rem}.nr6-l{margin-right:-8rem}.nr7-l{margin-right:-16rem}.nb1-l{margin-bottom:-.25rem}.nb2-l{margin-bottom:-.5rem}.nb3-l{margin-bottom:-1rem}.nb4-l{margin-bottom:-2rem}.nb5-l{margin-bottom:-4rem}.nb6-l{margin-bottom:-8rem}.nb7-l{margin-bottom:-16rem}.nt1-l{margin-top:-.25rem}.nt2-l{margin-top:-.5rem}.nt3-l{margin-top:-1rem}.nt4-l{margin-top:-2rem}.nt5-l{margin-top:-4rem}.nt6-l{margin-top:-8rem}.nt7-l{margin-top:-16rem}.strike-l{text-decoration:line-through}.underline-l{text-decoration:underline}.no-underline-l{text-decoration:none}.tl-l{text-align:left}.tr-l{text-align:right}.tc-l{text-align:center}.tj-l{text-align:justify}.ttc-l{text-transform:capitalize}.ttl-l{text-transform:lowercase}.ttu-l{text-transform:uppercase}.ttn-l{text-transform:none}.f-6-l,.f-headline-l{font-size:6rem}.f-5-l,.f-subheadline-l{font-size:5rem}.f1-l{font-size:3rem}.f2-l{font-size:2.25rem}.f3-l{font-size:1.5rem}.f4-l{font-size:1.25rem}.f5-l{font-size:1rem}.f6-l{font-size:.875rem}.f7-l{font-size:.75rem}.measure-l{max-width:30em}.measure-wide-l{max-width:34em}.measure-narrow-l{max-width:20em}.indent-l{text-indent:1em;margin-top:0;margin-bottom:0}.small-caps-l{font-variant:small-caps}.truncate-l{white-space:nowrap;overflow:hidden;text-overflow:ellipsis}.center-l{margin-left:auto}.center-l,.mr-auto-l{margin-right:auto}.ml-auto-l{margin-left:auto}.clip-l{position:fixed!important;_position:absolute!important;clip:rect(1px 1px 1px 1px);clip:rect(1px,1px,1px,1px)}.ws-normal-l{white-space:normal}.nowrap-l{white-space:nowrap}.pre-l{white-space:pre}.v-base-l{vertical-align:baseline}.v-mid-l{vertical-align:middle}.v-top-l{vertical-align:top}.v-btm-l{vertical-align:bottom}}@font-face{font-family:Inter;font-style:normal;font-weight:400;src:url(https://media.urbit.org/fonts/Inter-Regular.woff2) format("woff2")}@font-face{font-family:Inter;font-style:italic;font-weight:400;src:url(https://media.urbit.org/fonts/Inter-Italic.woff2) format("woff2")}@font-face{font-family:Inter;font-style:normal;font-weight:700;src:url(https://media.urbit.org/fonts/Inter-Bold.woff2) format("woff2")}@font-face{font-family:Inter;font-style:italic;font-weight:700;src:url(https://media.urbit.org/fonts/Inter-BoldItalic.woff2) format("woff2")}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-extralight.woff);font-weight:200}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-light.woff);font-weight:300}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-regular.woff);font-weight:400}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-medium.woff);font-weight:500}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-semibold.woff);font-weight:600}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-bold.woff);font-weight:700}a,button,h1,h2,h3,h4,h5,h6,input,p,textarea{margin-block-end:unset;margin-block-start:unset;font-family:Inter,sans-serif}button{background:none;color:inherit;border:none;cursor:pointer;outline:inherit;padding:0}p{font-size:16px;line-height:24px}code,pre{padding:8px;background-color:#f9f9f9}code{white-space:pre-wrap}a{color:inherit;text-decoration:inherit}button,input,select,textarea{outline:none}h1{font-size:48px;line-height:64px}h1,h2{font-weight:700}h2{font-size:32px;line-height:48px}h3{font-size:24px}h3,h4{line-height:32px;font-weight:700}h4{font-size:20px}.header-2{font-size:32px;line-height:48px;font-weight:700}.body-regular{font-size:16px;line-height:24px;font-weight:600}.body-large{font-size:20px;line-height:24px}.label-regular,.label-regular-mono{font-size:14px;line-height:24px}.label-regular-mono{font-family:Source Code Pro,monospace}.label-small-mono{font-family:Source Code Pro,monospace}.label-small,.label-small-mono{font-size:12px;line-height:24px}.label-small-2{font-size:12px;line-height:16px}.body-regular-400{font-size:16px;line-height:24px;font-weight:400}.plus-font{font-size:48px;line-height:24px}.fw-bold{font-weight:700}.bg-v-light-gray{background-color:#f9f9f9}.gray-50{color:#7f7f7f}.gray-30{color:#b1b2b3}.gray-10{color:#e6e6e6}.green{color:#2aa779}.green-medium{color:#2ed196}.red{color:#ee5432}.w-336{width:336px}.w-688{width:688px}.mw-336{max-width:336px}.mw-688{max-width:688px}.w-680{width:680px}.w-16{width:16px}.mb-33{width:33px}.h-80{height:80px}.b-gray-30{border-color:#b1b2b3}.header-menu-item{border-bottom:1px solid;border-color:#b1b2b3;color:#b1b2b3;flex-basis:148px;padding-bottom:3px;font-size:14px}.header-menu-item,.publish{float:left;vertical-align:middle;line-height:24px}.publish{font-size:20px;font-weight:700;color:#7f7f7f;margin-left:16px;margin-top:16px;margin-bottom:8px}.create{float:right;font-size:14px;line-height:16px;font-weight:600;text-align:right;margin-right:16px;margin-top:22px}.path-control{width:100%;border-bottom:1px solid;border-color:#b1b2b3;height:28px;clear:both}.h-modulo-header{height:48px}.h-publish-header{height:76px;top:48px}.h-inner{height:calc(100% - 124px);top:48px}.h-footer{height:76px}::placeholder{color:#b1b2b3}.bg-red{background-color:#ee5432}.bg-gray-30{background-color:#b1b2b3}.two-lines{-webkit-line-clamp:2}.five-lines,.two-lines{display:-webkit-box;-webkit-box-orient:vertical;word-wrap:break-word;overflow:hidden}.five-lines{-webkit-line-clamp:5}.one-line{word-wrap:break-word;overflow:hidden;white-space:nowrap;text-overflow:ellipsis}.spinner-pending{position:relative;background-color:#fff}.spinner-pending,.spinner-pending:after{content:"";border-radius:100%;height:16px;width:16px}.spinner-pending:after{background-color:grey;position:absolute;clip:rect(0,16px,16px,8px);animation:spin 1s cubic-bezier(.745,.045,.355,1) infinite}@keyframes spin{0%{transform:rotate(0deg)}25%{transform:rotate(90deg)}50%{transform:rotate(180deg)}75%{transform:rotate(270deg)}to{transform:rotate(1turn)}}.spinner-nostart{width:8px;height:8px;border-radius:100%;content:"";background-color:#000} \ No newline at end of file +/*! normalize.css v7.0.0 | MIT License | github.com/necolas/normalize.css */html{line-height:1.15;-ms-text-size-adjust:100%;-webkit-text-size-adjust:100%}body{margin:0}article,aside,footer,header,nav,section{display:block}h1{font-size:2em;margin:.67em 0}figcaption,figure,main{display:block}figure{margin:1em 40px}hr{box-sizing:content-box;height:0;overflow:visible}pre{font-family:monospace,monospace;font-size:1em}a{background-color:transparent;-webkit-text-decoration-skip:objects}abbr[title]{border-bottom:none;text-decoration:underline;-webkit-text-decoration:underline dotted;text-decoration:underline dotted}b,strong{font-weight:inherit;font-weight:bolder}code,kbd,samp{font-family:monospace,monospace;font-size:1em}dfn{font-style:italic}mark{background-color:#ff0;color:#000}small{font-size:80%}sub,sup{font-size:75%;line-height:0;position:relative;vertical-align:baseline}sub{bottom:-.25em}sup{top:-.5em}audio,video{display:inline-block}audio:not([controls]){display:none;height:0}img{border-style:none}svg:not(:root){overflow:hidden}button,input,optgroup,select,textarea{font-family:sans-serif;font-size:100%;line-height:1.15;margin:0}button,input{overflow:visible}button,select{text-transform:none}[type=reset],[type=submit],button,html [type=button]{-webkit-appearance:button}[type=button]::-moz-focus-inner,[type=reset]::-moz-focus-inner,[type=submit]::-moz-focus-inner,button::-moz-focus-inner{border-style:none;padding:0}[type=button]:-moz-focusring,[type=reset]:-moz-focusring,[type=submit]:-moz-focusring,button:-moz-focusring{outline:1px dotted ButtonText}fieldset{padding:.35em .75em .625em}legend{box-sizing:border-box;color:inherit;display:table;max-width:100%;padding:0;white-space:normal}progress{display:inline-block;vertical-align:baseline}textarea{overflow:auto}[type=checkbox],[type=radio]{box-sizing:border-box;padding:0}[type=number]::-webkit-inner-spin-button,[type=number]::-webkit-outer-spin-button{height:auto}[type=search]{-webkit-appearance:textfield;outline-offset:-2px}[type=search]::-webkit-search-cancel-button,[type=search]::-webkit-search-decoration{-webkit-appearance:none}::-webkit-file-upload-button{-webkit-appearance:button;font:inherit}details,menu{display:block}summary{display:list-item}canvas{display:inline-block}[hidden],template{display:none}.aspect-ratio{height:0;position:relative}.aspect-ratio--16x9{padding-bottom:56.25%}.aspect-ratio--9x16{padding-bottom:177.77%}.aspect-ratio--4x3{padding-bottom:75%}.aspect-ratio--3x4{padding-bottom:133.33%}.aspect-ratio--6x4{padding-bottom:66.6%}.aspect-ratio--4x6{padding-bottom:150%}.aspect-ratio--8x5{padding-bottom:62.5%}.aspect-ratio--5x8{padding-bottom:160%}.aspect-ratio--7x5{padding-bottom:71.42%}.aspect-ratio--5x7{padding-bottom:140%}.aspect-ratio--1x1{padding-bottom:100%}.aspect-ratio--object{position:absolute;top:0;right:0;bottom:0;left:0;width:100%;height:100%;z-index:100}.cover{background-size:cover!important}.contain{background-size:contain!important}.bg-center{background-position:50%}.bg-center,.bg-top{background-repeat:no-repeat}.bg-top{background-position:top}.bg-right{background-position:100%}.bg-bottom,.bg-right{background-repeat:no-repeat}.bg-bottom{background-position:bottom}.bg-left{background-repeat:no-repeat;background-position:0}.ba{border-style:solid;border-width:1px}.bt{border-top-style:solid;border-top-width:1px}.br{border-right-style:solid;border-right-width:1px}.bb{border-bottom-style:solid;border-bottom-width:1px}.bl{border-left-style:solid;border-left-width:1px}.bn{border-style:none;border-width:0}.b--black{border-color:#000}.b--white{border-color:#fff}.b--gray0{border-color:#333}.b--gray1{border-color:#4d4d4d}.b--gray2{border-color:#7f7f7f}.b--gray3{border-color:#b1b2b3}.b--gray4{border-color:#e6e6e6}.b--gray5{border-color:#f9f9f9}.b--blue0{border-color:#ecf6ff}.b--blue1{border-color:#b0c7ff}.b--blue2{border-color:#4330fc}.b--blue3{border-color:#190d7b}.b--red0{border-color:#f9d6ce}.b--red1{border-color:#ffa073}.b--red2{border-color:#ee5432}.b--red3{border-color:#c10d30}.b--green0{border-color:#bdebcc}.b--green1{border-color:#2ed196}.b--green2{border-color:#2aa779}.b--green3{border-color:#286e55}.b--yellow0{border-color:#ffefc5}.b--yellow1{border-color:#ffd972}.b--yellow2{border-color:#fcc440}.b--yellow3{border-color:#ee892b}.b--transparent{border-color:transparent}.br0{border-radius:0}.br1{border-radius:.125rem}.br2{border-radius:.25rem}.br3{border-radius:.5rem}.br4{border-radius:1rem}.br-100{border-radius:100%}.br-pill{border-radius:9999px}.br--bottom{border-top-left-radius:0;border-top-right-radius:0}.br--top{border-bottom-right-radius:0}.br--right,.br--top{border-bottom-left-radius:0}.br--right{border-top-left-radius:0}.br--left{border-top-right-radius:0;border-bottom-right-radius:0}.b--dotted{border-style:dotted}.b--dashed{border-style:dashed}.b--solid{border-style:solid}.b--none{border-style:none}.bw0{border-width:0}.bw1{border-width:.125rem}.bw2{border-width:.25rem}.bw3{border-width:.5rem}.bw4{border-width:1rem}.bw5{border-width:2rem}.bt-0{border-top-width:0}.br-0{border-right-width:0}.bb-0{border-bottom-width:0}.bl-0{border-left-width:0}.shadow-1{box-shadow:0 0 4px 2px rgba(0,0,0,.2)}.shadow-2{box-shadow:0 0 8px 2px rgba(0,0,0,.2)}.shadow-3{box-shadow:2px 2px 4px 2px rgba(0,0,0,.2)}.shadow-4{box-shadow:2px 2px 8px 0 rgba(0,0,0,.2)}.shadow-5{box-shadow:4px 4px 8px 0 rgba(0,0,0,.2)}.border-box,a,article,aside,blockquote,body,code,dd,div,dl,dt,fieldset,figcaption,figure,footer,form,h1,h2,h3,h4,h5,h6,header,html,input[type=email],input[type=number],input[type=password],input[type=tel],input[type=text],input[type=url],legend,li,main,nav,ol,p,pre,section,table,td,textarea,th,tr,ul{box-sizing:border-box}.pre{overflow-x:auto;overflow-y:hidden;overflow:scroll}.pa0{padding:0}.ma0,.na0{margin:0}.pl0{padding-left:0}.ml0,.nl0{margin-left:0}.pr0{padding-right:0}.mr0,.nr0{margin-right:0}.pt0{padding-top:0}.mt0,.nt0{margin-top:0}.pb0{padding-bottom:0}.mb0,.nb0{margin-bottom:0}.pv0{padding-top:0;padding-bottom:0}.mv0,.nv0{margin-top:0;margin-bottom:0}.ph0{padding-left:0;padding-right:0}.mh0,.nh0{margin-left:0;margin-right:0}.pa1{padding:.25rem}.ma1{margin:.25rem}.na1{margin:-.25rem}.pl1{padding-left:.25rem}.ml1{margin-left:.25rem}.nl1{margin-left:-.25rem}.pr1{padding-right:.25rem}.mr1{margin-right:.25rem}.nr1{margin-right:-.25rem}.pt1{padding-top:.25rem}.mt1{margin-top:.25rem}.nt1{margin-top:-.25rem}.pb1{padding-bottom:.25rem}.mb1{margin-bottom:.25rem}.nb1{margin-bottom:-.25rem}.pv1{padding-top:.25rem;padding-bottom:.25rem}.mv1{margin-top:.25rem;margin-bottom:.25rem}.nv1{margin-top:-.25rem;margin-bottom:-.25rem}.ph1{padding-left:.25rem;padding-right:.25rem}.mh1{margin-left:.25rem;margin-right:.25rem}.nh1{margin-left:-.25rem;margin-right:-.25rem}.pa2{padding:.5rem}.ma2{margin:.5rem}.na2{margin:-.5rem}.pl2{padding-left:.5rem}.ml2{margin-left:.5rem}.nl2{margin-left:-.5rem}.pr2{padding-right:.5rem}.mr2{margin-right:.5rem}.nr2{margin-right:-.5rem}.pt2{padding-top:.5rem}.mt2{margin-top:.5rem}.nt2{margin-top:-.5rem}.pb2{padding-bottom:.5rem}.mb2{margin-bottom:.5rem}.nb2{margin-bottom:-.5rem}.pv2{padding-top:.5rem;padding-bottom:.5rem}.mv2{margin-top:.5rem;margin-bottom:.5rem}.nv2{margin-top:-.5rem;margin-bottom:-.5rem}.ph2{padding-left:.5rem;padding-right:.5rem}.mh2{margin-left:.5rem;margin-right:.5rem}.nh2{margin-left:-.5rem;margin-right:-.5rem}.pa3{padding:.75rem}.ma3{margin:.75rem}.na3{margin:-.75rem}.pl3{padding-left:.75rem}.ml3{margin-left:.75rem}.nl3{margin-left:-.75rem}.pr3{padding-right:.75rem}.mr3{margin-right:.75rem}.nr3{margin-right:-.75rem}.pt3{padding-top:.75rem}.mt3{margin-top:.75rem}.nt3{margin-top:-.75rem}.pb3{padding-bottom:.75rem}.mb3{margin-bottom:.75rem}.nb3{margin-bottom:-.75rem}.pv3{padding-top:.75rem;padding-bottom:.75rem}.mv3{margin-top:.75rem;margin-bottom:.75rem}.nv3{margin-top:-.75rem;margin-bottom:-.75rem}.ph3{padding-left:.75rem;padding-right:.75rem}.mh3{margin-left:.75rem;margin-right:.75rem}.nh3{margin-left:-.75rem;margin-right:-.75rem}.pa4{padding:1rem}.ma4{margin:1rem}.na4{margin:-1rem}.pl4{padding-left:1rem}.ml4{margin-left:1rem}.nl4{margin-left:-1rem}.pr4{padding-right:1rem}.mr4{margin-right:1rem}.nr4{margin-right:-1rem}.pt4{padding-top:1rem}.mt4{margin-top:1rem}.nt4{margin-top:-1rem}.pb4{padding-bottom:1rem}.mb4{margin-bottom:1rem}.nb4{margin-bottom:-1rem}.pv4{padding-top:1rem;padding-bottom:1rem}.mv4{margin-top:1rem;margin-bottom:1rem}.nv4{margin-top:-1rem;margin-bottom:-1rem}.ph4{padding-left:1rem;padding-right:1rem}.mh4{margin-left:1rem;margin-right:1rem}.nh4{margin-left:-1rem;margin-right:-1rem}.pa5{padding:1.25rem}.ma5{margin:1.25rem}.na5{margin:-1.25rem}.pl5{padding-left:1.25rem}.ml5{margin-left:1.25rem}.nl5{margin-left:-1.25rem}.pr5{padding-right:1.25rem}.mr5{margin-right:1.25rem}.nr5{margin-right:-1.25rem}.pt5{padding-top:1.25rem}.mt5{margin-top:1.25rem}.nt5{margin-top:-1.25rem}.pb5{padding-bottom:1.25rem}.mb5{margin-bottom:1.25rem}.nb5{margin-bottom:-1.25rem}.pv5{padding-top:1.25rem;padding-bottom:1.25rem}.mv5{margin-top:1.25rem;margin-bottom:1.25rem}.nv5{margin-top:-1.25rem;margin-bottom:-1.25rem}.ph5{padding-left:1.25rem;padding-right:1.25rem}.mh5{margin-left:1.25rem;margin-right:1.25rem}.nh5{margin-left:-1.25rem;margin-right:-1.25rem}.pa6{padding:1.5rem}.ma6{margin:1.5rem}.na6{margin:-1.5rem}.pl6{padding-left:1.5rem}.ml6{margin-left:1.5rem}.nl6{margin-left:-1.5rem}.pr6{padding-right:1.5rem}.mr6{margin-right:1.5rem}.nr6{margin-right:-1.5rem}.pt6{padding-top:1.5rem}.mt6{margin-top:1.5rem}.nt6{margin-top:-1.5rem}.pb6{padding-bottom:1.5rem}.mb6{margin-bottom:1.5rem}.nb6{margin-bottom:-1.5rem}.pv6{padding-top:1.5rem;padding-bottom:1.5rem}.mv6{margin-top:1.5rem;margin-bottom:1.5rem}.nv6{margin-top:-1.5rem;margin-bottom:-1.5rem}.ph6{padding-left:1.5rem;padding-right:1.5rem}.mh6{margin-left:1.5rem;margin-right:1.5rem}.nh6{margin-left:-1.5rem;margin-right:-1.5rem}.pa7{padding:2rem}.ma7{margin:2rem}.na7{margin:-2rem}.pl7{padding-left:2rem}.ml7{margin-left:2rem}.nl7{margin-left:-2rem}.pr7{padding-right:2rem}.mr7{margin-right:2rem}.nr7{margin-right:-2rem}.pt7{padding-top:2rem}.mt7{margin-top:2rem}.nt7{margin-top:-2rem}.pb7{padding-bottom:2rem}.mb7{margin-bottom:2rem}.nb7{margin-bottom:-2rem}.pv7{padding-top:2rem;padding-bottom:2rem}.mv7{margin-top:2rem;margin-bottom:2rem}.nv7{margin-top:-2rem;margin-bottom:-2rem}.ph7{padding-left:2rem;padding-right:2rem}.mh7{margin-left:2rem;margin-right:2rem}.nh7{margin-left:-2rem;margin-right:-2rem}.pa8{padding:3rem}.ma8{margin:3rem}.na8{margin:-3rem}.pl8{padding-left:3rem}.ml8{margin-left:3rem}.nl8{margin-left:-3rem}.pr8{padding-right:3rem}.mr8{margin-right:3rem}.nr8{margin-right:-3rem}.pt8{padding-top:3rem}.mt8{margin-top:3rem}.nt8{margin-top:-3rem}.pb8{padding-bottom:3rem}.mb8{margin-bottom:3rem}.nb8{margin-bottom:-3rem}.pv8{padding-top:3rem;padding-bottom:3rem}.mv8{margin-top:3rem;margin-bottom:3rem}.nv8{margin-top:-3rem;margin-bottom:-3rem}.ph8{padding-left:3rem;padding-right:3rem}.mh8{margin-left:3rem;margin-right:3rem}.nh8{margin-left:-3rem;margin-right:-3rem}.pa9{padding:4rem}.ma9{margin:4rem}.na9{margin:-4rem}.pl9{padding-left:4rem}.ml9{margin-left:4rem}.nl9{margin-left:-4rem}.pr9{padding-right:4rem}.mr9{margin-right:4rem}.nr9{margin-right:-4rem}.pt9{padding-top:4rem}.mt9{margin-top:4rem}.nt9{margin-top:-4rem}.pb9{padding-bottom:4rem}.mb9{margin-bottom:4rem}.nb9{margin-bottom:-4rem}.pv9{padding-top:4rem;padding-bottom:4rem}.mv9{margin-top:4rem;margin-bottom:4rem}.nv9{margin-top:-4rem;margin-bottom:-4rem}.ph9{padding-left:4rem;padding-right:4rem}.mh9{margin-left:4rem;margin-right:4rem}.nh9{margin-left:-4rem;margin-right:-4rem}.pa10{padding:6rem}.ma10{margin:6rem}.na10{margin:-6rem}.pl10{padding-left:6rem}.ml10{margin-left:6rem}.nl10{margin-left:-6rem}.pr10{padding-right:6rem}.mr10{margin-right:6rem}.nr10{margin-right:-6rem}.pt10{padding-top:6rem}.mt10{margin-top:6rem}.nt10{margin-top:-6rem}.pb10{padding-bottom:6rem}.mb10{margin-bottom:6rem}.nb10{margin-bottom:-6rem}.pv10{padding-top:6rem;padding-bottom:6rem}.mv10{margin-top:6rem;margin-bottom:6rem}.nv10{margin-top:-6rem;margin-bottom:-6rem}.ph10{padding-left:6rem;padding-right:6rem}.mh10{margin-left:6rem;margin-right:6rem}.nh10{margin-left:-6rem;margin-right:-6rem}.pa11{padding:10rem}.ma11{margin:10rem}.na11{margin:-10rem}.pl11{padding-left:10rem}.ml11{margin-left:10rem}.nl11{margin-left:-10rem}.pr11{padding-right:10rem}.mr11{margin-right:10rem}.nr11{margin-right:-10rem}.pt11{padding-top:10rem}.mt11{margin-top:10rem}.nt11{margin-top:-10rem}.pb11{padding-bottom:10rem}.mb11{margin-bottom:10rem}.nb11{margin-bottom:-10rem}.pv11{padding-top:10rem;padding-bottom:10rem}.mv11{margin-top:10rem;margin-bottom:10rem}.nv11{margin-top:-10rem;margin-bottom:-10rem}.ph11{padding-left:10rem;padding-right:10rem}.mh11{margin-left:10rem;margin-right:10rem}.nh11{margin-left:-10rem;margin-right:-10rem}.pa12{padding:18rem}.ma12{margin:18rem}.na12{margin:-18rem}.pl12{padding-left:18rem}.ml12{margin-left:18rem}.nl12{margin-left:-18rem}.pr12{padding-right:18rem}.mr12{margin-right:18rem}.nr12{margin-right:-18rem}.pt12{padding-top:18rem}.mt12{margin-top:18rem}.nt12{margin-top:-18rem}.pb12{padding-bottom:18rem}.mb12{margin-bottom:18rem}.nb12{margin-bottom:-18rem}.pv12{padding-top:18rem;padding-bottom:18rem}.mv12{margin-top:18rem;margin-bottom:18rem}.nv12{margin-top:-18rem;margin-bottom:-18rem}.ph12{padding-left:18rem;padding-right:18rem}.mh12{margin-left:18rem;margin-right:18rem}.nh12{margin-left:-18rem;margin-right:-18rem}.top-0{top:0}.right-0{right:0}.bottom-0{bottom:0}.left-0{left:0}.top-1{top:1rem}.right-1{right:1rem}.bottom-1{bottom:1rem}.left-1{left:1rem}.top-2{top:2rem}.right-2{right:2rem}.bottom-2{bottom:2rem}.left-2{left:2rem}.top--1{top:-1rem}.right--1{right:-1rem}.bottom--1{bottom:-1rem}.left--1{left:-1rem}.top--2{top:-2rem}.right--2{right:-2rem}.bottom--2{bottom:-2rem}.left--2{left:-2rem}.absolute--fill{top:0;right:0;bottom:0;left:0}.cf:after,.cf:before{content:" ";display:table}.cf:after{clear:both}.cf{*zoom:1}.cl{clear:left}.cr{clear:right}.cb{clear:both}.cn{clear:none}.dn{display:none}.di{display:inline}.db{display:block}.dib{display:inline-block}.dit{display:inline-table}.dt{display:table}.dtc{display:table-cell}.dt-row{display:table-row}.dt-row-group{display:table-row-group}.dt-column{display:table-column}.dt-column-group{display:table-column-group}.dt--fixed{table-layout:fixed;width:100%}.flex{display:flex}.inline-flex{display:inline-flex}.flex-auto{flex:1 1 auto;min-width:0;min-height:0}.flex-none{flex:none}.flex-column{flex-direction:column}.flex-row{flex-direction:row}.flex-wrap{flex-wrap:wrap}.flex-nowrap{flex-wrap:nowrap}.flex-wrap-reverse{flex-wrap:wrap-reverse}.flex-column-reverse{flex-direction:column-reverse}.flex-row-reverse{flex-direction:row-reverse}.items-start{align-items:flex-start}.items-end{align-items:flex-end}.items-center{align-items:center}.items-baseline{align-items:baseline}.items-stretch{align-items:stretch}.self-start{align-self:flex-start}.self-end{align-self:flex-end}.self-center{align-self:center}.self-baseline{align-self:baseline}.self-stretch{align-self:stretch}.justify-start{justify-content:flex-start}.justify-end{justify-content:flex-end}.justify-center{justify-content:center}.justify-between{justify-content:space-between}.justify-around{justify-content:space-around}.content-start{align-content:flex-start}.content-end{align-content:flex-end}.content-center{align-content:center}.content-between{align-content:space-between}.content-around{align-content:space-around}.content-stretch{align-content:stretch}.order-0{order:0}.order-1{order:1}.order-2{order:2}.order-3{order:3}.order-4{order:4}.order-5{order:5}.order-6{order:6}.order-7{order:7}.order-8{order:8}.order-last{order:99999}.flex-grow-0{flex-grow:0}.flex-grow-1{flex-grow:1}.flex-shrink-0{flex-shrink:0}.flex-shrink-1{flex-shrink:1}.fl{float:left}.fl,.fr{_display:inline}.fr{float:right}.fn{float:none}.sans-serif{font-family:-apple-system,BlinkMacSystemFont,avenir next,avenir,helvetica neue,helvetica,ubuntu,roboto,noto,segoe ui,arial,sans-serif}.serif{font-family:georgia,times,serif}.system-sans-serif{font-family:sans-serif}.system-serif{font-family:serif}.code,code{font-family:Consolas,monaco,monospace}.courier{font-family:Courier Next,courier,monospace}.helvetica{font-family:helvetica neue,helvetica,sans-serif}.avenir{font-family:avenir next,avenir,sans-serif}.athelas{font-family:athelas,georgia,serif}.georgia{font-family:georgia,serif}.times{font-family:times,serif}.bodoni{font-family:Bodoni MT,serif}.calisto{font-family:Calisto MT,serif}.garamond{font-family:garamond,serif}.baskerville{font-family:baskerville,serif}.i{font-style:italic}.fs-normal{font-style:normal}.normal{font-weight:400}.b{font-weight:700}.fw1{font-weight:100}.fw2{font-weight:200}.fw3{font-weight:300}.fw4{font-weight:400}.fw5{font-weight:500}.fw6{font-weight:600}.fw7{font-weight:700}.fw8{font-weight:800}.fw9{font-weight:900}.input-reset{-webkit-appearance:none;-moz-appearance:none}.button-reset::-moz-focus-inner,.input-reset::-moz-focus-inner{border:0;padding:0}.debug *{outline:1px solid gold}.debug-white *{outline:1px solid #fff}.debug-black *{outline:1px solid #000}.debug-grid{background:transparent url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAICAYAAADED76LAAAAFElEQVR4AWPAC97/9x0eCsAEPgwAVLshdpENIxcAAAAASUVORK5CYII=) repeat 0 0}.debug-grid-16{background:transparent url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAABAAAAAQCAYAAAAf8/9hAAAAMklEQVR4AWOgCLz/b0epAa6UGuBOqQHOQHLUgFEDnAbcBZ4UGwDOkiCnkIhdgNgNxAYAiYlD+8sEuo8AAAAASUVORK5CYII=) repeat 0 0}.debug-grid-8-solid{background:#fff url(data:image/gif;base64,R0lGODdhCAAIAPEAAADw/wDx/////wAAACwAAAAACAAIAAACDZQvgaeb/lxbAIKA8y0AOw==) repeat 0 0}.debug-grid-16-solid{background:#fff url(data:image/gif;base64,R0lGODdhEAAQAPEAAADw/wDx/xXy/////ywAAAAAEAAQAAACIZyPKckYDQFsb6ZqD85jZ2+BkwiRFKehhqQCQgDHcgwEBQA7) repeat 0 0}.link{text-decoration:none}.link,.link:active,.link:focus,.link:hover,.link:link,.link:visited{transition:color .15s ease-in}.link:focus{outline:1px dotted currentColor}.list{list-style-type:none}.h1{height:1rem}.h2{height:2rem}.h3{height:4rem}.h4{height:8rem}.h5{height:16rem}.h-25{height:25%}.h-50{height:50%}.h-75{height:75%}.h-100{height:100%}.min-h-100{min-height:100%}.vh-25{height:25vh}.vh-50{height:50vh}.vh-75{height:75vh}.vh-100{height:100vh}.min-vh-100{min-height:100vh}.h-auto{height:auto}.h-inherit{height:inherit}.black{color:#000}.white{color:#fff}.gray0{color:#333}.gray1{color:#4d4d4d}.gray2{color:#7f7f7f}.gray3{color:#b1b2b3}.gray4{color:#e6e6e6}.gray5{color:#f9f9f9}.blue0{color:#ecf6ff}.blue1{color:#b0c7ff}.blue2{color:#4330fc}.blue3{color:#190d7b}.red0{color:#f9d6ce}.red1{color:#ffa073}.red2{color:#ee5432}.red3{color:#c10d30}.green0{color:#bdebcc}.green1{color:#2ed196}.green2{color:#2aa779}.green3{color:#286e55}.yellow0{color:#ffefc5}.yellow1{color:#ffd972}.yellow2{color:#fcc440}.yellow3{color:#ee892b}.bg-black{background-color:#000}.bg-white{background-color:#fff}.bg-gray0{background-color:#333}.bg-gray1{background-color:#4d4d4d}.bg-gray2{background-color:#7f7f7f}.bg-gray3{background-color:#b1b2b3}.bg-gray4{background-color:#e6e6e6}.bg-gray5{background-color:#f9f9f9}.bg-blue0{background-color:#ecf6ff}.bg-blue1{background-color:#b0c7ff}.bg-blue2{background-color:#4330fc}.bg-blue3{background-color:#190d7b}.bg-red0{background-color:#f9d6ce}.bg-red1{background-color:#ffa073}.bg-red2{background-color:#ee5432}.bg-red3{background-color:#c10d30}.bg-green0{background-color:#bdebcc}.bg-green1{background-color:#2ed196}.bg-green2{background-color:#2aa779}.bg-green3{background-color:#286e55}.bg-yellow0{background-color:#ffefc5}.bg-yellow1{background-color:#ffd972}.bg-yellow2{background-color:#fcc440}.bg-yellow3{background-color:#ee892b}.bg-transparent{background-color:transparent}.hover-black:focus,.hover-black:hover{color:#000}.hover-white:focus,.hover-white:hover{color:#fff}.hover-gray0:focus,.hover-gray0:hover{color:#333}.hover-gray1:focus,.hover-gray1:hover{color:#4d4d4d}.hover-gray2:focus,.hover-gray2:hover{color:#7f7f7f}.hover-gray3:focus,.hover-gray3:hover{color:#b1b2b3}.hover-gray4:focus,.hover-gray4:hover{color:#e6e6e6}.hover-gray5:focus,.hover-gray5:hover{color:#f9f9f9}.hover-blue0:focus,.hover-blue0:hover{color:#ecf6ff}.hover-blue1:focus,.hover-blue1:hover{color:#b0c7ff}.hover-blue2:focus,.hover-blue2:hover{color:#4330fc}.hover-blue3:focus,.hover-blue3:hover{color:#190d7b}.hover-red0:focus,.hover-red0:hover{color:#f9d6ce}.hover-red1:focus,.hover-red1:hover{color:#ffa073}.hover-red2:focus,.hover-red2:hover{color:#ee5432}.hover-red3:focus,.hover-red3:hover{color:#c10d30}.hover-green0:focus,.hover-green0:hover{color:#bdebcc}.hover-green1:focus,.hover-green1:hover{color:#2ed196}.hover-green2:focus,.hover-green2:hover{color:#2aa779}.hover-green3:focus,.hover-green3:hover{color:#286e55}.hover-yellow0:focus,.hover-yellow0:hover{color:#ffefc5}.hover-yellow1:focus,.hover-yellow1:hover{color:#ffd972}.hover-yellow2:focus,.hover-yellow2:hover{color:#fcc440}.hover-yellow3:focus,.hover-yellow3:hover{color:#ee892b}.hover-bg-black:focus,.hover-bg-black:hover{background-color:#000}.hover-bg-white:focus,.hover-bg-white:hover{background-color:#fff}.hover-bg-gray0:focus,.hover-bg-gray0:hover{background-color:#333}.hover-bg-gray1:focus,.hover-bg-gray1:hover{background-color:#4d4d4d}.hover-bg-gray2:focus,.hover-bg-gray2:hover{background-color:#7f7f7f}.hover-bg-gray3:focus,.hover-bg-gray3:hover{background-color:#b1b2b3}.hover-bg-gray4:focus,.hover-bg-gray4:hover{background-color:#e6e6e6}.hover-bg-gray5:focus,.hover-bg-gray5:hover{background-color:#f9f9f9}.hover-bg-blue0:focus,.hover-bg-blue0:hover{background-color:#ecf6ff}.hover-bg-blue1:focus,.hover-bg-blue1:hover{background-color:#b0c7ff}.hover-bg-blue2:focus,.hover-bg-blue2:hover{background-color:#4330fc}.hover-bg-blue3:focus,.hover-bg-blue3:hover{background-color:#190d7b}.hover-bg-red0:focus,.hover-bg-red0:hover{background-color:#f9d6ce}.hover-bg-red1:focus,.hover-bg-red1:hover{background-color:#ffa073}.hover-bg-red2:focus,.hover-bg-red2:hover{background-color:#ee5432}.hover-bg-red3:focus,.hover-bg-red3:hover{background-color:#c10d30}.hover-bg-green0:focus,.hover-bg-green0:hover{background-color:#bdebcc}.hover-bg-green1:focus,.hover-bg-green1:hover{background-color:#2ed196}.hover-bg-green2:focus,.hover-bg-green2:hover{background-color:#2aa779}.hover-bg-green3:focus,.hover-bg-green3:hover{background-color:#286e55}.hover-bg-yellow0:focus,.hover-bg-yellow0:hover{background-color:#ffefc5}.hover-bg-yellow1:focus,.hover-bg-yellow1:hover{background-color:#ffd972}.hover-bg-yellow2:focus,.hover-bg-yellow2:hover{background-color:#fcc440}.hover-bg-yellow3:focus,.hover-bg-yellow3:hover{background-color:#ee892b}.hover-bg-transparent:focus,.hover-bg-transparent:hover{background-color:transparent}img{max-width:100%}.tracked{letter-spacing:.1em}.tracked-tight{letter-spacing:-.05em}.tracked-mega{letter-spacing:.25em}.lh-solid{line-height:1.333333}.lh-title{line-height:1.5}.lh-copy{line-height:1.666666}.mw1{max-width:1rem}.mw2{max-width:2rem}.mw3{max-width:4rem}.mw4{max-width:8rem}.mw5{max-width:16rem}.mw6{max-width:32rem}.mw7{max-width:48rem}.mw8{max-width:64rem}.mw9{max-width:96rem}.mw-none{max-width:none}.mw-100{max-width:100%}.nested-copy-line-height ol,.nested-copy-line-height p,.nested-copy-line-height ul{line-height:1.5}.nested-headline-line-height h1,.nested-headline-line-height h2,.nested-headline-line-height h3,.nested-headline-line-height h4,.nested-headline-line-height h5,.nested-headline-line-height h6{line-height:1.25}.nested-list-reset ol,.nested-list-reset ul{padding-left:0;margin-left:0;list-style-type:none}.nested-copy-indent p+p{text-indent:1em;margin-top:0;margin-bottom:0}.nested-copy-separator p+p{margin-top:1.5em}.nested-img img{width:100%;max-width:100%;display:block}.nested-links a{color:#357edd;transition:color .15s ease-in}.nested-links a:focus,.nested-links a:hover{color:#96ccff;transition:color .15s ease-in}.dim{opacity:1}.dim,.dim:focus,.dim:hover{transition:opacity .15s ease-in}.dim:focus,.dim:hover{opacity:.5}.dim:active{opacity:.8;transition:opacity .15s ease-out}.glow,.glow:focus,.glow:hover{transition:opacity .15s ease-in}.glow:focus,.glow:hover{opacity:1}.hide-child .child{opacity:0;transition:opacity .15s ease-in}.hide-child:active .child,.hide-child:focus .child,.hide-child:hover .child{opacity:1;transition:opacity .15s ease-in}.underline-hover:focus,.underline-hover:hover{text-decoration:underline}.grow{-moz-osx-font-smoothing:grayscale;-webkit-backface-visibility:hidden;backface-visibility:hidden;-webkit-transform:translateZ(0);transform:translateZ(0);transition:-webkit-transform .25s ease-out;transition:transform .25s ease-out;transition:transform .25s ease-out,-webkit-transform .25s ease-out}.grow:focus,.grow:hover{-webkit-transform:scale(1.05);transform:scale(1.05)}.grow:active{-webkit-transform:scale(.9);transform:scale(.9)}.grow-large{-moz-osx-font-smoothing:grayscale;-webkit-backface-visibility:hidden;backface-visibility:hidden;-webkit-transform:translateZ(0);transform:translateZ(0);transition:-webkit-transform .25s ease-in-out;transition:transform .25s ease-in-out;transition:transform .25s ease-in-out,-webkit-transform .25s ease-in-out}.grow-large:focus,.grow-large:hover{-webkit-transform:scale(1.2);transform:scale(1.2)}.grow-large:active{-webkit-transform:scale(.95);transform:scale(.95)}.pointer:hover,.shadow-hover{cursor:pointer}.shadow-hover{position:relative;transition:all .5s cubic-bezier(.165,.84,.44,1)}.shadow-hover:after{content:"";box-shadow:0 0 16px 2px rgba(0,0,0,.2);border-radius:inherit;opacity:0;position:absolute;top:0;left:0;width:100%;height:100%;z-index:-1;transition:opacity .5s cubic-bezier(.165,.84,.44,1)}.shadow-hover:focus:after,.shadow-hover:hover:after{opacity:1}.bg-animate,.bg-animate:focus,.bg-animate:hover{transition:background-color .15s ease-in-out}.o-100{opacity:1}.o-90{opacity:.9}.o-80{opacity:.8}.o-70{opacity:.7}.o-60{opacity:.6}.o-50{opacity:.5}.o-40{opacity:.4}.o-30{opacity:.3}.o-20{opacity:.2}.o-10{opacity:.1}.o-05{opacity:.05}.o-025{opacity:.025}.o-0{opacity:0}.rotate-45{-webkit-transform:rotate(45deg);transform:rotate(45deg)}.rotate-90{-webkit-transform:rotate(90deg);transform:rotate(90deg)}.rotate-135{-webkit-transform:rotate(135deg);transform:rotate(135deg)}.rotate-180{-webkit-transform:rotate(180deg);transform:rotate(180deg)}.rotate-225{-webkit-transform:rotate(225deg);transform:rotate(225deg)}.rotate-270{-webkit-transform:rotate(270deg);transform:rotate(270deg)}.rotate-315{-webkit-transform:rotate(315deg);transform:rotate(315deg)}.outline{outline:1px solid}.outline-transparent{outline:1px solid transparent}.outline-0{outline:0}.overflow-visible{overflow:visible}.overflow-hidden{overflow:hidden}.overflow-scroll{overflow:scroll}.overflow-auto{overflow:auto}.overflow-x-visible{overflow-x:visible}.overflow-x-hidden{overflow-x:hidden}.overflow-x-scroll{overflow-x:scroll}.overflow-x-auto{overflow-x:auto}.overflow-y-visible{overflow-y:visible}.overflow-y-hidden{overflow-y:hidden}.overflow-y-scroll{overflow-y:scroll}.overflow-y-auto{overflow-y:auto}.static{position:static}.relative{position:relative}.absolute{position:absolute}.fixed{position:fixed}.collapse{border-collapse:collapse;border-spacing:0}.striped--light-silver:nth-child(odd){background-color:#aaa}.striped--moon-gray:nth-child(odd){background-color:#ccc}.striped--light-gray:nth-child(odd){background-color:#eee}.striped--near-white:nth-child(odd){background-color:#f4f4f4}.stripe-light:nth-child(odd){background-color:hsla(0,0%,100%,.1)}.stripe-dark:nth-child(odd){background-color:rgba(0,0,0,.1)}.strike{text-decoration:line-through}.underline{text-decoration:underline}.no-underline{text-decoration:none}.tl{text-align:left}.tr{text-align:right}.tc{text-align:center}.tj{text-align:justify}.ttc{text-transform:capitalize}.ttl{text-transform:lowercase}.ttu{text-transform:uppercase}.ttn{text-transform:none}.v-base{vertical-align:baseline}.v-mid{vertical-align:middle}.v-top{vertical-align:top}.v-btm{vertical-align:bottom}.f1{font-size:4.5rem}.f2{font-size:4rem}.f3{font-size:3rem}.f4{font-size:2rem}.f5{font-size:1.5rem}.f6{font-size:1.125rem}.f7{font-size:1rem}.f8{font-size:.875rem}.f9{font-size:.75rem}.measure{max-width:30em}.measure-wide{max-width:34em}.measure-narrow{max-width:20em}.small-caps{font-variant:small-caps}.indent{text-indent:1em;margin-top:0;margin-bottom:0}.truncate{white-space:nowrap;overflow:hidden;text-overflow:ellipsis}.overflow-container{overflow-y:scroll}.center{margin-left:auto}.center,.mr-auto{margin-right:auto}.ml-auto{margin-left:auto}.clip{position:fixed!important;_position:absolute!important;clip:rect(1px 1px 1px 1px);clip:rect(1px,1px,1px,1px)}.ws-normal{white-space:normal}.nowrap{white-space:nowrap}.pre{white-space:pre}.w1{width:1rem}.w2{width:2rem}.w3{width:4rem}.w4{width:8rem}.w5{width:16rem}.w-10{width:10%}.w-20{width:20%}.w-25{width:25%}.w-30{width:30%}.w-33{width:33%}.w-34{width:34%}.w-40{width:40%}.w-50{width:50%}.w-60{width:60%}.w-70{width:70%}.w-75{width:75%}.w-80{width:80%}.w-90{width:90%}.w-100{width:100%}.w-third{width:33.33333%}.w-two-thirds{width:66.66667%}.w-auto{width:auto}.z-0{z-index:0}.z-1{z-index:1}.z-2{z-index:2}.z-3{z-index:3}.z-4{z-index:4}.z-5{z-index:5}.z-999{z-index:999}.z-9999{z-index:9999}.z-max{z-index:2147483647}.z-inherit{z-index:inherit}.z-initial{z-index:auto}.z-unset{z-index:unset}@media screen and (min-width:34.375em) and (max-width:46.875em){.aspect-ratio-m{height:0;position:relative}.aspect-ratio--16x9-m{padding-bottom:56.25%}.aspect-ratio--9x16-m{padding-bottom:177.77%}.aspect-ratio--4x3-m{padding-bottom:75%}.aspect-ratio--3x4-m{padding-bottom:133.33%}.aspect-ratio--6x4-m{padding-bottom:66.6%}.aspect-ratio--4x6-m{padding-bottom:150%}.aspect-ratio--8x5-m{padding-bottom:62.5%}.aspect-ratio--5x8-m{padding-bottom:160%}.aspect-ratio--7x5-m{padding-bottom:71.42%}.aspect-ratio--5x7-m{padding-bottom:140%}.aspect-ratio--1x1-m{padding-bottom:100%}.aspect-ratio--object-m{position:absolute;top:0;right:0;bottom:0;left:0;width:100%;height:100%;z-index:100}.cover-m{background-size:cover!important}.contain-m{background-size:contain!important}.bg-center-m{background-position:50%}.bg-center-m,.bg-top-m{background-repeat:no-repeat}.bg-top-m{background-position:top}.bg-right-m{background-position:100%}.bg-bottom-m,.bg-right-m{background-repeat:no-repeat}.bg-bottom-m{background-position:bottom}.bg-left-m{background-repeat:no-repeat;background-position:0}.ba-m{border-style:solid;border-width:1px}.bt-m{border-top-style:solid;border-top-width:1px}.br-m{border-right-style:solid;border-right-width:1px}.bb-m{border-bottom-style:solid;border-bottom-width:1px}.bl-m{border-left-style:solid;border-left-width:1px}.bn-m{border-style:none;border-width:0}.br0-m{border-radius:0}.br1-m{border-radius:.125rem}.br2-m{border-radius:.25rem}.br3-m{border-radius:.5rem}.br4-m{border-radius:1rem}.br-100-m{border-radius:100%}.br-pill-m{border-radius:9999px}.br--bottom-m{border-top-left-radius:0;border-top-right-radius:0}.br--top-m{border-bottom-right-radius:0}.br--right-m,.br--top-m{border-bottom-left-radius:0}.br--right-m{border-top-left-radius:0}.br--left-m{border-top-right-radius:0;border-bottom-right-radius:0}.b--dotted-m{border-style:dotted}.b--dashed-m{border-style:dashed}.b--solid-m{border-style:solid}.b--none-m{border-style:none}.bw0-m{border-width:0}.bw1-m{border-width:.125rem}.bw2-m{border-width:.25rem}.bw3-m{border-width:.5rem}.bw4-m{border-width:1rem}.bw5-m{border-width:2rem}.bt-0-m{border-top-width:0}.br-0-m{border-right-width:0}.bb-0-m{border-bottom-width:0}.bl-0-m{border-left-width:0}.shadow-1-m{box-shadow:0 0 4px 2px rgba(0,0,0,.2)}.shadow-2-m{box-shadow:0 0 8px 2px rgba(0,0,0,.2)}.shadow-3-m{box-shadow:2px 2px 4px 2px rgba(0,0,0,.2)}.shadow-4-m{box-shadow:2px 2px 8px 0 rgba(0,0,0,.2)}.shadow-5-m{box-shadow:4px 4px 8px 0 rgba(0,0,0,.2)}.pa0-m{padding:0}.ma0-m,.na0-m{margin:0}.pl0-m{padding-left:0}.ml0-m,.nl0-m{margin-left:0}.pr0-m{padding-right:0}.mr0-m,.nr0-m{margin-right:0}.pt0-m{padding-top:0}.mt0-m,.nt0-m{margin-top:0}.pb0-m{padding-bottom:0}.mb0-m,.nb0-m{margin-bottom:0}.pv0-m{padding-top:0;padding-bottom:0}.mv0-m,.nv0-m{margin-top:0;margin-bottom:0}.ph0-m{padding-left:0;padding-right:0}.mh0-m,.nh0-m{margin-left:0;margin-right:0}.pa1-m{padding:.25rem}.ma1-m{margin:.25rem}.na1-m{margin:-.25rem}.pl1-m{padding-left:.25rem}.ml1-m{margin-left:.25rem}.nl1-m{margin-left:-.25rem}.pr1-m{padding-right:.25rem}.mr1-m{margin-right:.25rem}.nr1-m{margin-right:-.25rem}.pt1-m{padding-top:.25rem}.mt1-m{margin-top:.25rem}.nt1-m{margin-top:-.25rem}.pb1-m{padding-bottom:.25rem}.mb1-m{margin-bottom:.25rem}.nb1-m{margin-bottom:-.25rem}.pv1-m{padding-top:.25rem;padding-bottom:.25rem}.mv1-m{margin-top:.25rem;margin-bottom:.25rem}.nv1-m{margin-top:-.25rem;margin-bottom:-.25rem}.ph1-m{padding-left:.25rem;padding-right:.25rem}.mh1-m{margin-left:.25rem;margin-right:.25rem}.nh1-m{margin-left:-.25rem;margin-right:-.25rem}.pa2-m{padding:.5rem}.ma2-m{margin:.5rem}.na2-m{margin:-.5rem}.pl2-m{padding-left:.5rem}.ml2-m{margin-left:.5rem}.nl2-m{margin-left:-.5rem}.pr2-m{padding-right:.5rem}.mr2-m{margin-right:.5rem}.nr2-m{margin-right:-.5rem}.pt2-m{padding-top:.5rem}.mt2-m{margin-top:.5rem}.nt2-m{margin-top:-.5rem}.pb2-m{padding-bottom:.5rem}.mb2-m{margin-bottom:.5rem}.nb2-m{margin-bottom:-.5rem}.pv2-m{padding-top:.5rem;padding-bottom:.5rem}.mv2-m{margin-top:.5rem;margin-bottom:.5rem}.nv2-m{margin-top:-.5rem;margin-bottom:-.5rem}.ph2-m{padding-left:.5rem;padding-right:.5rem}.mh2-m{margin-left:.5rem;margin-right:.5rem}.nh2-m{margin-left:-.5rem;margin-right:-.5rem}.pa3-m{padding:.75rem}.ma3-m{margin:.75rem}.na3-m{margin:-.75rem}.pl3-m{padding-left:.75rem}.ml3-m{margin-left:.75rem}.nl3-m{margin-left:-.75rem}.pr3-m{padding-right:.75rem}.mr3-m{margin-right:.75rem}.nr3-m{margin-right:-.75rem}.pt3-m{padding-top:.75rem}.mt3-m{margin-top:.75rem}.nt3-m{margin-top:-.75rem}.pb3-m{padding-bottom:.75rem}.mb3-m{margin-bottom:.75rem}.nb3-m{margin-bottom:-.75rem}.pv3-m{padding-top:.75rem;padding-bottom:.75rem}.mv3-m{margin-top:.75rem;margin-bottom:.75rem}.nv3-m{margin-top:-.75rem;margin-bottom:-.75rem}.ph3-m{padding-left:.75rem;padding-right:.75rem}.mh3-m{margin-left:.75rem;margin-right:.75rem}.nh3-m{margin-left:-.75rem;margin-right:-.75rem}.pa4-m{padding:1rem}.ma4-m{margin:1rem}.na4-m{margin:-1rem}.pl4-m{padding-left:1rem}.ml4-m{margin-left:1rem}.nl4-m{margin-left:-1rem}.pr4-m{padding-right:1rem}.mr4-m{margin-right:1rem}.nr4-m{margin-right:-1rem}.pt4-m{padding-top:1rem}.mt4-m{margin-top:1rem}.nt4-m{margin-top:-1rem}.pb4-m{padding-bottom:1rem}.mb4-m{margin-bottom:1rem}.nb4-m{margin-bottom:-1rem}.pv4-m{padding-top:1rem;padding-bottom:1rem}.mv4-m{margin-top:1rem;margin-bottom:1rem}.nv4-m{margin-top:-1rem;margin-bottom:-1rem}.ph4-m{padding-left:1rem;padding-right:1rem}.mh4-m{margin-left:1rem;margin-right:1rem}.nh4-m{margin-left:-1rem;margin-right:-1rem}.pa5-m{padding:1.25rem}.ma5-m{margin:1.25rem}.na5-m{margin:-1.25rem}.pl5-m{padding-left:1.25rem}.ml5-m{margin-left:1.25rem}.nl5-m{margin-left:-1.25rem}.pr5-m{padding-right:1.25rem}.mr5-m{margin-right:1.25rem}.nr5-m{margin-right:-1.25rem}.pt5-m{padding-top:1.25rem}.mt5-m{margin-top:1.25rem}.nt5-m{margin-top:-1.25rem}.pb5-m{padding-bottom:1.25rem}.mb5-m{margin-bottom:1.25rem}.nb5-m{margin-bottom:-1.25rem}.pv5-m{padding-top:1.25rem;padding-bottom:1.25rem}.mv5-m{margin-top:1.25rem;margin-bottom:1.25rem}.nv5-m{margin-top:-1.25rem;margin-bottom:-1.25rem}.ph5-m{padding-left:1.25rem;padding-right:1.25rem}.mh5-m{margin-left:1.25rem;margin-right:1.25rem}.nh5-m{margin-left:-1.25rem;margin-right:-1.25rem}.pa6-m{padding:1.5rem}.ma6-m{margin:1.5rem}.na6-m{margin:-1.5rem}.pl6-m{padding-left:1.5rem}.ml6-m{margin-left:1.5rem}.nl6-m{margin-left:-1.5rem}.pr6-m{padding-right:1.5rem}.mr6-m{margin-right:1.5rem}.nr6-m{margin-right:-1.5rem}.pt6-m{padding-top:1.5rem}.mt6-m{margin-top:1.5rem}.nt6-m{margin-top:-1.5rem}.pb6-m{padding-bottom:1.5rem}.mb6-m{margin-bottom:1.5rem}.nb6-m{margin-bottom:-1.5rem}.pv6-m{padding-top:1.5rem;padding-bottom:1.5rem}.mv6-m{margin-top:1.5rem;margin-bottom:1.5rem}.nv6-m{margin-top:-1.5rem;margin-bottom:-1.5rem}.ph6-m{padding-left:1.5rem;padding-right:1.5rem}.mh6-m{margin-left:1.5rem;margin-right:1.5rem}.nh6-m{margin-left:-1.5rem;margin-right:-1.5rem}.pa7-m{padding:2rem}.ma7-m{margin:2rem}.na7-m{margin:-2rem}.pl7-m{padding-left:2rem}.ml7-m{margin-left:2rem}.nl7-m{margin-left:-2rem}.pr7-m{padding-right:2rem}.mr7-m{margin-right:2rem}.nr7-m{margin-right:-2rem}.pt7-m{padding-top:2rem}.mt7-m{margin-top:2rem}.nt7-m{margin-top:-2rem}.pb7-m{padding-bottom:2rem}.mb7-m{margin-bottom:2rem}.nb7-m{margin-bottom:-2rem}.pv7-m{padding-top:2rem;padding-bottom:2rem}.mv7-m{margin-top:2rem;margin-bottom:2rem}.nv7-m{margin-top:-2rem;margin-bottom:-2rem}.ph7-m{padding-left:2rem;padding-right:2rem}.mh7-m{margin-left:2rem;margin-right:2rem}.nh7-m{margin-left:-2rem;margin-right:-2rem}.pa8-m{padding:3rem}.ma8-m{margin:3rem}.na8-m{margin:-3rem}.pl8-m{padding-left:3rem}.ml8-m{margin-left:3rem}.nl8-m{margin-left:-3rem}.pr8-m{padding-right:3rem}.mr8-m{margin-right:3rem}.nr8-m{margin-right:-3rem}.pt8-m{padding-top:3rem}.mt8-m{margin-top:3rem}.nt8-m{margin-top:-3rem}.pb8-m{padding-bottom:3rem}.mb8-m{margin-bottom:3rem}.nb8-m{margin-bottom:-3rem}.pv8-m{padding-top:3rem;padding-bottom:3rem}.mv8-m{margin-top:3rem;margin-bottom:3rem}.nv8-m{margin-top:-3rem;margin-bottom:-3rem}.ph8-m{padding-left:3rem;padding-right:3rem}.mh8-m{margin-left:3rem;margin-right:3rem}.nh8-m{margin-left:-3rem;margin-right:-3rem}.pa9-m{padding:4rem}.ma9-m{margin:4rem}.na9-m{margin:-4rem}.pl9-m{padding-left:4rem}.ml9-m{margin-left:4rem}.nl9-m{margin-left:-4rem}.pr9-m{padding-right:4rem}.mr9-m{margin-right:4rem}.nr9-m{margin-right:-4rem}.pt9-m{padding-top:4rem}.mt9-m{margin-top:4rem}.nt9-m{margin-top:-4rem}.pb9-m{padding-bottom:4rem}.mb9-m{margin-bottom:4rem}.nb9-m{margin-bottom:-4rem}.pv9-m{padding-top:4rem;padding-bottom:4rem}.mv9-m{margin-top:4rem;margin-bottom:4rem}.nv9-m{margin-top:-4rem;margin-bottom:-4rem}.ph9-m{padding-left:4rem;padding-right:4rem}.mh9-m{margin-left:4rem;margin-right:4rem}.nh9-m{margin-left:-4rem;margin-right:-4rem}.pa10-m{padding:6rem}.ma10-m{margin:6rem}.na10-m{margin:-6rem}.pl10-m{padding-left:6rem}.ml10-m{margin-left:6rem}.nl10-m{margin-left:-6rem}.pr10-m{padding-right:6rem}.mr10-m{margin-right:6rem}.nr10-m{margin-right:-6rem}.pt10-m{padding-top:6rem}.mt10-m{margin-top:6rem}.nt10-m{margin-top:-6rem}.pb10-m{padding-bottom:6rem}.mb10-m{margin-bottom:6rem}.nb10-m{margin-bottom:-6rem}.pv10-m{padding-top:6rem;padding-bottom:6rem}.mv10-m{margin-top:6rem;margin-bottom:6rem}.nv10-m{margin-top:-6rem;margin-bottom:-6rem}.ph10-m{padding-left:6rem;padding-right:6rem}.mh10-m{margin-left:6rem;margin-right:6rem}.nh10-m{margin-left:-6rem;margin-right:-6rem}.pa11-m{padding:10rem}.ma11-m{margin:10rem}.na11-m{margin:-10rem}.pl11-m{padding-left:10rem}.ml11-m{margin-left:10rem}.nl11-m{margin-left:-10rem}.pr11-m{padding-right:10rem}.mr11-m{margin-right:10rem}.nr11-m{margin-right:-10rem}.pt11-m{padding-top:10rem}.mt11-m{margin-top:10rem}.nt11-m{margin-top:-10rem}.pb11-m{padding-bottom:10rem}.mb11-m{margin-bottom:10rem}.nb11-m{margin-bottom:-10rem}.pv11-m{padding-top:10rem;padding-bottom:10rem}.mv11-m{margin-top:10rem;margin-bottom:10rem}.nv11-m{margin-top:-10rem;margin-bottom:-10rem}.ph11-m{padding-left:10rem;padding-right:10rem}.mh11-m{margin-left:10rem;margin-right:10rem}.nh11-m{margin-left:-10rem;margin-right:-10rem}.pa12-m{padding:18rem}.ma12-m{margin:18rem}.na12-m{margin:-18rem}.pl12-m{padding-left:18rem}.ml12-m{margin-left:18rem}.nl12-m{margin-left:-18rem}.pr12-m{padding-right:18rem}.mr12-m{margin-right:18rem}.nr12-m{margin-right:-18rem}.pt12-m{padding-top:18rem}.mt12-m{margin-top:18rem}.nt12-m{margin-top:-18rem}.pb12-m{padding-bottom:18rem}.mb12-m{margin-bottom:18rem}.nb12-m{margin-bottom:-18rem}.pv12-m{padding-top:18rem;padding-bottom:18rem}.mv12-m{margin-top:18rem;margin-bottom:18rem}.nv12-m{margin-top:-18rem;margin-bottom:-18rem}.ph12-m{padding-left:18rem;padding-right:18rem}.mh12-m{margin-left:18rem;margin-right:18rem}.nh12-m{margin-left:-18rem;margin-right:-18rem}.top-0-m{top:0}.right-0-m{right:0}.bottom-0-m{bottom:0}.left-0-m{left:0}.top-1-m{top:1rem}.right-1-m{right:1rem}.bottom-1-m{bottom:1rem}.left-1-m{left:1rem}.top-2-m{top:2rem}.right-2-m{right:2rem}.bottom-2-m{bottom:2rem}.left-2-m{left:2rem}.top--1-m{top:-1rem}.right--1-m{right:-1rem}.bottom--1-m{bottom:-1rem}.left--1-m{left:-1rem}.top--2-m{top:-2rem}.right--2-m{right:-2rem}.bottom--2-m{bottom:-2rem}.left--2-m{left:-2rem}.absolute--fill-m{top:0;right:0;bottom:0;left:0}.cf-m:after,.cf-m:before{content:" ";display:table}.cf-m:after{clear:both}.cf-m{*zoom:1}.cl-m{clear:left}.cr-m{clear:right}.cb-m{clear:both}.cn-m{clear:none}.dn-m{display:none}.di-m{display:inline}.db-m{display:block}.dib-m{display:inline-block}.dit-m{display:inline-table}.dt-m{display:table}.dtc-m{display:table-cell}.dt-row-m{display:table-row}.dt-row-group-m{display:table-row-group}.dt-column-m{display:table-column}.dt-column-group-m{display:table-column-group}.dt--fixed-m{table-layout:fixed;width:100%}.flex-m{display:flex}.inline-flex-m{display:inline-flex}.flex-auto-m{flex:1 1 auto;min-width:0;min-height:0}.flex-none-m{flex:none}.flex-column-m{flex-direction:column}.flex-row-m{flex-direction:row}.flex-wrap-m{flex-wrap:wrap}.flex-nowrap-m{flex-wrap:nowrap}.flex-wrap-reverse-m{flex-wrap:wrap-reverse}.flex-column-reverse-m{flex-direction:column-reverse}.flex-row-reverse-m{flex-direction:row-reverse}.items-start-m{align-items:flex-start}.items-end-m{align-items:flex-end}.items-center-m{align-items:center}.items-baseline-m{align-items:baseline}.items-stretch-m{align-items:stretch}.self-start-m{align-self:flex-start}.self-end-m{align-self:flex-end}.self-center-m{align-self:center}.self-baseline-m{align-self:baseline}.self-stretch-m{align-self:stretch}.justify-start-m{justify-content:flex-start}.justify-end-m{justify-content:flex-end}.justify-center-m{justify-content:center}.justify-between-m{justify-content:space-between}.justify-around-m{justify-content:space-around}.content-start-m{align-content:flex-start}.content-end-m{align-content:flex-end}.content-center-m{align-content:center}.content-between-m{align-content:space-between}.content-around-m{align-content:space-around}.content-stretch-m{align-content:stretch}.order-0-m{order:0}.order-1-m{order:1}.order-2-m{order:2}.order-3-m{order:3}.order-4-m{order:4}.order-5-m{order:5}.order-6-m{order:6}.order-7-m{order:7}.order-8-m{order:8}.order-last-m{order:99999}.flex-grow-0-m{flex-grow:0}.flex-grow-1-m{flex-grow:1}.flex-shrink-0-m{flex-shrink:0}.flex-shrink-1-m{flex-shrink:1}.fl-m{float:left}.fl-m,.fr-m{_display:inline}.fr-m{float:right}.fn-m{float:none}.i-m{font-style:italic}.fs-normal-m{font-style:normal}.normal-m{font-weight:400}.b-m{font-weight:700}.fw1-m{font-weight:100}.fw2-m{font-weight:200}.fw3-m{font-weight:300}.fw4-m{font-weight:400}.fw5-m{font-weight:500}.fw6-m{font-weight:600}.fw7-m{font-weight:700}.fw8-m{font-weight:800}.fw9-m{font-weight:900}.h1-m{height:1rem}.h2-m{height:2rem}.h3-m{height:4rem}.h4-m{height:8rem}.h5-m{height:16rem}.h-25-m{height:25%}.h-50-m{height:50%}.h-75-m{height:75%}.h-100-m{height:100%}.min-h-100-m{min-height:100%}.vh-25-m{height:25vh}.vh-50-m{height:50vh}.vh-75-m{height:75vh}.vh-100-m{height:100vh}.min-vh-100-m{min-height:100vh}.h-auto-m{height:auto}.h-inherit-m{height:inherit}.tracked-m{letter-spacing:.1em}.tracked-tight-m{letter-spacing:-.05em}.tracked-mega-m{letter-spacing:.25em}.lh-solid-m{line-height:1.333333}.lh-title-m{line-height:1.5}.lh-copy-m{line-height:1.666666}.mw1-m{max-width:1rem}.mw2-m{max-width:2rem}.mw3-m{max-width:4rem}.mw4-m{max-width:8rem}.mw5-m{max-width:16rem}.mw6-m{max-width:32rem}.mw7-m{max-width:48rem}.mw8-m{max-width:64rem}.mw9-m{max-width:96rem}.mw-none-m{max-width:none}.mw-100-m{max-width:100%}.o-100-m{opacity:1}.o-90-m{opacity:.9}.o-80-m{opacity:.8}.o-70-m{opacity:.7}.o-60-m{opacity:.6}.o-50-m{opacity:.5}.o-40-m{opacity:.4}.o-30-m{opacity:.3}.o-20-m{opacity:.2}.o-10-m{opacity:.1}.o-05-m{opacity:.05}.o-025-m{opacity:.025}.o-0-m{opacity:0}.rotate-45-m{-webkit-transform:rotate(45deg);transform:rotate(45deg)}.rotate-90-m{-webkit-transform:rotate(90deg);transform:rotate(90deg)}.rotate-135-m{-webkit-transform:rotate(135deg);transform:rotate(135deg)}.rotate-180-m{-webkit-transform:rotate(180deg);transform:rotate(180deg)}.rotate-225-m{-webkit-transform:rotate(225deg);transform:rotate(225deg)}.rotate-270-m{-webkit-transform:rotate(270deg);transform:rotate(270deg)}.rotate-315-m{-webkit-transform:rotate(315deg);transform:rotate(315deg)}.outline-m{outline:1px solid}.outline-transparent-m{outline:1px solid transparent}.outline-0-m{outline:0}.overflow-visible-m{overflow:visible}.overflow-hidden-m{overflow:hidden}.overflow-scroll-m{overflow:scroll}.overflow-auto-m{overflow:auto}.overflow-x-visible-m{overflow-x:visible}.overflow-x-hidden-m{overflow-x:hidden}.overflow-x-scroll-m{overflow-x:scroll}.overflow-x-auto-m{overflow-x:auto}.overflow-y-visible-m{overflow-y:visible}.overflow-y-hidden-m{overflow-y:hidden}.overflow-y-scroll-m{overflow-y:scroll}.overflow-y-auto-m{overflow-y:auto}.static-m{position:static}.relative-m{position:relative}.absolute-m{position:absolute}.fixed-m{position:fixed}.strike-m{text-decoration:line-through}.underline-m{text-decoration:underline}.no-underline-m{text-decoration:none}.tl-m{text-align:left}.tr-m{text-align:right}.tc-m{text-align:center}.tj-m{text-align:justify}.ttc-m{text-transform:capitalize}.ttl-m{text-transform:lowercase}.ttu-m{text-transform:uppercase}.ttn-m{text-transform:none}.f1-m{font-size:4.5rem}.f2-m{font-size:4rem}.f3-m{font-size:3rem}.f4-m{font-size:2rem}.f5-m{font-size:1.5rem}.f6-m{font-size:1.125rem}.f7-m{font-size:1rem}.f8-m{font-size:.875rem}.f9-m{font-size:.75rem}.measure-m{max-width:30em}.measure-wide-m{max-width:34em}.measure-narrow-m{max-width:20em}.small-caps-m{font-variant:small-caps}.indent-m{text-indent:1em;margin-top:0;margin-bottom:0}.truncate-m{white-space:nowrap;overflow:hidden;text-overflow:ellipsis}.clip-m{position:fixed!important;_position:absolute!important;clip:rect(1px 1px 1px 1px);clip:rect(1px,1px,1px,1px)}.ws-normal-m{white-space:normal}.nowrap-m{white-space:nowrap}.pre-m{white-space:pre}.w1-m{width:1rem}.w2-m{width:2rem}.w3-m{width:4rem}.w4-m{width:8rem}.w5-m{width:16rem}.w-10-m{width:10%}.w-20-m{width:20%}.w-25-m{width:25%}.w-30-m{width:30%}.w-33-m{width:33%}.w-34-m{width:34%}.w-40-m{width:40%}.w-50-m{width:50%}.w-60-m{width:60%}.w-70-m{width:70%}.w-75-m{width:75%}.w-80-m{width:80%}.w-90-m{width:90%}.w-100-m{width:100%}.w-third-m{width:33.33333%}.w-two-thirds-m{width:66.66667%}.w-auto-m{width:auto}}@media screen and (min-width:46.875em) and (max-width:60em){.aspect-ratio-l{height:0;position:relative}.aspect-ratio--16x9-l{padding-bottom:56.25%}.aspect-ratio--9x16-l{padding-bottom:177.77%}.aspect-ratio--4x3-l{padding-bottom:75%}.aspect-ratio--3x4-l{padding-bottom:133.33%}.aspect-ratio--6x4-l{padding-bottom:66.6%}.aspect-ratio--4x6-l{padding-bottom:150%}.aspect-ratio--8x5-l{padding-bottom:62.5%}.aspect-ratio--5x8-l{padding-bottom:160%}.aspect-ratio--7x5-l{padding-bottom:71.42%}.aspect-ratio--5x7-l{padding-bottom:140%}.aspect-ratio--1x1-l{padding-bottom:100%}.aspect-ratio--object-l{position:absolute;top:0;right:0;bottom:0;left:0;width:100%;height:100%;z-index:100}.cover-l{background-size:cover!important}.contain-l{background-size:contain!important}.bg-center-l{background-position:50%}.bg-center-l,.bg-top-l{background-repeat:no-repeat}.bg-top-l{background-position:top}.bg-right-l{background-position:100%}.bg-bottom-l,.bg-right-l{background-repeat:no-repeat}.bg-bottom-l{background-position:bottom}.bg-left-l{background-repeat:no-repeat;background-position:0}.ba-l{border-style:solid;border-width:1px}.bt-l{border-top-style:solid;border-top-width:1px}.br-l{border-right-style:solid;border-right-width:1px}.bb-l{border-bottom-style:solid;border-bottom-width:1px}.bl-l{border-left-style:solid;border-left-width:1px}.bn-l{border-style:none;border-width:0}.br0-l{border-radius:0}.br1-l{border-radius:.125rem}.br2-l{border-radius:.25rem}.br3-l{border-radius:.5rem}.br4-l{border-radius:1rem}.br-100-l{border-radius:100%}.br-pill-l{border-radius:9999px}.br--bottom-l{border-top-left-radius:0;border-top-right-radius:0}.br--top-l{border-bottom-right-radius:0}.br--right-l,.br--top-l{border-bottom-left-radius:0}.br--right-l{border-top-left-radius:0}.br--left-l{border-top-right-radius:0;border-bottom-right-radius:0}.b--dotted-l{border-style:dotted}.b--dashed-l{border-style:dashed}.b--solid-l{border-style:solid}.b--none-l{border-style:none}.bw0-l{border-width:0}.bw1-l{border-width:.125rem}.bw2-l{border-width:.25rem}.bw3-l{border-width:.5rem}.bw4-l{border-width:1rem}.bw5-l{border-width:2rem}.bt-0-l{border-top-width:0}.br-0-l{border-right-width:0}.bb-0-l{border-bottom-width:0}.bl-0-l{border-left-width:0}.shadow-1-l{box-shadow:0 0 4px 2px rgba(0,0,0,.2)}.shadow-2-l{box-shadow:0 0 8px 2px rgba(0,0,0,.2)}.shadow-3-l{box-shadow:2px 2px 4px 2px rgba(0,0,0,.2)}.shadow-4-l{box-shadow:2px 2px 8px 0 rgba(0,0,0,.2)}.shadow-5-l{box-shadow:4px 4px 8px 0 rgba(0,0,0,.2)}.pa0-l{padding:0}.ma0-l,.na0-l{margin:0}.pl0-l{padding-left:0}.ml0-l,.nl0-l{margin-left:0}.pr0-l{padding-right:0}.mr0-l,.nr0-l{margin-right:0}.pt0-l{padding-top:0}.mt0-l,.nt0-l{margin-top:0}.pb0-l{padding-bottom:0}.mb0-l,.nb0-l{margin-bottom:0}.pv0-l{padding-top:0;padding-bottom:0}.mv0-l,.nv0-l{margin-top:0;margin-bottom:0}.ph0-l{padding-left:0;padding-right:0}.mh0-l,.nh0-l{margin-left:0;margin-right:0}.pa1-l{padding:.25rem}.ma1-l{margin:.25rem}.na1-l{margin:-.25rem}.pl1-l{padding-left:.25rem}.ml1-l{margin-left:.25rem}.nl1-l{margin-left:-.25rem}.pr1-l{padding-right:.25rem}.mr1-l{margin-right:.25rem}.nr1-l{margin-right:-.25rem}.pt1-l{padding-top:.25rem}.mt1-l{margin-top:.25rem}.nt1-l{margin-top:-.25rem}.pb1-l{padding-bottom:.25rem}.mb1-l{margin-bottom:.25rem}.nb1-l{margin-bottom:-.25rem}.pv1-l{padding-top:.25rem;padding-bottom:.25rem}.mv1-l{margin-top:.25rem;margin-bottom:.25rem}.nv1-l{margin-top:-.25rem;margin-bottom:-.25rem}.ph1-l{padding-left:.25rem;padding-right:.25rem}.mh1-l{margin-left:.25rem;margin-right:.25rem}.nh1-l{margin-left:-.25rem;margin-right:-.25rem}.pa2-l{padding:.5rem}.ma2-l{margin:.5rem}.na2-l{margin:-.5rem}.pl2-l{padding-left:.5rem}.ml2-l{margin-left:.5rem}.nl2-l{margin-left:-.5rem}.pr2-l{padding-right:.5rem}.mr2-l{margin-right:.5rem}.nr2-l{margin-right:-.5rem}.pt2-l{padding-top:.5rem}.mt2-l{margin-top:.5rem}.nt2-l{margin-top:-.5rem}.pb2-l{padding-bottom:.5rem}.mb2-l{margin-bottom:.5rem}.nb2-l{margin-bottom:-.5rem}.pv2-l{padding-top:.5rem;padding-bottom:.5rem}.mv2-l{margin-top:.5rem;margin-bottom:.5rem}.nv2-l{margin-top:-.5rem;margin-bottom:-.5rem}.ph2-l{padding-left:.5rem;padding-right:.5rem}.mh2-l{margin-left:.5rem;margin-right:.5rem}.nh2-l{margin-left:-.5rem;margin-right:-.5rem}.pa3-l{padding:.75rem}.ma3-l{margin:.75rem}.na3-l{margin:-.75rem}.pl3-l{padding-left:.75rem}.ml3-l{margin-left:.75rem}.nl3-l{margin-left:-.75rem}.pr3-l{padding-right:.75rem}.mr3-l{margin-right:.75rem}.nr3-l{margin-right:-.75rem}.pt3-l{padding-top:.75rem}.mt3-l{margin-top:.75rem}.nt3-l{margin-top:-.75rem}.pb3-l{padding-bottom:.75rem}.mb3-l{margin-bottom:.75rem}.nb3-l{margin-bottom:-.75rem}.pv3-l{padding-top:.75rem;padding-bottom:.75rem}.mv3-l{margin-top:.75rem;margin-bottom:.75rem}.nv3-l{margin-top:-.75rem;margin-bottom:-.75rem}.ph3-l{padding-left:.75rem;padding-right:.75rem}.mh3-l{margin-left:.75rem;margin-right:.75rem}.nh3-l{margin-left:-.75rem;margin-right:-.75rem}.pa4-l{padding:1rem}.ma4-l{margin:1rem}.na4-l{margin:-1rem}.pl4-l{padding-left:1rem}.ml4-l{margin-left:1rem}.nl4-l{margin-left:-1rem}.pr4-l{padding-right:1rem}.mr4-l{margin-right:1rem}.nr4-l{margin-right:-1rem}.pt4-l{padding-top:1rem}.mt4-l{margin-top:1rem}.nt4-l{margin-top:-1rem}.pb4-l{padding-bottom:1rem}.mb4-l{margin-bottom:1rem}.nb4-l{margin-bottom:-1rem}.pv4-l{padding-top:1rem;padding-bottom:1rem}.mv4-l{margin-top:1rem;margin-bottom:1rem}.nv4-l{margin-top:-1rem;margin-bottom:-1rem}.ph4-l{padding-left:1rem;padding-right:1rem}.mh4-l{margin-left:1rem;margin-right:1rem}.nh4-l{margin-left:-1rem;margin-right:-1rem}.pa5-l{padding:1.25rem}.ma5-l{margin:1.25rem}.na5-l{margin:-1.25rem}.pl5-l{padding-left:1.25rem}.ml5-l{margin-left:1.25rem}.nl5-l{margin-left:-1.25rem}.pr5-l{padding-right:1.25rem}.mr5-l{margin-right:1.25rem}.nr5-l{margin-right:-1.25rem}.pt5-l{padding-top:1.25rem}.mt5-l{margin-top:1.25rem}.nt5-l{margin-top:-1.25rem}.pb5-l{padding-bottom:1.25rem}.mb5-l{margin-bottom:1.25rem}.nb5-l{margin-bottom:-1.25rem}.pv5-l{padding-top:1.25rem;padding-bottom:1.25rem}.mv5-l{margin-top:1.25rem;margin-bottom:1.25rem}.nv5-l{margin-top:-1.25rem;margin-bottom:-1.25rem}.ph5-l{padding-left:1.25rem;padding-right:1.25rem}.mh5-l{margin-left:1.25rem;margin-right:1.25rem}.nh5-l{margin-left:-1.25rem;margin-right:-1.25rem}.pa6-l{padding:1.5rem}.ma6-l{margin:1.5rem}.na6-l{margin:-1.5rem}.pl6-l{padding-left:1.5rem}.ml6-l{margin-left:1.5rem}.nl6-l{margin-left:-1.5rem}.pr6-l{padding-right:1.5rem}.mr6-l{margin-right:1.5rem}.nr6-l{margin-right:-1.5rem}.pt6-l{padding-top:1.5rem}.mt6-l{margin-top:1.5rem}.nt6-l{margin-top:-1.5rem}.pb6-l{padding-bottom:1.5rem}.mb6-l{margin-bottom:1.5rem}.nb6-l{margin-bottom:-1.5rem}.pv6-l{padding-top:1.5rem;padding-bottom:1.5rem}.mv6-l{margin-top:1.5rem;margin-bottom:1.5rem}.nv6-l{margin-top:-1.5rem;margin-bottom:-1.5rem}.ph6-l{padding-left:1.5rem;padding-right:1.5rem}.mh6-l{margin-left:1.5rem;margin-right:1.5rem}.nh6-l{margin-left:-1.5rem;margin-right:-1.5rem}.pa7-l{padding:2rem}.ma7-l{margin:2rem}.na7-l{margin:-2rem}.pl7-l{padding-left:2rem}.ml7-l{margin-left:2rem}.nl7-l{margin-left:-2rem}.pr7-l{padding-right:2rem}.mr7-l{margin-right:2rem}.nr7-l{margin-right:-2rem}.pt7-l{padding-top:2rem}.mt7-l{margin-top:2rem}.nt7-l{margin-top:-2rem}.pb7-l{padding-bottom:2rem}.mb7-l{margin-bottom:2rem}.nb7-l{margin-bottom:-2rem}.pv7-l{padding-top:2rem;padding-bottom:2rem}.mv7-l{margin-top:2rem;margin-bottom:2rem}.nv7-l{margin-top:-2rem;margin-bottom:-2rem}.ph7-l{padding-left:2rem;padding-right:2rem}.mh7-l{margin-left:2rem;margin-right:2rem}.nh7-l{margin-left:-2rem;margin-right:-2rem}.pa8-l{padding:3rem}.ma8-l{margin:3rem}.na8-l{margin:-3rem}.pl8-l{padding-left:3rem}.ml8-l{margin-left:3rem}.nl8-l{margin-left:-3rem}.pr8-l{padding-right:3rem}.mr8-l{margin-right:3rem}.nr8-l{margin-right:-3rem}.pt8-l{padding-top:3rem}.mt8-l{margin-top:3rem}.nt8-l{margin-top:-3rem}.pb8-l{padding-bottom:3rem}.mb8-l{margin-bottom:3rem}.nb8-l{margin-bottom:-3rem}.pv8-l{padding-top:3rem;padding-bottom:3rem}.mv8-l{margin-top:3rem;margin-bottom:3rem}.nv8-l{margin-top:-3rem;margin-bottom:-3rem}.ph8-l{padding-left:3rem;padding-right:3rem}.mh8-l{margin-left:3rem;margin-right:3rem}.nh8-l{margin-left:-3rem;margin-right:-3rem}.pa9-l{padding:4rem}.ma9-l{margin:4rem}.na9-l{margin:-4rem}.pl9-l{padding-left:4rem}.ml9-l{margin-left:4rem}.nl9-l{margin-left:-4rem}.pr9-l{padding-right:4rem}.mr9-l{margin-right:4rem}.nr9-l{margin-right:-4rem}.pt9-l{padding-top:4rem}.mt9-l{margin-top:4rem}.nt9-l{margin-top:-4rem}.pb9-l{padding-bottom:4rem}.mb9-l{margin-bottom:4rem}.nb9-l{margin-bottom:-4rem}.pv9-l{padding-top:4rem;padding-bottom:4rem}.mv9-l{margin-top:4rem;margin-bottom:4rem}.nv9-l{margin-top:-4rem;margin-bottom:-4rem}.ph9-l{padding-left:4rem;padding-right:4rem}.mh9-l{margin-left:4rem;margin-right:4rem}.nh9-l{margin-left:-4rem;margin-right:-4rem}.pa10-l{padding:6rem}.ma10-l{margin:6rem}.na10-l{margin:-6rem}.pl10-l{padding-left:6rem}.ml10-l{margin-left:6rem}.nl10-l{margin-left:-6rem}.pr10-l{padding-right:6rem}.mr10-l{margin-right:6rem}.nr10-l{margin-right:-6rem}.pt10-l{padding-top:6rem}.mt10-l{margin-top:6rem}.nt10-l{margin-top:-6rem}.pb10-l{padding-bottom:6rem}.mb10-l{margin-bottom:6rem}.nb10-l{margin-bottom:-6rem}.pv10-l{padding-top:6rem;padding-bottom:6rem}.mv10-l{margin-top:6rem;margin-bottom:6rem}.nv10-l{margin-top:-6rem;margin-bottom:-6rem}.ph10-l{padding-left:6rem;padding-right:6rem}.mh10-l{margin-left:6rem;margin-right:6rem}.nh10-l{margin-left:-6rem;margin-right:-6rem}.pa11-l{padding:10rem}.ma11-l{margin:10rem}.na11-l{margin:-10rem}.pl11-l{padding-left:10rem}.ml11-l{margin-left:10rem}.nl11-l{margin-left:-10rem}.pr11-l{padding-right:10rem}.mr11-l{margin-right:10rem}.nr11-l{margin-right:-10rem}.pt11-l{padding-top:10rem}.mt11-l{margin-top:10rem}.nt11-l{margin-top:-10rem}.pb11-l{padding-bottom:10rem}.mb11-l{margin-bottom:10rem}.nb11-l{margin-bottom:-10rem}.pv11-l{padding-top:10rem;padding-bottom:10rem}.mv11-l{margin-top:10rem;margin-bottom:10rem}.nv11-l{margin-top:-10rem;margin-bottom:-10rem}.ph11-l{padding-left:10rem;padding-right:10rem}.mh11-l{margin-left:10rem;margin-right:10rem}.nh11-l{margin-left:-10rem;margin-right:-10rem}.pa12-l{padding:18rem}.ma12-l{margin:18rem}.na12-l{margin:-18rem}.pl12-l{padding-left:18rem}.ml12-l{margin-left:18rem}.nl12-l{margin-left:-18rem}.pr12-l{padding-right:18rem}.mr12-l{margin-right:18rem}.nr12-l{margin-right:-18rem}.pt12-l{padding-top:18rem}.mt12-l{margin-top:18rem}.nt12-l{margin-top:-18rem}.pb12-l{padding-bottom:18rem}.mb12-l{margin-bottom:18rem}.nb12-l{margin-bottom:-18rem}.pv12-l{padding-top:18rem;padding-bottom:18rem}.mv12-l{margin-top:18rem;margin-bottom:18rem}.nv12-l{margin-top:-18rem;margin-bottom:-18rem}.ph12-l{padding-left:18rem;padding-right:18rem}.mh12-l{margin-left:18rem;margin-right:18rem}.nh12-l{margin-left:-18rem;margin-right:-18rem}.top-0-l{top:0}.right-0-l{right:0}.bottom-0-l{bottom:0}.left-0-l{left:0}.top-1-l{top:1rem}.right-1-l{right:1rem}.bottom-1-l{bottom:1rem}.left-1-l{left:1rem}.top-2-l{top:2rem}.right-2-l{right:2rem}.bottom-2-l{bottom:2rem}.left-2-l{left:2rem}.top--1-l{top:-1rem}.right--1-l{right:-1rem}.bottom--1-l{bottom:-1rem}.left--1-l{left:-1rem}.top--2-l{top:-2rem}.right--2-l{right:-2rem}.bottom--2-l{bottom:-2rem}.left--2-l{left:-2rem}.absolute--fill-l{top:0;right:0;bottom:0;left:0}.cf-l:after,.cf-l:before{content:" ";display:table}.cf-l:after{clear:both}.cf-l{*zoom:1}.cl-l{clear:left}.cr-l{clear:right}.cb-l{clear:both}.cn-l{clear:none}.dn-l{display:none}.di-l{display:inline}.db-l{display:block}.dib-l{display:inline-block}.dit-l{display:inline-table}.dt-l{display:table}.dtc-l{display:table-cell}.dt-row-l{display:table-row}.dt-row-group-l{display:table-row-group}.dt-column-l{display:table-column}.dt-column-group-l{display:table-column-group}.dt--fixed-l{table-layout:fixed;width:100%}.flex-l{display:flex}.inline-flex-l{display:inline-flex}.flex-auto-l{flex:1 1 auto;min-width:0;min-height:0}.flex-none-l{flex:none}.flex-column-l{flex-direction:column}.flex-row-l{flex-direction:row}.flex-wrap-l{flex-wrap:wrap}.flex-nowrap-l{flex-wrap:nowrap}.flex-wrap-reverse-l{flex-wrap:wrap-reverse}.flex-column-reverse-l{flex-direction:column-reverse}.flex-row-reverse-l{flex-direction:row-reverse}.items-start-l{align-items:flex-start}.items-end-l{align-items:flex-end}.items-center-l{align-items:center}.items-baseline-l{align-items:baseline}.items-stretch-l{align-items:stretch}.self-start-l{align-self:flex-start}.self-end-l{align-self:flex-end}.self-center-l{align-self:center}.self-baseline-l{align-self:baseline}.self-stretch-l{align-self:stretch}.justify-start-l{justify-content:flex-start}.justify-end-l{justify-content:flex-end}.justify-center-l{justify-content:center}.justify-between-l{justify-content:space-between}.justify-around-l{justify-content:space-around}.content-start-l{align-content:flex-start}.content-end-l{align-content:flex-end}.content-center-l{align-content:center}.content-between-l{align-content:space-between}.content-around-l{align-content:space-around}.content-stretch-l{align-content:stretch}.order-0-l{order:0}.order-1-l{order:1}.order-2-l{order:2}.order-3-l{order:3}.order-4-l{order:4}.order-5-l{order:5}.order-6-l{order:6}.order-7-l{order:7}.order-8-l{order:8}.order-last-l{order:99999}.flex-grow-0-l{flex-grow:0}.flex-grow-1-l{flex-grow:1}.flex-shrink-0-l{flex-shrink:0}.flex-shrink-1-l{flex-shrink:1}.fl-l{float:left}.fl-l,.fr-l{_display:inline}.fr-l{float:right}.fn-l{float:none}.i-l{font-style:italic}.fs-normal-l{font-style:normal}.normal-l{font-weight:400}.b-l{font-weight:700}.fw1-l{font-weight:100}.fw2-l{font-weight:200}.fw3-l{font-weight:300}.fw4-l{font-weight:400}.fw5-l{font-weight:500}.fw6-l{font-weight:600}.fw7-l{font-weight:700}.fw8-l{font-weight:800}.fw9-l{font-weight:900}.h1-l{height:1rem}.h2-l{height:2rem}.h3-l{height:4rem}.h4-l{height:8rem}.h5-l{height:16rem}.h-25-l{height:25%}.h-50-l{height:50%}.h-75-l{height:75%}.h-100-l{height:100%}.min-h-100-l{min-height:100%}.vh-25-l{height:25vh}.vh-50-l{height:50vh}.vh-75-l{height:75vh}.vh-100-l{height:100vh}.min-vh-100-l{min-height:100vh}.h-auto-l{height:auto}.h-inherit-l{height:inherit}.tracked-l{letter-spacing:.1em}.tracked-tight-l{letter-spacing:-.05em}.tracked-mega-l{letter-spacing:.25em}.lh-solid-l{line-height:1.333333}.lh-title-l{line-height:1.5}.lh-copy-l{line-height:1.666666}.mw1-l{max-width:1rem}.mw2-l{max-width:2rem}.mw3-l{max-width:4rem}.mw4-l{max-width:8rem}.mw5-l{max-width:16rem}.mw6-l{max-width:32rem}.mw7-l{max-width:48rem}.mw8-l{max-width:64rem}.mw9-l{max-width:96rem}.mw-none-l{max-width:none}.mw-100-l{max-width:100%}.o-100-l{opacity:1}.o-90-l{opacity:.9}.o-80-l{opacity:.8}.o-70-l{opacity:.7}.o-60-l{opacity:.6}.o-50-l{opacity:.5}.o-40-l{opacity:.4}.o-30-l{opacity:.3}.o-20-l{opacity:.2}.o-10-l{opacity:.1}.o-05-l{opacity:.05}.o-025-l{opacity:.025}.o-0-l{opacity:0}.rotate-45-l{-webkit-transform:rotate(45deg);transform:rotate(45deg)}.rotate-90-l{-webkit-transform:rotate(90deg);transform:rotate(90deg)}.rotate-135-l{-webkit-transform:rotate(135deg);transform:rotate(135deg)}.rotate-180-l{-webkit-transform:rotate(180deg);transform:rotate(180deg)}.rotate-225-l{-webkit-transform:rotate(225deg);transform:rotate(225deg)}.rotate-270-l{-webkit-transform:rotate(270deg);transform:rotate(270deg)}.rotate-315-l{-webkit-transform:rotate(315deg);transform:rotate(315deg)}.outline-l{outline:1px solid}.outline-transparent-l{outline:1px solid transparent}.outline-0-l{outline:0}.overflow-visible-l{overflow:visible}.overflow-hidden-l{overflow:hidden}.overflow-scroll-l{overflow:scroll}.overflow-auto-l{overflow:auto}.overflow-x-visible-l{overflow-x:visible}.overflow-x-hidden-l{overflow-x:hidden}.overflow-x-scroll-l{overflow-x:scroll}.overflow-x-auto-l{overflow-x:auto}.overflow-y-visible-l{overflow-y:visible}.overflow-y-hidden-l{overflow-y:hidden}.overflow-y-scroll-l{overflow-y:scroll}.overflow-y-auto-l{overflow-y:auto}.static-l{position:static}.relative-l{position:relative}.absolute-l{position:absolute}.fixed-l{position:fixed}.strike-l{text-decoration:line-through}.underline-l{text-decoration:underline}.no-underline-l{text-decoration:none}.tl-l{text-align:left}.tr-l{text-align:right}.tc-l{text-align:center}.tj-l{text-align:justify}.ttc-l{text-transform:capitalize}.ttl-l{text-transform:lowercase}.ttu-l{text-transform:uppercase}.ttn-l{text-transform:none}.f1-l{font-size:4.5rem}.f2-l{font-size:4rem}.f3-l{font-size:3rem}.f4-l{font-size:2rem}.f5-l{font-size:1.5rem}.f6-l{font-size:1.125rem}.f7-l{font-size:1rem}.f8-l{font-size:.875rem}.f9-l{font-size:.75rem}.measure-l{max-width:30em}.measure-wide-l{max-width:34em}.measure-narrow-l{max-width:20em}.small-caps-l{font-variant:small-caps}.indent-l{text-indent:1em;margin-top:0;margin-bottom:0}.truncate-l{white-space:nowrap;overflow:hidden;text-overflow:ellipsis}.clip-l{position:fixed!important;_position:absolute!important;clip:rect(1px 1px 1px 1px);clip:rect(1px,1px,1px,1px)}.ws-normal-l{white-space:normal}.nowrap-l{white-space:nowrap}.pre-l{white-space:pre}.w1-l{width:1rem}.w2-l{width:2rem}.w3-l{width:4rem}.w4-l{width:8rem}.w5-l{width:16rem}.w-10-l{width:10%}.w-20-l{width:20%}.w-25-l{width:25%}.w-30-l{width:30%}.w-33-l{width:33%}.w-34-l{width:34%}.w-40-l{width:40%}.w-50-l{width:50%}.w-60-l{width:60%}.w-70-l{width:70%}.w-75-l{width:75%}.w-80-l{width:80%}.w-90-l{width:90%}.w-100-l{width:100%}.w-third-l{width:33.33333%}.w-two-thirds-l{width:66.66667%}.w-auto-l{width:auto}}@media screen and (min-width:60em){.aspect-ratio-xl{height:0;position:relative}.aspect-ratio--16x9-xl{padding-bottom:56.25%}.aspect-ratio--9x16-xl{padding-bottom:177.77%}.aspect-ratio--4x3-xl{padding-bottom:75%}.aspect-ratio--3x4-xl{padding-bottom:133.33%}.aspect-ratio--6x4-xl{padding-bottom:66.6%}.aspect-ratio--4x6-xl{padding-bottom:150%}.aspect-ratio--8x5-xl{padding-bottom:62.5%}.aspect-ratio--5x8-xl{padding-bottom:160%}.aspect-ratio--7x5-xl{padding-bottom:71.42%}.aspect-ratio--5x7-xl{padding-bottom:140%}.aspect-ratio--1x1-xl{padding-bottom:100%}.aspect-ratio--object-xl{position:absolute;top:0;right:0;bottom:0;left:0;width:100%;height:100%;z-index:100}.cover-xl{background-size:cover!important}.contain-xl{background-size:contain!important}.bg-center-xl{background-position:50%}.bg-center-xl,.bg-top-xl{background-repeat:no-repeat}.bg-top-xl{background-position:top}.bg-right-xl{background-position:100%}.bg-bottom-xl,.bg-right-xl{background-repeat:no-repeat}.bg-bottom-xl{background-position:bottom}.bg-left-xl{background-repeat:no-repeat;background-position:0}.ba-xl{border-style:solid;border-width:1px}.bt-xl{border-top-style:solid;border-top-width:1px}.br-xl{border-right-style:solid;border-right-width:1px}.bb-xl{border-bottom-style:solid;border-bottom-width:1px}.bl-xl{border-left-style:solid;border-left-width:1px}.bn-xl{border-style:none;border-width:0}.br0-xl{border-radius:0}.br1-xl{border-radius:.125rem}.br2-xl{border-radius:.25rem}.br3-xl{border-radius:.5rem}.br4-xl{border-radius:1rem}.br-100-xl{border-radius:100%}.br-pill-xl{border-radius:9999px}.br--bottom-xl{border-top-left-radius:0;border-top-right-radius:0}.br--top-xl{border-bottom-right-radius:0}.br--right-xl,.br--top-xl{border-bottom-left-radius:0}.br--right-xl{border-top-left-radius:0}.br--left-xl{border-top-right-radius:0;border-bottom-right-radius:0}.b--dotted-xl{border-style:dotted}.b--dashed-xl{border-style:dashed}.b--solid-xl{border-style:solid}.b--none-xl{border-style:none}.bw0-xl{border-width:0}.bw1-xl{border-width:.125rem}.bw2-xl{border-width:.25rem}.bw3-xl{border-width:.5rem}.bw4-xl{border-width:1rem}.bw5-xl{border-width:2rem}.bt-0-xl{border-top-width:0}.br-0-xl{border-right-width:0}.bb-0-xl{border-bottom-width:0}.bl-0-xl{border-left-width:0}.shadow-1-xl{box-shadow:0 0 4px 2px rgba(0,0,0,.2)}.shadow-2-xl{box-shadow:0 0 8px 2px rgba(0,0,0,.2)}.shadow-3-xl{box-shadow:2px 2px 4px 2px rgba(0,0,0,.2)}.shadow-4-xl{box-shadow:2px 2px 8px 0 rgba(0,0,0,.2)}.shadow-5-xl{box-shadow:4px 4px 8px 0 rgba(0,0,0,.2)}.pa0-xl{padding:0}.ma0-xl,.na0-xl{margin:0}.pl0-xl{padding-left:0}.ml0-xl,.nl0-xl{margin-left:0}.pr0-xl{padding-right:0}.mr0-xl,.nr0-xl{margin-right:0}.pt0-xl{padding-top:0}.mt0-xl,.nt0-xl{margin-top:0}.pb0-xl{padding-bottom:0}.mb0-xl,.nb0-xl{margin-bottom:0}.pv0-xl{padding-top:0;padding-bottom:0}.mv0-xl,.nv0-xl{margin-top:0;margin-bottom:0}.ph0-xl{padding-left:0;padding-right:0}.mh0-xl,.nh0-xl{margin-left:0;margin-right:0}.pa1-xl{padding:.25rem}.ma1-xl{margin:.25rem}.na1-xl{margin:-.25rem}.pl1-xl{padding-left:.25rem}.ml1-xl{margin-left:.25rem}.nl1-xl{margin-left:-.25rem}.pr1-xl{padding-right:.25rem}.mr1-xl{margin-right:.25rem}.nr1-xl{margin-right:-.25rem}.pt1-xl{padding-top:.25rem}.mt1-xl{margin-top:.25rem}.nt1-xl{margin-top:-.25rem}.pb1-xl{padding-bottom:.25rem}.mb1-xl{margin-bottom:.25rem}.nb1-xl{margin-bottom:-.25rem}.pv1-xl{padding-top:.25rem;padding-bottom:.25rem}.mv1-xl{margin-top:.25rem;margin-bottom:.25rem}.nv1-xl{margin-top:-.25rem;margin-bottom:-.25rem}.ph1-xl{padding-left:.25rem;padding-right:.25rem}.mh1-xl{margin-left:.25rem;margin-right:.25rem}.nh1-xl{margin-left:-.25rem;margin-right:-.25rem}.pa2-xl{padding:.5rem}.ma2-xl{margin:.5rem}.na2-xl{margin:-.5rem}.pl2-xl{padding-left:.5rem}.ml2-xl{margin-left:.5rem}.nl2-xl{margin-left:-.5rem}.pr2-xl{padding-right:.5rem}.mr2-xl{margin-right:.5rem}.nr2-xl{margin-right:-.5rem}.pt2-xl{padding-top:.5rem}.mt2-xl{margin-top:.5rem}.nt2-xl{margin-top:-.5rem}.pb2-xl{padding-bottom:.5rem}.mb2-xl{margin-bottom:.5rem}.nb2-xl{margin-bottom:-.5rem}.pv2-xl{padding-top:.5rem;padding-bottom:.5rem}.mv2-xl{margin-top:.5rem;margin-bottom:.5rem}.nv2-xl{margin-top:-.5rem;margin-bottom:-.5rem}.ph2-xl{padding-left:.5rem;padding-right:.5rem}.mh2-xl{margin-left:.5rem;margin-right:.5rem}.nh2-xl{margin-left:-.5rem;margin-right:-.5rem}.pa3-xl{padding:.75rem}.ma3-xl{margin:.75rem}.na3-xl{margin:-.75rem}.pl3-xl{padding-left:.75rem}.ml3-xl{margin-left:.75rem}.nl3-xl{margin-left:-.75rem}.pr3-xl{padding-right:.75rem}.mr3-xl{margin-right:.75rem}.nr3-xl{margin-right:-.75rem}.pt3-xl{padding-top:.75rem}.mt3-xl{margin-top:.75rem}.nt3-xl{margin-top:-.75rem}.pb3-xl{padding-bottom:.75rem}.mb3-xl{margin-bottom:.75rem}.nb3-xl{margin-bottom:-.75rem}.pv3-xl{padding-top:.75rem;padding-bottom:.75rem}.mv3-xl{margin-top:.75rem;margin-bottom:.75rem}.nv3-xl{margin-top:-.75rem;margin-bottom:-.75rem}.ph3-xl{padding-left:.75rem;padding-right:.75rem}.mh3-xl{margin-left:.75rem;margin-right:.75rem}.nh3-xl{margin-left:-.75rem;margin-right:-.75rem}.pa4-xl{padding:1rem}.ma4-xl{margin:1rem}.na4-xl{margin:-1rem}.pl4-xl{padding-left:1rem}.ml4-xl{margin-left:1rem}.nl4-xl{margin-left:-1rem}.pr4-xl{padding-right:1rem}.mr4-xl{margin-right:1rem}.nr4-xl{margin-right:-1rem}.pt4-xl{padding-top:1rem}.mt4-xl{margin-top:1rem}.nt4-xl{margin-top:-1rem}.pb4-xl{padding-bottom:1rem}.mb4-xl{margin-bottom:1rem}.nb4-xl{margin-bottom:-1rem}.pv4-xl{padding-top:1rem;padding-bottom:1rem}.mv4-xl{margin-top:1rem;margin-bottom:1rem}.nv4-xl{margin-top:-1rem;margin-bottom:-1rem}.ph4-xl{padding-left:1rem;padding-right:1rem}.mh4-xl{margin-left:1rem;margin-right:1rem}.nh4-xl{margin-left:-1rem;margin-right:-1rem}.pa5-xl{padding:1.25rem}.ma5-xl{margin:1.25rem}.na5-xl{margin:-1.25rem}.pl5-xl{padding-left:1.25rem}.ml5-xl{margin-left:1.25rem}.nl5-xl{margin-left:-1.25rem}.pr5-xl{padding-right:1.25rem}.mr5-xl{margin-right:1.25rem}.nr5-xl{margin-right:-1.25rem}.pt5-xl{padding-top:1.25rem}.mt5-xl{margin-top:1.25rem}.nt5-xl{margin-top:-1.25rem}.pb5-xl{padding-bottom:1.25rem}.mb5-xl{margin-bottom:1.25rem}.nb5-xl{margin-bottom:-1.25rem}.pv5-xl{padding-top:1.25rem;padding-bottom:1.25rem}.mv5-xl{margin-top:1.25rem;margin-bottom:1.25rem}.nv5-xl{margin-top:-1.25rem;margin-bottom:-1.25rem}.ph5-xl{padding-left:1.25rem;padding-right:1.25rem}.mh5-xl{margin-left:1.25rem;margin-right:1.25rem}.nh5-xl{margin-left:-1.25rem;margin-right:-1.25rem}.pa6-xl{padding:1.5rem}.ma6-xl{margin:1.5rem}.na6-xl{margin:-1.5rem}.pl6-xl{padding-left:1.5rem}.ml6-xl{margin-left:1.5rem}.nl6-xl{margin-left:-1.5rem}.pr6-xl{padding-right:1.5rem}.mr6-xl{margin-right:1.5rem}.nr6-xl{margin-right:-1.5rem}.pt6-xl{padding-top:1.5rem}.mt6-xl{margin-top:1.5rem}.nt6-xl{margin-top:-1.5rem}.pb6-xl{padding-bottom:1.5rem}.mb6-xl{margin-bottom:1.5rem}.nb6-xl{margin-bottom:-1.5rem}.pv6-xl{padding-top:1.5rem;padding-bottom:1.5rem}.mv6-xl{margin-top:1.5rem;margin-bottom:1.5rem}.nv6-xl{margin-top:-1.5rem;margin-bottom:-1.5rem}.ph6-xl{padding-left:1.5rem;padding-right:1.5rem}.mh6-xl{margin-left:1.5rem;margin-right:1.5rem}.nh6-xl{margin-left:-1.5rem;margin-right:-1.5rem}.pa7-xl{padding:2rem}.ma7-xl{margin:2rem}.na7-xl{margin:-2rem}.pl7-xl{padding-left:2rem}.ml7-xl{margin-left:2rem}.nl7-xl{margin-left:-2rem}.pr7-xl{padding-right:2rem}.mr7-xl{margin-right:2rem}.nr7-xl{margin-right:-2rem}.pt7-xl{padding-top:2rem}.mt7-xl{margin-top:2rem}.nt7-xl{margin-top:-2rem}.pb7-xl{padding-bottom:2rem}.mb7-xl{margin-bottom:2rem}.nb7-xl{margin-bottom:-2rem}.pv7-xl{padding-top:2rem;padding-bottom:2rem}.mv7-xl{margin-top:2rem;margin-bottom:2rem}.nv7-xl{margin-top:-2rem;margin-bottom:-2rem}.ph7-xl{padding-left:2rem;padding-right:2rem}.mh7-xl{margin-left:2rem;margin-right:2rem}.nh7-xl{margin-left:-2rem;margin-right:-2rem}.pa8-xl{padding:3rem}.ma8-xl{margin:3rem}.na8-xl{margin:-3rem}.pl8-xl{padding-left:3rem}.ml8-xl{margin-left:3rem}.nl8-xl{margin-left:-3rem}.pr8-xl{padding-right:3rem}.mr8-xl{margin-right:3rem}.nr8-xl{margin-right:-3rem}.pt8-xl{padding-top:3rem}.mt8-xl{margin-top:3rem}.nt8-xl{margin-top:-3rem}.pb8-xl{padding-bottom:3rem}.mb8-xl{margin-bottom:3rem}.nb8-xl{margin-bottom:-3rem}.pv8-xl{padding-top:3rem;padding-bottom:3rem}.mv8-xl{margin-top:3rem;margin-bottom:3rem}.nv8-xl{margin-top:-3rem;margin-bottom:-3rem}.ph8-xl{padding-left:3rem;padding-right:3rem}.mh8-xl{margin-left:3rem;margin-right:3rem}.nh8-xl{margin-left:-3rem;margin-right:-3rem}.pa9-xl{padding:4rem}.ma9-xl{margin:4rem}.na9-xl{margin:-4rem}.pl9-xl{padding-left:4rem}.ml9-xl{margin-left:4rem}.nl9-xl{margin-left:-4rem}.pr9-xl{padding-right:4rem}.mr9-xl{margin-right:4rem}.nr9-xl{margin-right:-4rem}.pt9-xl{padding-top:4rem}.mt9-xl{margin-top:4rem}.nt9-xl{margin-top:-4rem}.pb9-xl{padding-bottom:4rem}.mb9-xl{margin-bottom:4rem}.nb9-xl{margin-bottom:-4rem}.pv9-xl{padding-top:4rem;padding-bottom:4rem}.mv9-xl{margin-top:4rem;margin-bottom:4rem}.nv9-xl{margin-top:-4rem;margin-bottom:-4rem}.ph9-xl{padding-left:4rem;padding-right:4rem}.mh9-xl{margin-left:4rem;margin-right:4rem}.nh9-xl{margin-left:-4rem;margin-right:-4rem}.pa10-xl{padding:6rem}.ma10-xl{margin:6rem}.na10-xl{margin:-6rem}.pl10-xl{padding-left:6rem}.ml10-xl{margin-left:6rem}.nl10-xl{margin-left:-6rem}.pr10-xl{padding-right:6rem}.mr10-xl{margin-right:6rem}.nr10-xl{margin-right:-6rem}.pt10-xl{padding-top:6rem}.mt10-xl{margin-top:6rem}.nt10-xl{margin-top:-6rem}.pb10-xl{padding-bottom:6rem}.mb10-xl{margin-bottom:6rem}.nb10-xl{margin-bottom:-6rem}.pv10-xl{padding-top:6rem;padding-bottom:6rem}.mv10-xl{margin-top:6rem;margin-bottom:6rem}.nv10-xl{margin-top:-6rem;margin-bottom:-6rem}.ph10-xl{padding-left:6rem;padding-right:6rem}.mh10-xl{margin-left:6rem;margin-right:6rem}.nh10-xl{margin-left:-6rem;margin-right:-6rem}.pa11-xl{padding:10rem}.ma11-xl{margin:10rem}.na11-xl{margin:-10rem}.pl11-xl{padding-left:10rem}.ml11-xl{margin-left:10rem}.nl11-xl{margin-left:-10rem}.pr11-xl{padding-right:10rem}.mr11-xl{margin-right:10rem}.nr11-xl{margin-right:-10rem}.pt11-xl{padding-top:10rem}.mt11-xl{margin-top:10rem}.nt11-xl{margin-top:-10rem}.pb11-xl{padding-bottom:10rem}.mb11-xl{margin-bottom:10rem}.nb11-xl{margin-bottom:-10rem}.pv11-xl{padding-top:10rem;padding-bottom:10rem}.mv11-xl{margin-top:10rem;margin-bottom:10rem}.nv11-xl{margin-top:-10rem;margin-bottom:-10rem}.ph11-xl{padding-left:10rem;padding-right:10rem}.mh11-xl{margin-left:10rem;margin-right:10rem}.nh11-xl{margin-left:-10rem;margin-right:-10rem}.pa12-xl{padding:18rem}.ma12-xl{margin:18rem}.na12-xl{margin:-18rem}.pl12-xl{padding-left:18rem}.ml12-xl{margin-left:18rem}.nl12-xl{margin-left:-18rem}.pr12-xl{padding-right:18rem}.mr12-xl{margin-right:18rem}.nr12-xl{margin-right:-18rem}.pt12-xl{padding-top:18rem}.mt12-xl{margin-top:18rem}.nt12-xl{margin-top:-18rem}.pb12-xl{padding-bottom:18rem}.mb12-xl{margin-bottom:18rem}.nb12-xl{margin-bottom:-18rem}.pv12-xl{padding-top:18rem;padding-bottom:18rem}.mv12-xl{margin-top:18rem;margin-bottom:18rem}.nv12-xl{margin-top:-18rem;margin-bottom:-18rem}.ph12-xl{padding-left:18rem;padding-right:18rem}.mh12-xl{margin-left:18rem;margin-right:18rem}.nh12-xl{margin-left:-18rem;margin-right:-18rem}.top-0-xl{top:0}.right-0-xl{right:0}.bottom-0-xl{bottom:0}.left-0-xl{left:0}.top-1-xl{top:1rem}.right-1-xl{right:1rem}.bottom-1-xl{bottom:1rem}.left-1-xl{left:1rem}.top-2-xl{top:2rem}.right-2-xl{right:2rem}.bottom-2-xl{bottom:2rem}.left-2-xl{left:2rem}.top--1-xl{top:-1rem}.right--1-xl{right:-1rem}.bottom--1-xl{bottom:-1rem}.left--1-xl{left:-1rem}.top--2-xl{top:-2rem}.right--2-xl{right:-2rem}.bottom--2-xl{bottom:-2rem}.left--2-xl{left:-2rem}.absolute--fill-xl{top:0;right:0;bottom:0;left:0}.cf-xl:after,.cf-xl:before{content:" ";display:table}.cf-xl:after{clear:both}.cf-xl{*zoom:1}.cl-xl{clear:left}.cr-xl{clear:right}.cb-xl{clear:both}.cn-xl{clear:none}.dn-xl{display:none}.di-xl{display:inline}.db-xl{display:block}.dib-xl{display:inline-block}.dit-xl{display:inline-table}.dt-xl{display:table}.dtc-xl{display:table-cell}.dt-row-xl{display:table-row}.dt-row-group-xl{display:table-row-group}.dt-column-xl{display:table-column}.dt-column-group-xl{display:table-column-group}.dt--fixed-xl{table-layout:fixed;width:100%}.flex-xl{display:flex}.inline-flex-xl{display:inline-flex}.flex-auto-xl{flex:1 1 auto;min-width:0;min-height:0}.flex-none-xl{flex:none}.flex-column-xl{flex-direction:column}.flex-row-xl{flex-direction:row}.flex-wrap-xl{flex-wrap:wrap}.flex-nowrap-xl{flex-wrap:nowrap}.flex-wrap-reverse-xl{flex-wrap:wrap-reverse}.flex-column-reverse-xl{flex-direction:column-reverse}.flex-row-reverse-xl{flex-direction:row-reverse}.items-start-xl{align-items:flex-start}.items-end-xl{align-items:flex-end}.items-center-xl{align-items:center}.items-baseline-xl{align-items:baseline}.items-stretch-xl{align-items:stretch}.self-start-xl{align-self:flex-start}.self-end-xl{align-self:flex-end}.self-center-xl{align-self:center}.self-baseline-xl{align-self:baseline}.self-stretch-xl{align-self:stretch}.justify-start-xl{justify-content:flex-start}.justify-end-xl{justify-content:flex-end}.justify-center-xl{justify-content:center}.justify-between-xl{justify-content:space-between}.justify-around-xl{justify-content:space-around}.content-start-xl{align-content:flex-start}.content-end-xl{align-content:flex-end}.content-center-xl{align-content:center}.content-between-xl{align-content:space-between}.content-around-xl{align-content:space-around}.content-stretch-xl{align-content:stretch}.order-0-xl{order:0}.order-1-xl{order:1}.order-2-xl{order:2}.order-3-xl{order:3}.order-4-xl{order:4}.order-5-xl{order:5}.order-6-xl{order:6}.order-7-xl{order:7}.order-8-xl{order:8}.order-last-xl{order:99999}.flex-grow-0-xl{flex-grow:0}.flex-grow-1-xl{flex-grow:1}.flex-shrink-0-xl{flex-shrink:0}.flex-shrink-1-xl{flex-shrink:1}.fl-xl{float:left}.fl-xl,.fr-xl{_display:inline}.fr-xl{float:right}.fn-xl{float:none}.i-xl{font-style:italic}.fs-normal-xl{font-style:normal}.normal-xl{font-weight:400}.b-xl{font-weight:700}.fw1-xl{font-weight:100}.fw2-xl{font-weight:200}.fw3-xl{font-weight:300}.fw4-xl{font-weight:400}.fw5-xl{font-weight:500}.fw6-xl{font-weight:600}.fw7-xl{font-weight:700}.fw8-xl{font-weight:800}.fw9-xl{font-weight:900}.h1-xl{height:1rem}.h2-xl{height:2rem}.h3-xl{height:4rem}.h4-xl{height:8rem}.h5-xl{height:16rem}.h-25-xl{height:25%}.h-50-xl{height:50%}.h-75-xl{height:75%}.h-100-xl{height:100%}.min-h-100-xl{min-height:100%}.vh-25-xl{height:25vh}.vh-50-xl{height:50vh}.vh-75-xl{height:75vh}.vh-100-xl{height:100vh}.min-vh-100-xl{min-height:100vh}.h-auto-xl{height:auto}.h-inherit-xl{height:inherit}.tracked-xl{letter-spacing:.1em}.tracked-tight-xl{letter-spacing:-.05em}.tracked-mega-xl{letter-spacing:.25em}.lh-solid-xl{line-height:1.333333}.lh-title-xl{line-height:1.5}.lh-copy-xl{line-height:1.666666}.mw1-xl{max-width:1rem}.mw2-xl{max-width:2rem}.mw3-xl{max-width:4rem}.mw4-xl{max-width:8rem}.mw5-xl{max-width:16rem}.mw6-xl{max-width:32rem}.mw7-xl{max-width:48rem}.mw8-xl{max-width:64rem}.mw9-xl{max-width:96rem}.mw-none-xl{max-width:none}.mw-100-xl{max-width:100%}.o-100-xl{opacity:1}.o-90-xl{opacity:.9}.o-80-xl{opacity:.8}.o-70-xl{opacity:.7}.o-60-xl{opacity:.6}.o-50-xl{opacity:.5}.o-40-xl{opacity:.4}.o-30-xl{opacity:.3}.o-20-xl{opacity:.2}.o-10-xl{opacity:.1}.o-05-xl{opacity:.05}.o-025-xl{opacity:.025}.o-0-xl{opacity:0}.rotate-45-xl{-webkit-transform:rotate(45deg);transform:rotate(45deg)}.rotate-90-xl{-webkit-transform:rotate(90deg);transform:rotate(90deg)}.rotate-135-xl{-webkit-transform:rotate(135deg);transform:rotate(135deg)}.rotate-180-xl{-webkit-transform:rotate(180deg);transform:rotate(180deg)}.rotate-225-xl{-webkit-transform:rotate(225deg);transform:rotate(225deg)}.rotate-270-xl{-webkit-transform:rotate(270deg);transform:rotate(270deg)}.rotate-315-xl{-webkit-transform:rotate(315deg);transform:rotate(315deg)}.outline-xl{outline:1px solid}.outline-transparent-xl{outline:1px solid transparent}.outline-0-xl{outline:0}.overflow-visible-xl{overflow:visible}.overflow-hidden-xl{overflow:hidden}.overflow-scroll-xl{overflow:scroll}.overflow-auto-xl{overflow:auto}.overflow-x-visible-xl{overflow-x:visible}.overflow-x-hidden-xl{overflow-x:hidden}.overflow-x-scroll-xl{overflow-x:scroll}.overflow-x-auto-xl{overflow-x:auto}.overflow-y-visible-xl{overflow-y:visible}.overflow-y-hidden-xl{overflow-y:hidden}.overflow-y-scroll-xl{overflow-y:scroll}.overflow-y-auto-xl{overflow-y:auto}.static-xl{position:static}.relative-xl{position:relative}.absolute-xl{position:absolute}.fixed-xl{position:fixed}.strike-xl{text-decoration:line-through}.underline-xl{text-decoration:underline}.no-underline-xl{text-decoration:none}.tl-xl{text-align:left}.tr-xl{text-align:right}.tc-xl{text-align:center}.tj-xl{text-align:justify}.ttc-xl{text-transform:capitalize}.ttl-xl{text-transform:lowercase}.ttu-xl{text-transform:uppercase}.ttn-xl{text-transform:none}.f1-xl{font-size:4.5rem}.f2-xl{font-size:4rem}.f3-xl{font-size:3rem}.f4-xl{font-size:2rem}.f5-xl{font-size:1.5rem}.f6-xl{font-size:1.125rem}.f7-xl{font-size:1rem}.f8-xl{font-size:.875rem}.f9-xl{font-size:.75rem}.measure-xl{max-width:30em}.measure-wide-xl{max-width:34em}.measure-narrow-xl{max-width:20em}.small-caps-xl{font-variant:small-caps}.indent-xl{text-indent:1em;margin-top:0;margin-bottom:0}.truncate-xl{white-space:nowrap;overflow:hidden;text-overflow:ellipsis}.clip-xl{position:fixed!important;_position:absolute!important;clip:rect(1px 1px 1px 1px);clip:rect(1px,1px,1px,1px)}.ws-normal-xl{white-space:normal}.nowrap-xl{white-space:nowrap}.pre-xl{white-space:pre}.w1-xl{width:1rem}.w2-xl{width:2rem}.w3-xl{width:4rem}.w4-xl{width:8rem}.w5-xl{width:16rem}.w-10-xl{width:10%}.w-20-xl{width:20%}.w-25-xl{width:25%}.w-30-xl{width:30%}.w-33-xl{width:33%}.w-34-xl{width:34%}.w-40-xl{width:40%}.w-50-xl{width:50%}.w-60-xl{width:60%}.w-70-xl{width:70%}.w-75-xl{width:75%}.w-80-xl{width:80%}.w-90-xl{width:90%}.w-100-xl{width:100%}.w-third-xl{width:33.33333%}.w-two-thirds-xl{width:66.66667%}.w-auto-xl{width:auto}}@font-face{font-family:Inter;font-style:normal;font-weight:400;src:url(https://media.urbit.org/fonts/Inter-Regular.woff2) format("woff2")}@font-face{font-family:Inter;font-style:italic;font-weight:400;src:url(https://media.urbit.org/fonts/Inter-Italic.woff2) format("woff2")}@font-face{font-family:Inter;font-style:normal;font-weight:700;src:url(https://media.urbit.org/fonts/Inter-Bold.woff2) format("woff2")}@font-face{font-family:Inter;font-style:italic;font-weight:700;src:url(https://media.urbit.org/fonts/Inter-BoldItalic.woff2) format("woff2")}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-extralight.woff);font-weight:200}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-light.woff);font-weight:300}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-regular.woff);font-weight:400}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-medium.woff);font-weight:500}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-semibold.woff);font-weight:600}@font-face{font-family:Source Code Pro;src:url(https://storage.googleapis.com/media.urbit.org/fonts/scp-bold.woff);font-weight:700}body,html{height:100%;width:100%;-webkit-font-smoothing:antialiased;overflow:hidden}a,button,h1,h2,h3,h4,h5,h6,input,p,textarea{margin-block-end:unset;margin-block-start:unset;-webkit-margin-before:unset;-webkit-margin-after:unset;font-family:Inter,sans-serif;padding:0}button,input,textarea{outline:none;-webkit-appearance:none;border:none;background-color:#fff}h2{font-weight:400}a{color:#000;text-decoration:none}.inter{font-family:Inter,sans-serif}.mono{font-family:Source Code Pro,monospace}@media (max-width:34.375em){.dn-s{display:none}.flex-basis-100-s,.flex-basis-full-s{flex-basis:100%}.h-100-m-40-s{height:calc(100% - 40px)}.black-s{color:#000}}@media (min-width:34.375em){.db-ns{display:block}.flex-basis-30-ns{flex-basis:30vw}.h-100-m-40-ns{height:calc(100% - 40px)}}.spinner-pending{position:relative;background-color:#fff}.spinner-pending,.spinner-pending:after{content:"";border-radius:100%;height:16px;width:16px}.spinner-pending:after{background-color:grey;position:absolute;clip:rect(0,16px,16px,8px);animation:spin 1s cubic-bezier(.745,.045,.355,1) infinite}@keyframes spin{0%{transform:rotate(0deg)}25%{transform:rotate(90deg)}50%{transform:rotate(180deg)}75%{transform:rotate(270deg)}to{transform:rotate(1turn)}}.spinner-nostart{width:8px;height:8px;border-radius:100%;content:"";background-color:#000} \ No newline at end of file diff --git a/pkg/arvo/app/publish/img/Home.png b/pkg/arvo/app/publish/img/Home.png new file mode 100644 index 0000000000000000000000000000000000000000..8fddc78950caa149faab85d7a655724f965dce45 GIT binary patch literal 679 zcmV;Y0$BZtP)@~0drDELIAGL9O(c600d`2O+f$vv5yP40>Q>mWgQW`c$A0oo-X>CNnn$6$v4 zSsCkFzq&4CO*&*F_!)lk6oRa{@xmOf-r9TSuJw_oQ9A#8SYdEc6cNmoEG1Nrr#*cXpsbP zntYw7(1w0(E6a&bdVgQ*_ z3?Org0c^`u#u%O9#o*77ED)Auj5T&fjPzO?ur_0~3S>4l;6hw}cQ?aZ$z}#jWsGY| zvlBKkK+uiWM;TrOn;1}|C%&%+9n1|7^u_meBA%OLTKo?9f*tC21q%Z{W5*{9&>jMo z|0}k{b8}3KOi;tbd#IjYnGB)NFYI_hnWGu-6J;z6_<I4qEqP@OXp)=>d$Bo{yK!VIE29P<$05Yc-K;{$!7)MwiNf&<^@Jq;mucV7_z-z`> zF`kH|ikowca)wZbm*N8xq4f&VZ)_OP#Z!M|rXKDfr2EiRXpK@ZW1PzH+_*V&td0== zD)iN_<{0q1k%35$1N8JDb N002ovPDHLkV1hV2DwqHO literal 0 HcmV?d00001 diff --git a/pkg/arvo/app/publish/img/SwitcherClosed.png b/pkg/arvo/app/publish/img/SwitcherClosed.png new file mode 100644 index 0000000000000000000000000000000000000000..119ab2b3c93b8c32114073a72164dd1464f545e0 GIT binary patch literal 1377 zcmV-n1)lneP)^lHwA`F#r+9SPTF_NNm09gu$2r0E7?&Ach5d7M68hRnK*r7-3myh zQX@9QC^uySpai4IWOA%FzHfjwK0ZuA-g95j77RjBcAgD|LKkIOUg+%XT;(P9-;&K{ zU#?XC?q6BSzVT=N&J*r=N-&&ECO-hG256cVqmrxxh}1qL2W0H&?LDa|$`{;}d%*nS z;%hf=-1y8i*PP*kZLK}0s;WT&K$7Hha25Z`;NT+hL_3L)g~?%v)Lbuq9ZP19l&k~HL;=!`~}ckSxAz*8U( z6h*n%77V(gQk+Vl&pJchJGwsMsEaF#vh%ESOl0X8wNc&ORSAVc-*Q#Okx(d9cTc0t zj!*&;a|XM*x+XYk;)*QGi_WplSgc_uxRGhLhoNx&1Rf>`ArIFIXvU@iq6LU%(*WKH zCnhI<)ph-C-g#TW)qsh~$%S&c^2}0Z`9ocwxyUnjE4UdjF*%tomn%KB@lqzE>iX<& zyz;k#n*pY2KIM)rWtR5px<1cKLo>J;aAa^W=z1mx04!ye6_F-zGk_3c?%%hs!*3>V zy$NpLzP_H?=ob@&ZiW3|g79a7 zXf#@U;o!kYYZJWPED1LNxc8=}zpt;mxd}^qr>AE;JD>1{0RYh6-hTVVLx=V@Ga<8_ zIX*o-`<54ZePcisyTyq;R*S30y-4UA14^aRj;lZXIA@xT2U6j1$J{`?FX2Vr#`PwE zd_Euk?)$5^n-?E048;5Qc$HiD3drSh9oK%kzS^Sr(m=fbQ7`igH6WMEbzJ}Xm*P6b zcX+Kqm;rt$9uQ=JUy26=7~rSk0nP^at$2W=0V^vj?S3mB;A8+}EHJIll>Amaz{vnY zh#8ROhNJ0lIJ_#dc!1+iAdxs6X$uDL)W+fP)>{Md{>XaQ@PO-0Fp)SMZ3_l7;jQ6o z1M$8X&)lux{w$D49Db5_&h-%fEFhXq14IiD&87hWF+__H1!K%;SONKbJ}g3vC@90d zMxz>*WhsKRcuqF^$4kyJCB&eNvAQj4u~8pau}syLEe zx&3BcfRGsq%bIe=%H;}KSXem8Qy35C=NC`i$>$%h3tHBBs;a6%K+ZekH|FL(XN(1S z3iJ}jSm5UGbDuh61ej7)wLk&Dvdl36_q!`ia}AfTT)CT0r(fr+^?xUwPM^4ZFRB|BYNO*TEQ5ipA2&MPuPi zxm;;DYqLS#Rgb>_5YRA3;DL7hnmt)p(!q)LmbRBeb7QOAB9S{LU}!&c4Dq3h@NevbS5 z{=RvxpP%z1sDq*?0r30)4{kp|!<5o60DzEiz4Kgy(j)*7LXrTM4bYn~jB#0(lbfAF zY6TTV3G=*gnF5jnGMPg_MhrtAu4M#Q8HmT@=Q&L7-FW(1vrAC{{H@9YrJ7VJRU!9Qe3J$;iXV8-PYEA#p~VmU3+``9aciO%F@zO zbE#D7%;)oOYufZjg<`SlGbZRo`Q*tFVgX%1XQw zXqtBV(c{P0N_xp2UN()=tFkO71ppwtXAq!e#lLyt#4bX}Dr>>dnn)yaol^S3*Q2AW zHWLCoFI)x?;}k^+6VL(sN&EKhJ-r=@w;+V*`(ExoV~J{I6;J|J| zh|Wq2^Gl#!@vrsviY+ZId6s&Z8c?tJLkABwheDyhSn2^7UII^0e2$eCJ4_5{)ZzgK z1~hWNO=)#3pM4M-#s*Je|xp31n#BOrS8XuHqnYlxjE zM=pVhiNyP}sr2c}xW^;l^&>}md_Ld26M46SBL?JhD{}241OQAYa&8qz43MPg8=@#a zs*LNpj(b1;G?~xm+nmU|6&$+@#H47CD2mIKab4H({SWu%v)QcZRPLw2(c555ioPg{ zV%5@C*LB?g`N7KK;^J;6^FIlWuLELIboXW^Jox3;oZBWaSqV0>3Cx}a8r1}*`vHw; z0`m=#Ml->c9ijg+VPRpx$4ZN9dxG^$m{1dWN~wp14p+Cu*G;H;DDnux3afoV*WU}o zq-a1Cn`fjnToOgb7Co5lN0UT?au?^uXsZdYH7*oj4>huz5A z5Hr9{b_{S^fZOaCK-b$$o=-^fxtamBcA+?Kt-)x6OymahmgQvvjN9Xn|Cs!o)#E4&D5ai9lapWAV+3SGmgTj(fMJx* z0od5X*L5AYNAIj^npX9C>;HzPY46@19bMHcnx+gx9|mk~bIPr+E^wfqR{nveCNJ#> zcYY#@{%eE~t)-=f`L8&hmP{sdyjc8O$}G&EUCL(nR30}$F3Kn0`nPS)Lb(|q;s^#= z33UULVpu-aKV*%odWY9%!XRutgxiE=6J*%><}EgDo(3ljaRl$N(dH}^7^g<*T&?Em zng&=XiV_BRiRZ~F00FDNs8PF2tmm4w)h$UHFdxD&Mr2v8dP!^X4;K0 z9OUlAu!ocWyNhJ#+zf_Ia~{gqU)3*X7QFe0v9bSF_nlIW zO)jcpmAcy#M0S2VWmdHJXby|i#7nj90!(XPpF6P7@Rt=+Z%tI>|AiCfwX-LD(ow!2 nCT3&o&+xbEl8tw|Q~}fab;<8pRzI8zbQOcAtDnm{r-UW|!9h~0 diff --git a/pkg/arvo/app/publish/img/popout.png b/pkg/arvo/app/publish/img/popout.png new file mode 100644 index 0000000000000000000000000000000000000000..4aab0146071719d8e454150df2af0470997cb531 GIT binary patch literal 1480 zcmV;(1vmPMP)3YoQ$H;BDS3-br%HF(#q?ku>)GU>^1?{XZD=sB%|wHyO`Wt8q9g%zqXoA~+67jWs{C0a>ez1wYWk8UNGWUdHXpArAYuFgd_nh=%7Q;^-)=tljU|H zrGkp0_(jomjsl%F$m9+I8Ps)cpp+3paUc?joD@V?Y@-wp02H)W5M424c=%NDT)`0# ziA4Ggihgd&96%uG4~N48=J=Tbkx1mEL2;&dhga%qXBrwB&sSA#|D&<7@d_`Y>t%j^ zerGi3&Y65}4B}(bG%hBi( zV?vE6y3PT3S5OqiPe6Owor03ovk{6nA%tkby`f`li~^mCqSOe0*vU?Ks;UqO1b*VG zkOQr)%@=Cx>ShaqqSz}Cm)On50)dvVxGLjFV?+IUb}T|TAPCf`VS`?;_Yz-O{P23c zzq4Zl)Grw3?d>uymus4Vpjz=;|Y2v$17> z(*m4k%K)bZIL)Rvz-9LWL&K5Z0PF+M@S?eVO|O1;@ZiDEUR>1*_8$QR1O(KIRFslt zEAp_|Zve%ApyY`asR$tfEAp_|ehPGVg~I?aK0dz9<# zbrx^QQzeV-2Fy@e6;C9RY;29iv+uPne_?B@0dsS6-kZ_rqQ< z`}eOk*REYVzXhRx1Hg_Q-m@0U1YnZ^BhlzoQSp-<9qqyOc0J_{}vN<8iO?3ohv)St6m>@iD zFnUHN^Y3A9ia4X|dco^;3YrvjYNXg;F1OgpRTW1bK7822jwz)N1P~HugPD7GkMotq zkLhIc^MU}u&jNIPkd4h}vrTvIOcyj4Yy_sJraoL;%oVl?>iVc4%klyNM%nn}?TPOx zrEZ=A?SxY5zBMuNBO42?n-2:0),i=2;i1?t-1:0),r=1;r2?n-2:0),i=2;i8)throw new Error("warningWithoutStack() currently supports at most 8 arguments.");if(!e){if("undefined"!=typeof console){var a=r.map(function(e){return""+e});a.unshift("Warning: "+t),Function.prototype.apply.call(console.error,console,a)}try{var l=0,o="Warning: "+t.replace(/%s/g,function(){return r[l++]});throw new Error(o)}catch(e){}}},C={};function M(e,t){var n=e.constructor,r=n&&(n.displayName||n.name)||"ReactClass",i=r+"."+t;C[i]||(x(!1,"Can't call %s on a component that is not yet mounted. This is a no-op, but it might indicate a bug in your application. Instead, assign to `this.state` directly or define a `state = {};` class property with the desired state in the %s component.",t,r),C[i]=!0)}var S={isMounted:function(e){return!1},enqueueForceUpdate:function(e,t,n){M(e,"forceUpdate")},enqueueReplaceState:function(e,t,n,r){M(e,"replaceState")},enqueueSetState:function(e,t,n,r){M(e,"setState")}},E={};function T(e,t,n){this.props=e,this.context=t,this.refs=E,this.updater=n||S}Object.freeze(E),T.prototype.isReactComponent={},T.prototype.setState=function(e,t){"object"!=typeof e&&"function"!=typeof e&&null!=e&&_(!1,"setState(...): takes an object of state variables to update or a function which returns an object of state variables."),this.updater.enqueueSetState(this,e,t,"setState")},T.prototype.forceUpdate=function(e){this.updater.enqueueForceUpdate(this,e,"forceUpdate")};var P={isMounted:["isMounted","Instead, make sure to clean up subscriptions and pending requests in componentWillUnmount to prevent memory leaks."],replaceState:["replaceState","Refactor your code to use setState instead (see https://github.com/facebook/react/issues/3236)."]},L=function(e,t){Object.defineProperty(T.prototype,e,{get:function(){w(!1,"%s(...) is deprecated in plain JavaScript React classes. %s",t[0],t[1])}})};for(var R in P)P.hasOwnProperty(R)&&L(R,P[R]);function O(){}function D(e,t,n){this.props=e,this.context=t,this.refs=E,this.updater=n||S}O.prototype=T.prototype;var I=D.prototype=new O;I.constructor=D,t(I,T.prototype),I.isPureReactComponent=!0;var A={current:null},j={current:null},U=/^(.*)[\\\/]/,H=1;function z(e){if(null==e)return null;if("number"==typeof e.tag&&x(!1,"Received an unexpected object in getComponentName(). This is likely a bug in React. Please file an issue."),"function"==typeof e)return e.displayName||e.name||null;if("string"==typeof e)return e;switch(e){case d:return"ConcurrentMode";case l:return"Fragment";case a:return"Portal";case s:return"Profiler";case o:return"StrictMode";case p:return"Suspense"}if("object"==typeof e)switch(e.$$typeof){case u:return"Context.Consumer";case c:return"Context.Provider";case h:return r=e,i=e.render,f="ForwardRef",g=i.displayName||i.name||"",r.displayName||(""!==g?f+"("+g+")":f);case m:return z(e.type);case v:var t=(n=e)._status===H?n._result:null;if(t)return z(t)}var n,r,i,f,g;return null}var Z={},F=null;function W(e){F=e}Z.getCurrentStack=null,Z.getStackAddendum=function(){var e="";if(F){var t=z(F.type),n=F._owner;e+=function(e,t,n){var r="";if(t){var i=t.fileName,a=i.replace(U,"");if(/^index\./.test(a)){var l=i.match(U);if(l){var o=l[1];o&&(a=o.replace(U,"")+"/"+a)}}r=" (at "+a+":"+t.lineNumber+")"}else n&&(r=" (created by "+n+")");return"\n in "+(e||"Unknown")+r}(t,F._source,n&&z(n.type))}var r=Z.getCurrentStack;return r&&(e+=r()||""),e};var V={ReactCurrentDispatcher:A,ReactCurrentOwner:j,assign:t};t(V,{ReactDebugCurrentFrame:Z,ReactComponentTreeHook:{}});var Y=function(e,t){if(!e){for(var n=V.ReactDebugCurrentFrame.getStackAddendum(),r=arguments.length,i=Array(r>2?r-2:0),a=2;a1){for(var u=Array(c),f=0;f.")}return t}(t);if(!ye[n]){ye[n]=!0;var r="";e&&e._owner&&e._owner!==j.current&&(r=" It was passed a child from "+z(e._owner.type)+"."),W(e),Y(!1,'Each child in a list should have a unique "key" prop.%s%s See https://fb.me/react-warning-keys for more information.',n,r),W(null)}}}function _e(e,t){if("object"==typeof e)if(Array.isArray(e))for(var n=0;n",a=" Did you accidentally export a JSX literal instead of a component?"):s=typeof e,Y(!1,"React.createElement: type is invalid -- expected a string (for built-in components) or a class/function (for composite components) but got: %s.%s",s,a)}var c=J.apply(this,arguments);if(null==c)return c;if(r)for(var u=2;u is not supported and will be removed in a future major release. Did you mean to render instead?")),n.Provider},set:function(e){n.Provider=e}},_currentValue:{get:function(){return n._currentValue},set:function(e){n._currentValue=e}},_currentValue2:{get:function(){return n._currentValue2},set:function(e){n._currentValue2=e}},_threadCount:{get:function(){return n._threadCount},set:function(e){n._threadCount=e}},Consumer:{get:function(){return r||(r=!0,Y(!1,"Rendering is not supported and will be removed in a future major release. Did you mean to render instead?")),n.Consumer}}}),n.Consumer=a,n._currentRenderer=null,n._currentRenderer2=null,n},forwardRef:function(e){return null!=e&&e.$$typeof===m?x(!1,"forwardRef requires a render function but received a `memo` component. Instead of forwardRef(memo(...)), use memo(forwardRef(...))."):"function"!=typeof e?x(!1,"forwardRef requires a render function but was given %s.",null===e?"null":typeof e):0!==e.length&&2!==e.length&&x(!1,"forwardRef render functions accept exactly two parameters: props and ref. %s",1===e.length?"Did you forget to use the ref parameter?":"Any additional parameter will be undefined."),null!=e&&(null!=e.defaultProps||null!=e.propTypes)&&x(!1,"forwardRef render functions do not support propTypes or defaultProps. Did you accidentally pass a React component?"),{$$typeof:h,render:e}},lazy:function(e){var t={$$typeof:v,_ctor:e,_status:-1,_result:null},n=void 0,r=void 0;return Object.defineProperties(t,{defaultProps:{configurable:!0,get:function(){return n},set:function(e){Y(!1,"React.lazy(...): It is not supported to assign `defaultProps` to a lazy component import. Either specify them where the component is defined, or create a wrapping component around it."),n=e,Object.defineProperty(t,"defaultProps",{enumerable:!0})}},propTypes:{configurable:!0,get:function(){return r},set:function(e){Y(!1,"React.lazy(...): It is not supported to assign `propTypes` to a lazy component import. Either specify them where the component is defined, or create a wrapping component around it."),r=e,Object.defineProperty(t,"propTypes",{enumerable:!0})}}}),t},memo:function(e,t){return me(e)||x(!1,"memo: The first argument must be a component. Instead received: %s",null===e?"null":typeof e),{$$typeof:m,type:e,compare:void 0===t?null:t}},useCallback:function(e,t){return ve().useCallback(e,t)},useContext:function(e,t){var n=ve();if(void 0!==t&&Y(!1,"useContext() second argument is reserved for future use in React. Passing it is not supported. You passed: %s.%s",t,"number"==typeof t&&Array.isArray(arguments[2])?"\n\nDid you call array.map(useContext)? Calling Hooks inside a loop is not supported. Learn more at https://fb.me/rules-of-hooks":""),void 0!==e._context){var r=e._context;r.Consumer===e?Y(!1,"Calling useContext(Context.Consumer) is not supported, may cause bugs, and will be removed in a future major release. Did you mean to call useContext(Context) instead?"):r.Provider===e&&Y(!1,"Calling useContext(Context.Provider) is not supported. Did you mean to call useContext(Context) instead?")}return n.useContext(e,t)},useEffect:function(e,t){return ve().useEffect(e,t)},useImperativeHandle:function(e,t,n){return ve().useImperativeHandle(e,t,n)},useDebugValue:function(e,t){return ve().useDebugValue(e,t)},useLayoutEffect:function(e,t){return ve().useLayoutEffect(e,t)},useMemo:function(e,t){return ve().useMemo(e,t)},useReducer:function(e,t,n){return ve().useReducer(e,t,n)},useRef:function(e){return ve().useRef(e)},useState:function(e){return ve().useState(e)},Fragment:l,StrictMode:o,Suspense:p,createElement:xe,cloneElement:function(e,n,r){for(var i=function(e,n,r){null==e&&_(!1,"React.cloneElement(...): The argument must be a React element, but you passed %s.",e);var i=void 0,a=t({},e.props),l=e.key,o=e.ref,s=e._self,c=e._source,u=e._owner;if(null!=n){Q(n)&&(o=n.ref,u=j.current),K(n)&&(l=""+n.key);var f=void 0;for(i in e.type&&e.type.defaultProps&&(f=e.type.defaultProps),n)q.call(n,i)&&!B.hasOwnProperty(i)&&(void 0===n[i]&&void 0!==f?a[i]=f[i]:a[i]=n[i])}var d=arguments.length-2;if(1===d)a.children=r;else if(d>1){for(var h=Array(d),p=0;p=t){r=e;break}e=e.next}while(e!==n);null===r?r=n:r===n&&(n=s,u()),(t=r.previous).next=r.previous=s,s.next=r,s.previous=t}}function d(){if(-1===l&&null!==n&&1===n.priorityLevel){s=!0;try{do{f()}while(null!==n&&1===n.priorityLevel)}finally{s=!1,null!==n?u():c=!1}}}function h(e){s=!0;var i=r;r=e;try{if(e)for(;null!==n;){var a=t.unstable_now();if(!(n.expirationTime<=a))break;do{f()}while(null!==n&&n.expirationTime<=a)}else if(null!==n)do{f()}while(null!==n&&!M())}finally{s=!1,r=i,null!==n?u():c=!1,d()}}var p,m,v=Date,g="function"==typeof setTimeout?setTimeout:void 0,b="function"==typeof clearTimeout?clearTimeout:void 0,y="function"==typeof requestAnimationFrame?requestAnimationFrame:void 0,k="function"==typeof cancelAnimationFrame?cancelAnimationFrame:void 0;function _(e){p=y(function(t){b(m),e(t)}),m=g(function(){k(p),e(t.unstable_now())},100)}if("object"==typeof performance&&"function"==typeof performance.now){var w=performance;t.unstable_now=function(){return w.now()}}else t.unstable_now=function(){return v.now()};var x,C,M,N=null;if("undefined"!=typeof window?N=window:void 0!==i&&(N=i),N&&N._schedMock){var S=N._schedMock;x=S[0],C=S[1],M=S[2],t.unstable_now=S[3]}else if("undefined"==typeof window||"function"!=typeof MessageChannel){var E=null,T=function(e){if(null!==E)try{E(e)}finally{E=null}};x=function(e){null!==E?setTimeout(x,0,e):(E=e,setTimeout(T,0,!1))},C=function(){E=null},M=function(){return!1}}else{"undefined"!=typeof console&&("function"!=typeof y&&console.error("This browser doesn't support requestAnimationFrame. Make sure that you load a polyfill in older browsers. https://fb.me/react-polyfills"),"function"!=typeof k&&console.error("This browser doesn't support cancelAnimationFrame. Make sure that you load a polyfill in older browsers. https://fb.me/react-polyfills"));var P=null,L=!1,R=-1,O=!1,D=!1,I=0,A=33,j=33;M=function(){return I<=t.unstable_now()};var U=new MessageChannel,H=U.port2;U.port1.onmessage=function(){L=!1;var e=P,n=R;P=null,R=-1;var r=t.unstable_now(),i=!1;if(0>=I-r){if(!(-1!==n&&n<=r))return O||(O=!0,_(z)),P=e,void(R=n);i=!0}if(null!==e){D=!0;try{e(i)}finally{D=!1}}};var z=function(e){if(null!==P){_(z);var t=e-I+j;tt&&(t=8),j=tt?H.postMessage(void 0):O||(O=!0,_(z))},C=function(){P=null,L=!1,R=-1}}t.unstable_ImmediatePriority=1,t.unstable_UserBlockingPriority=2,t.unstable_NormalPriority=3,t.unstable_IdlePriority=5,t.unstable_LowPriority=4,t.unstable_runWithPriority=function(e,n){switch(e){case 1:case 2:case 3:case 4:case 5:break;default:e=3}var r=a,i=l;a=e,l=t.unstable_now();try{return n()}finally{a=r,l=i,d()}},t.unstable_next=function(e){switch(a){case 1:case 2:case 3:var n=3;break;default:n=a}var r=a,i=l;a=n,l=t.unstable_now();try{return e()}finally{a=r,l=i,d()}},t.unstable_scheduleCallback=function(e,r){var i=-1!==l?l:t.unstable_now();if("object"==typeof r&&null!==r&&"number"==typeof r.timeout)r=i+r.timeout;else switch(a){case 1:r=i+-1;break;case 2:r=i+250;break;case 5:r=i+1073741823;break;case 4:r=i+1e4;break;default:r=i+5e3}if(e={callback:e,priorityLevel:a,expirationTime:r,next:null,previous:null},null===n)n=e.next=e.previous=e,u();else{i=null;var o=n;do{if(o.expirationTime>r){i=o;break}o=o.next}while(o!==n);null===i?i=n:i===n&&(n=e,u()),(r=i.previous).next=i.previous=e,e.next=i,e.previous=r}return e},t.unstable_cancelCallback=function(e){var t=e.next;if(null!==t){if(t===e)n=null;else{e===n&&(n=t);var r=e.previous;r.next=t,t.previous=r}e.next=e.previous=null}},t.unstable_wrapCallback=function(e){var n=a;return function(){var r=a,i=l;a=n,l=t.unstable_now();try{return e.apply(this,arguments)}finally{a=r,l=i,d()}}},t.unstable_getCurrentPriorityLevel=function(){return a},t.unstable_shouldYield=function(){return!r&&(null!==n&&n.expirationTime=a){u=f;break}f=f.next}while(f!==h);null===u?u=h:u===h&&(h=c,w());var d=u.previous;d.next=u.previous=c,c.next=u,c.previous=d}}}function C(){if(-1===g&&null!==h&&h.priorityLevel===n){y=!0;try{do{x()}while(null!==h&&h.priorityLevel===n)}finally{y=!1,null!==h?w():k=!1}}}function M(n){y=!0;var r=p;p=n;try{if(n)for(;!(null===h||e&&m);){var i=t.unstable_now();if(!(h.expirationTime<=i))break;do{x()}while(null!==h&&h.expirationTime<=i&&(!e||!m))}else if(null!==h)do{if(e&&m)break;x()}while(null!==h&&!P())}finally{y=!1,p=r,null!==h?w():k=!1,C()}}var N,S,E,T,P,L=Date,R="function"==typeof setTimeout?setTimeout:void 0,O="function"==typeof clearTimeout?clearTimeout:void 0,D="function"==typeof requestAnimationFrame?requestAnimationFrame:void 0,I="function"==typeof cancelAnimationFrame?cancelAnimationFrame:void 0,A=function(e){N=D(function(t){O(S),e(t)}),S=R(function(){I(N),e(t.unstable_now())},100)};if(_){var j=performance;t.unstable_now=function(){return j.now()}}else t.unstable_now=function(){return L.now()};var U=null;if("undefined"!=typeof window?U=window:void 0!==i&&(U=i),U&&U._schedMock){var H=U._schedMock;E=H[0],T=H[1],P=H[2],t.unstable_now=H[3]}else if("undefined"==typeof window||"function"!=typeof MessageChannel){var z=null,Z=function(e){if(null!==z)try{z(e)}finally{z=null}};E=function(e,t){null!==z?setTimeout(E,0,e):(z=e,setTimeout(Z,0,!1))},T=function(){z=null},P=function(){return!1}}else{"undefined"!=typeof console&&("function"!=typeof D&&console.error("This browser doesn't support requestAnimationFrame. Make sure that you load a polyfill in older browsers. https://fb.me/react-polyfills"),"function"!=typeof I&&console.error("This browser doesn't support cancelAnimationFrame. Make sure that you load a polyfill in older browsers. https://fb.me/react-polyfills"));var F=null,W=!1,V=-1,Y=!1,q=!1,B=0,$=33,G=33;P=function(){return B<=t.unstable_now()};var Q=new MessageChannel,K=Q.port2;Q.port1.onmessage=function(e){W=!1;var n=F,r=V;F=null,V=-1;var i=t.unstable_now(),a=!1;if(B-i<=0){if(!(-1!==r&&r<=i))return Y||(Y=!0,A(X)),F=n,void(V=r);a=!0}if(null!==n){q=!0;try{n(a)}finally{q=!1}}};var X=function(e){if(null!==F){A(X);var t=e-B+G;tp){y=k;break}k=k.next}while(k!==h);null===y?y=h:y===h&&(h=b,w());var _=y.previous;_.next=y.previous=b,b.next=y,b.previous=_}return b},t.unstable_cancelCallback=function(e){var t=e.next;if(null!==t){if(t===e)h=null;else{e===h&&(h=t);var n=e.previous;n.next=t,t.previous=n}e.next=e.previous=null}},t.unstable_wrapCallback=function(e){var n=v;return function(){var r=v,i=g;v=n,g=t.unstable_now();try{return e.apply(this,arguments)}finally{v=r,g=i,C()}}},t.unstable_getCurrentPriorityLevel=function(){return v},t.unstable_shouldYield=function(){return!p&&(null!==h&&h.expirationTimethis.eventPool.length&&this.eventPool.push(e)}function je(e){e.eventPool=[],e.getPooled=Ie,e.release=Ae}f(De.prototype,{preventDefault:function(){this.defaultPrevented=!0;var e=this.nativeEvent;e&&(e.preventDefault?e.preventDefault():"unknown"!=typeof e.returnValue&&(e.returnValue=!1),this.isDefaultPrevented=Re)},stopPropagation:function(){var e=this.nativeEvent;e&&(e.stopPropagation?e.stopPropagation():"unknown"!=typeof e.cancelBubble&&(e.cancelBubble=!0),this.isPropagationStopped=Re)},persist:function(){this.isPersistent=Re},isPersistent:Oe,destructor:function(){var e,t=this.constructor.Interface;for(e in t)this[e]=null;this.nativeEvent=this._targetInst=this.dispatchConfig=null,this.isPropagationStopped=this.isDefaultPrevented=Oe,this._dispatchInstances=this._dispatchListeners=null}}),De.Interface={type:null,target:null,currentTarget:function(){return null},eventPhase:null,bubbles:null,cancelable:null,timeStamp:function(e){return e.timeStamp||Date.now()},defaultPrevented:null,isTrusted:null},De.extend=function(e){function t(){}function n(){return r.apply(this,arguments)}var r=this;t.prototype=r.prototype;var i=new t;return f(i,n.prototype),n.prototype=i,n.prototype.constructor=n,n.Interface=f({},r.Interface,e),n.extend=r.extend,je(n),n},je(De);var Ue=De.extend({data:null}),He=De.extend({data:null}),ze=[9,13,27,32],Ze=ge&&"CompositionEvent"in window,Fe=null;ge&&"documentMode"in document&&(Fe=document.documentMode);var We=ge&&"TextEvent"in window&&!Fe,Ve=ge&&(!Ze||Fe&&8=Fe),Ye=String.fromCharCode(32),qe={beforeInput:{phasedRegistrationNames:{bubbled:"onBeforeInput",captured:"onBeforeInputCapture"},dependencies:["compositionend","keypress","textInput","paste"]},compositionEnd:{phasedRegistrationNames:{bubbled:"onCompositionEnd",captured:"onCompositionEndCapture"},dependencies:"blur compositionend keydown keypress keyup mousedown".split(" ")},compositionStart:{phasedRegistrationNames:{bubbled:"onCompositionStart",captured:"onCompositionStartCapture"},dependencies:"blur compositionstart keydown keypress keyup mousedown".split(" ")},compositionUpdate:{phasedRegistrationNames:{bubbled:"onCompositionUpdate",captured:"onCompositionUpdateCapture"},dependencies:"blur compositionupdate keydown keypress keyup mousedown".split(" ")}},Be=!1;function $e(e,t){switch(e){case"keyup":return-1!==ze.indexOf(t.keyCode);case"keydown":return 229!==t.keyCode;case"keypress":case"mousedown":case"blur":return!0;default:return!1}}function Ge(e){return"object"==typeof(e=e.detail)&&"data"in e?e.data:null}var Qe=!1;var Ke={eventTypes:qe,extractEvents:function(e,t,n,r){var i=void 0,a=void 0;if(Ze)e:{switch(e){case"compositionstart":i=qe.compositionStart;break e;case"compositionend":i=qe.compositionEnd;break e;case"compositionupdate":i=qe.compositionUpdate;break e}i=void 0}else Qe?$e(e,n)&&(i=qe.compositionEnd):"keydown"===e&&229===n.keyCode&&(i=qe.compositionStart);return i?(Ve&&"ko"!==n.locale&&(Qe||i!==qe.compositionStart?i===qe.compositionEnd&&Qe&&(a=Le()):(Te="value"in(Ee=r)?Ee.value:Ee.textContent,Qe=!0)),i=Ue.getPooled(i,t,n,r),a?i.data=a:null!==(a=Ge(n))&&(i.data=a),ve(i),a=i):a=null,(e=We?function(e,t){switch(e){case"compositionend":return Ge(t);case"keypress":return 32!==t.which?null:(Be=!0,Ye);case"textInput":return(e=t.data)===Ye&&Be?null:e;default:return null}}(e,n):function(e,t){if(Qe)return"compositionend"===e||!Ze&&$e(e,t)?(e=Le(),Pe=Te=Ee=null,Qe=!1,e):null;switch(e){case"paste":return null;case"keypress":if(!(t.ctrlKey||t.altKey||t.metaKey)||t.ctrlKey&&t.altKey){if(t.char&&1