Merge branch 'test' of https://github.com/urbit/urbit into test

Conflicts:
	urb/urbit.pill
	urb/zod/base/ape/hood/core.hook
	urb/zod/base/lib/helm/core.hook
This commit is contained in:
Philip C Monk 2015-06-03 17:31:37 -04:00
commit 1357ce6198
31 changed files with 456 additions and 443 deletions

View File

@ -6,13 +6,8 @@
/- *talk, *bit-api /- *talk, *bit-api
/+ talk, sole, http, mean /+ talk, sole, http, mean
!: !:
:::: sivtyv-barnel :::: sivtyv-barnel
:: be sure to have oauth2-code markk :: be sure to have oauth2-code markk
|% |%
++ axle ++ axle
@ -86,7 +81,7 @@ $: cred=(unit ,[app-secret=@t client-id=@t])
:- %- publish :- %- publish
:~ [%lin & 'secret and client id saved successfully'] :~ [%lin & 'secret and client id saved successfully']
[%lin & 'please click on the url below to continue authentication'] [%lin & 'please click on the url below to continue authentication']
[%url prl] [%url prl ~]
== ==
~ ~
:: ::

View File

@ -124,12 +124,12 @@ $% [%diff %json json]
== ==
-- --
!: !:
|_ [hid=hide vat=axle] |_ [bowl vat=axle]
:: ::
::++ prep ,_`. ::++ prep ,_`.
:: ::
++ peer ++ peer
|= [[ost=bone you=ship] pax=path] |= pax=path
^- [(list move) _+>.$] ^- [(list move) _+>.$]
:_ +>.$ :_ +>.$
=+ lis=(~(tap by insts.vat)) =+ lis=(~(tap by insts.vat))
@ -137,12 +137,12 @@ $% [%diff %json json]
:: ::
++ spam ++ spam
|= jon=json |= jon=json
%+ turn (~(tap by sup.hid)) %+ turn (~(tap by sup))
|= [sub=bone @ pax=path] |= [sub=bone @ pax=path]
^- move ^- move
[sub %diff %json jon] [sub %diff %json jon]
++ httpreq ++ httpreq
|= $: ost=bone pour-path=wire |= $: pour-path=wire
domain=(list cord) end-point=path domain=(list cord) end-point=path
req-type=$?(%get %delt [%post json]) headers=math req-type=$?(%get %delt [%post json]) headers=math
queries=quay queries=quay
@ -173,7 +173,7 @@ $% [%diff %json json]
== ==
:: ::
++ poke-cloud-auth ++ poke-cloud-auth
|= [[ost=bone you=ship] [cde=cord typ=cord]] |= [cde=cord typ=cord]
^- [(list move) _+>.$] ^- [(list move) _+>.$]
?: =(%do typ) ?: =(%do typ)
=. authc.do.auth.vat =. authc.do.auth.vat
@ -182,11 +182,11 @@ $% [%diff %json json]
=. access.gce.toke.vat =. access.gce.toke.vat
cde cde
:_ +>.$ :_ +>.$
:- (list-instances-gce ost) :- list-instances-gce
~ ~[(publish [%lin & 'successfully authenticated to gce']~)]
:: ::
++ poke-cloud-secret ++ poke-cloud-secret
|= [[ost=bone you=ship] secret=cord typ=cord] |= [secret=cord typ=cord]
^- [(list move) _+>.$] ^- [(list move) _+>.$]
?+ typ ~|(missing-platform=typ !!) ?+ typ ~|(missing-platform=typ !!)
%do %do
@ -194,24 +194,14 @@ $% [%diff %json json]
[~ secret] [~ secret]
:_ +>.$ :_ +>.$
:_ ~ :_ ~
%^ httpreq ost /auth-do %+ httpreq /auth-do
:^ ~[%digitalocean %cloud] `path`/v1/oauth/token :^ ~[%digitalocean %cloud] `path`/v1/oauth/token
[%post ~] [%post ~]
:- ~ `quay`['client_secret'^secret (auth-queries (need authc.do.auth.vat))] :- ~ `quay`['client_secret'^secret (auth-queries (need authc.do.auth.vat))]
%gce
=. client-secret.gce.auth.vat
[~ secret]
:_ +>.$
:_ ~
%^ httpreq ost /auth-gce
:^ ~[%google %cloud] `path`/v1/oauth/token
[%post ~]
:- (mo ['Content-Type' 'application/json' ~] ['Authorization' (cat 3 'Bearer ' access.do.toke.vat) ~] ~)
`quay`['client_secret'^secret %'access_token'^(need authc.gce.auth.vat) ~] ::(auth-queries (need authc.gcp.auth.vat))]
== ==
:: ::
++ receive-auth ++ receive-auth
|= [ost=bone pour-path=cord resp=httr] |= [pour-path=cord resp=httr]
^- [(list move) _+>.$] ^- [(list move) _+>.$]
~| resp ~| resp
=+ body=(rash q:(need r.resp) apex:poja) =+ body=(rash q:(need r.resp) apex:poja)
@ -223,48 +213,40 @@ $% [%diff %json json]
refresh.do.toke.vat re refresh.do.toke.vat re
== ==
:_ +>.$ :_ +>.$
:~ (list-instances-do ost) :~ list-instances-do
(publish ost our.hid [%lin & 'successfully authenticated']~) (publish [%lin & 'successfully authenticated']~)
== ==
%auth-gce
:_ +>.$
~
== ==
:: ::
++ poke-json ++ poke-json
|= [[ost=bone you=ship] act=json] |= act=json
^- [(list move) _+>.$] ^- [(list move) _+>.$]
=+ do=(need ((ot action/so ~):jo act)) =+ do=(need ((ot action/so ~):jo act))
:_ +>.$ :_ +>.$
:_ ~ :_ ~
?+ do !! ?+ do !!
%list %list
(list-instances-do ost) list-instances-do
:: ::
%create-do %create-do
(create-do ost act) (create-do act)
::
%create-gce-disk
(create-gce-disk ost act)
:: ::
%create-gce %create-gce
(create-gce ost act) (create-gce-disk act)
:: ::
?(%start %stop %reboot %delete) ?(%start %stop %reboot %delete)
=+ id=(need ((ot id/so ~):jo act)) =+ id=(need ((ot id/so ~):jo act))
(instance-action ost id do) (instance-action id do)
== ==
:: ::
++ instance-action ++ instance-action
|= $: os=bone id=@t |= $: id=@t
$= action $? $= action $?
%start %stop %reboot %delete %start %stop %reboot %delete
== == == ==
=+ d=(~(got by insts.vat) id) =+ d=(~(got by insts.vat) id)
~| 'can\'t find id' ~| 'can\'t find id'
=+ typ=?~(d !! -.d) =+ typ=?~(d !! -.d)
~& typ
~! typ
?- typ ?- typ
%do %do
=+ meth=?:(?=(%delete action) %delt [%post (jobe type/s/(convert-do action) ~)]) =+ meth=?:(?=(%delete action) %delt [%post (jobe type/s/(convert-do action) ~)])
@ -272,7 +254,7 @@ $% [%diff %json json]
~& 'do i get here?' ~& 'do i get here?'
=+ ^= req =+ ^= req
%- httpreq :* %- httpreq :*
os /action-test /action-test
~[%digitalocean %api] ~[%digitalocean %api]
?:(?=(%delt meth) /v2/droplets/[id] /v2/droplets/[id]/actions) ?:(?=(%delt meth) /v2/droplets/[id] /v2/droplets/[id]/actions)
meth meth
@ -282,11 +264,20 @@ $% [%diff %json json]
== ==
req req
%gce %gce
!! ?- action
%start
!!
%stop
!!
%reboot
!!
%delete
!!
== ==
==
:: ::
++ create-do ++ create-do
|= [os=bone act=json] |= act=json
=+ ^- deets=create-req-do =+ ^- deets=create-req-do
%- need %- need
%. act %. act
@ -302,7 +293,7 @@ $% [%diff %json json]
ipv6.deets private-networking.deets user-data.deets ipv6.deets private-networking.deets user-data.deets
== ==
%- httpreq :* %- httpreq :*
os /create-do /create-do
~[%digitalocean %api] /v2/droplets ~[%digitalocean %api] /v2/droplets
[%post body] [%post body]
%^ mo ['Content-Type' 'application/json; charset=utf-8' ~] %^ mo ['Content-Type' 'application/json; charset=utf-8' ~]
@ -312,70 +303,69 @@ $% [%diff %json json]
== ==
:: ::
++ create-gce-disk ++ create-gce-disk
|= [os=bone act=json] :: num=(unit ,@u) |= act=json :: num=(unit ,@u)
:: =. name ?~(num name ... =+ :- name=(need ((ot name/so ~):jo act))
snapshot=(need ((ot 'instance_image'^so ~):jo act))
=+ :- name=(need ((ot name/so ~):jo act)) =+ :- name=(need ((ot name/so ~):jo act))
snap=(need ((ot snap/so ~):jo act)) snap=(need ((ot snap/so ~):jo act))
=+ ^- body=json =+ ^- body=json
(jobe name/s/name %'sourceSnapshot'^s/'compute/v1/projects/urbcloud/global/snapshots/snapshot-1' ~) ::^so/snap ~) (jobe name/s/name %'sourceSnapshot'^s/'compute/v1/projects/urbcloud/global/snapshots/snapshot-1' ~) ::^so/snap ~)
%- httpreq %- httpreq
:* os /create-gce-disk :* /create-gce-disk/snapshot/name
~['googleapis' 'www'] /compute/v1/projects/urbcloud/zones/us-central1-b/disks ~['googleapis' 'www'] /compute/v1/projects/urbcloud/zones/us-central1-b/disks
[%post body] [%post body]
%^ mo ['Content-Type' 'application/json' ~] %^ mo ['Content-Type' 'application/json' ~]
['Authorization' (cat 3 'Bearer ' access.gce.toke.vat) ~] ['Authorization' (cat 3 'Bearer ' access.gce.toke.vat) ~]
~ ~
~ ~
== ==
::
++ ask-disk-status ++ ask-disk-status
|= [os=bone pax=path] ^- move |= pax=path ^- move
=+ safe=(slav %uv ?~(pax !! -.pax)) ~& 'ask disk status'
=+ :- safe=(slav %uv ?~(pax !! -.pax))
snap=?.(?=([* ^] pax) !! i.t.pax)
=+ link=(need (epur ?~(pax !! safe))) =+ link=(need (epur ?~(pax !! safe)))
=. r.link ['access_token'^access.gce.toke.vat r.link] =. r.link ['access_token'^access.gce.toke.vat r.link]
:^ os %them `wire`/disk-status :^ ost %them `wire`/disk-status/snap
`(unit hiss)`[~ [link [%get ~ ~]]] `(unit hiss)`[~ [link [%get ~ ~]]]
:: ::
++ disk-status ::receive ++ disk-status ::receive
|= [ost=bone resp=httr] |= [ins-img=@t resp=httr]
^- [(list move) _+>.$] ^- [(list move) _+>.$]
~& 'disk status called'
=+ hcode=p.resp =+ hcode=p.resp
?: =('200' hcode) ?: =('200' hcode)
~| 'did not receive 200' !! ~| 'did not receive 200' !!
=+ :-(parsed=(rash q:(need r.resp) apex:poja) jo) =+ :-(parsed=(rash q:(need r.resp) apex:poja) jo)
~& parsed
=+ :- status=(need ((ot status/so ~) parsed)) =+ :- status=(need ((ot status/so ~) parsed))
lin=(need ((ot 'selfLink'^so ~) parsed)) lin=(need ((ot 'selfLink'^so ~) parsed))
=+ link=(scot %uv lin) =+ link=(scot %uv lin)
?: =('DONE' status) ?: =('DONE' status)
~& resp ~& resp
~& 'boot disk now running, now starting instance' ~& 'boot disk now running, now starting instance'
=+ target=(need ((ot 'targetLink'^so ~):jo parsed)) =+ target=(need ((ot 'targetLink'^so ~):jo parsed))
=+ nam=-:(flop q.q:(need (epur target))) =+ nam=-:(flop q.q:(need (epur target)))
~& nam ~& nam
::(create-gce-disk ost nam 'tbd') :_ +>.$ ~[(create-gce nam ins-img)]
:- ~ +>.$
:_ +>.$ :_ +>.$
[ost %wait `path`[%check-status link ~] `@da`(add ~s3 lat.hid)]~ :: refesh every 10 sec [ost %wait `path`[%check-status link ins-img ~] `@da`(add ~s3 now)]~ :: refesh every 10 sec
:: ::
++ create-gce ++ create-gce
|= [os=bone act=json] |= [name=@t snap=@t]
=+ ^- deets=create-req-gce ~& create-gce-received/snap
%- need =+ src=(cat 3 'compute/v1/projects/urbcloud/zones/us-central1-b/disks/' name)
%. act
=> jo
%- ot
:~ project/so zone/so name/so %'machine_type'^so
==
=+ src=(cat 3 'compute/v1/projects/urbcloud/zones/us-central1-b/disks/' name.deets)
=+ ^- body=json =+ ^- body=json
%- jobe %- jobe
:~ name/s/'name-provided' 'machineType'^s/'zones/us-central1-b/machineTypes/n1-standard-1' :~ name/s/name 'machineType'^s/'zones/us-central1-b/machineTypes/n1-standard-1'
:- %disks :- %a :_ ~ :- %disks :- %a :_ ~
(jobe boot/b/%.y type/s/'persistent' source/s/src ~) (jobe boot/b/%.y type/s/'persistent' source/s/src ~)
:- 'networkInterfaces' :- %a :_ ~ :- 'networkInterfaces' :- %a :_ ~
(joba 'network' `json`[%s 'global/networks/default']) (joba 'network' `json`[%s 'global/networks/default'])
== ==
%- httpreq %- httpreq
:* `bone`os `path`/create-gce :* `path`/create-gce
`(list cord)`~['googleapis' 'www'] `path`/compute/v1/projects/urbcloud/zones/us-central1-b/'instances' `(list cord)`~['googleapis' 'www'] `path`/compute/v1/projects/urbcloud/zones/us-central1-b/'instances'
[%post `json`body] [%post `json`body]
%^ mo ['Content-Type' 'application/json' ~] %^ mo ['Content-Type' 'application/json' ~]
@ -385,24 +375,24 @@ $% [%diff %json json]
== ==
:: ::
++ wake ++ wake
|= [[ost=bone him=ship pour-path=path] ~] |= [pour-path=path ~]
?+ -.pour-path !! ?+ -.pour-path !!
%refresh-do %refresh-do
:_ +>.$ :_ +>.$
[(list-instances-do ost)]~ [list-instances-do]~
%refresh-gce %refresh-gce
:_ +>.$ :_ +>.$
[(list-instances-gce ost)]~ [list-instances-gce]~
%check-status %check-status
:_ +>.$ :_ +>.$
[(ask-disk-status ost +.pour-path)]~ [(ask-disk-status +.pour-path)]~
== ==
:: ::
++ list-instances-gce ++ list-instances-gce
|= os=bone
=+ ^= lis =+ ^= lis
:* os /list-gce :*
~[%googleapis %www] /compute/v1/projects/urbcloud/zones/['us-central1-a']/'instances' /list-gce
~[%googleapis %www] /compute/v1/projects/urbcloud/zones/['us-central1-a']/'instances'
%get ~ %get ~
^- quay ^- quay
[%'access_token' access.gce.toke.vat]~ [%'access_token' access.gce.toke.vat]~
@ -410,7 +400,7 @@ $% [%diff %json json]
(httpreq lis) (httpreq lis)
:: ::
++ receive-list-gce ++ receive-list-gce
|= [os=bone resp=httr] |= resp=httr
^- [(list move) _+>.$] ^- [(list move) _+>.$]
=+ parsed=(rash q:(need r.resp) apex:poja) :: body httr to json =+ parsed=(rash q:(need r.resp) apex:poja) :: body httr to json
=+ items=(need ((ot items/(ar some) ~):jo parsed)) =+ items=(need ((ot items/(ar some) ~):jo parsed))
@ -433,16 +423,15 @@ $% [%diff %json json]
|=(a=[@t instance] (~(has by insts.vat) id.a)) |=(a=[@t instance] (~(has by insts.vat) id.a))
=. insts.vat =. insts.vat
(~(gas by insts.vat) new) (~(gas by insts.vat) new)
=+ buf=`@da`(add ~s10 lat.hid) =+ buf=`@da`(add ~s10 now)
:_ +>.$ :_ +>.$
=+ lis=(~(tap by insts.vat)) =+ lis=(~(tap by insts.vat))
:_ (spam (state-to-json (turn lis |=(a=[@t instance] +.a)))) :_ (spam (state-to-json (turn lis |=(a=[@t instance] +.a))))
[os %wait /refresh-gce buf] [ost %wait /refresh-gce buf]
:: ::
++ list-instances-do ++ list-instances-do
|= os=bone
=+ ^= lis =+ ^= lis
:~ os /list-do :~ /list-do
~[%digitalocean %api] /v2/droplets ~[%digitalocean %api] /v2/droplets
%get %get
(mo ['Content-Type' 'application/json' ~] ['Authorization' (cat 3 'Bearer ' access.do.toke.vat) ~] ~) (mo ['Content-Type' 'application/json' ~] ['Authorization' (cat 3 'Bearer ' access.do.toke.vat) ~] ~)
@ -450,7 +439,7 @@ $% [%diff %json json]
(httpreq lis) (httpreq lis)
:: ::
++ receive-list-do ++ receive-list-do
|= [ost=bone resp=httr] |= resp=httr
^- [(list move) _+>.$] ^- [(list move) _+>.$]
=+ parsed=(rash q:(need r.resp) apex:poja) :: parse httr to json =+ parsed=(rash q:(need r.resp) apex:poja) :: parse httr to json
~| recieve-list/parsed ~| recieve-list/parsed
@ -473,28 +462,26 @@ $% [%diff %json json]
image/(ot name/so ~) ::disk/ni image/(ot name/so ~) ::disk/ni
networks/parse-ip-do networks/parse-ip-do
== ==
=+ buf=`@da`(add ~s10 lat.hid) =+ buf=`@da`(add ~s10 now)
:_ +>.$ :_ +>.$
=+ lis=(~(tap by insts.vat) *(list ,[@t instance])) =+ lis=(~(tap by insts.vat) *(list ,[@t instance]))
:_ (spam (state-to-json (turn lis |=(a=[@t instance] +.a)))) :_ (spam (state-to-json (turn lis |=(a=[@t instance] +.a))))
[ost %wait /refresh-do buf] [ost %wait /refresh-do buf]
++ thou ++ thou
|= [[ost=bone him=ship pour-path=path] resp=httr] |= [pour-path=path resp=httr]
^- [(list move) _+>.$] ^- [(list move) _+>.$]
?+ -.pour-path ~& pour-path !! ?+ -.pour-path ~& pour-path !!
%auth-do %auth-do
(receive-auth ost -.pour-path resp) (receive-auth -.pour-path resp)
:: ::
%auth-gce %auth-gce
(receive-auth ost -.pour-path resp) (receive-auth -.pour-path resp)
:: ::
%list-do %list-do
(receive-list-do ost resp) (receive-list-do resp)
%list-gce %list-gce
(receive-list-gce ost resp) (receive-list-gce resp)
:: :_ +>.$
:: ~
:: ::
$? $?
%delete %reboot %'power_cycle' %shutdown %'power_off' %delete %reboot %'power_cycle' %shutdown %'power_off'
@ -506,32 +493,34 @@ $% [%diff %json json]
:_ +>.$ ~ :_ +>.$ ~
:: ::
?(%create-gce-disk %disk-status) ?(%create-gce-disk %disk-status)
(disk-status ost resp) =+ snap=?~(t.pour-path !! i.t.pour-path)
~& snap/snap
(disk-status snap resp)
:: ::
%check-status %check-status
:_ +>.$ ~[(ask-disk-status ost +.pour-path)] :_ +>.$ ~[(ask-disk-status +.pour-path)]
:: ::
%pub %pub
:_ +>.$ ~ :_ +>.$ ~
:: ::
== ==
++ publish ++ publish
|= [ost=bone you=ship act=(list speech)] |= [act=(list speech)]
^- move ^- move
=+ ^= spchz =+ ^= spchz
%+ turn act %+ turn act
|= sp=speech |= sp=speech
=+ ^= tail =+ ^= tail
:- ^- audience :- ^- audience
:+ :- `partner`[%& our.hid ?+((clan our.hid) !! %czar %court, %duke %porch)] :+ :- `partner`[%& our ?+((clan our) !! %czar %court, %duke %porch)]
^- (pair envelope delivery) ^- (pair envelope delivery)
[`envelope`[& ~] %pending] [`envelope`[& ~] %pending]
~ ~
~ ~
`statement`[lat.hid ~ sp] `statement`[now ~ sp]
^- thought ^- thought
:- `@`(sham eny.hid tail) :- `@`(sham eny tail)
tail tail
=+ mez=[%talk-command [%publish `(list thought)`spchz]] =+ mez=[%talk-command [%publish `(list thought)`spchz]]
[ost %send /pub [our.hid %talk] %poke mez] [ost %send /pub [our %talk] %poke mez]
-- --

View File

@ -32,7 +32,8 @@
q=dojo-build :: general build q=dojo-build :: general build
== :: == ::
++ dojo-build :: one ford step ++ dojo-build :: one ford step
$% [%ex p=twig] :: hoon expression $% [%ec p=mark q=twig] :: caged expression
[%ex p=twig] :: hoon expression
[%di p=dojo-model] :: dialog [%di p=dojo-model] :: dialog
[%dv p=path] :: gate from source [%dv p=path] :: gate from source
[%fi p=dojo-filter q=dojo-source] :: filter [%fi p=dojo-filter q=dojo-source] :: filter
@ -149,7 +150,7 @@
[%volt p=(set beam) q=(cask ,*)] :: unsafe add type [%volt p=(set beam) q=(cask ,*)] :: unsafe add type
== :: == ::
++ sign :: ++ sign ::
$% [%made p=@uvH q=gage] :: $% [%made p=@uvH q=gage] ::
[%unto p=cuft] :: [%unto p=cuft] ::
== :: == ::
-- :: -- ::
@ -166,8 +167,16 @@
++ dp-command :: ++dojo-command ++ dp-command :: ++dojo-command
%+ knee *dojo-command |. ~+ %+ knee *dojo-command |. ~+
;~ pose ;~ pose
%+ stag %poke ;~ pfix bar
%+ cook
|= [a=path b=dojo-config]
^- dojo-command
[%poke [our.hid %hood] [0 %ge [0 [%cat %hood a]] b]]
;~(plug (most fas sym) dp-config)
==
::
;~ pfix col ;~ pfix col
%+ stag %poke
%+ cook %+ cook
|= [a=goal b=(each dojo-source (trel term path dojo-config))] |= [a=goal b=(each dojo-source (trel term path dojo-config))]
^- (pair goal dojo-source) ^- (pair goal dojo-source)
@ -221,9 +230,9 @@
;~ pose ;~ pose
;~(pfix lus (stag %ge dp-model-cat)) ;~(pfix lus (stag %ge dp-model-cat))
;~(pfix wut (stag %di dp-model-dog)) ;~(pfix wut (stag %di dp-model-dog))
;~(pfix pam (stag %sc dp-model-pig))
;~(pfix buc (stag %va sym)) ;~(pfix buc (stag %va sym))
(stag %ex dp-twig) (stag %ex dp-twig)
;~(pfix pam (stag %ec ;~(plug sym ;~(pfix dot dp-twig))))
(ifix [sel ser] (stag %tu (most ace dp-source))) (ifix [sel ser] (stag %tu (most ace dp-source)))
== ==
:: ::
@ -256,7 +265,6 @@
== ==
:: ::
++ dp-config :: ++dojo-config ++ dp-config :: ++dojo-config
%+ cook |=(a=dojo-config a)
;~ plug ;~ plug
(star ;~(pfix ace dp-value)) (star ;~(pfix ace dp-value))
%+ cook %+ cook
@ -338,6 +346,7 @@
|= bul=dojo-build |= bul=dojo-build
^+ [bul +>] ^+ [bul +>]
?- -.bul ?- -.bul
%ec [bul +>.$]
%ex [bul +>.$] %ex [bul +>.$]
%di =^(mod +>.$ (dy-init-model p.bul) [[%di mod] +>.$]) %di =^(mod +>.$ (dy-init-model p.bul) [[%di mod] +>.$])
%dv [bul +>.$] %dv [bul +>.$]
@ -546,7 +555,8 @@
%di [/dial (dy-silk-init-modo (dy-cage p.p.p.q.u.cud) q.p.q.u.cud)] %di [/dial (dy-silk-init-modo (dy-cage p.p.p.q.u.cud) q.p.q.u.cud)]
%ge [/gent (dy-silk-init-modo (dy-cage p.p.p.q.u.cud) q.p.q.u.cud)] %ge [/gent (dy-silk-init-modo (dy-cage p.p.p.q.u.cud) q.p.q.u.cud)]
%dv [/hand (dy-silk-device p.q.u.cud)] %dv [/hand (dy-silk-device p.q.u.cud)]
%ex [/hand [%ride p.q.u.cud [[%done ~ %$ dy-twig-head] [%reef ~]]]] %ec [/hand [%cast p.q.u.cud (dy-mare q.q.u.cud)]]
%ex [/hand (dy-mare p.q.u.cud)]
%tu :- /hand %tu :- /hand
:+ %done ~ :+ %done ~
:- %noun :- %noun
@ -557,6 +567,11 @@
(slop hed $(p.q.u.cud t.p.q.u.cud)) (slop hed $(p.q.u.cud t.p.q.u.cud))
== ==
:: ::
++ dy-mare :: build expression
|= gen=twig
^- silk
[%ride gen [[%done ~ %$ dy-twig-head] [%reef ~]]]
::
++ dy-step :: advance project ++ dy-step :: advance project
|= nex=@ud |= nex=@ud
^+ +>+> ^+ +>+>
@ -648,7 +663,9 @@
++ he-unto :: result from behn ++ he-unto :: result from behn
|= cit=cuft |= cit=cuft
^+ +> ^+ +>
?> ?=(%coup -.cit) ?. ?=(%coup -.cit)
~& [%strange-unto cit]
+>
?~ p.cit ?~ p.cit
(he-diff %txt ">=") (he-diff %txt ">=")
(he-diff %tan u.p.cit) (he-diff %tan u.p.cit)

View File

@ -55,8 +55,8 @@
~? ?=(^ saw) [%kiln-spam-lame u.saw] ~? ?=(^ saw) [%kiln-spam-lame u.saw]
[~ +>] [~ +>]
:: ::
++ coup-drum (wrap take-coup):from-drum ++ coup-drum-phat (wrap take-coup-phat):from-drum
++ diff-sole-effect-drum (wrap diff-sole-effect):from-drum ++ diff-sole-effect-drum-phat (wrap diff-sole-effect-phat):from-drum
++ from-helm ++ from-helm
=- [wrap=- *helm-work] =- [wrap=- *helm-work]
|* fun=_=>(*helm-work |=(* abet)) |* fun=_=>(*helm-work |=(* abet))
@ -80,12 +80,14 @@
:: ::
++ poke-dill-belt (wrap poke-dill-belt):from-drum ++ poke-dill-belt (wrap poke-dill-belt):from-drum
++ poke-helm-init (wrap poke-init):from-helm ++ poke-helm-init (wrap poke-init):from-helm
++ poke-hood-link (wrap poke-link):from-drum
++ poke-hood-mass (wrap poke-mass):from-helm ++ poke-hood-mass (wrap poke-mass):from-helm
++ poke-hood-sync (wrap poke-sync):from-kiln ++ poke-hood-sync (wrap poke-sync):from-kiln
++ poke-hood-unsync (wrap poke-unsync):from-kiln ++ poke-hood-unsync (wrap poke-unsync):from-kiln
++ poke-hood-unix (wrap poke-unix):from-kiln ++ poke-hood-unix (wrap poke-unix):from-kiln
++ poke-hood-verb (wrap poke-verb):from-helm ++ poke-hood-verb (wrap poke-verb):from-helm
++ poke-hood-begin (wrap poke-begin):from-helm ++ poke-hood-begin (wrap poke-begin):from-helm
++ poke-hood-invite (wrap poke-invite):from-helm
++ poke-hood-merge (wrap poke-merge):from-kiln ++ poke-hood-merge (wrap poke-merge):from-kiln
++ poke-hood-reload (wrap poke-reload):from-helm ++ poke-hood-reload (wrap poke-reload):from-helm
++ poke-hood-reset (wrap poke-reset):from-helm ++ poke-hood-reset (wrap poke-reset):from-helm
@ -100,10 +102,10 @@
++ made-kiln (wrap take-made):from-kiln ++ made-kiln (wrap take-made):from-kiln
++ init-helm |=([way=wire *] [~ +>]) ++ init-helm |=([way=wire *] [~ +>])
++ note-helm (wrap take-note):from-helm ++ note-helm (wrap take-note):from-helm
++ reap-drum (wrap reap):from-drum ++ reap-drum-phat (wrap reap-phat):from-drum
++ onto-drum (wrap take-onto):from-drum ++ onto-drum (wrap take-onto):from-drum
++ peer-drum (wrap peer):from-drum ++ peer-drum (wrap peer):from-drum
++ quit-drum (wrap quit):from-drum ++ quit-drum-phat (wrap quit-phat):from-drum
++ went-helm (wrap take-went):from-helm ++ went-helm (wrap take-went):from-helm
++ writ-kiln-sync (wrap take-writ):from-kiln ++ writ-kiln-sync (wrap take-writ):from-kiln
-- --

View File

@ -8,7 +8,7 @@
:::: :::::: interfaces :::: :::::: interfaces
!: :: :: !: :: ::
=> |% :: => |% ::
++ axle ,[eye=face gam=game] :: agent state ++ axon ,[%0 eye=face gam=game] :: agent state
++ card ,[%diff %sole-effect sole-effect] :: update ++ card ,[%diff %sole-effect sole-effect] :: update
++ face (map bone sole-share) :: console state ++ face (map bone sole-share) :: console state
++ move (pair bone card) :: cause and action ++ move (pair bone card) :: cause and action
@ -25,7 +25,7 @@
:: :: :: :: :: ::
|_ $: bowl :: system state |_ $: bowl :: system state
moz=(list move) :: pending actions moz=(list move) :: pending actions
[%0 axle] :: server state, v0 axon :: server state, v0
== :: == ::
:: :: :: :: :: ::
:::: :::::: process tools :::: :::::: process tools
@ -41,7 +41,7 @@
++ flap |=(con=bike (echo eels con)) :: update all clients ++ flap |=(con=bike (echo eels con)) :: update all clients
++ here ~(. go gam) :: game core ++ here ~(. go gam) :: game core
:: :: :: :: :: ::
:::: :::::: server logic :::: :::::: process logic
:: :: :: :: :: ::
++ fail (fect %bel ~) :: user error ++ fail (fect %bel ~) :: user error
++ fect |=(sole-effect (dish %diff %sole-effect +<)) :: update console ++ fect |=(sole-effect (dish %diff %sole-effect +<)) :: update console
@ -57,7 +57,7 @@
++ wild (flap |=(_. show:+<)) :: full update ++ wild (flap |=(_. show:+<)) :: full update
++ word |=(tape (flap |=(_+> (fect:+< txt/+>+<)))) :: ++ word |=(tape (flap |=(_+> (fect:+< txt/+>+<)))) ::
:: :: :: :: :: ::
:::: :::::: console UI :::: :::::: process UI
:: :: :: :: :: ::
++ work :: console action ++ work :: console action
|= act=sole-action :: |= act=sole-action ::
@ -77,6 +77,8 @@
:::: :::::: arvo handlers :::: :::::: arvo handlers
:: :: :: :: :: ::
++ peer-sole |=(* abet:show:seen) :: console subscribe ++ peer-sole |=(* abet:show:seen) :: console subscribe
++ prep |= (unit (pair (list move) axon)) :: update self
abet:?~(+< +> wild(+<+ +<+)) ::
++ poke-sole-action |=(sole-action abet:(work +<)) :: console input ++ poke-sole-action |=(sole-action abet:(work +<)) :: console input
++ pull-sole |=(* abet:sawn) :: console unsubscribe ++ pull-sole |=(* abet:sawn) :: console unsubscribe
-- --

View File

@ -20,7 +20,6 @@
:::: :::::: past state :::: :::::: past state
:: :: :: :: :: ::
=> |% :: => |% ::
++ agon (unit ,[(list move) axon]) :: boot argument
++ axon $%([%1 axle] [%0 axle-0]) :: all states ++ axon $%([%1 axle] [%0 axle-0]) :: all states
++ axle-0 ,[eye=face gam=game-0] :: old axle ++ axle-0 ,[eye=face gam=game-0] :: old axle
++ game-0 ,[who=? box=board boo=board] :: old game ++ game-0 ,[who=? box=board boo=board] :: old game
@ -97,6 +96,7 @@
:: :: :: :: :: ::
++ peer-sole |=(* abet:show:seen) :: console subscribe ++ peer-sole |=(* abet:show:seen) :: console subscribe
++ poke-sole-action |=(sole-action abet:(work +<)) :: console input ++ poke-sole-action |=(sole-action abet:(work +<)) :: console input
++ prep |=(agon abet:?~(+< +> (heal +<+>))) :: load state ++ prep |= (unit (pair (list move) axon)) :: update self
abet:?~(+< +> wild:(heal +<+>)) ::
++ pull-sole |=(* abet:sawn) :: console unsubscribe ++ pull-sole |=(* abet:sawn) :: console unsubscribe
-- --

View File

@ -22,7 +22,6 @@
:::: :::::: past state :::: :::::: past state
:: :: :: :: :: ::
=> |% :: => |% ::
++ agon (unit ,[(list move) axon]) :: boot argument
++ axon $%([%1 axle] [%0 axle-0]) :: all states ++ axon $%([%1 axle] [%0 axle-0]) :: all states
++ axle-0 ,[eye=face gam=game-0] :: old axle ++ axle-0 ,[eye=face gam=game-0] :: old axle
++ game-0 ,[who=? box=board boo=board] :: old game ++ game-0 ,[who=? box=board boo=board] :: old game
@ -109,7 +108,8 @@
++ peer-sole |=(* abet:show:seen) :: console subscribe ++ peer-sole |=(* abet:show:seen) :: console subscribe
++ poke-sole-action |=(sole-action abet:(work +<)) :: console input ++ poke-sole-action |=(sole-action abet:(work +<)) :: console input
++ poke-oct3-move |=(point abet:wild:(kick +<)) :: urbit move ++ poke-oct3-move |=(point abet:wild:(kick +<)) :: urbit move
++ prep |=(agon abet:?~(+< +> (heal +<+>))) :: load state ++ prep |= (unit (pair (list move) axon)) :: update self
abet:?~(+< +> wild:(heal +<+>)) ::
++ pull-oct3 |=(* abet:(hail |)) :: urbit unsubscribe ++ pull-oct3 |=(* abet:(hail |)) :: urbit unsubscribe
++ pull-sole |=(* abet:sawn) :: console unsubscribe ++ pull-sole |=(* abet:sawn) :: console unsubscribe
-- --

View File

@ -723,9 +723,11 @@
|= [inv=sole-edit buf=(list ,@c)] |= [inv=sole-edit buf=(list ,@c)]
^- (list sole-edit) ^- (list sole-edit)
?~ buf ~ ?~ buf ~
?: =(';' i.buf) =+ txt=(tufa buf)
((sh-sane-rule sh-scad) inv (tufa t.buf)) ?: =(& -:(rose txt aurf:urlp)) ~
?: =('@' i.buf) ?: =(';' -.txt)
((sh-sane-rule sh-scad) inv +.txt)
?: =('@' -.txt)
(sh-sane-chat +.buf) (sh-sane-chat +.buf)
(sh-sane-chat buf) (sh-sane-chat buf)
:: ::
@ -749,11 +751,14 @@
++ sh-pork :: parse work ++ sh-pork :: parse work
^- (unit work) ^- (unit work)
?~ buf.say.she ~ ?~ buf.say.she ~
?: =(';' -.buf.say.she) =+ txt=(tufa buf.say.she)
(rust (tufa +.buf.say.she) sh-scad) =+ rou=(rust txt aurf:urlp)
?: =('@' -.buf.say.she) ?^ rou `[%say %url u.rou]
`[%say %lin | (crip (tufa +.buf.say.she))] ?: =(';' -.txt)
`[%say %lin & (crip (tufa buf.say.she))] (rust +.txt sh-scad)
?: =('@' -.txt)
`[%say %lin | (crip +.txt)]
`[%say %lin & (crip txt)]
:: ::
++ sh-lame :: send error ++ sh-lame :: send error
|= txt=tape |= txt=tape
@ -1628,7 +1633,7 @@
^- tape ^- tape
?+ -.sep "" ?+ -.sep ""
%url %url
(earn p.sep) [':' ' ' (earf p.sep)]
:: ::
%lin %lin
=+ txt=(trip q.sep) =+ txt=(trip q.sep)
@ -1639,7 +1644,7 @@
(weld " " txt) (weld " " txt)
:: ::
%app %app
[' ' (trip p.sep)] "[{(trip p.sep)}]: {(trip q.sep)}"
== ==
-- --
:: ::

View File

@ -413,7 +413,7 @@
vix=(bex +((cut 0 [25 2] mag))) :: width of sender vix=(bex +((cut 0 [25 2] mag))) :: width of sender
tay=(cut 0 [27 5] mag) :: message type tay=(cut 0 [27 5] mag) :: message type
== ==
?> =(7 vez) ?> =(6 vez)
?> =(chk (end 0 20 (mug bod))) ?> =(chk (end 0 20 (mug bod)))
:+ [(end 3 wix bod) (cut 3 [wix vix] bod)] :+ [(end 3 wix bod) (cut 3 [wix vix] bod)]
(kins tay) (kins tay)
@ -433,7 +433,7 @@
=+ tay=(ksin q.kec) =+ tay=(ksin q.kec)
%+ mix %+ mix
%+ can 0 %+ can 0
:~ [3 7] :~ [3 6]
[20 (mug bod)] [20 (mug bod)]
[2 yax] [2 yax]
[2 qax] [2 qax]
@ -1018,7 +1018,7 @@
++ gnaw :: gnaw:am ++ gnaw :: gnaw:am
|= [kay=cape ryn=lane pac=rock] :: process packet |= [kay=cape ryn=lane pac=rock] :: process packet
^- [p=(list boon) q=fort] ^- [p=(list boon) q=fort]
?. =(7 (end 0 3 pac)) [~ fox] ?. =(6 (end 0 3 pac)) [~ fox]
=+ kec=(bite pac) =+ kec=(bite pac)
?: (goop p.p.kec) [~ fox] ?: (goop p.p.kec) [~ fox]
?. (~(has by urb.ton.fox) q.p.kec) ?. (~(has by urb.ton.fox) q.p.kec)

View File

@ -53,6 +53,7 @@
++ whir $| ~ :: wire subset ++ whir $| ~ :: wire subset
$% [%at p=hole q=whir] :: authenticated $% [%at p=hole q=whir] :: authenticated
[%ay p=span:ship q=span:,@uvH ~] :: remote duct [%ay p=span:ship q=span:,@uvH ~] :: remote duct
[%ha p=path:beak] :: GET request
[%he p=whir] :: HEAD request [%he p=whir] :: HEAD request
[%hi p=mark ~] :: outbound HTTP [%hi p=mark ~] :: outbound HTTP
[%si ~] :: response done [%si ~] :: response done
@ -605,10 +606,10 @@
:: kes (~(del by kes) hen) :: kes (~(del by kes) hen)
:: == :: ==
:: ~& eyre-them/(earn p.u.p.kyz) :: ~& eyre-them/(earn p.u.p.kyz)
%+ pass-note hi//[p.kyz] =+ wir=hi//[p.kyz]
?: ?=(%hiss p.q.kyz) ?: ?=(%hiss p.q.kyz)
[%e %meta :(slop !>(%them) !>(~) q.q.kyz)] (pass-note wir [%e %meta :(slop !>(%them) !>(~) q.q.kyz)])
(ford-req root-beak [%cast %hiss %done ~ q.kyz]) (back wir %hiss q.kyz)
:: ::
%they :: inbound response %they :: inbound response
=+ kas=(need (~(get by q.ask) p.kyz)) =+ kas=(need (~(get by q.ask) p.kyz))
@ -673,8 +674,8 @@
?+ -.tee !! ?+ -.tee !!
%ay (ames-gram (slav %p p.tee) got/~ (slav %uv q.tee) |2.sih) %ay (ames-gram (slav %p p.tee) got/~ (slav %uv q.tee) |2.sih)
%hi =+ cay=[%httr !>(`httr`p.sih)] %hi =+ cay=[%httr !>(`httr`p.sih)]
?: ?=(%httr p.tee) (give-sigh ~ cay) ?: ?=(%httr p.tee) (give-sigh %& cay)
(pass-note si/~ (ford-req root-beak [%cast p.tee %done `cay])) (back si/~ p.tee cay)
== ==
:: ::
%unto :: XX horrible %unto :: XX horrible
@ -686,8 +687,8 @@
%diff %diff
?> ?=([%of @ ^] tee) ?> ?=([%of @ ^] tee)
?. ?=(%json p.p.cuf) ?. ?=(%json p.p.cuf)
::~> %slog.`rose/[" " "[" "]"]^~[>%backing< >p.p.cuf< (sell q.p.cuf)] ::~> %slog.`%*(. >[%backing p.p.cuf %q-p-cuf]< &3.+> (sell q.p.cuf))
(back tee 0v0 %json p.cuf) (back tee %json p.cuf)
(get-rush:(ire-ix p.tee) q.tee ((hard json) q.q.p.cuf)) (get-rush:(ire-ix p.tee) q.tee ((hard json) q.q.p.cuf))
:: ::
%quit (axom tee [%mean ~]) %quit (axom tee [%mean ~])
@ -716,7 +717,7 @@
=. our (need hov) :: XX =. our (need hov) :: XX
|- ^+ ..axon |- ^+ ..axon
?- tee ?- tee
[?(%on %ay) *] ~|(e/ford/lost/-.tee !!) $|(~ [?(%on %ay) *]) ~|(e/ford/lost/tee !!)
[%si ~] (give-sigh q.sih) [%si ~] (give-sigh q.sih)
[%hi ^] [%hi ^]
?: ?=(%| -.q.sih) ?: ?=(%| -.q.sih)
@ -759,13 +760,15 @@
=^ jon ..ya ~(stat-json ya p.tee cyz) =^ jon ..ya ~(stat-json ya p.tee cyz)
$(tee q.tee, q.q.p.q.sih (add-json jon q.q.cay)) $(tee q.tee, q.q.p.q.sih (add-json jon q.q.cay))
:: ::
~ [%ha *]
:: ~& e/ford/hen :: ~& e/ford/hen
?. ?=(%& -.q.sih) ?. ?=(%& -.q.sih)
(fail 404 p.sih p.q.sih) (fail 404 p.sih p.q.sih)
=* cay p.q.sih =* cay p.q.sih
?. ?=(%mime p.cay) ?. ?=(%mime p.cay)
=- (back tee p.sih %mime cay(q.q -)) =+ bek=-:(need (tome p.tee))
=- (pass-note tee (ford-req bek [%flag p.sih -]))
=- `silk`[%cast %mime %done ~ cay(q.q -)]
?+ p.cay q.q.cay :: inject dependency long-poll ?+ p.cay q.q.cay :: inject dependency long-poll
%urb =| urb=[[%html ~] [[%head ~] marl] [[%body ~] manx marl] ~] %urb =| urb=[[%html ~] [[%head ~] marl] [[%body ~] manx marl] ~]
.*(.(urb q.q.cay) !=((add-poll p.sih urb))) .*(.(urb q.q.cay) !=((add-poll p.sih urb)))
@ -802,9 +805,8 @@
|=([him=ship gam=gram] (pass-note ~ %a %want [our him] [%e -.gam] +.gam)) |=([him=ship gam=gram] (pass-note ~ %a %want [our him] [%e -.gam] +.gam))
:: ::
++ back :: %ford bounce ++ back :: %ford bounce
|= [tea=whir dep=@uvH mar=mark cay=cage] |= [tea=whir mar=mark cay=cage]
=+ sil=`silk`[%cast mar %flag dep %done ~ cay] (pass-note tea (ford-req root-beak [%cast mar %done ~ cay]))
(pass-note tea (ford-req root-beak sil))
:: ::
++ ford-kill (pass-note ~ %f [%exec our *beak ~]) :: XX unused ++ ford-kill (pass-note ~ %f [%exec our *beak ~]) :: XX unused
++ ford-req |=([bek=beak kas=silk] [%f [%exec our bek `kas]]) ++ ford-req |=([bek=beak kas=silk] [%f [%exec our bek `kas]])
@ -812,7 +814,7 @@
++ fail ++ fail
|= [sas=@ud dep=@uvH mez=tang] |= [sas=@ud dep=@uvH mez=tang]
^+ +> ^+ +>
:: (back ~ dep %tang !>(mez)) :: tang->urb chain may be source of failure :: (back ha/~ dep %tang !>(mez)) ::tang->urb chain may be source of failure
(give-html sas ~ (add-poll dep (render-tang mez))) (give-html sas ~ (add-poll dep (render-tang mez)))
:: ::
++ give-html ++ give-html
@ -870,6 +872,7 @@
++ abet ..handle ++ abet ..handle
++ done . ++ done .
++ teba |*(a=$+(* ..handle) |*(b=* %_(done ..handle (a b)))) ++ teba |*(a=$+(* ..handle) |*(b=* %_(done ..handle (a b))))
++ back (teba ^back)
++ give-html (teba ^give-html) ++ give-html (teba ^give-html)
++ give-thou (teba ^give-thou) ++ give-thou (teba ^give-thou)
++ give-json (teba ^give-json) ++ give-json (teba ^give-json)
@ -1098,7 +1101,8 @@
?(%beam %spur) ?(%beam %spur)
=+ ext=(fall p.pok %urb) =+ ext=(fall p.pok %urb)
=+ bem=?-(-.hem %beam p.hem, %spur [root-beak p.hem]) =+ bem=?-(-.hem %beam p.hem, %spur [root-beak p.hem])
=+ wir=?+(mef !! %get ~, %head [%he ~]) =+ wir=`whir`[%ha (tope -.bem ~)]
=. wir ?+(mef !! %get wir, %head [%he wir])
~| bad-beam/q.bem ~| bad-beam/q.bem
?< =([~ 0] (sky %cw (tope bem(+ ~, r [%da now])))) ?< =([~ 0] (sky %cw (tope bem(+ ~, r [%da now]))))
=- ?.(aut [%& %| -] [%| (pass-note -)]) :: XX properly =- ?.(aut [%& %| -] [%| (pass-note -)]) :: XX properly
@ -1124,8 +1128,8 @@
=^ orx ..ya ?:(is-anon new-view:for-client [(need grab-oryx) ..ya]) =^ orx ..ya ?:(is-anon new-view:for-client [(need grab-oryx) ..ya])
=+ [vew=(ire-ix (oryx-to-ixor orx)) cay=[%json !>(`json`s.hem)]] =+ [vew=(ire-ix (oryx-to-ixor orx)) cay=[%json !>(`json`s.hem)]]
?: ?=(%json q.hem) ((teba new-mess.vew) p.hem r.hem cay) ?: ?=(%json q.hem) ((teba new-mess.vew) p.hem r.hem cay)
%+ pass-note [%to (oryx-to-ixor orx) (scot %p p.p.hem) q.p.hem r.hem] %+ back to/[(oryx-to-ixor orx) (scot %p p.p.hem) q.p.hem r.hem]
(ford-req root-beak [%cast q.hem %done ~ cay]) [q.hem cay]
:: ::
%poll %poll
?: ?=([~ %js] p.pok) :: XX treat non-json cases? ?: ?=([~ %js] p.pok) :: XX treat non-json cases?

View File

@ -57,6 +57,7 @@
++ calx :: concrete cache line ++ calx :: concrete cache line
$% [%hood p=calm q=(pair beam cage) r=hood] :: compile $% [%hood p=calm q=(pair beam cage) r=hood] :: compile
[%bake p=calm q=(trel mark beam heel) r=(unit vase)]:: load [%bake p=calm q=(trel mark beam heel) r=(unit vase)]:: load
[%lilt p=calm q=arch r=(jug mark mark)] :: translation graph
[%slit p=calm q=[p=type q=type] r=type] :: slam type [%slit p=calm q=[p=type q=type] r=type] :: slam type
[%slim p=calm q=[p=type q=twig] r=(pair type nock)]:: mint [%slim p=calm q=[p=type q=twig] r=(pair type nock)]:: mint
[%slap p=calm q=[p=vase q=twig] r=vase] :: compute [%slap p=calm q=[p=vase q=twig] r=vase] :: compute
@ -81,6 +82,7 @@
?+ sem !! ?+ sem !!
%hood ?>(?=(%hood -.cax) r.cax) %hood ?>(?=(%hood -.cax) r.cax)
%bake ?>(?=(%bake -.cax) r.cax) %bake ?>(?=(%bake -.cax) r.cax)
%lilt ?>(?=(%lilt -.cax) r.cax)
%slap ?>(?=(%slap -.cax) r.cax) %slap ?>(?=(%slap -.cax) r.cax)
%slam ?>(?=(%slam -.cax) r.cax) %slam ?>(?=(%slam -.cax) r.cax)
%slim ?>(?=(%slim -.cax) r.cax) %slim ?>(?=(%slim -.cax) r.cax)
@ -437,9 +439,9 @@
%+ cope %+ cope
|- ^- (bolt (list (pair gage gage))) |- ^- (bolt (list (pair gage gage)))
?~ p.gag (fine cof ~) ?~ p.gag (fine cof ~)
%+ cope (fret ^$(gag q.i.p.gag)) %+ cope (fret ^$(gag q.i.p.gag, cof cof))
|= [cof=cafe val=gage] |= [cof=cafe val=gage]
%+ cope ^$(p.gag t.p.gag) %+ cope ^$(p.gag t.p.gag, cof cof)
|= [cof=cafe rex=(list (pair gage gage))] |= [cof=cafe rex=(list (pair gage gage))]
(fine cof [[p.i.p.gag val] rex]) (fine cof [[p.i.p.gag val] rex])
|= [cof=cafe rex=(list (pair gage gage))] |= [cof=cafe rex=(list (pair gage gage))]
@ -828,18 +830,24 @@
$(yom t.yom, axe (peg axe 3)) $(yom t.yom, axe (peg axe 3))
:: ::
++ lace :: load and check ++ lace :: load and check
|= [cof=cafe for=mark bem=beam arg=heel] |= [cof=cafe for=mark bem=beam]
^- (bolt (unit vase)) ^- (bolt (unit (burg heel vase)))
%+ cope (lend cof bem) %+ cope (lend cof bem)
|= [cof=cafe arc=arch] |= [cof=cafe arc=arch]
?^ q.arc ?^ q.arc
(cope (cope (liar cof bem) (lake for)) (fest (norm ska bem))) %+ (fest (norm ska bem)) cof
?: (~(has by r.arc) %hook) |=([cof=cafe arg=heel] (cope (liar cof bem) (lake for)))
%+ cope (fade cof %hook bem) ?. (~(has by r.arc) %hook)
|= [cof=cafe hyd=hood] (flue cof)
%+ cope (cope (abut:(meow bem arg) cof hyd) (lake for)) %+ cope (lend cof bem(s [%hook s.bem]))
(fest (norm ska bem)) |= [cof=cafe arc=arch]
(flue cof) ?~ q.arc
(flue cof)
%+ (fest (norm ska bem(s [%hook s.bem]))) cof
|= [cof=cafe arg=heel]
%+ cope (fade cof %hook bem)
|= [cof=cafe hyd=hood]
(cope (abut:(meow bem arg) cof hyd) (lake for))
:: ::
++ lake :: check/coerce ++ lake :: check/coerce
|= for=mark |= for=mark
@ -912,6 +920,7 @@
^- (bolt arch) ^- (bolt arch)
=+ von=(save ~ %cy bem) =+ von=(save ~ %cy bem)
?~ von [p=cof q=[%1 [%y bem ~] ~ ~]] ?~ von [p=cof q=[%1 [%y bem ~] ~ ~]]
:: %+ flag (norm ska bem)
(fine cof ((hard arch) q.q:(need u.von))) (fine cof ((hard arch) q.q:(need u.von)))
:: ::
++ liar :: load vase ++ liar :: load vase
@ -925,40 +934,73 @@
(fine cof q.u.u.von) (fine cof q.u.u.von)
:: ::
++ lily :: translation targets ++ lily :: translation targets
|= [cof=cafe for=mark] |= [cof=cafe for=mark] ^- (bolt (set ,@tas))
^- (bolt (list ,@tas)) %+ cope (lilt cof)
|= [cof=cafe lil=(jug mark mark)]
(fine cof (~(get ju lil) for))
::
++ lilt
|= cof=cafe ^- (bolt (jug mark mark))
%+ cope (lend cof [bek /mar])
|= [cof=cafe arc=arch]
%+ (clef %lilt) (fine cof arc)
|= [cof=cafe arc=arch]
:: =- =+((cope - |=([cafe lil=(jug mark mark)] ~&(lil=lil (flue cof)))) +<)
=+ all=(~(tap by r.arc))
~! all
|- ^- (bolt (jug mark mark))
?~ all (flue cof)
%+ cope $(cof cof, all t.all)
|= [cof=cafe lil=(jug mark mark)]
=* for p.i.all
=+ raf=(fang cof for) =+ raf=(fang cof for)
?: =(%2 -.q.raf) (flue cof) ?: =(%2 -.q.raf) (fine cof lil)
%+ cope raf %+ cope raf
|= [cof=cafe vax=vase] |= [cof=cafe vax=vase]
%+ fine cof %+ fine cof
%- ~(gas ju lil)
~| weg=(jam 3 p.vax)
%+ weld %+ weld
^- (list ,@tas) ^- (list ,[mark mark])
?. (slob %garb p.vax) ~ ?. (slob %grab p.vax) ~
=+ gav=((soft (list ,@tas)) q:(slap vax [%cnzy %garb])) =+ gab=(slap vax [%cnzy %grab])
?~(gav ~ u.gav) :: =+ opt=(skip (sloe p.gap) |=(fro=mark =(fro %noun)))
(turn (sloe p.gab) |=(fro=mark [fro for]))
?. (slob %grow p.vax) ~ ?. (slob %grow p.vax) ~
=+ gow=(slap vax [%cnzy %grow]) =+ gow=(slap vax [%cnzy %grow])
(sort (sloe p.gow) aor) (turn (sloe p.gow) |=(too=mark [for too]))
:: ::
++ lima :: load at depth ++ lima :: load at depth
|= [cof=cafe for=mark bem=beam arg=heel] |= [cof=cafe for=mark bem=beam arg=heel]
%+ (clef %bake) [p=cof q=[%0 p=[bem `~] q=[for bem arg]]] %+ (clef %bake) [p=cof q=[%0 p=[bem `~] q=[for bem arg]]]
|= [cof=cafe for=mark bem=beam arg=heel] |= [cof=cafe for=mark bem=beam arg=heel]
^- (bolt (unit vase)) ^- (bolt (unit vase))
%+ cope (lend cof bem) %+ cope
|= [cof=cafe arc=arch] %+ cope (lend cof bem)
^- (bolt (unit vase)) |= [cof=cafe arc=arch] ^- (bolt (map mark (burg heel vase)))
?: (~(has by r.arc) for) ?~ r.arc (flue cof)
(lace cof for bem(s [for s.bem]) arg) %+ cope $(r.arc l.r.arc)
=+ haz=(turn (~(tap by r.arc) ~) |=([a=@tas b=~] a)) |= [cof=cafe lam=(map mark (burg heel vase))]
?~ haz (flue cof) %+ cope ^$(r.arc r.r.arc, cof cof)
%+ cope (lion cof for haz) |= [cof=cafe ram=(map mark (burg heel vase))]
=. for p.n.r.arc
%+ cope
?. ((sane %tas) for) (flue cof)
(lace cof for bem(s [for s.bem]))
|= [cof=cafe nod=(unit (burg heel vase))]
%+ fine cof
?^(nod [[for u.nod] lam ram] (~(uni by lam) ram))
|= [cof=cafe mal=(map mark (burg heel vase))]
=+ lit=(~(get by mal) for)
?^ lit
(cope (u.lit cof arg) (fest bem))
=+ opt=(sa (turn (~(tap by mal)) head)) :: XX asymptotics
%+ cope (lion cof for opt)
|= [cof=cafe wuy=(list ,@tas)] |= [cof=cafe wuy=(list ,@tas)]
?~ wuy (flue cof) ?~ wuy (flue cof)
%+ cope (cope (make cof %bake i.wuy bem arg) furl) %+ cope ((~(got by mal) i.wuy) cof arg)
|= [cof=cafe hoc=cage] |= [cof=cafe hoc=vase]
%+ cope (lope cof i.wuy t.wuy q.hoc) %+ cope (lope cof i.wuy t.wuy hoc)
|= [cof=cafe vax=vase] |= [cof=cafe vax=vase]
((fest bem) cof vax) ((fest bem) cof vax)
:: ::
@ -972,7 +1014,7 @@
?~ s.mob ?~ s.mob
%+ flag %+ flag
(norm ska mob) (norm ska mob)
(flaw cof leaf/"beam unavailable" (smyt (tope bem)) ~) (flaw cof leaf/"blank path" (smyt (tope bem)) ~)
^$(s.mob t.s.mob, mer [i.s.mob mer]) ^$(s.mob t.s.mob, mer [i.s.mob mer])
:: ::
++ link :: translate ++ link :: translate
@ -996,22 +1038,24 @@
`(slap gab [%cnzy for]) `(slap gab [%cnzy for])
?~ zat ?~ zat
(flaw cof [%leaf "ford: no link: {<[for too]>}"]~) (flaw cof [%leaf "ford: no link: {<[for too]>}"]~)
~| [%link-maul for too]
(maul cof u.zat vax) (maul cof u.zat vax)
:: ::
++ lion :: translation search ++ lion :: translation search
|= [cof=cafe too=mark fro=(list mark)] |= [cof=cafe too=mark fro=(set mark)]
:: ~& lion/[too=too fro=(sa fro)] :: ~& lion/[too=too fro=(sa fro)]
^- (bolt (list mark)) ^- (bolt (list mark))
=| $: war=(map mark (list mark)) =| $: war=(map mark (list mark))
pax=(list mark) won=[p=mark q=(qeu mark)] pax=(list mark) won=[p=mark q=(qeu mark)]
== ==
%. [cof fro] %. [cof fro]
|= [cof=cafe fro=(list mark)] ^- (bolt (list mark)) |= [cof=cafe fro=(set mark)] ^- (bolt (list mark))
?: =(too p.won) ?: =(too p.won)
(fine cof (flop pax)) (fine cof (flop pax))
=. fro (skip fro ~(has by war)) =+ for=(skip (~(tap by fro)) ~(has by war))
=: q.won (~(gas to q.won) fro) =. for (sort for aor) :: XX useful?
war (~(gas by war) (turn fro |=(mark [+< pax]))) =: q.won (~(gas to q.won) for)
war (~(gas by war) (turn for |=(mark [+< pax])))
== ==
?: =(~ q.won) ?: =(~ q.won)
(flue cof) (flue cof)
@ -1064,7 +1108,7 @@
== ==
:: ::
%bake %bake
:: ~& [%bake-start (tope q.kas)] :: ~& > [p.kas (tope q.kas)]
%+ cool |.(leaf/"ford: bake {<p.kas>} {<(tope q.kas)>}") %+ cool |.(leaf/"ford: bake {<p.kas>} {<(tope q.kas)>}")
%+ cope (lima cof p.kas q.kas r.kas) %+ cope (lima cof p.kas q.kas r.kas)
|= [cof=cafe vux=(unit vase)] |= [cof=cafe vux=(unit vase)]
@ -1074,7 +1118,7 @@
:: ::
%boil %boil
^- (bolt gage) ^- (bolt gage)
%+ cool |.(leaf/"ford: boil {<p.kas>} {<(tope q.kas)>} {<r.kas>}") :: %+ cool |.(leaf/"ford: boil {<p.kas>} {<(tope q.kas)>} {<r.kas>}")
%+ cope (lamp cof q.kas) %+ cope (lamp cof q.kas)
|= [cof=cafe bem=beam] |= [cof=cafe bem=beam]
%+ cope (lime cof p.kas bem r.kas) %+ cope (lime cof p.kas bem r.kas)
@ -1112,7 +1156,7 @@
|= [cof=cafe cay=cage] |= [cof=cafe cay=cage]
^- (bolt gage) ^- (bolt gage)
%+ cool |.(leaf/"ford: casting {<p.cay>} to {<p.kas>}") %+ cool |.(leaf/"ford: casting {<p.cay>} to {<p.kas>}")
%+ cope (lion cof p.kas p.cay ~) %+ cope (lion cof p.kas p.cay `~)
|= [cof=cafe wuy=(list ,@tas)] |= [cof=cafe wuy=(list ,@tas)]
%+ cope %+ cope
?~ wuy ?~ wuy
@ -1180,7 +1224,7 @@
|= [cof=cafe key=gage] |= [cof=cafe key=gage]
%+ cope (fret (make cof q.i.p.kas)) %+ cope (fret (make cof q.i.p.kas))
|= [cof=cafe val=gage] |= [cof=cafe val=gage]
%+ cope ^^$(cof cof, p.kas t.p.kas) %+ cope ^^$(p.kas t.p.kas, cof cof)
|= [cof=cafe rex=(list (pair gage gage))] |= [cof=cafe rex=(list (pair gage gage))]
(fine cof [[key val] rex]) (fine cof [[key val] rex])
|= [cof=cafe rex=(list (pair gage gage))] |= [cof=cafe rex=(list (pair gage gage))]
@ -1299,7 +1343,7 @@
?~ src (fine cof ..body) ?~ src (fine cof ..body)
%+ cope (wilt cof i.src) %+ cope (wilt cof i.src)
|= [cof=cafe sel=_..body] |= [cof=cafe sel=_..body]
^$(cof cof, src t.src, ..body sel) ^$(src t.src, ..body sel, cof cof)
:: ::
++ chad :: atomic list ++ chad :: atomic list
|= [cof=cafe bax=vase doe=term hon=horn] |= [cof=cafe bax=vase doe=term hon=horn]
@ -1369,7 +1413,7 @@
%+ cope %+ cope
|- ^- (bolt (list vase)) |- ^- (bolt (list vase))
?~ p.hon (flue cof) ?~ p.hon (flue cof)
%+ cope ^$(hon i.p.hon) %+ cope ^$(cof cof, hon i.p.hon)
|= [cof=cafe vax=vase] |= [cof=cafe vax=vase]
%+ cope ^$(cof cof, p.hon t.p.hon) %+ cope ^$(cof cof, p.hon t.p.hon)
|= [cof=cafe tev=(list vase)] |= [cof=cafe tev=(list vase)]

View File

@ -1027,6 +1027,7 @@
%lynx `%c %lynx `%c
%merg `%c %merg `%c
%them `%e %them `%e
%wait `%t
%want `%a %want `%a
%warp `%c %warp `%c
== ==

View File

@ -62,7 +62,7 @@
[%many p=(list coin)] :: [%many p=(list coin)] ::
== :: == ::
++ cord ,@t :: text atom (UTF-8) ++ cord ,@t :: text atom (UTF-8)
++ dock (pair ,@p term) :: message target ++ dock (pair ,@p term) :: message target
++ date ,[[a=? y=@ud] m=@ud t=tarp] :: parsed date ++ date ,[[a=? y=@ud] m=@ud t=tarp] :: parsed date
++ dime ,[p=@ta q=@] :: ++ dime ,[p=@ta q=@] ::
++ each |*([a=$+(* *) b=$+(* *)] $%([& p=a] [| p=b])) :: either a or b ++ each |*([a=$+(* *) b=$+(* *)] $%([& p=a] [| p=b])) :: either a or b
@ -2051,6 +2051,14 @@
(~(del by a) b) (~(del by a) b)
(~(put by a) b e) (~(put by a) b e)
:: ::
+- gas :: concatenate
|* b=(list ,[p=* q=*])
=> .(b `(list ,_?>(?=([[* ^] ^] a) [p=p q=n.q]:n.a))`b)
|- ^+ a
?~ b
a
$(b t.b, a (put(+< a) p.i.b q.i.b))
::
+- get :: gets set by key +- get :: gets set by key
|* b=* |* b=*
=+ c=(~(get by a) b) =+ c=(~(get by a) b)

View File

@ -1242,6 +1242,10 @@
=+ nex=$(tep t.tep) =+ nex=$(tep t.tep)
?~(nex ~ [~ i.tep u.nex]) ?~(nex ~ [~ i.tep u.nex])
:: ::
++ earf :: purf to tape
|= purf
(weld (earn p) ?~(q "" `tape`['#' (trip u.q)]))
::
++ earl :: localize purl ++ earl :: localize purl
|= [who=@p pul=purl] |= [who=@p pul=purl]
^- purl ^- purl
@ -1301,6 +1305,8 @@
++ apat :: 2396 abs_path ++ apat :: 2396 abs_path
%+ cook deft %+ cook deft
(ifix [fas ;~(pose fas (easy ~))] (more fas smeg)) (ifix [fas ;~(pose fas (easy ~))] (more fas smeg))
++ aurf :: 2396 with fragment
;~(plug auri (punt ;~(pfix hax (cook crip (star pque)))))
++ auri :: 2396 URL ++ auri :: 2396 URL
%+ cook %+ cook
|= a=purl |= a=purl
@ -2152,6 +2158,7 @@
++ pred ,[p=@ta q=@tas r=@ta ~] :: proto-path ++ pred ,[p=@ta q=@tas r=@ta ~] :: proto-path
++ prod ,[p=prom q=tape r=tape] :: prompt ++ prod ,[p=prom q=tape r=tape] :: prompt
++ prom ?(%text %pass %none) :: format type ++ prom ?(%text %pass %none) :: format type
++ purf (pair purl (unit ,@t)) :: url with fragment
++ purl ,[p=hart q=pork r=quay] :: parsed url ++ purl ,[p=hart q=pork r=quay] :: parsed url
++ putt :: outgoing message ++ putt :: outgoing message
$: ski=snow :: sequence acked/sent $: ski=snow :: sequence acked/sent

View File

@ -8,5 +8,5 @@
|= $: [now=@da eny=@uvI bec=beak] |= $: [now=@da eny=@uvI bec=beak]
[arg=(list term) ~] [arg=(list term) ~]
== ==
:+ %hood-reload-desk %home :+ %hood-reload-desk %base
arg arg

View File

@ -0,0 +1,11 @@
::
:::: /hook/gate/invite/hood/cat
::
/? 314
::
::::
!:
|= $: [now=@da eny=@uvI bec=beak]
[[who=@p myl=@t ~] ~]
==
[%hood-invite who myl]

View File

@ -0,0 +1,11 @@
::
:::: /hook/gate/link/hood/cat
::
/? 314
::
::::
!:
|= $: [now=@da eny=@uvI bec=beak]
[[who=ship dap=term ~] ~]
==
[%hood-link who dap]

View File

@ -6,6 +6,6 @@
:::: ::::
!: !:
|= $: [now=@da eny=@uvI bec=beak] |= $: [now=@da eny=@uvI bec=beak]
[[who=@p dap=term ~] ~] [[syd=desk dap=term ~] ~]
== ==
[%hood-start who dap] [%hood-start syd dap]

View File

@ -115,7 +115,7 @@
:: ::
++ drum-path :: encode path ++ drum-path :: encode path
|= gyl=gill |= gyl=gill
[%drum (scot %p p.gyl) q.gyl ~] [%drum %phat (scot %p p.gyl) q.gyl ~]
:: ::
++ drum-phat :: decode path ++ drum-phat :: decode path
|= way=wire ^- gill |= way=wire ^- gill
@ -127,6 +127,7 @@
=> |% :: arvo structures => |% :: arvo structures
++ pear :: request ++ pear :: request
$% [%sole-action p=sole-action] :: $% [%sole-action p=sole-action] ::
[%talk-command command:talk] ::
== :: == ::
++ lime :: update ++ lime :: update
$% [%dill-blit dill-blit] :: $% [%dill-blit dill-blit] ::
@ -175,7 +176,7 @@
-- --
-- --
|_ [moz=(list move) biz=(list dill-blit)] |_ [moz=(list move) biz=(list dill-blit)]
++ diff-sole-effect :: ++ diff-sole-effect-phat ::
|= [way=wire fec=sole-effect] |= [way=wire fec=sole-effect]
=< se-abet =< se-view =< se-abet =< se-view
=+ gyl=(drum-phat way) =+ gyl=(drum-phat way)
@ -202,7 +203,12 @@
=< se-abet =< se-view =< se-abet =< se-view
(se-born wel) (se-born wel)
:: ::
++ reap :: ++ poke-link ::
|= gyl=gill
=< se-abet =< se-view
(se-link gyl)
::
++ reap-phat ::
|= [way=wire saw=(unit tang)] |= [way=wire saw=(unit tang)]
=< se-abet =< se-view =< se-abet =< se-view
=+ gyl=(drum-phat way) =+ gyl=(drum-phat way)
@ -210,7 +216,7 @@
(se-join gyl) (se-join gyl)
(se-dump:(se-drop & gyl) u.saw) (se-dump:(se-drop & gyl) u.saw)
:: ::
++ take-coup :: ++ take-coup-phat ::
|= [way=wire saw=(unit tang)] |= [way=wire saw=(unit tang)]
=< se-abet =< se-view =< se-abet =< se-view
?~ saw +> ?~ saw +>
@ -228,11 +234,11 @@
?- -.saw ?- -.saw
%| (se-dump p.saw) %| (se-dump p.saw)
%& ?> =(q.wel p.p.saw) %& ?> =(q.wel p.p.saw)
:: =. +>.$ (se-text "[{<p.saw>}]") :: =. +>.$ (se-text "live {<p.saw>}")
+>.$(fur (~(put by fur) q.wel `[p.wel %da r.p.saw])) +>.$(fur (~(put by fur) q.wel `[p.wel %da r.p.saw]))
== ==
:: ::
++ quit ++ quit-phat ::
|= way=wire |= way=wire
=< se-abet =< se-view =< se-abet =< se-view
=+ gyl=(drum-phat way) =+ gyl=(drum-phat way)
@ -243,6 +249,9 @@
:: :: :: :: :: ::
++ se-abet :: resolve ++ se-abet :: resolve
^- (quip move *drum-part) ^- (quip move *drum-part)
?. se-ably
=. . se-adit
[(flop moz) +>+>+<+]
=. . se-adze:se-adit =. . se-adze:se-adit
:_ %_(+>+>+<+ bin (~(put by bin) ost `source`+>+<)) :_ %_(+>+>+<+ bin (~(put by bin) ost `source`+>+<))
^- (list move) ^- (list move)
@ -251,6 +260,7 @@
?~ biz ~ ?~ biz ~
[ost %diff %dill-blit ?~(t.biz i.biz [%mor (flop biz)])]~ [ost %diff %dill-blit ?~(t.biz i.biz [%mor (flop biz)])]~
:: ::
++ se-ably (~(has by sup) ost) :: caused by console
++ se-adit :: update servers ++ se-adit :: update servers
=+ yar=(~(tap by ray)) =+ yar=(~(tap by ray))
|- ^+ +> |- ^+ +>
@ -260,6 +270,7 @@
%= $ %= $
yar t.yar yar t.yar
+> +>
=. +>.$ (se-text "activated app {(trip p.i.yar)}/{(trip q.i.yar)}")
%- se-emit(fur (~(put by fur) q.i.yar ~)) %- se-emit(fur (~(put by fur) q.i.yar ~))
[ost %conf [%drum p.i.yar q.i.yar ~] [our q.i.yar] %load our p.i.yar] [ost %conf [%drum p.i.yar q.i.yar ~] [our q.i.yar] %load our p.i.yar]
== ==
@ -338,14 +349,6 @@
(se-text "[already running {<p.wel>}/{<q.wel>}]") (se-text "[already running {<p.wel>}/{<q.wel>}]")
+>(ray (~(put in ray) wel), eel (~(put in eel) [our q.wel])) +>(ray (~(put in ray) wel), eel (~(put in eel) [our q.wel]))
:: ::
++ se-dump :: print tanks
|= tac=(list tank)
^+ +>
=+ wol=`wall`(zing (turn tac |=(a=tank (~(win re a) [0 edg]))))
|- ^+ +>.^$
?~ wol +>.^$
$(wol t.wol, +>.^$ (se-blit %out (tuba i.wol)))
::
++ se-drop :: disconnect ++ se-drop :: disconnect
|= [pej=? gyl=gill] |= [pej=? gyl=gill]
^+ +> ^+ +>
@ -356,9 +359,18 @@
=. +>.$ ?. &(?=(^ lag) !=(gyl u.lag)) =. +>.$ ?. &(?=(^ lag) !=(gyl u.lag))
+>.$(inx 0) +>.$(inx 0)
(se-alas u.lag) (se-alas u.lag)
=. +>.$ (se-text "[detached from {<gyl>}]") =. +>.$ (se-text "[unlinked from {<gyl>}]")
se-prom(liv.maz ?~(fug & liv.maz)) se-prom(liv.maz ?~(fug & liv.maz))
:: ::
++ se-dump :: print tanks
|= tac=(list tank)
^+ +>
?. se-ably (se-talk tac)
=+ wol=`wall`(zing (turn tac |=(a=tank (~(win re a) [0 edg]))))
|- ^+ +>.^$
?~ wol +>.^$
$(wol t.wol, +>.^$ (se-blit %out (tuba i.wol)))
::
++ se-joke :: prepare connection ++ se-joke :: prepare connection
|= gyl=gill |= gyl=gill
^+ +> ^+ +>
@ -370,7 +382,7 @@
++ se-join :: confirm connection ++ se-join :: confirm connection
|= gyl=gill |= gyl=gill
^+ +> ^+ +>
=. +> (se-text "[connected to {<gyl>}]") =. +> (se-text "[linked to {<gyl>}]")
?> =(~ (~(got by fug) gyl)) ?> =(~ (~(got by fug) gyl))
(se-alas:se-prom(liv.maz |, fug (~(put by fug) gyl `*target)) gyl) (se-alas:se-prom(liv.maz |, fug (~(put by fug) gyl `*target)) gyl)
:: ::
@ -467,8 +479,15 @@
|= mov=move |= mov=move
%_(+> moz [mov moz]) %_(+> moz [mov moz])
:: ::
++ se-talk
|= tac=(list tank)
^+ +>
(se-emit 0 %poke /drum/talk [our %talk] (said our %drum now eny tac))
::
++ se-text :: return text ++ se-text :: return text
|= txt=tape |= txt=tape
^+ +>
?. se-ably (se-talk [%leaf txt]~)
(se-blit %out (tuba txt)) (se-blit %out (tuba txt))
:: ::
++ se-poke :: send a poke ++ se-poke :: send a poke

View File

@ -27,10 +27,6 @@
++ hood-init :: report init ++ hood-init :: report init
$: him=ship :: $: him=ship ::
== :: == ::
++ hood-start :: start (local) server
$: syd=desk :: desk
dap=term :: program
== ::
++ hood-reset :: reset command ++ hood-reset :: reset command
,~ :: ,~ ::
++ helm-verb :: reset command ++ helm-verb :: reset command
@ -53,10 +49,11 @@
[%poke wire dock pear] :: [%poke wire dock pear] ::
[%want wire sock path *] :: send message [%want wire sock path *] :: send message
== :: == ::
++ move (pair bone card) :: user-level move
++ pear :: poke fruit ++ pear :: poke fruit
$% [%hood-unsync desk ship desk] :: $% [%hood-unsync desk ship desk] ::
[%talk-command command:talk] ::
== :: == ::
++ move (pair bone card) :: user-level move
-- --
|_ moz=(list move) |_ moz=(list move)
++ abet :: resolve ++ abet :: resolve
@ -84,17 +81,14 @@
|= ~ =< abet |= ~ =< abet
(emit %flog /heft %crud %hax-heft ~) (emit %flog /heft %crud %hax-heft ~)
:: ::
++ poke-start :: start a server
|= hood-start =< abet
(emit %conf /helm [our dap] %load our syd)
::
++ poke-reload |=(all=(list term) (poke-reload-desk %home all)) ++ poke-reload |=(all=(list term) (poke-reload-desk %home all))
++ poke-reload-desk :: reload vanes ++ poke-reload-desk :: reload vanes
|= [syd=desk all=(list term)] =< abet |= [syd=desk all=(list term)] =< abet
%- emil %- emil
%- flop %- flop
%+ turn all %+ turn all
=+ ark=(arch .^(%cy /(scot %p our)/[syd]/(scot %da now)/arvo)) =+ top=`path`/(scot %p our)/[syd]/(scot %da now)/arvo
=+ ark=(arch .^(%cy top))
=+ van=(~(tap by r.ark)) =+ van=(~(tap by r.ark))
|= nam=@tas |= nam=@tas
=. nam =. nam
@ -105,12 +99,15 @@
?> ?=([[@ ~] ~] zaz) ?> ?=([[@ ~] ~] zaz)
`term`p.i.zaz `term`p.i.zaz
=+ tip=(end 3 1 nam) =+ tip=(end 3 1 nam)
=+ way=[(scot %p our) %home (scot %da now) %arvo nam %hoon ~] =+ way=(welp top /[nam])
=+ fil=(,@ .^(%cx way)) =+ fil=(,@ .^(%cx (welp way /hoon)))
:* %flog [%flog /reload [%veer ?:(=('z' tip) %$ tip) way fil]]
/reload ::
[%veer ?:(=('z' tip) %$ tip) way (,@ .^(%cx way))] ++ poke-invite :: send invite; fake
== |= [who=@p myl=@t] =< abet
%^ emit %poke /helm/invite
:- [our %talk]
(said our %helm now eny [%leaf "invited: {<who>} at {(trip myl)}"]~)
:: ::
++ poke-reset :: reset system ++ poke-reset :: reset system
|= hood-reset =< abet |= hood-reset =< abet
@ -151,7 +148,6 @@
:: ::
++ take-onto :: result of %conf ++ take-onto :: result of %conf
|= saw=(each suss tang) =< abet |= saw=(each suss tang) =< abet
~& [%take-onto saw]
%- emit %- emit
?- -.saw ?- -.saw
%| [%flog ~ %crud %onto `tang`p.saw] %| [%flog ~ %crud %onto `tang`p.saw]

View File

@ -156,24 +156,7 @@
++ spam ++ spam
|= mes=(list tank) |= mes=(list tank)
%- emit %- emit
:* %poke /kiln/spam [%poke /kiln/spam [our %talk] (said our %kiln now eny mes)]
[our %talk] %talk-command
^- command:talk
:- %publish
%- flop
=< acc
%+ roll mes
=< .(eny ^eny)
|= [tan=tank acc=(list thought:talk) eny=@uvI]
^- [acc=(list thought:talk) eny=@uvI]
=+ (sham eny mes)
:_ -
:_ acc
^- thought:talk
:+ -
[[[%& our (main our)] [*envelope:talk %pending]] ~ ~]
[now *bouquet:talk [%app (crip ~(ram re tan))]]
==
:: ::
++ auto ++ auto
|= hood-sync |= hood-sync
@ -198,6 +181,8 @@
== ==
:: ::
++ start ++ start
=. . %- spam
[leaf/"activated sync from {<sud>} on {<her>} to {<syd>}" ~]
%- blab :_ ~ %- blab :_ ~
:* ost %warp :* ost %warp
/kiln/sync/[syd]/(scot %p her)/[sud] /kiln/sync/[syd]/(scot %p her)/[sud]
@ -208,7 +193,7 @@
|= rot=riot |= rot=riot
?~ rot ?~ rot
%^ spam %^ spam
leaf/"bad %writ response on autosync" leaf/"bad %writ response on sync"
leaf/"from {<sud>} on {<her>} to {<syd>}" leaf/"from {<sud>} on {<her>} to {<syd>}"
~ ~
=. let ?. ?=(%w p.p.u.rot) let ((hard ,@ud) q.q.r.u.rot) =. let ?. ?=(%w p.p.u.rot) let ((hard ,@ud) q.q.r.u.rot)
@ -227,9 +212,10 @@
=. +>.$ =. +>.$
%- spam %- spam
?: ?=(%& -.mes) ?: ?=(%& -.mes)
[leaf/"autosync succeeded from {<sud>} on {<her>} to {<syd>}" ~] ~
:: [leaf/"sync succeeded from {<sud>} on {<her>} to {<syd>}" ~]
?+ p.p.mes ?+ p.p.mes
:* leaf/"autosync failed from {<sud>} on {<her>} to {<syd>}" :* leaf/"sync failed from {<sud>} on {<her>} to {<syd>}"
leaf/"please manually merge the desks with" leaf/"please manually merge the desks with"
leaf/":+merge %{(trip syd)} {(scow %p her)} %{(trip sud)}" leaf/":+merge %{(trip syd)} {(scow %p her)} %{(trip sud)}"
leaf/"" leaf/""
@ -238,8 +224,8 @@
== ==
:: ::
%no-ali-desk %no-ali-desk
:~ leaf/"{<sud>} on {<her>} does not exist, so the sync" :~ leaf/"sync activated from {<sud>} on {<her>} to {<syd>}"
leaf/"into {<syd>} will begin automatically when it does" leaf/"note: {<sud>} on {<her>} is a blank desk"
== ==
== ==
%- blab :_ ~ %- blab :_ ~
@ -342,7 +328,7 @@
?: =(%meld gem) ?: =(%meld gem)
?: ?=(%& -.are) ?: ?=(%& -.are)
?. auto ?. auto
=+ "successfully merged with strategy {<gem>}" =+ "merged with strategy {<gem>}"
win:(spam leaf/- ?~(p.are ~ [>`(set path)`p.are< ~])) win:(spam leaf/- ?~(p.are ~ [>`(set path)`p.are< ~]))
=+ "mashing conflicts" =+ "mashing conflicts"
=> .(+>.$ (spam leaf/- ~)) => .(+>.$ (spam leaf/- ~))
@ -368,7 +354,7 @@
=+ "failed to merge with strategy {<p.p.are>}" =+ "failed to merge with strategy {<p.p.are>}"
lose:(spam leaf/- q.p.are) lose:(spam leaf/- q.p.are)
?: ?=(%& -.are) ?: ?=(%& -.are)
=+ "successfully merged with strategy {<gem>}" =+ "merged with strategy {<gem>}"
win:(spam leaf/- ?~(p.are ~ [>`(set path)`p.are< ~])) win:(spam leaf/- ?~(p.are ~ [>`(set path)`p.are< ~]))
?. auto ?. auto
=+ "failed to merge with strategy {<p.p.are>}" =+ "failed to merge with strategy {<p.p.are>}"

View File

@ -16,4 +16,23 @@
%czar %court %czar %court
%king %floor %king %floor
== ==
::
++ said :: app message
|= [our=@p dap=term now=@da eny=@uvI mes=(list tank)]
:- %talk-command
^- command
:- %publish
%- flop
=< acc
%+ roll mes
=< .(eny ^eny)
|= [tan=tank acc=(list thought) eny=@uvI]
^- [acc=(list thought) eny=@uvI]
=+ (sham eny mes)
:_ -
:_ acc
^- thought
:+ -
[[[%& our (main our)] [*envelope %pending]] ~ ~]
[now *bouquet [%app dap (crip ~(ram re tan))]]
-- --

View File

@ -72,7 +72,7 @@
^- $+(json (unit statement)) ^- $+(json (unit statement))
=- (ot date/di bouquet/(as (ar so)) speech/(of -) ~) =- (ot date/di bouquet/(as (ar so)) speech/(of -) ~)
:~ lin/(ot say/bo txt/so ~) :~ lin/(ot say/bo txt/so ~)
url/(su auri:urlp) url/(su aurf:urlp)
:: exp/(cu |=(a=cord [a ~]) so) :: exp/(cu |=(a=cord [a ~]) so)
:: inv/(ot ship/(su fed:ag) party/(su urs:ab) ~) :: inv/(ot ship/(su fed:ag) party/(su urs:ab) ~)
== ==

View File

@ -89,7 +89,7 @@
~| stub/-.a ~| stub/-.a
?+ -.a !! ?+ -.a !!
%lin (jobe say/[%b p.a] txt/[%s q.a] ~) %lin (jobe say/[%b p.a] txt/[%s q.a] ~)
%url (jobe url/[%s (crip (earn p.a))] ~) %url (jobe url/[%s (crip (earf p.a))] ~)
%exp (jobe code/[%s p.a] ~) %exp (jobe code/[%s p.a] ~)
%app (jobe txt/[%s p.a] ~) %app (jobe txt/[%s p.a] ~)
:: %inv (jobe ship/(jope p.a) party/[%s q.a] ~) :: %inv (jobe ship/(jope p.a) party/[%s q.a] ~)

View File

@ -9,7 +9,6 @@
!: !:
^- manx ^- manx
=+ do=(~(get by qix.gas) %'code') =+ do=(~(get by qix.gas) %'code')
=+ g=(~(get by qix.gas) %'access_token')
;html ;html
;head ;head
@ -21,11 +20,10 @@
;title: DO & GCE Manager ;title: DO & GCE Manager
== ==
;body ;body
;* =+ d=?~(do ~ (trip u.do)) ;script:"""
=+ g=?~(g ~ (trip u.g)) var authcode = \{}
~& d authcode.do='{?~(do ~ (trip u.do))}'
:_ ~ """
;script: authcode='{?~(d g d)}'; console.log(authcode)
;div#container; ;div#container;
;script@"/home/pub/cloud/src/main.js"; ;script@"/home/pub/cloud/src/main.js";
== ==

View File

@ -9,6 +9,18 @@ tr = React.DOM.tr
td = React.DOM.td td = React.DOM.td
input = React.DOM.input input = React.DOM.input
function HashToJSON() {
var pairs = window.location.hash.slice(1).split('&');
var result = {};
pairs.forEach(function(pair) {
pair = pair.split('=');
result[pair[0]] = decodeURIComponent(pair[1] || '');
});
return JSON.parse(JSON.stringify(result));
}
DOControls = React.createClass({ DOControls = React.createClass({
createDroplet: function(){ createDroplet: function(){
urb.send({appl: "cloud", urb.send({appl: "cloud",
@ -62,10 +74,10 @@ GCEControls = React.createClass({
urb.send({ urb.send({
appl: 'cloud', appl: 'cloud',
data: {action:'create-gce', data: {action:'create-gce',
project:$('#project').val(), // project:$('#project').val(),
zone:$('#zone').val(), // zone:$('#zone').val(),
name:$('#gname').val(), // name:$('#gname').val(),
machine_type:$('#machine_type').val() // machine_type:$('#machine_type').val() /
}, },
mark: 'json'}) mark: 'json'})
}, },
@ -73,10 +85,11 @@ GCEControls = React.createClass({
createDisk: function(){ createDisk: function(){
urb.send({ urb.send({
appl: 'cloud', appl: 'cloud',
data: {action:'create-gce-disk', data: {action:'create-gce',
snap:$('#gsnap').val(), snap:$('#gsnap').val(),
number:$('#number').val(), number:$('#number').val(),
name:$('#gcpName').val()}, name:$('#gcpName').val(),
instance_img:$('#instance_image').val()},
mark: 'json'}) mark: 'json'})
}, },
@ -88,7 +101,8 @@ GCEControls = React.createClass({
b({onClick:this.createDisk}, 'Create Disk From Image'), b({onClick:this.createDisk}, 'Create Disk From Image'),
input({id:'gcpName',placeholder:'Name for GCE Disk and Instance'}), input({id:'gcpName',placeholder:'Name for GCE Disk and Instance'}),
input({id:'number',placeholder:'Number of instances'}), input({id:'number',placeholder:'Number of instances'}),
input({id:'gsnap',placeholder:'Snapshot'}) input({id:'gsnap',placeholder:'Snapshot'}),
input({id:'instance_image',placeholder:'Instance Image'})
]), ]),
div({}, [ div({}, [
a({href:ghref},"Get Google Authcode"), a({href:ghref},"Get Google Authcode"),
@ -97,16 +111,9 @@ GCEControls = React.createClass({
div({}, [ div({}, [
input({id:"gappsecret"}, input({id:"gappsecret"},
b({onClick:this.props.sendSecret('gce','#gappsecret')}, "Send Google Secret")) b({onClick:this.props.sendSecret('gce','#gappsecret')}, "Send Google Secret"))
]), ])
div({}, [
b({onClick:this.createDroplet}, "Create Droplet"),
input({id:"project",placeholder:"project"}),
input({id:"zone",placeholder:"zone"}),
input({id:"gname",placeholder:"Name of droplet"}),
input({id:"machine_type",placeholder:"Machine Type"}),
//input({id:"image",placeholder:"Image"}),
]) ])
])) )
} }
}) })
@ -114,8 +121,8 @@ Droplet = React.createClass({
dropletAction:function(id, action){ dropletAction:function(id, action){
urb.send({ urb.send({
appl:"cloud", appl:"cloud",
data: {action: action, data: {action:action,
id: id}}) id:id}})
}, },
render: function() { render: function() {
@ -143,10 +150,11 @@ Page = recl({
handleClick: function(platform){ handleClick: function(platform){
return function(){ return function(){
console.log(platform); console.log(platform);
console.log(window.authcode.platform)
if(window.authcode.length !== ''){ if(window.authcode.length !== ''){
urb.send({ urb.send({
appl: "cloud", appl: "cloud",
data: {authcode:window.authcode, data: {authcode:authcode[platform],
platform:platform}, platform:platform},
mark: "cloud-auth"}) mark: "cloud-auth"})
} else { console.log("nocode") } } else { console.log("nocode") }
@ -182,6 +190,8 @@ Page = recl({
} }
}) })
var hash = HashToJSON() //pull out hash of query string for gce authcode
authcode.gce = hash.access_token
mounted = React.render(Page({droplets:[]}), $("#container")[0]) mounted = React.render(Page({droplets:[]}), $("#container")[0])
urb.bind("/", function(err,d) { urb.bind("/", function(err,d) {

View File

@ -1,6 +1,6 @@
:: ::
:: ::
:::: /hook/hymn/fab/octo/pub/ :::: /hook/hymn/fab/oct3/pub/
:: ::
^- manx ^- manx
;html ;html
@ -8,9 +8,9 @@
;meta(charset "utf-8"); ;meta(charset "utf-8");
;script(type "text/javascript", src "//cdnjs.cloudflare.com/ajax/libs/jquery/2.1.1/jquery.js"); ;script(type "text/javascript", src "//cdnjs.cloudflare.com/ajax/libs/jquery/2.1.1/jquery.js");
;script(type "text/javascript", src "/~~/~/at/base/lib/urb.js"); ;script(type "text/javascript", src "/~~/~/at/base/lib/urb.js");
;link(type "text/css", rel "stylesheet", href "/home/lib/base.css"); ;link(type "text/css", rel "stylesheet", href "/demo/lib/base.css");
;link(type "text/css", rel "stylesheet", href "/home/pub/octo/src/main.css"); ;link(type "text/css", rel "stylesheet", href "/demo/pub/oct3/src/main.css");
;title: :octo ;title: :oct3
== ==
;body ;body
;div#what ;div#what
@ -26,6 +26,6 @@
== ==
;div#bord; ;div#bord;
;div#audi; ;div#audi;
;script(type "text/javascript", src "/home/pub/octo/src/main.js"); ;script(type "text/javascript", src "/demo/pub/oct3/src/main.js");
== ==
== ==

View File

@ -0,0 +1,37 @@
#what, #bord, #audi { width: 600px; text-align: center; position: absolute;
left: 50%; margin-left: -300px; }
#what { height: 36px; top: 18px; }
#bord { height: 600px; position: absolute; top: 111px; opacity: .3; }
#audi { top: 760px; }
.turn #bord { opacity: 1; }
#message { position:absolute; left: 0; top: 0; width: 100%; height: 90px;
line-height: 90px; background-color: #000; color: #fff;
text-align: center; }
#message .ship { display: inline; }
#what { font-family: "bau"; }
#what div { display: inline-block; }
.ship { padding: .3rem; font-weight: 400; letter-spacing: 1px;
text-transform: uppercase; line-height:2rem; }
.ship:before { content: "~"; font-weight: 500; font-size: 1rem; }
.waiting.ship:before { content: "Waiting"; color: #ccc; }
#what #x, #what #o { border: 2px solid #fff; }
.x #what #x, .o #what #o { border: 2px solid red; }
#what #ship, #what #user { padding: .6rem; }
#what .as { width: 1.6rem; }
#audi h1,
#vs { margin: 0 1rem; padding: .3rem; color: #fff; background-color: #000; }
#audi h1 { font-size: .9rem; text-transform: uppercase; display:
inline-block; background-color: #ccc; }
#audi h1:after { content: ""; margin: 0; }
#audi .ship { color: #ccc; }
.spac { font-size: 100px; line-height: 200px; }
.spac { width: 198px; height: 198px; border: 1px solid #000;
text-align: center; float: left; cursor: pointer; }
.spac[data-index="0-0"], .spac[data-index="1-0"], .spac[data-index="2-0"]
{ border-left: 0; }
.spac[data-index="0-0"], .spac[data-index="0-1"], .spac[data-index="0-2"]
{ border-top: 0; }
.spac[data-index="2-0"], .spac[data-index="2-1"], .spac[data-index="2-2"]
{ border-bottom: 0; }
.spac[data-index="0-2"], .spac[data-index="1-2"], .spac[data-index="2-2"]
{ border-right: 0; }

View File

@ -53,20 +53,23 @@ $(function() {
state.plo = "" state.plo = ""
if(!state.plx) if(!state.plx)
state.plx = "" state.plx = ""
$('#o .ship').toggleClass('waiting', (state.plo=="")).text(state.plo.slice(1)) $('#o .ship').toggleClass('waiting', (state.plo=="")).
$('#x .ship').toggleClass('waiting', (state.plx=="")).text(state.plx.slice(1)) text(state.plo.slice(1))
$('#x .ship').toggleClass('waiting', (state.plx=="")).
text(state.plx.slice(1))
} }
message = function(mess) { message = function(mess) {
mess = mess.split('"')[1] mess = mess.split('"')[1]
mess = mess.split("=") mess = mess.split("=")
mess = "<div class='ship'>"+mess[0].slice(1)+"</div> ["+symb[lett.indexOf(mess[1].toLowerCase())+1]+"] WINS" mess = "<div class='ship'>"+mess[0].slice(1) +
"</div> ["+symb[lett.indexOf(mess[1].toLowerCase())+1]+"] WINS"
$('body').append('<div id="message">'+mess+'</div>') $('body').append('<div id="message">'+mess+'</div>')
setTimeout(function() { $('#message').fadeOut().remove(); }, 2000) setTimeout(function() { $('#message').fadeOut().remove(); }, 2000)
} }
urb.appl = 'octo' urb.appl = 'oct3'
urb.bind('/octo', function(err,res) { urb.bind('/oct3', function(err,res) {
if(typeof(res.data) == 'string') if(typeof(res.data) == 'string')
return message(res.data) return message(res.data)
assign(res.data) assign(res.data)
@ -81,6 +84,6 @@ $(function() {
data = $.map( data = $.map(
$t.attr('data-index').split('-'), $t.attr('data-index').split('-'),
function(i) { return Number(i); }) function(i) { return Number(i); })
urb.send({mark:'octo-move',data:data}) urb.send({mark:'oct3-move',data:data})
}) })
}) })

View File

@ -1,151 +0,0 @@
#what,
#bord,
#audi {
width: 600px;
text-align: center;
position: absolute;
left: 50%;
margin-left: -300px;
}
#what {
height: 36px;
top: 18px;
}
#bord {
height: 600px;
position: absolute;
top: 111px;
opacity: .3;
}
#audi {
top: 760px;
}
.turn #bord {
opacity: 1;
}
#message {
position:absolute;
left: 0; top: 0;
width: 100%; height: 90px;
line-height: 90px;
background-color: #000;
color: #fff;
text-align: center;
}
#message .ship {
display: inline;
}
#what {
font-family: "bau";
}
#what div {
display: inline-block;
}
.ship {
padding: .3rem;
font-weight: 400;
letter-spacing: 1px;
text-transform: uppercase;
line-height:2rem;
}
.ship:before {
content: "~";
font-weight: 500;
font-size: 1rem;
}
.waiting.ship:before {
content: "Waiting";
color: #ccc;
}
#what #x,
#what #o {
border: 2px solid #fff;
}
.x #what #x,
.o #what #o {
border: 2px solid red;
}
#what #ship,
#what #user {
padding: .6rem;
}
#what .as {
width: 1.6rem;
}
#audi h1,
#vs {
margin: 0 1rem;
padding: .3rem;
color: #fff;
background-color: #000;
}
#audi h1 {
font-size: .9rem;
text-transform: uppercase;
display: inline-block;
background-color: #ccc;
}
#audi h1:after {
content: "";
margin: 0;
}
#audi .ship {
color: #ccc;
}
.spac {
font-size: 100px;
line-height: 200px;
}
.spac {
width: 198px;
height: 198px;
border: 1px solid #000;
text-align: center;
float: left;
cursor: pointer;
}
.spac[data-index="0-0"],
.spac[data-index="1-0"],
.spac[data-index="2-0"] {
border-left: 0;
}
.spac[data-index="0-0"],
.spac[data-index="0-1"],
.spac[data-index="0-2"] {
border-top: 0;
}
.spac[data-index="2-0"],
.spac[data-index="2-1"],
.spac[data-index="2-2"] {
border-bottom: 0;
}
.spac[data-index="0-2"],
.spac[data-index="1-2"],
.spac[data-index="2-2"] {
border-right: 0;
}

View File

@ -59,11 +59,11 @@
[%ext p=@tas q=*] :: extended action [%ext p=@tas q=*] :: extended action
[%fat p=torso q=speech] :: attachment [%fat p=torso q=speech] :: attachment
:: [%inv p=station] :: invite to station :: [%inv p=station] :: invite to station
[%url p=purl] :: parsed url [%url p=purf] :: parsed url
[%ire p=serial q=speech] :: in-reply-to [%ire p=serial q=speech] :: in-reply-to
[%lin p=? q=@t] :: no=@, text line [%lin p=? q=@t] :: no=@, text line
[%mor p=(list speech)] :: multiplex [%mor p=(list speech)] :: multiplex
[%app p=@t] :: app message [%app p=@tas q=@t] :: app message
== :: == ::
++ serial ,@uvH :: unique identity ++ serial ,@uvH :: unique identity
++ partner (each station passport) :: interlocutor ++ partner (each station passport) :: interlocutor