diff --git a/ape/cloud.hoon b/ape/cloud.hoon index ff49306280..a391a6139a 100644 --- a/ape/cloud.hoon +++ b/ape/cloud.hoon @@ -42,7 +42,7 @@ $: auth+{do+keys gce+keys} toke+{do+tokens gce+tokens} insts+(map @t instance) - images+(map {{@t @t} image}) + images+(map {@t @t} image) == ++ keys {authc+(unit @t) client-secret+(unit @t)} ++ tokens {access+@t refresh+@t} @@ -146,7 +146,7 @@ (ot name/so ~) :: ++ parse-id-text - |= jon=json + |= jon+json ?.(?=({?($n $s) *} jon) ~ (some p.jon)) :: ++ create-do-body @@ -198,8 +198,8 @@ snapshot/s/snapshot == ++ map-to-list - |= a+(map {{@t @t} image}) - ^- liz=(list image) + |= a+(map {@t @t} image) + ^- liz+(list image) %+ turn (~(tap by a) *(list {{@t @t} image})) |=(a+{{@t @t} image} `image`+.a) :: @@ -259,7 +259,7 @@ ^- {(list move) _+>.$} :_ +>.$ =+ lis=(~(tap by insts.vat)) - [ost %diff %json (instance-to-json (turn lis |=(a=[@t instance] +.a)))]~ + [ost %diff %json (instance-to-json (turn lis |=(a+{@t instance} +.a)))]~ :: ++ spam |= jon+json @@ -276,7 +276,7 @@ |= sp+speech =+ ^= tail :- ^- audience - :+ :- `partner`[%& our ?+((clan our) !! %czar %court, %duke %porch)] + :+ :- `partner`[%& our ?+((clan our) !! $czar %court, $duke %porch)] ^- (pair envelope delivery) [`envelope`[& ~] %pending] ~ @@ -287,7 +287,7 @@ tail =+ mez=[%talk-command [%publish `(list thought)`spchz]] [ost %send /pub [our %talk] %poke mez] -++ thou-pub |=(~ :_(+>.$ ~)) +++ thou-pub |=($~ :_(+>.$ ~)) :::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::: :: authentication :: :::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::: @@ -308,7 +308,7 @@ |= {secret+cord typ+cord} ^- {(list move) _+>.$} ?+ typ ~|(missing-platform=typ !!) - %do + $do =. client-secret.do.auth.vat [~ secret] :_ +>.$ @@ -337,7 +337,7 @@ :::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::: ++ create-do |= act+json - =+ ^- deets=create-req-do + =+ ^- deets+create-req-do %- need %. act => jo @@ -351,7 +351,7 @@ 'priv_networking'^(mu bo) 'user_data'^(mu so) == - =+ ^- body=json + =+ ^- body+json %- create-do-body :* name.deets size.deets @@ -372,7 +372,7 @@ ~ == :: -++ thou-create-do |=([path resp=httr] ~&(resp :_(+>.$ ~))) +++ thou-create-do |=({path resp+httr} ~&(resp :_(+>.$ ~))) :::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::: :: create google instances :: :::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::: @@ -426,13 +426,13 @@ :: ++ create-gce |= jon+json - ++ ^- {name+@t image+@t number+@ud} + =+ ^- {name+@t image+@t number+@ud} (need ((ot name/so 'instance_img'^so number/ni ~):jo jon)) |- ^- (list move) ?~ number ~ :_ $(number (dec number)) =+ nam=(cat 3 name (scot %ud number)) - =+ ^- body=json + =+ ^- body+json %- jobe :~ name/s/nam 'machineType'^s/'zones/us-central1-a/machineTypes/n1-standard-1' @@ -479,7 +479,7 @@ ?- typ $do =+ ^= meth - ?: ?=(%delete -.action) + ?: ?=($delete -.action) %delt :- %post %+ jobe type/s/(convert-do -.action) @@ -489,7 +489,7 @@ %- httpreq :* /do/[-.action] ~[%digitalocean %api] - ?:(?=(%delt meth) /v2/droplets/[id] /v2/droplets/[id]/actions) + ?:(?=($delt meth) /v2/droplets/[id] /v2/droplets/[id]/actions) meth %^ mo ['Content-Type' 'application/json' ~] ['Authorization' (cat 3 'Bearer ' access.do.toke.vat) ~] ~ @@ -507,7 +507,7 @@ =+ end=/compute/v1/projects/urbcloud/zones/us-central1-a/instances/[name] %- httpreq :* /gce-act/[-.action] ~['googleapis' 'www'] - (welp end [?:(?=(%reboot -.action) 'reset' -.action) ~]) + (welp end [?:(?=($reboot -.action) 'reset' -.action) ~]) [%post ~] head-query == @@ -556,7 +556,7 @@ :: ++ thou-list-gce-zones :: instances |= {pax+path resp+httr} - ^- [(list move) _+>.$] + ^- {(list move) _+>.$} =+ parsed=(rash q:(need r.resp) apex:poja) :: body httr to json ~| 'no list received or bad json' =+ items=(need ((ot items/(ar some) ~):jo parsed)) @@ -615,18 +615,20 @@ :: list digital ocean droplets and images :: ::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::: ++ list-do -:+((list-something-do %droplets) (list-something-do %images) ~) + :+((list-something-do %droplets) (list-something-do %images) ~) ++ list-something-do |= som+@tas =+ ^= lis :~ /list-do/[som] - ~[%digitalocean %api] /v2/[som] - %get - %- mo - :~ ['Content-Type' 'application/json' ~] - ['Authorization' (cat 3 'Bearer ' access.do.toke.vat) ~] + ~[%digitalocean %api] + /v2/[som] + %get + %- mo + :~ ['Content-Type' 'application/json' ~] + ['Authorization' (cat 3 'Bearer ' access.do.toke.vat) ~] + == == - (httpreq lis) + (httpreq lis) :: ++ thou-list-do-droplets |= {pax+path resp+httr} @@ -663,7 +665,7 @@ %- spam %- instance-to-json %+ turn (~(tap by insts.vat) *(list {@t instance})) - |=(a=[@t instance] +.a) + |=(a+{@t instance} +.a) :: ++ thou-list-do-images |= {pax+path resp+httr} @@ -680,9 +682,10 @@ =. images.vat %- mo %+ weld images - %+ skip (~(tap by images.vat) *(list ,[[@t @t] image])) + %+ skip (~(tap by images.vat) *(list {{@t @t} image})) |=(a+{{@t @t} image} ?=($do ->.a)) - :_ +>.$ ~[(spam `json`(image-to-json `(list image)`(map-to-list images.vat)))] + :_ +>.$ + ~[(spam `json`(image-to-json `(list image)`(map-to-list images.vat)))] :: ++ wake-refresh-do |=({path $~} [list-do +>.$]) -- diff --git a/ape/twit.hoon b/ape/twit.hoon index 8f578a78df..a00945cca4 100644 --- a/ape/twit.hoon +++ b/ape/twit.hoon @@ -10,40 +10,40 @@ [twitter .] |% ++ twit-path :: valid peer path - $% :: [%home ~] :: home timeline - [%user p=@t ~] :: user's tweets - [%post p=span:,@uv ~] :: status of status + $% :: [%home $~] :: home timeline + {$user p+@t $~} :: user's tweets + {$post p+span $~} :: status of status == :: ++ axle :: app state - $: %0 - kes=(map span keys:twit-do) :: auth - out=(map ,@uvI (each ,[span cord] stat)) :: sent tweets - ran=(map path ,[p=@ud q=@da]) :: polls active - fed=(jar path stat) :: feed cache + $: $0 + kes+(map span keys:twit-do) :: auth + out+(map @uvI (each {span cord} stat)) :: sent tweets + ran+(map path {p+@ud q+@da}) :: polls active + fed+(jar path stat) :: feed cache == :: ++ gift :: subscription action - $% [%quit ~] :: terminate - [%diff gilt] :: send data + $% {$quit $~} :: terminate + {$diff gilt} :: send data == ++ gilt - $% [%twit-feed p=(list stat)] :: posts in feed - [%twit-stat p=stat] :: tweet accepted - [%ares term (list tank)] + $% {$twit-feed p+(list stat)} :: posts in feed + {$twit-stat p+stat} :: tweet accepted + {$ares term (list tank)} == :: -++ move ,[bone card] +++ move {bone card} ++ card :: arvo request $? gift - $% [%them path ~ u=hiss] :: HTTP request - [%poke wire dock %talk-command command:talk] :: - [%wait path p=@da] :: timeout + $% {$them path $~ u+hiss} :: HTTP request + {$poke wire dock $talk-command command:talk} :: + {$wait path p+@da} :: timeout == == :: ++ sign :: arvo response - $% [%e %thou p=httr] :: HTTP result - [%t %wake ~] :: timeout ping + $% {$e $thou p+httr} :: HTTP result + {$t $wake $~} :: timeout ping == :: ++ stat twit-stat :: recieved tweet @@ -51,22 +51,22 @@ !: :::: :: -|_ [bowl axle] +|_ {bowl axle} ++ any-auth ?~(kes (auth) (auth p.n.kes)) :: use any keys ++ auth :: build API door - |= a=span + |= a+span ~| [%no-auth a] ~(. twit (~(got by kes) a) now `@`eny) :: ++ cull :: remove seen tweets - |= [pax=path rep=(list stat)] ^+ rep + |= {pax+path rep+(list stat)} ^+ rep =+ pev=(sa (turn (~(get ja fed) pax) |=(stat id))) (skip rep |=(stat (~(has in pev) id))) :: ++ done [*(list move) .] ++ dely :: next polling timeout - |= pax=path - ^- [(unit time) _ran] + |= pax+path + ^- {(unit time) _ran} =+ cur=(~(get by ran) pax) =+ tym=(add now (mul ~s8 (bex ?~(cur 0 p.u.cur)))) :: ~& dely/`@dr`(sub tym now) @@ -75,7 +75,7 @@ [`tym (~(put by ran) pax ?~(cur 0 (min 5 +(p.u.cur))) tym)] :: ++ wait :: ensure poll by path - |= [pax=path mof=(list move)] + |= {pax+path mof+(list move)} =^ tym ran (dely pax) :_ +>.$ ?~ tym @@ -86,13 +86,13 @@ mof :: ++ poke-twit-do :: recieve request - |= act=twit-do + |= act+twit-do ^+ [*(list move) +>] ?- -.q.act - %auth + $auth :- [(print "authed @{(trip p.act)}")]~ +>.$(kes (~(put by kes) p.act p.q.act)) :: XX verify key - %post + $post =: out (~(put by out) p.q.act %& p.act q.q.act) ran (~(del by ran) /peer/home) == @@ -102,12 +102,12 @@ == :: ++ wake-peer - |= [pax=path ~] ^+ done + |= {pax+path ~} ^+ done ~& twit-wake/peer/pax :_ +>.$ ?. (~(has by ran) peer/pax) :: ignore if retracted ~ - =+ => |=([a=bone @ b=path] [b a]) + =+ => |=({a+bone @ b+path} [b a]) pus=(~(gas ju *(jug path bone)) (turn (~(tap by sup)) .)) ?~ (~(get ju pus) pax) ~ @@ -115,7 +115,7 @@ (pear | our pax) :: ++ thou - |= [pax=path hit=httr] ^+ done + |= {pax+path hit+httr} ^+ done ?+ p.hit ~|([%unknown-code p.hit] !!) 429 :: Rate-limit =. ran (~(put by ran) pax 6 now) @@ -128,7 +128,7 @@ =+ jon=(need (poja q:(need r.hit))) :: ~& twit-resp/%.(jon ?+(-.jon !! %o stat:twir, %a (ar:jo stat:twir))) ?+ pax ~|([%http-missed pax] !!) - [%post @ ~] :: post acknowledged + {$post @ $~} :: post acknowledged =+ ^= rep ~| [%bad-post jon] (need %.(jon stat:twir)) @@ -137,7 +137,8 @@ =+ pax=/[who.rep]/status/(rsh 3 2 (scot %ui id.rep)) :- (print (earn [& ~ `/com/twitter] `pax ~)) (spam pax (tweet-good rep)) - [%peer *] :: feed data + :: + {$peer *} :: feed data =+ ^= rep ~| [%bad-feed jon] (need %.(jon (ar:jo stat:twir))) @@ -152,28 +153,28 @@ (wait pax (spam t.pax [%diff twit-feed/(flop ren)] ~)) == :: - ?(400 401 403 404) :: Err - =+ ^- git=gift + ?($400 $401 $403 $404) :: Err + =+ ^- git+gift =+ err=%.(q:(need r.hit) ;~(biff poja mean:twir)) :^ %diff %ares %bad-http [leaf/"HTTP Code {}" (turn (need err) mean:twip)] ?+ pax [[ost git]~ +>.$] - [%post @ ~] + {$post @ ~} [(spam pax git ~) +>.$] == == -++ tweet-good |=(rep=stat `(list gift)`~[[%diff %twit-stat rep] [%quit ~]]) -++ peer |=(pax=path :_(+> (pear & src pax))) :: accept subscription +++ tweet-good |=(rep+stat `(list gift)`~[[%diff %twit-stat rep] [%quit ~]]) +++ peer |=(pax+path :_(+> (pear & src pax))) :: accept subscription ++ pear :: poll, possibly returning current data - |= [ver=? @ pax=path] + |= {ver+? @ pax+path} ^- (list move) ?. ?=(twit-path pax) ~|([%missed-path pax] !!) => .(pax `twit-path`pax) - ?: ?=(%post -.pax) + ?: ?=($post -.pax) ?. ver ~ =+ sta=(~(get by out) (slav %uv p.pax)) - ?. ?=([~ %| ^] sta) :: post not received + ?. ?=({$~ $| ^} sta) :: post not received ~ ~[[ost %diff %twit-stat p.u.sta] [ost %quit ~]] =+ ole=(~(get ja fed) pax) @@ -185,18 +186,18 @@ =+ opt=?~(ole ~ ['since_id' (lutt:twit id.i.ole)]~) =+ aut=any-auth ?- -.pax - %user (stat-user:aut [(to-sd p.pax)]~ opt) -:: %home (stat-home:auth ~ opt) + $user (stat-user:aut [(to-sd p.pax)]~ opt) +:: $home (stat-home:auth ~ opt) == :: ++ to-sd :: parse user name/numb - |= a=span ^- sd:twit + |= a+span ^- sd:twit ~| [%not-user a] %+ rash a ;~(pose (stag %user-id dem) (stag %screen-name user:twir)) :: -:: ++ pull :: release subscription -:: |= ost=bone +:: ++ pull :: release subscription +:: |= ost+bone :: ?. (~(has by sup) ost) `+>.$ :: XX should not occur :: =+ [his pax]=(~(got by sup) ost) :: ?: (lth 1 ~(wyt in (~(get ju pus) pax))) @@ -207,13 +208,14 @@ :: `+>.$ :: ++ spam :: send by path - |= [a=path b=(list gift)] ^- (list move) + |= {a+path b+(list gift)} ^- (list move) %- zing ^- (list (list move)) %+ turn (~(tap by sup)) - |= [ost=bone @ pax=path] + |= {ost+bone @ pax+path} ?. =(pax a) ~ - (turn b |=(c=gift [ost c])) + (turn b |=(c+gift [ost c])) :: ++ print - |=(mes=tape [ost %poke / [our %talk] (said our %twit now eny leaf/mes ~)]) + |= mes+tape + [ost %poke / [our %talk] (said:^talk our %twit now eny leaf/mes ~)] -- diff --git a/ape/write.hoon b/ape/write.hoon index 0359d6d500..672e16cd7f 100644 --- a/ape/write.hoon +++ b/ape/write.hoon @@ -2,10 +2,10 @@ :: :::: /hoon/write/app :: -|_ [bowl ~] +|_ {bowl $~} ++ beak-now byk(r [%da now]) ++ poke-json - |= jon=json + |= jon+json =- (poke--data (need (- jon.+))) => jo %- ot :~ @@ -14,23 +14,23 @@ == :: ++ poke-write-paste - |= [typ=?(%hoon %md %txt) txt=@t] + |= {typ+?($hoon $md $txt) txt+@t} (poke--data [`typ /pub/paste/(scot %da now)] %mime / (taco txt)) :: ++ poke--data - |= [[ext=(unit ,@t) pax=path] dat=$%([%json json] [%mime mime])] + |= {{ext+(unit @t) pax+path} dat+$$({$json json} {$mime mime})} ?~ ext $(ext [~ -.dat]) =+ cay=?-(-.dat %json [-.dat !>(+.dat)], %mime [-.dat !>(+.dat)]) ?: =(u.ext -.dat) (made pax ~ `cay) [[ost %exec pax our ~ beak-now %cast u.ext `cay]~ +>.$] :: XX defer %nice :: ++ made - |= [pax=wire @ res=gage] + |= {pax+wire @ res+gage} ?. =(our src) ~|(foreign-write/[our=our src=src] !!) ?+ -.res ~|(gage/-.res !!) - %| (mean p.res) - %& =- [[ost %info / our -]~ +>.$] + $| (mean p.res) + $& =- [[ost %info / our -]~ +>.$] (foal :(welp (tope beak-now ~) pax /[-.p.res]) p.res) == -- diff --git a/lib/twitter.hoon b/lib/twitter.hoon index 95d6f1d633..806ae0ad0f 100644 --- a/lib/twitter.hoon +++ b/lib/twitter.hoon @@ -4,21 +4,21 @@ :: /? 314 /- twitter -=+ twit:twitter +=+ twit:^twitter !: :::: functions :: |% ++ fass :: rewrite path - |= a=path + |= a+path %- trip %^ gsub '-' '_' %+ reel a - |= [p=@t q=@t] + |= {p+@t q+@t} (cat 3 '/' (cat 3 p q)) :: ++ gsub :: replace chars - |= [a=@t b=@t t=@t] + |= {a+@t b+@t t+@t} ^- @t ?~ t t %+ add (lsh 3 1 $(t (rsh 3 1 t))) @@ -26,21 +26,21 @@ ?:(=(a c) b c) :: ++ oauth :: OAuth 1.0 header - |= $: med=meth - url=tape - pas=(list tape) - key=keys - zet=@ - ken=@ + |= $: med+meth + url+tape + pas+(list tape) + key+keys + zet+@ + ken+@ == ^- @t - =+ non=(turn (rip 2 (shaw zet 128 ken)) |=(a=@ ~(x ne a))) + =+ non=(turn (rip 2 (shaw zet 128 ken)) |=(a+@ ~(x ne a))) =+ tim=(slag 2 (scow %ui (unt zet))) =+ sky=(crip :(weld (urle (trip sec.con.key)) "&" (urle (trip sec.acc.key)))) =+ ^= bas ^- tape =+ ^= hds - %- reel :_ |=([p=tape q=tape] :(weld p "&" q)) + %- reel :_ |=({p+tape q+tape} :(weld p "&" q)) %- sort :_ aor %- weld :- pas ^- (list tape) @@ -69,27 +69,27 @@ == :: ++ valve :: produce request - |= $: med=meth - [rus=tape quy=quay] - key=keys - est=time - eny=@ + |= $: med+meth + {rus+tape quy+quay} + key+keys + est+time + eny+@ == ^- hiss =+ url="https://api.twitter.com/1.1{rus}.json" - =+ req=|=(a=tape (scan a auri:epur)) + =+ req=|=(a+tape (scan a auri:epur)) =+ ^= help - |= quy=(list ,[tape tape]) + |= quy+(list {tape tape}) ^- (list tape) %+ turn quy - |= a=[p=tape q=tape] + |= a+{p+tape q+tape} :(weld (urle p.a) "=" (urle q.a)) - =+ tan=(turn quy |=([p=@t q=@t] [(trip p) (trip q)])) - =+ har=(help (turn tan |=(p=[p=tape q=tape] [p.p (urle q.p)]))) + =+ tan=(turn quy |=({p+@t q+@t} [(trip p) (trip q)])) + =+ har=(help (turn tan |=(p+{p+tape q+tape} [p.p (urle q.p)]))) =+ hab=(help tan) - =+ lav=(reel har |=([p=tape q=tape] :(weld p "&" q))) + =+ lav=(reel har |=({p+tape q+tape} :(weld p "&" q))) =+ voy=?:(=(0 (lent lav)) ~ (scag (dec (lent lav)) `tape`lav)) - =+ vab=(reel hab |=([p=tape q=tape] :(weld p "&" q))) + =+ vab=(reel hab |=({p+tape q+tape} :(weld p "&" q))) =+ vur=(crip ?:(=(0 (lent vab)) ~ (scag (dec (lent vab)) `tape`vab))) =+ ^= head %- ~(gas by *math) @@ -109,17 +109,17 @@ ++ twip :: response printers |% ++ mean - |= [msg=@t num=@ud] ^- tank + |= {msg+@t num+@ud} ^- tank rose/[": " `~]^~[leaf/"Error {}" leaf/(trip msg)] -- ++ twir :: response parsers |% - ++ fasp |*([a=@tas b=*] [(gsub '-' '_' a) b]) + ++ fasp |*({a+@tas b+*} [(gsub '-' '_' a) b]) ++ user (cook crip (plus ;~(pose aln cab))) ++ mean (ot errors/(ar (ot message/so code/ni ~)) ~):jo ++ stat =+ jo - ^- $+(json (unit ,[id=@u who=@ta now=@da txt=@t])) + ^- $+(json (unit {id+@u who+@ta now+@da txt+@t})) %- ot :~ id/ni user/(ot (fasp screen-name/(su user)) ~) @@ -128,80 +128,80 @@ == ++ usel =+ jo - ^- $+(json (unit (list ,who=@ta))) + ^- $+(json (unit (list who+@ta))) =- (ot users/(ar -) ~) (ot (fasp screen-name/(su user)) ~) -- ++ twit => |% :: request structures - ++ dev ,@t :: device name - ++ gat ,@t :: grant type - ++ lat ,@t :: latitude + ++ dev @t :: device name + ++ gat @t :: grant type + ++ lat @t :: latitude ++ lid (list tid) - ++ lon ,@t :: longitude + ++ lon @t :: longitude ++ lsc (list scr) - ++ lst (list ,@t) - ++ nam ,@t :: location name - ++ pla ,@t :: place-id - ++ scr ,@t :: screen name - ++ slu ,@t :: category name - ++ tid ,@u - ++ tok ,@t :: oauth token - ++ url ,@t :: callback url + ++ lst (list @t) + ++ nam @t :: location name + ++ pla @t :: place-id + ++ scr @t :: screen name + ++ slu @t :: category name + ++ tid @u + ++ tok @t :: oauth token + ++ url @t :: callback url :: - ++ at ,[%access-token p=tok] - ++ de ,[%device p=dev] - ++ fo ,[%follow p=lid] - ++ gr ,[%grant-type p=gat] - ++ id ,[%id p=tid] - ++ ii ,[%'!inline' p=@t] - ++ is ,[%id p=lid] - ++ la ,[%lat p=lat] - ++ lo ,[%long p=lon] - ++ na ,[%name p=lid] - ++ oa ,[%oauth-callback p=url] - ++ os ,[%source-screen-name p=scr] - ++ pl ,[%place-id p=pla] - ++ qq ,[%q p=@t] - ++ sc ,[%screen-name p=scr] + ++ at {$access-token p+tok} + ++ de {$device p+dev} + ++ fo {$follow p+lid} + ++ gr {$grant-type p+gat} + ++ id {$id p+tid} + ++ ii {$'!inline' p+@t} + ++ is {$id p+lid} + ++ la {$lat p+lat} + ++ lo {$long p+lon} + ++ na {$name p+lid} + ++ oa {$oauth-callback p+url} + ++ os {$source-screen-name p+scr} + ++ pl {$place-id p+pla} + ++ qq {$q p+@t} + ++ sc {$screen-name p+scr} ++ sd ?(ui sc) - ++ ss ,[%screen-name p=lsc] - ++ sl ,[%slug p=slu] - ++ si ,[%source-id p=tid] - ++ st ,[%status p=@t] - ++ te ,[%text p=@t] - ++ ti ,[%target-id p=tid] - ++ ts ,[%target-screen-name p=scr] - ++ tr ,[%track p=lst] - ++ ur ,[%url p=url] - ++ ui ,[%user-id p=tid] - ++ us ,[%user-id p=lid] + ++ ss {$screen-name p+lsc} + ++ sl {$slug p+slu} + ++ si {$source-id p+tid} + ++ st {$status p+@t} + ++ te {$text p+@t} + ++ ti {$target-id p+tid} + ++ ts {$target-screen-name p+scr} + ++ tr {$track p+lst} + ++ ur {$url p+url} + ++ ui {$user-id p+tid} + ++ us {$user-id p+lid} -- - |_ [key=keys est=time eny=@uw] + |_ {key+keys est+time eny+@uw} ++ lutt |=(@ `@t`(rsh 3 2 (scot %ui +<))) ++ llsc |= (list scr) - (roll +< |=([p=scr q=@t] (cat 3 (cat 3 q ',') p))) + (roll +< |=({p+scr q+@t} (cat 3 (cat 3 q ',') p))) :: ++ llst - |= (list ,@t) - (roll +< |=([p=@t q=@t] (cat 3 (cat 3 q ',') p))) + |= (list @t) + (roll +< |=({p+@t q+@t} (cat 3 (cat 3 q ',') p))) :: ++ llid |= (list tid) - (roll +< |=([p=tid q=@t] (cat 3 (cat 3 q ',') (lutt p)))) + (roll +< |=({p+tid q+@t} (cat 3 (cat 3 q ',') (lutt p)))) :: ++ mold :: construct request - |* [med=meth pax=path a=$+(* *)] - |= [args=a quy=quay] + |* {med+meth pax+path a+$+(* *)} + |= {args+a quy+quay} (valve med (cowl pax args quy) key est eny) :: ++ cowl :: handle parameters - |= $: pax=path - ban=(list ,[p=@t q=?(@ (list ,@))]) - quy=quay + |= $: pax+path + ban+(list {p+@t q+?(@ (list @))}) + quy+quay == - ^- [path quay] + ^- {path quay} ?~ ban [(fass pax) quy] ?: =('!inline' p.i.ban) @@ -210,335 +210,335 @@ !! :- (fass pax) %+ welp quy - %+ turn `(list ,[p=@t q=?(@ (list ,@))])`ban - |= [p=@t q=?(@ (list ,@))] - ^- [@t @t] + %+ turn `(list {p+@t q+?(@ (list @))})`ban + |= {p+@t q+?(@ (list @))} + ^- {@t @t} :- (gsub '-' '_' p) ?@ q ?- p - ?(%id %source-id %target-id %user-id) (lutt q) + ?($id $source-id $target-id $user-id) (lutt q) @ `@t`q == ?- p - ?(%follow %id %name %user-id) (llid q) - %track (llst q) - %screen-name (llsc q) + ?($follow $id $name $user-id) (llid q) + $track (llst q) + $screen-name (llsc q) * !! == :: ++ stat-ment - (mold %get /statuses/mentions-timeline ,~) + (mold %get /statuses/mentions-timeline $~) :: ++ stat-user - (mold %get /statuses/user-timeline ,[sd ~]) + (mold %get /statuses/user-timeline {sd $~}) :: ++ stat-home - (mold %get /statuses/home-timeline ,~) + (mold %get /statuses/home-timeline $~) :: ++ stat-retw - (mold %get /statuses/retweets-of-me ,~) + (mold %get /statuses/retweets-of-me $~) :: ++ stat-rets-iddd - (mold %get /statuses/retweets ,[ii ~]) + (mold %get /statuses/retweets {ii $~}) :: ++ stat-show - (mold %get /statuses/show ,[id ~]) + (mold %get /statuses/show {id $~}) :: ++ stat-dest-iddd - (mold %post /statuses/destroy ,[ii ~]) + (mold %post /statuses/destroy {ii $~}) :: ++ stat-upda - (mold %post /statuses/update ,[st ~]) + (mold %post /statuses/update {st $~}) :: ++ stat-retw-iddd - (mold %post /statuses/retweet ,[ii ~]) + (mold %post /statuses/retweet {ii $~}) :: ++ stat-oemb-iddd - (mold %get /statuses/oembed ,[id ~]) + (mold %get /statuses/oembed {id $~}) :: ++ stat-oemb-urll - (mold %get /statuses/oembed ,[ur ~]) + (mold %get /statuses/oembed {ur $~}) :: ++ stat-retw-idss - (mold %get /statuses/retweeters/ids ,[id ~]) + (mold %get /statuses/retweeters/ids {id $~}) :: ++ sear-twee - (mold %get /search/tweets ,[qq ~]) + (mold %get /search/tweets {qq $~}) :: ++ stat-filt-foll - (mold %post /statuses/filter ,[?(fo tr) ~]) + (mold %post /statuses/filter {?(fo tr) $~}) :: ++ stat-samp - (mold %get /statuses/sample ,~) + (mold %get /statuses/sample $~) :: ++ stat-fire - (mold %get /statuses/firehose ,~) + (mold %get /statuses/firehose $~) :: ++ user - (mold %get /user ,~) + (mold %get /user $~) :: ++ site - (mold %get /site ,[fo ~]) + (mold %get /site {fo $~}) :: ++ dire - (mold %get /direct-messages ,~) + (mold %get /direct-messages $~) :: ++ dire-sent - (mold %get /direct-messages/sent ,~) + (mold %get /direct-messages/sent $~) :: ++ dire-show - (mold %get /direct-messages/show ,[id ~]) + (mold %get /direct-messages/show {id $~}) :: ++ dire-dest - (mold %post /direct-messages/destroy ,[id ~]) + (mold %post /direct-messages/destroy {id $~}) :: ++ dire-neww - (mold %post /direct-messages/new ,[sd te ~]) + (mold %post /direct-messages/new {sd te $~}) :: ++ frie-nore-idss - (mold %get /friendships/no-retweets/ids ,~) + (mold %get /friendships/no-retweets/ids $~) :: ++ frie-idss - (mold %get /friends/ids ,[sd ~]) + (mold %get /friends/ids {sd $~}) :: ++ foll-idss - (mold %get /followers/ids ,[sd ~]) + (mold %get /followers/ids {sd $~}) :: ++ frie-inco - (mold %get /friendships/incoming ,~) + (mold %get /friendships/incoming $~) :: ++ frie-outg - (mold %get /friendships/outgoing ,~) + (mold %get /friendships/outgoing $~) :: ++ frie-crea - (mold %post /friendships/create ,[sd ~]) + (mold %post /friendships/create {sd $~}) :: ++ frie-dest - (mold %post /friendships/destroy ,[sd ~]) + (mold %post /friendships/destroy {sd $~}) :: ++ frie-upda - (mold %post /friendships/update ,[sd ~]) + (mold %post /friendships/update {sd $~}) :: ++ frie-show - (mold %get /friendships/show ,[?(si os) ?(ti ts) ~]) + (mold %get /friendships/show {?(si os) ?(ti ts) $~}) :: ++ frie-list - (mold %get /friends/list ,[sd ~]) + (mold %get /friends/list {sd $~}) :: ++ foll-list - (mold %get /followers/list ,[sd ~]) + (mold %get /followers/list {sd $~}) :: ++ frie-look - (mold %get /friendships/lookup ,[?(us ss) ~]) + (mold %get /friendships/lookup {?(us ss) $~}) :: ++ acco-sett-gett - (mold %get /account/settings ,~) + (mold %get /account/settings $~) :: ++ acco-veri - (mold %get /account/verify-credentials ,~) + (mold %get /account/verify-credentials $~) :: ++ acco-sett-post - (mold %post /account/settings ,~) + (mold %post /account/settings $~) :: ++ acco-upda-deli - (mold %post /account/update-delivery-device ,[de ~]) + (mold %post /account/update-delivery-device {de $~}) :: ++ acco-upda-prof - (mold %post /account/update-profile ,~) + (mold %post /account/update-profile $~) :: ++ acco-upda-prof-back - (mold %post /account/update-profile-background-image ,~) + (mold %post /account/update-profile-background-image $~) :: ++ acco-upda-prof-colo - (mold %post /account/update-profile-colors ,~) + (mold %post /account/update-profile-colors $~) :: ++ bloc-list - (mold %get /blocks/list ,~) + (mold %get /blocks/list $~) :: ++ bloc-idss - (mold %get /blocks/ids ,~) + (mold %get /blocks/ids $~) :: ++ bloc-crea - (mold %post /blocks/create ,[sd ~]) + (mold %post /blocks/create {sd $~}) :: ++ bloc-dest - (mold %post /blocks/destroy ,[sd ~]) + (mold %post /blocks/destroy {sd $~}) :: ++ user-look - (mold %get /users/lookup ,[?(us ss) ~]) + (mold %get /users/lookup {?(us ss) $~}) :: ++ user-show - (mold %get /users/show ,[sd ~]) + (mold %get /users/show {sd $~}) :: ++ user-sear - (mold %get /users/search ,[qq ~]) + (mold %get /users/search {qq $~}) :: ++ user-cont-tees - (mold %get /users/contributees ,[sd ~]) + (mold %get /users/contributees {sd $~}) :: ++ user-cont-tors - (mold %get /users/contributors ,[sd ~]) + (mold %get /users/contributors {sd $~}) :: ++ acco-remo - (mold %post /account/remove-profile-banner ,~) + (mold %post /account/remove-profile-banner $~) :: ++ user-prof - (mold %get /users/profile-banner ,[sd ~]) + (mold %get /users/profile-banner {sd $~}) :: ++ mute-user-crea - (mold %post /mutes/users/create ,[sd ~]) + (mold %post /mutes/users/create {sd $~}) :: ++ mute-user-dest - (mold %post /mutes/users/destroy ,[sd ~]) + (mold %post /mutes/users/destroy {sd $~}) :: ++ mute-user-idss - (mold %get /mutes/users/ids ,~) + (mold %get /mutes/users/ids $~) :: ++ mute-user-list - (mold %get /mutes/users/list ,~) + (mold %get /mutes/users/list $~) :: ++ user-sugg-slug - (mold %get /users/suggestions ,[sl ~]) + (mold %get /users/suggestions {sl $~}) :: ++ user-sugg - (mold %get /users/suggestions ,~) + (mold %get /users/suggestions $~) :: ++ favo-list - (mold %get /favorites/list ,~) + (mold %get /favorites/list $~) :: ++ favo-dest - (mold %post /favorites/destroy ,[id ~]) + (mold %post /favorites/destroy {id $~}) :: ++ favo-crea - (mold %post /favorites/create ,[id ~]) + (mold %post /favorites/create {id $~}) :: ++ list-list - (mold %get /lists/list ,~) + (mold %get /lists/list $~) :: ++ list-stat - (mold %get /lists/statuses ,~) + (mold %get /lists/statuses $~) :: ++ list-memb-dest - (mold %post /lists/members/destroy ,~) + (mold %post /lists/members/destroy $~) :: ++ list-memb-hips - (mold %get /lists/memberships ,[sd ~]) + (mold %get /lists/memberships {sd $~}) :: ++ list-subs-bers - (mold %get /lists/subscribers ,~) + (mold %get /lists/subscribers $~) :: ++ list-subs-crea - (mold %post /lists/subscribers/create ,~) + (mold %post /lists/subscribers/create $~) :: ++ list-subs-show - (mold %get /lists/subscribers/show ,[sd ~]) + (mold %get /lists/subscribers/show {sd $~}) :: ++ list-subs-dest - (mold %post /lists/subscribers/destroy ,~) + (mold %post /lists/subscribers/destroy $~) :: ++ list-memb-crea-alll - (mold %post /lists/members/create-all ,[?(us ss) ~]) + (mold %post /lists/members/create-all {?(us ss) $~}) :: ++ list-memb-show - (mold %get /lists/members/show ,[sd ~]) + (mold %get /lists/members/show {sd $~}) :: ++ list-memb-bers - (mold %get /lists/members ,~) + (mold %get /lists/members $~) :: ++ list-memb-crea - (mold %post /lists/members/create ,[sd ~]) + (mold %post /lists/members/create {sd $~}) :: ++ list-dest - (mold %post /lists/destroy ,~) + (mold %post /lists/destroy $~) :: ++ list-upda - (mold %post /lists/update ,~) + (mold %post /lists/update $~) :: ++ list-crea - (mold %post /lists/create ,[na ~]) + (mold %post /lists/create {na $~}) :: ++ list-show - (mold %get /lists/show ,~) + (mold %get /lists/show $~) :: ++ list-subs-ions - (mold %get /lists/subscriptions ,[sd ~]) + (mold %get /lists/subscriptions {sd $~}) :: ++ list-memb-dest-alll - (mold %post /lists/members/destroy-all ,[?(us ss) ~]) + (mold %post /lists/members/destroy-all {?(us ss) $~}) :: ++ list-owne - (mold %get /lists/ownerships ,[sd ~]) + (mold %get /lists/ownerships {sd $~}) :: ++ save-list - (mold %get /saved-searches/list ,~) + (mold %get /saved-searches/list $~) :: ++ save-show-iddd - (mold %get /saved-searches/show ,[ii ~]) + (mold %get /saved-searches/show {ii $~}) :: ++ save-crea - (mold %post /saved-searches/create ,[qq ~]) + (mold %post /saved-searches/create {qq $~}) :: ++ save-dest-iddd - (mold %post /saved-searches/destroy ,[ii ~]) + (mold %post /saved-searches/destroy {ii $~}) :: ++ geoo-iddd-plac - (mold %get /geo/id ,[ii ~]) + (mold %get /geo/id {ii $~}) :: ++ geoo-reve - (mold %get /geo/reverse-geocode ,[la lo ~]) + (mold %get /geo/reverse-geocode {la lo $~}) :: ++ geoo-sear - (mold %get /geo/search ,~) + (mold %get /geo/search $~) :: ++ geoo-simi - (mold %get /geo/similar-places ,[la lo na ~]) + (mold %get /geo/similar-places {la lo na $~}) :: ++ tren-plac - (mold %get /trends/place ,[id ~]) + (mold %get /trends/place {id $~}) :: ++ tren-avai - (mold %get /trends/available ,~) + (mold %get /trends/available $~) :: ++ tren-clos - (mold %get /trends/closest ,[la lo ~]) + (mold %get /trends/closest {la lo $~}) :: ++ user-repo - (mold %post /users/report-spam ,[sd ~]) + (mold %post /users/report-spam {sd $~}) :: ++ oaut-auth-cate - (mold %get /oauth/authenticate ,~) + (mold %get /oauth/authenticate $~) :: ++ oaut-auth-rize - (mold %get /oauth/authorize ,~) + (mold %get /oauth/authorize $~) :: ++ oaut-acce - (mold %post /oauth/access-token ,~) + (mold %post /oauth/access-token $~) :: ++ oaut-requ - (mold %post /oauth/request-token ,[oa ~]) + (mold %post /oauth/request-token {oa $~}) :: ++ oaut-toke - (mold %post /oauth2/token ,[gr ~]) + (mold %post /oauth2/token {gr $~}) :: ++ oaut-inva - (mold %post /oauth2/invalidate-token ,[at ~]) + (mold %post /oauth2/invalidate-token {at $~}) :: ++ help-conf - (mold %get /help/configuration ,~) + (mold %get /help/configuration $~) :: ++ help-lang - (mold %get /help/languages ,~) + (mold %get /help/languages $~) :: ++ help-priv - (mold %get /help/privacy ,~) + (mold %get /help/privacy $~) :: ++ help-toss - (mold %get /help/tos ,~) + (mold %get /help/tos $~) :: ++ appl-rate - (mold %get /application/rate-limit-status ,~) + (mold %get /application/rate-limit-status $~) :: ++ stat-look - (mold %get /statuses/lookup ,[us ~]) + (mold %get /statuses/lookup {us $~}) -- -- diff --git a/sur/twitter.hoon b/sur/twitter.hoon index bd3447fbec..bdc6e38464 100644 --- a/sur/twitter.hoon +++ b/sur/twitter.hoon @@ -1,16 +1,16 @@ |% -++ twit-do => twit ,[p=span q=command] :: user and action -++ twit-stat ,[id=@u who=@ta now=@da txt=@t] :: recieved tweet +++ twit-do => twit {p+span q+command} :: user and action +++ twit-stat {id+@u who+@ta now+@da txt+@t} :: received tweet ++ twit |% ++ keys :: twitter-key type - $: con=[tok=@t sec=@t] :: user key pair - acc=[tok=@t sec=@t] :: app key pair + $: con+{tok+@t sec+@t} :: user key pair + acc+{tok+@t sec+@t} :: app key pair == :: ++ command :: poke action - $% [%auth p=keys] :: set API keys - [%post p=@uvI q=cord] :: post a tweet + $% {$auth p+keys} :: set API keys + {$post p+@uvI q+cord} :: post a tweet == -- --