diff options
Diffstat (limited to 'desk/lib/trill/utils.hoon')
-rw-r--r-- | desk/lib/trill/utils.hoon | 1054 |
1 files changed, 1054 insertions, 0 deletions
diff --git a/desk/lib/trill/utils.hoon b/desk/lib/trill/utils.hoon new file mode 100644 index 0000000..ffff8b8 --- /dev/null +++ b/desk/lib/trill/utils.hoon @@ -0,0 +1,1054 @@ +/- tp=trill-post, tlonc=tlon-channels, *boke, contact +/+ sr=sortug, ui=trill-ui, const=constants +|% +++ user-profile +|= [u=@p =bowl:gall] ^- res:contact +=/ io ~(. io:sr bowl) +=/ has-contacts .^(? %gu (weld (scry-pad:io %contacts) /$)) +=/ has-whom .^(? %gu (weld (scry-pad:io %whom) /$)) +=/ tact ?. has-contacts ~ +=/ rolo (scry:io %contacts /all rolodex:contact) +=/ utact (~(get by rolo) u) +=/ prof ?~ utact ~ for.u.utact +?~ prof ~ ?~ con.prof ~ (some con.prof) + +=/ whom ?. has-whom ~ +=/ whoms (scry:io %whom /1/contacts/mars whoms:contact) +(~(get by whoms) [%.y u]) +=/ res +[u tact whom] +res +++ flatten-fn +|= fn=full-node:tp ^- (list post:tp) + :: ~> %bout.[0 %flattening] + =/ child-list (tap:form:tp children.fn) + :- p.fn + :: =/ l %+ turn child-list |= [* f=full-node:tp] p.f + =/ flist=(list post:tp) + =| l=(list post:tp) + |- + ?~ child-list l + =/ child=full-node:tp +.i.child-list + =/ nl (weld l (flatten-fn child)) + $(child-list t.child-list, l nl) + %+ sort flist |= [a=post:tp b=post:tp] (gth id.b id.a) + +++ get-children-page +|= [fn=full-node:tp r=page-req:tp] ^- spage:tp + =/ l (tap:form:tp children.fn) + =| p=spage:tp + |- + ?~ l + %= p + p %+ sort p.p |= [a=post:tp b=post:tp] (gth id.b id.a) + == + =/ node=full-node:tp val.i.l + =/ id id.p.node + ?. (page-cond id count.p r) $(l t.l) :: TODO mmm can i exit here + =/ subpage (get-children-page node r) + =/ new-posts=(list post:tp) p.subpage + =/ oldest ?~ older.p older.subpage + ?: (lth id u.older.p) older.subpage older.p + =/ newest ?~ newer.p newer.subpage + ?: (gth id u.newer.p) newer.subpage newer.p + %= $ + p.p (weld p.p [p.node new-posts]) + older.p oldest + newer.p newest + count.p +(count.p) + l t.l + == +++ get-siblings-page +|= fn=full-node:tp ^- spage:tp + =/ pg (get-children-page fn [~ ~ thread-page-size:const]) + =/ ind (find ~[p.fn] p.pg) + ?~ ind *spage:tp + =/ start=@ ?: (lth u.ind thread-page-size:const) 0 (sub u.ind thread-page-size:const) + %= pg + p (swag [start thread-page-size:const] p.pg) + == +:: ++ get-siblings-page-2 +:: |= l=(list post:tp) ^- spage:tp +:: =/ pg (get-children-page fn [~ ~ thread-page-size:const]) +:: =/ ind (find ~[p] p.pg) +:: ?~ ind *spage:tp +:: =/ start=@ ?: (lth u.ind thread-page-size:const) 0 (sub u.ind thread-page-size:const) +:: %= pg +:: p (swag [start thread-page-size:const] p.pg) +:: == + + +++ flatten-fn-2 +|= fn=full-node:tp ^- (list post:tp) + :: ~> %bout.[0 %flattening-2] + =/ child-list (tap:form:tp children.fn) + :- p.fn + %- sort :_ |= [a=post:tp b=post:tp] (gth id.b id.a) + |- ^- (list post:tp) + ?~ child-list ~ + %+ weld (flatten-fn-2 +.i.child-list) + $(child-list t.child-list) + +++ common-thread + |= [p=post:tp f=gfeed:tp] ^- @ud + =/ pid thread.p + =/ l (tap:gorm:tp f) + %- lent + %+ skim l |= [k=pid:tp v=post:tp] + .= thread.v pid +:: ++ flatten-4 +:: |= p=post:tp ^- (list pid:tp) +:: ~> %bout.[0 %flattening-4] +:: =/ child-list ~(tap in children.fn) +:: =/ =pid:tp [author.p id.p] +:: :- pid +:: |- ^- (list post:tp) +:: ?~ child-list ~ +:: =/ child-post (~(get by feed) pid) +:: %+ weld (flatten-fn-p child-post) +:: $(child-list t.child-list) +:: +$ ll (list pid:tp) +:: ++ flatten-raw +:: |= [l=ll acc=ll] ^- ll +:: ?~ l acc +:: $(l t.l, acc [i.l acc]) + + +++ node-to-full-fake +|= p=post:tp ^- full-node:tp + =/ fake-children=full-graph:tp %- ~(rep in children.p) + |= [=pid:tp acc=full-graph:tp] + (put:form:tp acc pid *full-node:tp) + :- p fake-children +++ node-to-full +|= [p=post:tp f=gfeed:tp] ^- full-node:tp + =/ children (~(del in children.p) [author.p id.p]) :: else infinite loop. not that it should happen at all + :- p (convert-children children f) + ++ convert-children + |= [children=(set pid:tp) f=gfeed:tp] + ^- full-graph:tp + %- ~(rep in children) + |= [=pid:tp acc=full-graph:tp] + =/ n (get:gorm:tp f pid) + ?~ n ~& child-not-found=pid acc + =/ full-node (node-to-full u.n f) + (put:form:tp acc pid full-node) +++ sanitize +|= c=content-list:tp ^- ? +%+ roll c |= [i=block:tp acc=_&] +?. ?=(%paragraph -.i) acc +%+ roll p.i |= [ii=inline:tp iacc=_acc] +?. ?=(%link -.ii) iacc +?~ (de-purl:html href.ii) .n .y +++ block-size +|= =block:tp ^- @ud +?- -.block +%tasklist 0 :: TODO +%paragraph (inline-size p.block) +%blockquote (inline-size p.block) +%heading (lent (trip p.block)) +%media (media-size media.block) +%codeblock +?: (gth (lent (trip lang.block)) 400) 10.000 +(lent (trip code.block)) +%eval (lent (trip hoon.block)) +%ref +?: (gth (lent (trip app.block)) 400) 10.000 +(roll path.block |=([i=@t a=@] (add a (lent (trip i))))) +%json +?: (gth (lent (trip content.block)) 5.000) 10.000 +?: (gth (lent (trip origin.block)) 1.000) 10.000 +0 +%list %+ roll p.block |= [c=content-list:tp a=@ud] %+ add a +%+ roll c |= [b=block:tp aa=@ud] (add aa (block-size b)) +:: %table +:: %+ roll rows.block |= [i=(list contents:tp) a=@] +:: =/ inner-count=@ +:: %+ roll i |= [ii=contents:tp ia=@] +:: (add ia (post-size ii)) +:: (add inner-count a) +== +++ post-size +|= c=content-list:tp +=| count=@ +|- +?~ c count +=/ lc=@ (block-size i.c) +$(c t.c, count (add count lc)) +++ inline-token-size +|= i=inline:tp ^- @ud +?+ -.i (lent (trip p.i)) +%break 1 +%date 1 +%note (add (met 3 id.i) 10):: TODO) +%ship (lent (trip (scot %p p.i))) +%ruby (lent (trip p.i)) +%link +?: (gth (lent (trip href.i)) 400) 10.000 :: to prevent hacking through a huge href string +(lent (trip show.i)) +== +++ reduce-inline +|= [i=inline:tp chars=@ud] ^+ i +?- -.i +%break i +%date i +%note i :: TODO +%ship [%text (crip (weld (scag chars (trip (scot %ud p.i))) "..."))] +%ruby i(p (crip (scag chars (trip p.i)))) +%link i(show (crip (scag chars (trip show.i)))) +%bold + [-.i (crip (scag chars (trip +.i)))] +%codespan + [-.i (crip (scag chars (trip +.i)))] +%italic + [-.i (crip (scag chars (trip +.i)))] +%strike + [-.i (crip (scag chars (trip +.i)))] +%sub + [-.i (crip (scag chars (trip +.i)))] +%sup + [-.i (crip (scag chars (trip +.i)))] +%text + [-.i (crip (weld (scag chars (trip +.i)) "..."))] +%underline + [-.i (crip (scag chars (trip +.i)))] +== +++ inline-size +|= l=(list inline:tp) ^- @ +=| count=@ud +|- + ?~ l count + =/ lc=@ud (inline-token-size i.l) + $(l t.l, count (add count lc)) + + +++ media-size +|= =media:tp ^- @ +?- -.media +%video (lent (trip p.media)) +%audio (lent (trip p.media)) +%images %+ roll p.media +|= [[url=@t caption=@t] a=@] +%+ add a (add (met 3 url) (met 3 caption)) +== + +++ search +|= [q=@t p=post:tp] ^- ? +=/ latest=content-list:tp val:head:(pop:corm:tp contents.p) +?| (in-tags ~(tap in tags.p) q) (in-blocks latest q) == +++ in-tags +|= [tl=(list @t) q=@t] ^- ? +|- +?~ tl .n +?: (contains i.tl q) .y $(tl t.tl) +++ in-blocks +|= [bl=content-list:tp q=@t] ^- ? +|- +?~ bl .n +?: (in-block i.bl q) .y $(bl t.bl) +++ in-block +|= [i=block:tp q=@t] ^- ? +?- -.i + %paragraph (in-inline p.i q) + %blockquote (in-inline p.i q) + %heading (contains p.i q) + %codeblock (contains code.i q) + %eval (contains hoon.i q) + %json (contains content.i q) + %media (in-media media.i q) + %ref %| :: TODO + :: %table %| :: TODO + %tasklist .n :: TODO + %list + |- + ?~ p.i .n + ?: (in-blocks i.p.i q) .y $(p.i t.p.i) +== +++ in-media +|= [=media:tp q=@t] ^- ? +?. ?=(%images -.media) (contains p.media q) +=/ l p.media +|- +?~ l .n +?: ?| (contains url.i.l q) (contains caption.i.l q) == .y $(l t.l) +++ in-inline +|= [l=(list inline:tp) q=@t] ^- ? +|- +?~ l .n +=/ i i.l +=/ has ?+ -.i (contains p.i q) +%break %| +%ship (contains (scot %p p.i) q) +%date .n :: TODO +%note ?|((contains id.i q) (in-inline text.i q)) +%link ?|((contains href.i q) (contains show.i q)) +%ruby ?|((contains p.i q) (contains q.i q)) +== +?: has .y $(l t.l) +++ is-my-reply +|= [p=post:tp r=post:tp our=@p] ^- ? +?~ parent.r .n +?& .=(author.r our) !.=(author.p our) == +++ is-thread-child +|= [p=post:tp r=post:tp our=@p] ^- ? +?~ parent.r .n +?& .=(author.r our) .=(author.p our) == +++ houyi +|= children=full-graph:tp ^- @ud + ?~ children 0 + =/ lst (tap:form:tp children) + %+ add (lent lst) + %+ roll lst + |= [[=pid:tp n=full-node:tp] acc=@ud] + (add acc (houyi children.n)) + +++ latest-contents +|= cm=content-map:tp ^- content-list:tp + =/ latest (pry:corm:tp cm) + ?~ latest ~ +.u.latest +:: + +++ abbreviate-post +|= [cm=content-map:tp max-chars=@ud] ^- content-list:tp + =/ c (latest-contents cm) + :: we reduce the list of blocks. We count how many characters are there in each block. + :: If the block fits in our count, we insert the block in the filtered list. + :: If not, we cut the content of the box until it does. + =/ ret=content-list:tp + =< +< + %^ spin c [bl=*content-list:tp available=max-chars] + |= [b=block:tp [bl=_c available=@ud]] + :: We must return the same data type as the input + :: We don't want to map on the individual block so return as is + :- b + :: The state tho is what we're playing with. + :: We pass the current block and the available char count to another function + =/ cut=[(unit block:tp) @ud] (cut-block b available) + :: That function checks whether the block fits within the available count. + :: It returns a maybe block and the remaining count + :: If null, we return the list as is + ?~ -.cut [bl available] + :: If we get a block back, we add that to our block list, and update the available count + [[u.-.cut bl] +.cut] + (flop ret) +++ cut-block +:: now let's go inside the block +|= [b=block:tp available=@ud] +^- [(unit block:tp) @ud] +?+ -.b [~ 0] +:: :: This we can cut +%paragraph =/ inlines (cut-inlines p.b available) +?~ -.inlines [~ available] :- `[-.b -.inlines] +.inlines +:: :: these must go whole or nothing +:: :: %blockquote +:: :: %heading +:: :: %list +:: :: %media +:: :: %eval +:: :: %poll +:: :: %ref +:: :: %json +:: :: %table +== +++ cut-inlines +|= [li=(list inline:tp) available=@ud] ^+ [li available] +?: .=(0 available) [~ 0] +:: We spin again +=/ ret=[_li @ud] +=/ initial-state [*(list inline:tp) available] +=< + +%^ spin li initial-state +|= [l=inline:tp [nl=_li available=@ud]] +:: Again we're not mapping over the tokens, just mutating an internal state +:- l +:: If no more chars available we return of course +?: .=(0 available) [nl available] +:: We look at the size of the current token +=/ size (inline-token-size l) +:: If the size is smaller than available, we add to new list, and substract from available +?: (lte size available) +[[l nl] (sub available size)] +:: If size is bigger than available we reduce the token, insert to list, set avaibable as 0 +=/ reduced (reduce-inline l available) +[[reduced nl] 0] + +[(flop -.ret) +.ret] + +:: +:: +:: search +++ text-search +|= [q=@t length=@ud p=post:tp case=?] ^- tape + :: ~> %bout.[0 %text-search] + =/ t (content-to-md:ui contents.p) + :: ~2020.7.31..23.51.21 + +:: =/ hstk ?: case t (cass t) +:: =/ nedl ?: case (trip q) (cass (trip q)) +:: =/ i (find nedl hstk) +:: ?~ i "" +:: =/ start ?: (lte u.i length) 0 (sub u.i length) +:: ?: .=(start 0) +:: "{(swag [start (mul 2 length)] t)}..." +:: "...{(swag [start (mul 2 length)] t)}..." + "" + +++ contains +|= [container=cord query=cord] ^- ? +?~ (find (trip query) (trip container)) %| %& +:: +++ text-search-ind +|= [q=@t length=@ud p=post:tp case=?] ^- @t + :: ~> %bout.[0 %text-search-ind] + ?~ contents.p '' + =/ bl=(list block:tp) val:head:(pop:corm:tp contents.p) + =| ob=(list block:tp) + |- + ?~ bl '' + :: TODO proper counts + =/ i i.bl + =/ r=(unit completion) + ?+ -.i ~ + %paragraph (inline-ind p.i q length case) + %blockquote (inline-ind p.i q length case) + :: :: %list (from-inline p.i.bl q case) + %heading (cfind-index:sr q p.i length .n) + %codeblock (cfind-index:sr q code.i length .n) + %eval (cfind-index:sr q hoon.i length .n) + %json (cfind-index:sr q content.i length .n) + :: %media (in-media2 media.i q) + :: %ref snippet :: TODO + :: %table snippet :: TODO + :: %tasklist snippet + == + ?~ r $(bl t.bl, ob [i.bl ob]) + ?: (gte (met 3 snip.u.r) length) snip.u.r :: victory + =. u.r + ?. (gth left-amari.u.r 0) u.r :: go fetch stuff on the left + =/ left-fill=@t (fill-up-block left-amari.u.r ob .y) + =/ added (cat 3 left-fill snip.u.r) + u.r(snip added, left-amari (sub left-amari.u.r (met 3 left-fill))) + =. u.r + ?. (gth right-amari.u.r 0) u.r :: go fetch stuff on the right + =/ right-fill=@t (fill-up-block right-amari.u.r t.bl .n) + =/ added (cat 3 snip.u.r right-fill) + u.r(snip added, right-amari (sub right-amari.u.r (met 3 right-fill))) + + snip.u.r + + ++$ completion [snip=@t left-amari=@ud right-amari=@ud] +++ inline-ind +|= [l=(list inline:tp) q=@t length=@ud case=?] ^- (unit completion) + =| ob=(list inline:tp) + |- + ?~ l ~ + =/ r=(unit completion) + ?+ -.i.l (cfind-index:sr q p.i.l length .n) +%break ~ +%date ~ :: TODO +%note ~ ::TODO +%ship (cfind-index:sr q (scot %p p.i.l) length .n) +%link (cfind-index:sr q (cat 3 href.i.l show.i.l) length .n) +%ruby (cfind-index:sr q (cat 3 p.i.l q.i.l) length .n) + == + ?~ r $(l t.l, ob [i.l ob]) + ?: (gte (met 3 snip.u.r) length) r :: exit condition + =. u.r + ?. (gth left-amari.u.r 0) u.r :: go fetch stuff on the left + =/ left-fill=@t (fill-up left-amari.u.r ob .y) + =/ added (cat 3 left-fill snip.u.r) + u.r(snip added, left-amari (sub left-amari.u.r (met 3 left-fill))) + =. u.r + ?. (gth right-amari.u.r 0) u.r :: go fetch stuff on the right + =/ right-fill=@t (fill-up right-amari.u.r t.l .n) + =/ added (cat 3 snip.u.r right-fill) + u.r(snip added, right-amari (sub right-amari.u.r (met 3 right-fill))) + + r + +:: +++ fill-up-block +|= [length=@ud l=(list block:tp) backwards=?] ^- @t + =| acc=@t + |- + ?~ l acc + ?: ?=(%paragraph -.i.l) (fill-up length p.i.l backwards) + ?: ?=(%blockquote -.i.l) (fill-up length p.i.l backwards) + =/ string=@t + ?+ -.i.l '' + %heading p.i.l + %codeblock code.i.l + %eval hoon.i.l + %json content.i.l + :: %media (in-media2 media.i q) + :: %ref snippet :: TODO + :: %table snippet :: TODO + :: %tasklist snippet + :: :: %list (from-inline p.i.bl q case) + == + =. acc ?: backwards + =/ end (met 3 string) + =/ start ?: (lth end length) 0 (sub end length) + =/ piece=@t (cut 3 [start end] string) + (cat 3 piece acc) + :: forwards + =/ piece=@t (cut 3 [0 length] string) + (cat 3 acc piece) + + =/ size (met 3 acc) + ?: .=(size length) acc :: exit condition + ?: (gte size length) '' :: bug + $(l t.l, length (sub length size)) + +++ fill-up +|= [length=@ud l=(list inline:tp) backwards=?] ^- @t + =| acc=@t + |- + ?~ l acc + =/ string=@t + ?+ -.i.l p.i.l +%break '' +%date '' :: TODO +%note '' ::TODO +%ship (scot %p p.i.l) +%link (cat 3 href.i.l show.i.l) +%ruby (cat 3 p.i.l q.i.l) + == + =. acc ?: backwards + =/ end (met 3 string) + =/ start ?: (lth end length) 0 (sub end length) + =/ piece=@t (cut 3 [start end] string) + (cat 3 piece acc) + :: forwards + =/ piece=@t (cut 3 [0 length] string) + (cat 3 acc piece) + + + =/ size (met 3 acc) + ?: .=(size length) acc :: exit condition + ?: (gth size length) '' :: this should never happen + $(l t.l, length (sub length size)) + +:: +++ text-search2 +|= [q=@t length=@ud p=post:tp case=?] ^- @t + ~> %bout.[0 %text-search] + ?~ contents.p '' + =/ bl=(list block:tp) val:head:(pop:corm:tp contents.p) + =| snippet=@t + |- + ?~ bl snippet + :: TODO proper counts + ?: (gth (met 3 snippet) length) snippet + =/ i i.bl + =/ ns + ?+ -.i snippet + %paragraph (from-inline p.i q length case) + :: %blockquote (from-inline p.i q length case) + :: :: %list (from-inline p.i.bl q case) + :: %heading (cfind:sr q p.i .n) + :: %codeblock (cfind:sr q code.i .n) + :: %eval (cfind:sr q hoon.i .n) + :: %json (cfind:sr q content.i .n) + :: %media (in-media2 media.i q) + :: %ref snippet :: TODO + :: %table snippet :: TODO + :: %tasklist snippet + == + $(bl t.bl, snippet (cat 3 snippet ns)) +++ from-inline +|= [l=(list inline:tp) q=@t length=@ud case=?] ^- @t + =| snippet=@t + |- + ?~ l snippet + ?: (gth (met 3 snippet) length) snippet + =/ r + ?+ -.i.l (cfindi:sr q p.i.l .n) + %break '\0a' + %date .n :: TODO + %note .n ::TODO + %ship (cfindi:sr q (scot %p p.i.l) .n) + %link (cat 3 (cfindi:sr q href.i.l .n) (cfindi:sr q show.i.l .n)) + %ruby (cat 3 (cfindi:sr q p.i.l .n) (cfindi:sr q q.i.l .n)) + == + $(l t.l, snippet (cat 3 snippet r)) + +:: ++ search2 +:: |= [q=@t p=post:tp] ^- ? +:: ?~ contents.p .n +:: =/ latest=content-list:tp val:head:(pop:corm:tp contents.p) +:: =/ in-tags %+ roll ~(tap in tags.p) |= [i=cord a=_|] +:: ?: (cfind:sr q i .n) %& a +:: =/ in-blocks %+ roll latest |= [i=block:tp a=_|] +:: ?: ?- -.i +:: %paragraph (in-inline2 p.i q) +:: %blockquote (in-block p.i q) +:: %list (in-inline2 p.i q) +:: %heading (cfind:sr q p.i .n) +:: %codeblock (cfind:sr q code.i .n) +:: %eval (cfind:sr q hoon.i .n) +:: %json (cfind:sr q content.i .n) +:: %media (in-media2 media.i q) +:: %ref %| :: TODO +:: %table %| :: TODO +:: %tasklist .n +:: == %& a +:: ?| in-tags in-blocks == +++ in-media2 +|= [=media:tp q=@t] ^- ? +?. ?=(%images -.media) (cfind:sr q p.media .n) +%+ roll p.media |= [[url=cord caption=cord] a=_|] +?: (cfind:sr q url .n) %& a +:: ++ in-inline2 +:: |= [l=(list inline:tp) q=@t] ^- ? +:: |- +:: ?~ l .n +:: =/ i i.l +:: =/ r=? +:: ?+ -.i (cfind:sr q p.i .n) +:: %break .n +:: %date .n +:: %note .n +:: %ship (cfind:sr q (scot %p p.i) .n) +:: %link ?|((cfind:sr q href.i .n) (cfind:sr q show.i .n)) +:: %ruby ?|((cfind:sr q p.i .n) (cfind:sr q q.i .n)) +:: == +:: ?| r $(l t.l) == +:: +++ page-cond +|= [id=@da current=@ud r=page-req:tp] ^- ? +=/ need-more (lth current count.r) +?~ newer.r + :: newest not bound + ?~ older.r + :: neither oldest or newest is bound + need-more + :: oldest is bound, newest isn't + ?& need-more (lth id u.older.r) == + :: newest bound + ?~ older.r + :: newest is bound, oldest isn't + ?& need-more (gth id u.newer.r) == + :: both are bound + ?&(need-more (lth id u.older.r) (gth id u.newer.r)) +++ get-post-page +|= [feed=gfeed:tp req=page-req:tp] ^- page:tp +=/ from-bottom=? ?& ?=(%~ older.req) ?!(?=(%~ newer.req)) == +=/ l ?. from-bottom (tap:gorm:tp feed) (flop (tap:gorm:tp feed)) +=/ res +%+ roll l +|= [[=pid:tp =post:tp] a=[p=page:tp max=@da min=@da]] +=/ id id.pid +?^ parent.post a +=/ max ?: (gth id max.a) id max.a +=/ min ?: ?|((lth id min.a) .=(min.a *@da)) id min.a +:_ [max min] +=/ condition=? (page-cond id count.p.a req) +?. condition p.a +=/ posts [(node-to-full post feed) p.p.a] +:: +=/ oldest ?~ older.p.a `id + ?: (lth id u.older.p.a) `id older.p.a +=/ newest ?~ newer.p.a `id + ?: (gth id u.newer.p.a) `id newer.p.a +[posts newest oldest +(count.p.a)] +:: TODO arg gotta figure this out +=/ o + ?: .=(older.p.res `min.res) ~ older.p.res + :: ?: (lth count.res count.req) ~ +=/ n ?: .=(newer.p.res `max.res) ~ newer.p.res +=/ poasts ?. from-bottom (flop p.p.res) p.p.res +[poasts n o count.p.res] +:: ++ basic-filter +:: |= [=feed:tp req=page-req:tp filter=$-(post:tp ?)] +:: |= [[=id:tp =post:tp] a=spage:tp] +:: ?. (filter post) a +:: =/ posts [post p.a] +:: =/ oldest ?~ older.a `id +:: ?: (lth id u.older.a) `id older.a +:: [posts newer.r oldest +(count.a)] +:: TODO spage or page... +++ get-filtered-post-page-full +|= [feed=gfeed:tp req=page-req:tp filter=$-(post:tp ?)] ^- page:tp +=/ from-bottom=? ?& ?=(%~ older.req) ?!(?=(%~ newer.req)) == +=/ l ?. from-bottom (tap:gorm:tp feed) (flop (tap:gorm:tp feed)) +=/ res +%+ roll l +|= [[=pid:tp =post:tp] a=[p=page:tp max=@da min=@da]] +=/ id id.pid +?. (filter post) a +=/ condition=? (page-cond id count.p.a req) +=/ max ?: (gth id max.a) id max.a +=/ min ?: ?|((lth id min.a) .=(min.a *@da)) id min.a +:_ [max min] +?. condition p.a +=/ posts [(node-to-full post feed) p.p.a] +:: +=/ oldest ?~ older.p.a `id + ?: (lth id u.older.p.a) `id older.p.a +=/ newest ?~ newer.p.a `id + ?: (gth id u.newer.p.a) `id newer.p.a +[posts newest oldest +(count.p.a)] +:: TODO arg gottaa figure this out +=/ o + ?: .=(older.p.res `min.res) ~ older.p.res + :: ?: (lth count.res count.req) ~ +=/ n ?: .=(newer.p.res `max.res) ~ newer.p.res +=/ poasts ?. from-bottom (flop p.p.res) p.p.res +[poasts n o count.p.res] +++ get-filtered-post-page +|= [feed=gfeed:tp req=page-req:tp filter=$-(post:tp ?)] ^- spage:tp + =/ from-bottom=? ?& ?=(%~ older.req) ?!(?=(%~ newer.req)) == + =/ l ?. from-bottom (tap:gorm:tp feed) (flop (tap:gorm:tp feed)) + =/ res + %+ roll l + |= [[=pid:tp =post:tp] a=[p=spage:tp max=@da min=@da]] + =/ id id.pid + ?. (filter post) a + =/ condition=? (page-cond id count.p.a req) + =/ max ?: (gth id max.a) id max.a + =/ min ?: ?|((lth id min.a) .=(min.a *@da)) id min.a + :_ [max min] + ?. condition p.a + =/ posts [post p.p.a] + :: + =/ oldest ?~ older.p.a `id + ?: (lth id u.older.p.a) `id older.p.a + =/ newest ?~ newer.p.a `id + ?: (gth id u.newer.p.a) `id newer.p.a + [posts newest oldest +(count.p.a)] + :: TODO arg gottaa figure this out + =/ o + ?: .=(older.p.res `min.res) ~ older.p.res + :: ?: (lth count.res count.req) ~ + =/ n ?: .=(newer.p.res `max.res) ~ newer.p.res + =/ poasts ?. from-bottom (flop p.p.res) p.p.res + [poasts n o count.p.res] + +:: ++ get-tag-page +:: |= [feed=gfeed:tp tt=tags-table l=(list @t) r=page-req:tp] ^- page:tp +:: ~> %bout +:: =/ pids %+ roll l |= [i=@t a=(list pid:tp)] =/ ps (~(get by tt) i) +:: ?~ ps a (weld u.ps a) +:: =/ filter |= =post:tp (~(has in (sy pids)) [author.post id.post]) +:: (get-filtered-post-page-full feed r filter) + +:: ++ pcond +:: |= [id=@da r=page-req:tp] ^- ? +:: ?~ older.r +:: ?~ newer.r .y +:: (gth id u.newer.r) +:: ?~ newer.r +:: (lth id u.older.r) +:: ?& (lth id u.older.r) (gth id u.newer.r) == + +:: ++ get-tag-page-2 +:: |= [feed=gfeed:tp tt=tags-table l=(list @t) r=page-req:tp] ^- page:tp +:: =/ =pid-graph:tp +:: ~> %bout +:: %+ roll l |= [i=@t a=pid-graph:tp] +:: =/ pids-by-tag (~(get by tt) i) +:: ?~ pids-by-tag a =/ pl (flop u.pids-by-tag) +:: |- +:: ?~ pl a +:: ?. (pcond id.i.pl r) $(pl t.pl) +:: %= $ +:: a (put:porm:tp a id.i.pl ship.i.pl) +:: pl t.pl +:: == +:: =/ top (pry:porm:tp pid-graph) +:: =/ tom (ram:porm:tp pid-graph) +:: =/ max ?~ top ~ `-.u.top +:: =/ min ?~ tom ~ `-.u.tom +:: =/ res=page:tp +:: =| =page:tp +:: =/ pids (tap:porm:tp pid-graph) +:: |- +:: ?~ pids page +:: =/ id -.i.pids +:: ?: .=(count.page count.r) page +:: ?. (pcond id r) $(pids t.pids) +:: =/ post (get:gorm:tp feed [+.i.pids id]) +:: ?~ post $(pids t.pids) +:: =/ np=page:tp +:: =/ posts [(node-to-full u.post feed) p.page] +:: =/ oldest ?~ older.page `id +:: ?: (lth id u.older.page) `id older.page +:: =/ newest ?~ newer.page `id +:: ?: (gth id u.newer.page) `id newer.page +:: [posts newest oldest +(count.page)] +:: %= $ +:: page np +:: pids t.pids +:: == +:: =/ n ?: .=(max newer.res) ~ newer.res +:: =/ o ?: .=(min older.res) ~ older.res +:: res(newer n, older o, p (flop p.res)) + +:: ++ get-tag-page-3 +:: |= [feed=gfeed:tp tt=tags-table l=(list @t) r=page-req:tp] ^- page:tp +:: ~> %bout +:: =/ empty *page:tp +:: =| count=@ud +:: =/ posts=(list full-node:tp) +:: |- ^- (list full-node:tp) +:: ?~ l ~ +:: =/ pids (~(get by tt) i.l) +:: ?~ pids ~ +:: =/ pl (flop u.pids) +:: %+ welp ^- (list full-node:tp) +:: |- +:: ?~ pl ~ +:: ?: (gte count count.r) ~ +:: ?. (pcond +.i.pl r) $(pl t.pl) +:: =/ poast (get:gorm:tp feed i.pl) +:: ?~ poast $(pl t.pl) +:: =/ fn (node-to-full u.poast feed) +:: :- fn +:: $(pl t.pl, count +(count)) +:: $(l t.l) +:: :: +:: =/ newer ~ +:: =/ older ?~ posts ~ (some id:p:(rear posts)) +:: [posts newer older (lent posts)] + +++ tag-search + |= l=(list @t) + |= =post:tp ^- ? + |- + ?~ l .n + =/ ok=? ?& (~(has in tags.post) (crip (cass (trip i.l)))) ?=(%~ parent.post) == + ?: ok .y + $(l t.l) + +++ tag-search-old +|= [l=(list @t) feed=gfeed:tp r=page-req:tp] ^- page:tp + %+ roll (tap:gorm:tp feed) |= [[=pid:tp =post:tp] a=page:tp] + =/ id id.pid + =/ condition (page-cond id count.a r) + ?. condition a + =/ found + =/ has .y + |- + ?~ l has + ?& has + =/ ns (~(has in tags.post) (crip (cass (trip i.l)))) + $(l t.l, has ns) + == + =/ posts ?. found p.a :_ p.a + (node-to-full post feed) + =/ oldest ?~ older.a `id + ?: (lth id u.older.a) `id older.a + =/ count ?: .=(count.a count.r) count.r +(count.a) + [posts newer.r oldest count] +:: +++ search-filter-full +|= [feed=gfeed:tp req=page-req:tp filter=$-(post:tp ?)] ^- page:tp +=/ from-bottom=? ?& ?=(%~ older.req) ?!(?=(%~ newer.req)) == +=/ l ?. from-bottom (tap:gorm:tp feed) (flop (tap:gorm:tp feed)) +=/ res +%+ roll l +|= [[=pid:tp =post:tp] a=[p=page:tp max=@da min=@da]] +=/ id id.pid +?. (filter post) a +=/ condition=? (page-cond id count.p.a req) +=/ max ?: (gth id max.a) id max.a +=/ min ?: ?|((lth id min.a) .=(min.a *@da)) id min.a +:_ [max min] +?. condition p.a +=/ posts [(node-to-full post feed) p.p.a] +:: +=/ oldest ?~ older.p.a `id + ?: (lth id u.older.p.a) `id older.p.a +=/ newest ?~ newer.p.a `id + ?: (gth id u.newer.p.a) `id newer.p.a +[posts newest oldest +(count.p.a)] +=/ o + ?: .=(older.p.res `min.res) ~ older.p.res + :: ?: (lth count.res count.req) ~ +=/ n ?: .=(newer.p.res `max.res) ~ newer.p.res +=/ poasts ?. from-bottom (flop p.p.res) p.p.res +[poasts n o count.p.res] + +++ search-filter +|= [feed=gfeed:tp req=page-req:tp filter=$-(post:tp ?)] ^- spage:tp +=/ from-bottom=? ?& ?=(%~ older.req) ?!(?=(%~ newer.req)) == +=/ l ?. from-bottom (tap:gorm:tp feed) (flop (tap:gorm:tp feed)) +=/ res +%+ roll l +|= [[=pid:tp =post:tp] a=[p=spage:tp max=@da min=@da]] +=/ id id.pid +?. (filter post) a +=/ condition=? (page-cond id count.p.a req) +=/ max ?: (gth id max.a) id max.a +=/ min ?: ?|((lth id min.a) .=(min.a *@da)) id min.a +:_ [max min] +?. condition p.a +=/ posts [post p.p.a] +:: +=/ oldest ?~ older.p.a `id + ?: (lth id u.older.p.a) `id older.p.a +=/ newest ?~ newer.p.a `id + ?: (gth id u.newer.p.a) `id newer.p.a +[posts newest oldest +(count.p.a)] +=/ o + ?: .=(older.p.res `min.res) ~ older.p.res + :: ?: (lth count.res count.req) ~ +=/ n ?: .=(newer.p.res `max.res) ~ newer.p.res +=/ poasts ?. from-bottom (flop p.p.res) p.p.res +[poasts n o count.p.res] + +:: +++ tlon-scan-to-post + |= s=reference:tlonc ^- post:tp + =/ np *post:tp + ?: ?=(%post -.s) + =/ =memo:tlonc +>-.s + =/ children %- sy %+ turn (tap:on-replies:tlonc replies.+<.s) + |= [id=@da reply:tlonc] [author id] + %= np + id sent.memo + author author.memo + thread [~zod sent.memo] :: TODO mmm + parent ~ + contents (tlon-trill-contents content.memo sent.memo) + children children + == + :: + =/ =memo:tlonc +.reply.s + =/ par parent-id.-.reply.s + %= np + id sent.memo + author author.memo + thread [~zod par] :: TODO really? + parent (some [~zod par]) :: TODO mmm + contents (tlon-trill-contents content.memo sent.memo) + == +++ tlon-trill-contents + |= [l=(list verse:tlonc) =time] ^- content-map:tp + =/ cl=content-list:tp %+ roll l + |= [i=verse:tlonc a=content-list:tp] + ?: ?=(%block -.i) :_ a (tlon-block p.i) + =/ l p.i + =/ nb=content-list:tp *content-list:tp + =/ cl=content-list:tp + |- + ?~ l nb + =/ nnb=content-list:tp + ?: ?=(%task -.i.l) =/ task [(turn q.i.l tlon-inline) p.i.l] + =/ lb (last-block nb %tasklist) + =/ tl=(list task:tp) ?~ lb ~ ?. ?=(%tasklist -.u.lb) ~ p.u.lb + (snoc nb [%tasklist (snoc tl task)]) + ?: ?=(%blockquote -.i.l) + (snoc nb [%blockquote (turn p.i.l tlon-inline)]) + ?: ?=(%code -.i.l) + (snoc nb [%codeblock p.i.l '']) + ?: ?=(%block -.i.l) + (snoc nb [%ref %channels ~zod /]) :: TODO lol + :: + =/ bun=(list inline:tp) ~ + =/ f (flop nb) + =/ inlines ?~ f bun + =/ first=block:tp -.f + ?. ?=(%paragraph -.first) bun p.first + %+ snoc nb :- %paragraph + %+ snoc inlines + ?- -.i.l + %italics [%italic (crip (flatten-tlon-inline p.i.l))] + %bold [%bold (crip (flatten-tlon-inline p.i.l))] + %strike [%strike (crip (flatten-tlon-inline p.i.l))] + %inline-code [%codespan p.i.l] + %ship [%ship p.i.l] + %tag [%text p.i.l] + %link [%link p.i.l q.i.l] + %break [%break ~] + == + $(l t.l, nb nnb) + (weld cl a) + + =/ g=(list [@da content-list:tp]) :~([time (flop cl)]) + %+ gas:corm:tp *content-map:tp g + +:: +++ last-block +|= [l=content-list:tp tag=$?(%paragraph %tasklist)] ^- (unit block:tp) +=/ f (flop l) +|- +?~ f ~ +?: .=(tag -.i.f) (some i.f) $(f t.f) +++ tlon-block +|= b=block:tlonc ^- block:tp +?- -.b +%image [%media %images ~[[src.b alt.b]]] +%cite (tlon-cite +.b) +%header [%heading (crip (flatten-tlon-inline q.b)) p.b] +%listing (tlon-listing p.b) +%rule [%paragraph ~] +%code [%codeblock code.b lang.b] +== +++ tlon-listing +|= l=listing:tlonc ^- block:tp +?. ?=(%list -.l) [%paragraph (turn p.l tlon-inline)] +:: + ?: ?=(%tasklist p.l) :- %tasklist ~ :: TODO wtf is this%+ roll q.l :: TODO idgi what r does in this type + :- %list :_ ?=(%ordered p.l) ~ :: TODO i'm tired + :: :_ ~ :_ ~ %+ roll q.l tlon-listing + +++ tlon-inline +|= i=inline:tlonc ^- inline:tp +?@ i [%text i] +?- -.i +%italics [%italic (crip (flatten-tlon-inline p.i))] +%bold [%bold (crip (flatten-tlon-inline p.i))] +%strike [%strike (crip (flatten-tlon-inline p.i))] +%blockquote [%text (crip (weld "> " (flatten-tlon-inline p.i)))] +%inline-code [%codespan p.i] +%code [%codespan p.i] +%ship [%ship p.i] +%block [%break ~]:: [%ref %channels ~zod /] +%tag [%text p.i] +%link [%link p.i q.i] +%task [%text ''] +%break [%break ~] +== +++ flatten-tlon-inline +|= l=(list inline:tlonc) ^- tape +%+ roll l |= [i=inline:tlonc a=tape] +=/ res +?@ i (trip i) +?- -.i +%italics (flatten-tlon-inline p.i) +%bold (flatten-tlon-inline p.i) +%strike (flatten-tlon-inline p.i) +%blockquote (flatten-tlon-inline p.i) +%inline-code (trip p.i) +%code (trip p.i) +%ship (scow %p p.i) +%block (trip q.i) +%tag (trip p.i) +%link (trip p.i) +%task (flatten-tlon-inline q.i) +%break "" +== +" {a} {res}" +++ tlon-cite +|= c=cite:tlonc +:- %ref +?- -.c +%chan [%channels p.q.nest.c wer.c] :: TODO is this path ok? nah needs type of channel and whatever +%group [%groups p.flag.c /[q.flag.c]] +%desk [%app p.flag.c wer.c] :: TODO same +%bait [%groups p.grp.c wer.c] :: TODO same +== +:: ++ add-tag-lookup +:: |= [lt=(list @t) =pid:tp table=tags-table] ^- tags-table +:: %^ fold:sr lt table |= [tag=@t a=tags-table] +:: =/ cur (~(get by a) tag) +:: =/ nl ?~ cur +:: =/ bnt *threads +:: (put:torm:tp bnt pid ) +:: ~[pid] [pid u.cur] +:: (~(put by a) tag nl) + +-- |