Cleaning up old code

This commit is contained in:
Christian Carter 2013-09-28 13:21:18 -07:00
parent e4eae49cf9
commit 4caa90c68f
63 changed files with 14680 additions and 0 deletions

1658
arvo/ames.hoon Normal file

File diff suppressed because it is too large Load Diff

1198
arvo/batz.hoon Normal file

File diff suppressed because it is too large Load Diff

631
arvo/clay.hoon Normal file
View File

@ -0,0 +1,631 @@
::
:: clay (4c), revision control
::
|= pit=vase
^- vane
=>
::::::::::::::::::::::::::::::::::::::::::::::::::::::::
:: section 4cA, filesystem logic ::
::
|%
::
++ un :: per ship
|= [who=@p now=@da ruf=raft]
=+ ^= yar ^- room
=+ yar=(~(get by fat.ruf) who)
?~(yar *room u.yar)
=| yel=(list ,[p=duct q=card])
=| wot=(list ,[p=duct q=tape])
=| byn=(list ,[p=duct q=riot])
=| vag=(list ,[p=duct q=card])
=| say=(list ,[p=duct q=ship r=[p=@ud q=riff]])
|%
++ abet
^- [(list move) raft]
:_ ruf(fat (~(put by fat.ruf) who yar))
;: weld
%+ turn (flop yel)
|=([a=duct b=card] [[~ %gold who] hun.yar b])
::
%+ turn (flop wot)
|=([a=duct b=tape] [[~ %gold who] a [%wort b]])
::
%+ turn (flop byn)
|=([a=duct b=riot] [[~ %gold who] a [%writ b]])
::
%+ turn (flop vag)
|=([a=duct b=card] [[~ %gold who] a b])
::
%+ turn (flop say)
|=([a=duct b=ship c=*] [[~ %gold who] [/a a] [%want b %re c]])
==
::
++ doze
=+ saz=(turn (~(tap by dos.yar) ~) |=([a=@tas b=*] a))
=| nex=(unit ,@da)
|- ^+ nex
?~ saz nex
$(saz t.saz, nex (hunt nex doze:(di i.saz)))
::
++ fray
|= [hen=duct pal=(list disc) sab=saba]
^+ +>
?~ pal +>
$(pal t.pal, +> zoot:wake:(exec:(di i.pal) hen now [%| sab]))
::
++ wake
^+ .
=+ saz=(turn (~(tap by dos.yar) ~) |=([a=@tas b=*] a))
|- ^+ ..wake
?~ saz ..wake
$(saz t.saz, ..wake zoot:wake:(di i.saz))
::
++ de :: per desk
|_ [for=@p syd=@ta lim=@da qyx=cult dom=dome]
++ aeon :: act count through
|= lok=case
^- (unit ,@ud)
?- -.lok
%da
?: (gth p.lok lim) ~
|- ^- (unit ,@ud)
?~ hit.dom [~ let.dom]
?: (gte p.lok p.i.hit.dom) [~ let.dom]
$(hit.dom t.hit.dom, let.dom (dec let.dom))
::
%tas (~(get by lab.dom) p.lok)
%ud ?:((gth p.lok let.dom) ~ [~ p.lok])
==
::
++ ache :: arch report
^- arch
:+ p.ank.dom
?~(q.ank.dom ~ [~ p.u.q.ank.dom])
|- ^- (map ,@ta ,~)
?~ r.ank.dom ~
[[p.n.r.ank.dom ~] $(r.ank.dom l.r.ank.dom) $(r.ank.dom r.r.ank.dom)]
::
++ amor :: endpoint query
|= ren=?(%x %y %z)
^- (unit ,*)
?- ren
%x ?~(q.ank.dom ~ [~ q.u.q.ank.dom])
%y [~ ache]
%z [~ ank.dom]
==
::
++ ante :: rewind by change
|= lem=maki
^+ +>
?- -.lem
&
%_ +>
ank.dom ?. ?=(& -.p.lem) ank.dom
ank:(dusk:(zu ank.dom) p.p.lem)
lab.dom ?. ?=(| -.p.lem) lab.dom
(~(del by lab.dom) p.p.lem)
==
::
|
|- ^+ +>.^$
?~ s.p.lem +>.^$
$(s.p.lem t.s.p.lem, +>.^$ ^$(lem i.s.p.lem))
==
::
++ argo :: rewind to aeon
|= oan=@ud
^+ +>
?: =(let.dom oan) +>
?> ?=(^ hit.dom)
?> ?=(& -.q.i.hit.dom)
=> .(+> (ante q.i.hit.dom))
$(let.dom (dec let.dom), hit.dom t.hit.dom)
::
++ auto :: read at point
|= mun=mood
^- (unit)
?: ?=(%v p.mun)
[~ dom]
?: &(?=(%w p.mun) !?=(%ud -.q.mun))
?^(r.mun ~ [~ let.dom])
?: ?=(%w p.mun)
?> ?=(^ hit.dom) ?^(r.mun ~ [~ i.hit.dom])
(amor(ank.dom ank:(deny:(zu ank.dom) r.mun)) p.mun)
::
++ aver :: domestic read
|= mun=mood
^- (unit (unit ,*))
=+ nao=(aeon q.mun)
?~(nao ~ [~ (avid u.nao mun)])
::
++ avid :: seek and read
|= [oan=@ud mun=mood]
^- (unit)
?: &(?=(%w p.mun) !?=(%ud -.q.mun)) :: NB optimization
?^(r.mun ~ [~ oan])
(auto:(argo oan) mun)
::
++ balk :: read and send
|= [hen=duct oan=@ud mun=mood]
^+ +>
=+ vid=(avid oan mun)
?~ vid (blob hen) (blab hen mun u.vid)
::
++ blab :: ship result
|= [hen=duct mun=mood dat=*]
^+ +>
+>(byn [[hen ~ [p.mun q.mun syd] r.mun dat] byn])
::
++ bleb :: ship sequence
|= [hen=duct ins=@ud hip=(list frog)]
^+ +>
?~ hip +>
%= $
hip t.hip
ins +(ins)
+> (blab hen [%w [%ud ins] ~] i.hip)
==
::
++ blob :: ship stop
|= hen=duct
%_(+> byn [[hen ~] byn])
::
++ doze :: sleep until
=+ xiq=(~(tap by qyx) ~)
=| nex=(unit ,@da)
|- ^+ nex
?~ xiq nex
=+ ^= zis ^+ nex
?- -.q.i.xiq
& ?.(?=(%da -.q.p.q.i.xiq) ~ [~ p.q.p.q.i.xiq])
::
|
=+ mot=`moat`p.q.i.xiq
%+ hunt
?.(&(?=(%da -.p.mot) (lth now p.p.mot)) ~ [~ p.p.mot])
?.(&(?=(%da -.q.mot) (lth now p.q.mot)) ~ [~ p.q.mot])
==
$(xiq t.xiq, nex (hunt nex zis))
::
++ ease :: unsubscribe
|= hen=duct
^+ +>
+>(qyx (~(del by qyx) hen))
::
++ eave :: subscribe
|= [hen=duct rav=rave]
^+ +>
?- -.rav
&
=+ ver=(aver p.rav)
?~ ver
+>.$(qyx (~(put by qyx) hen rav))
?~ u.ver
(blob hen)
(blab hen p.rav u.u.ver)
::
|
=+ nab=(aeon p.p.rav)
?~ nab
?> =(~ (aeon q.p.rav))
+>.$(qyx (~(put by qyx) hen rav))
=+ huy=(aeon q.p.rav)
?: &(?=(^ huy) |((lth u.huy u.nab) &(=(0 u.huy) =(0 u.nab))))
(blob hen)
=+ top=?~(huy let.dom u.huy)
=+ seb=(slag (sub let.dom top) hit.dom)
=+ wid=(sub top u.nab)
=+ fud=(flop (scag wid seb))
=. +>.$ (bleb hen u.nab fud)
?^ huy
(blob hen)
=+ ^= ptr ^- case
?: =(0 u.nab) [%da @da]
=+(old=(slag wid seb) ?>(?=(^ old) `case`[%da p.i.old]))
+>.$(qyx (~(put by qyx) hen `rave`[%| ptr q.p.rav]))
==
::
++ edit :: apply changes
|= [hen=duct wen=@da lem=maki]
^+ +>
?- -.lem
&
%= +>.$
ank.dom ?. ?=(& -.p.lem) ank.dom
ank:(durn:(zu ank.dom) p.p.lem)
let.dom +(let.dom)
hit.dom :_(hit.dom [wen lem])
lab.dom ?. ?=(| -.p.lem) lab.dom
?< (~(has by lab.dom) p.p.lem)
(~(put by lab.dom) p.p.lem let.dom)
vag
?~(hez.yar vag :_(vag [u.hez.yar [%ergo who syd +(let.dom)]]))
::
yel
=+ pre=`path`~[(scot %p for) syd (scot %ud +(let.dom))]
?- -.p.lem
| :_ yel
[hen %note '=' %leaf :(weld (trip p.p.lem) " " (spud pre))]
& |- ^+ yel
?~ q.p.p.lem yel
:_ $(q.p.p.lem t.q.p.p.lem)
:- hen
:+ %note
?-(-.q.i.q.p.p.lem %del '-', %ins '+', %mut ':')
[%leaf (spud (weld pre p.i.q.p.p.lem))]
==
==
::
|
|- ^+ +>.^$
?~ s.p.lem +>.^$
$(s.p.lem t.s.p.lem, +>.^$ ^$(lem i.s.p.lem))
==
::
++ exec :: change and update
|= [hen=duct wen=@da lem=maki]
^+ +>
wake:(edit hen wen lem)
::
++ wake :: update subscribers
^+ .
=+ xiq=(~(tap by qyx) ~)
=| xaq=(list ,[p=duct q=rave])
|- ^+ ..wake
?~ xiq ..wake(qyx (~(gas by *cult) xaq))
?- -.q.i.xiq
&
=+ nao=(aeon q.p.q.i.xiq)
?~ nao $(xiq t.xiq, xaq [i.xiq xaq])
$(xiq t.xiq, ..wake (balk p.i.xiq u.nao p.q.i.xiq))
::
|
=+ mot=`moat`p.q.i.xiq
=+ nab=(aeon p.mot)
?: |(?=(~ nab) =(let.dom u.nab))
$(xiq t.xiq, xaq [i.xiq xaq])
?> (gte let.dom u.nab)
?> ?=(^ hit.dom)
=+ huy=(aeon q.mot)
?~ huy
=+ ptr=[%da p.i.hit.dom]
=+ fud=(flop (scag (sub let.dom u.nab) `(list frog)`hit.dom))
%= $
xiq t.xiq
xaq [[p.i.xiq [%| ptr q.mot]] xaq]
..wake (bleb p.i.xiq let.dom fud)
==
=+ yad=(slag (sub let.dom u.huy) `(list frog)`hit.dom)
=+ fud=(flop (scag (sub u.huy u.nab) yad))
%= $
xiq t.xiq
..wake (blob:(bleb p.i.xiq +(u.nab) fud))
==
==
::
++ zoot
%_(..de dos.yar (~(put by dos.yar) syd qyx dom))
--
::
++ di
|= syd=@ta
=+ ^= saq ^- desk
=+ saq=(~(get by dos.yar) syd)
?~(saq [~ [~ [@uvH ~ ~] 0 ~ ~]] u.saq)
~(. de who syd now p.saq q.saq)
::
++ fa
|= him=ship
=+ ^= raz
=+ raz=(~(get by rid.yar) him)
?~(raz [p=*rind q=*rink] u.raz)
|%
++ mete :: foreign request
|= [hen=duct ryf=riff]
^+ +>
=+ nux=(~(get by fod.p.raz) hen)
?^ nux
?> ?=(~ q.ryf)
%= +>.$
say [[[[%c (scot %ud u.nux) ~] hen] him [u.nux ryf]] say]
fod.p.raz (~(del by fod.p.raz) hen)
bim.p.raz (~(del by bim.p.raz) u.nux)
==
?~ q.ryf +>.$
=+ inx=nix.p.raz
%= +>.$
say [[[[%c (scot %ud inx) ~] hen] him [inx ryf]] say]
nix.p.raz +(nix.p.raz)
bim.p.raz (~(put by bim.p.raz) inx [hen ryf])
fod.p.raz (~(put by fod.p.raz) hen inx)
==
::
++ mote :: send/cancel request
|= [hen=duct ryf=riff]
^+ +>
(mete hen ryf)
:: =+ rym=(~(get by mir.q.raz) p.ryf)
:: ?~ rym (mete hen ryf)
:: =+ wex=~(. de [who p.ryf lim.u.rym qyx.u.rym dom.u.rym])
:: =+ wak=?~(q.ryf (ease:wex hen) (eave:wex hen u.q.ryf))
:: =: byn byn.wak
:: qyx.u.rym qyx.wak
:: dom.u.rym dom.wak
:: ==
:: +>.$(mir.q.raz (~(put by mir.q.raz) p.ryf u.rym))
::
++ poll :: pull result
|= [hen=duct syd=disc rot=riot]
^+ +>
=+ rum=(need (~(get by mir.q.raz) syd))
=+ kas=(need ask.rum)
=< abet
=< able
|%
++ abet
^+ +>.$
+>.$(mir.q.raz (~(put by mir.q.raz) syd rum))
::
++ able
^+ .
?~ rot
%- pith(ask.rum ~, lim.rum kas)
~(. de [him syd kas qyx.rum dom.rum])
?> ?=(%w p.p.u.rot)
?> =(syd r.p.u.rot)
?> =(~ q.u.rot)
?> ?=(%ud -.q.p.u.rot)
?> =(let.dom.rum p.q.p.u.rot)
=+ rog=((hard frog) r.u.rot)
=+ sab=`saba`[him syd [p.q.p.u.rot +(p.q.p.u.rot)] [q.rog ~]]
=. ..fa (fray hen pal.rum sab)
(pith (~(exec de [him syd lim.rum qyx.rum dom.rum]) hen rog))
::
++ pith
|= wex=_de
^+ +>
=+ wak=wake:wex
%_ +>.$
byn byn.wak
yel yel.wak
qyx.rum qyx.wak
dom.rum dom.wak
==
--
::
++ puke :: pull failed
|= [hen=duct syd=disc msg=tape]
^+ +>
%_ +>
mir.q.raz (~(del by mir.q.raz) syd)
yel [[hen [%note '?' %leaf msg]] yel]
==
::
++ pull :: pull changeset
|= [hen=duct syd=disc pal=(list disc)]
^+ +>
=+ ^= rum ^- rede
=+ rum=(~(get by mir.q.raz) syd)
?^ rum u.rum [~2000.1.1 ~ pal ~ [~ [@uvH ~ ~] 0 ~ ~]]
?> ?=(~ ask.rum)
=> .(ask.rum [~ now])
=. +>.$
%+ mete
[[%c %pull (scot %p him) syd ~] hen]
[syd ~ %| [%da lim.rum] [%da now]]
+>.$(mir.q.raz (~(put by mir.q.raz) syd rum))
::
++ tome :: accept response
|= [inx=@ud rot=riot]
^+ +>
:: ~& [%tome inx ?~(rot ~ [p.u.rot q.u.rot])]
=+ mub=(~(get by bim.p.raz) inx)
?~ mub +>.$
=+ die=?~(rot & &(?=(^ q.q.u.mub) ?=(& -.u.q.q.u.mub)))
%= +>.$
byn [[p.u.mub rot] byn]
bim.p.raz ?.(die bim.p.raz (~(del by bim.p.raz) inx))
fod.p.raz ?.(die fod.p.raz (~(del by fod.p.raz) p.u.mub))
hac.q.raz ?~ rot
hac.q.raz
%+ ~(put by hac.q.raz)
[p.p.u.rot q.p.u.rot r.p.u.rot q.u.rot]
r.u.rot
==
::
++ tref :: request rejected
|= [hen=duct tea=wire]
^+ +>
~& [%tref tea]
?. ?=([@ *] tea) +>
=+ xoc=(slay i.tea)
?: ?=([~ %$ %p @] xoc)
?> ?=([@ ~] t.tea)
(puke hen i.t.tea "system failure")
?. ?=([~ %$ %ud @] xoc) +>.$
=+ mub=(~(get by bim.p.raz) q.p.u.xoc)
?~ mub +>.$
%= +>.$
byn [[p.u.mub ~] byn]
fod.p.raz (~(del by fod.p.raz) q.p.u.xoc)
==
::
++ vera :: search
|= [syd=@tas ren=care lok=case way=path]
^- (unit)
=+ haz=(~(get by hac.q.raz) ren lok syd way)
?^ haz haz
=+ rym=(~(get by mir.q.raz) syd)
?~ rym ~
=+ vyr=(~(aver de [him syd lim.u.rym qyx.u.rym dom.u.rym]) ren lok way)
?~(vyr ~ u.vyr)
::
++ zoom
%_(+>.$ rid.yar (~(put by rid.yar) him raz))
--
--
--
::::::::::::::::::::::::::::::::::::::::::::::::::::::::
:: section 4cA, filesystem vane ::
:: ::
=| :: instrument state
$: ruf=raft :: revision tree
== ::
|= [now=@da eny=@ sky=||(* (unit))] :: activate
^? :: opaque core
|% ::
++ beat :: update
|= [wru=(unit writ) tea=wire hen=duct fav=curd]
=> .(fav ((hard card) fav))
^- [p=(list move) q=vane]
?+ -.fav [[[wru hen fav] ~] ..^$]
%crud
[[[wru [/d hen] %flog fav] ~] ..^$]
::
%deem
=. wru
?^ wru wru
?. =(%gold (adit hen)) ~
[~ %gold p.fav]
$(fav q.fav)
::
%init
:: [[%tell %0 %leaf "clay: home for {~(rend co ~ %p q.u.wru)}"] ~]
[~ ..^$(fat.ruf (~(put by fat.ruf) q.u.wru [hen ~ ~ ~ ~]))]
::
?(%into %info)
=. wru
?^ wru wru
?. =(%gold (adit hen)) ~
[~ %gold p.fav]
?> =(q.u.wru p.fav)
?: =(%$ q.fav)
?. ?=(%into -.fav) [~ ..^$]
=+ yar=(need (~(get by fat.ruf) p.fav))
[~ ..^$(fat.ruf (~(put by fat.ruf) p.fav yar(hez [~ hen])))]
=^ mos ruf
=+ ^= zot
zoot:(exec:(di:wake:(un q.u.wru now ruf) q.fav) hen now [%& r.fav])
abet:zot(hez.yar ?.(=(%into -.fav) hez.yar.zot [~ hen]))
[mos ..^$]
::
%pull
?> ?=(^ wru)
?> !=(q.u.wru q.fav)
=^ mos ruf
abet:zoom:(pull:(fa:(un q.u.wru now ruf) p.fav) hen q.fav r.fav)
[mos ..^$]
::
%warp
?> ?=(^ wru)
=^ mos ruf
=< abet
=+ une=(un q.u.wru now ruf)
:: ~& [%warp q.u.wru p.fav]
?. =(q.u.wru p.fav)
zoom:(mote:(fa:une p.fav) hen q.fav)
=+ wex=(di:une p.q.fav)
?~ q.q.fav
zoot:(ease:wex hen)
zoot:(eave:wex hen u.q.q.fav)
[mos ..^$]
::
%wart
?> ?=(%ru q.fav)
?~ s.fav [~ ..^$]
=^ mos ruf
=< abet
=< zoom
(tome:(fa:(un q.u.wru now ruf) p.fav) ((hard ,[@ud riot]) u.s.fav))
[mos ..^$]
::
%went
?: =(%good q.fav) [~ ..^$]
?> ?=([@ *] tea)
=+ une=(un q.u.wru now ruf)
=^ mos ruf
?+ i.tea ~&([%went-wrong tea] !!)
%pull
abet:zoom:(tref:(fa:une p.fav) hen t.tea)
==
[mos ..^$]
::
%wake
=+ dal=(turn (~(tap by fat.ruf) ~) |=([a=@p b=room] a))
=| mos=(list move)
|- ^- [p=(list move) q=vane]
?~ dal [mos ..^^$(las.ruf now)]
=^ som ruf abet:wake:(un i.dal now ruf)
$(dal t.dal, mos (weld som mos))
::
%wort
?> ?=([@ *] tea)
=+ une=(un q.u.wru now ruf)
=^ mos ruf
?+ i.tea !!
%pull
?> ?=([@ @ ~] t.tea)
=+ xoc=(slay i.t.tea)
?> ?=([~ %$ %p @] xoc)
=< abet
=< zoom
(puke:(fa:(un q.u.wru now ruf) q.p.u.xoc) hen i.t.t.tea p.fav)
==
[mos ..^$]
::
%writ
?> ?=([@ *] tea)
=+ une=(un q.u.wru now ruf)
=^ mos ruf
?+ i.tea ~&([%writ-bad tea] !!)
%pull
?> ?=([@ @ ~] t.tea)
=+ xoc=(slay i.t.tea)
?> ?=([~ %$ %p @] xoc)
=< abet
=< zoom
(poll:(fa:(un q.u.wru now ruf) q.p.u.xoc) hen i.t.t.tea p.fav)
==
[mos ..^$]
==
::
++ come
|= old=vase
^- vane
~|(%load-nest-clay !!)
::
++ doze
|= [now=@da hen=duct]
=| nex=(unit ,@da)
=+ dal=(turn (~(tap by fat.ruf) ~) |=([a=@p b=room] a))
|- ^+ nex
?~ dal nex
$(dal t.dal, nex (hunt nex doze:(un i.dal now ruf)))
::
++ flee stay
::
++ load
|= new=vase
^- vane
?. (~(nest ut -:!>(ruf)) & p.new)
(come new)
..^$(ruf (raft q.new))
::
++ raze
^- vane
..$(ruf *raft)
::
++ scry :: inspect
|= [our=ship ron=@tas his=ship syd=disc lot=coin tyl=path]
^- (unit)
=+ luk=?.(?=(%$ -.lot) ~ ((soft case) p.lot))
=+ run=((soft care) ron)
?~ luk ~
?~ run ~
?. =(our his)
(vera:(fa:(un our now ruf) his) syd u.run u.luk tyl)
=+ vyr=(aver:(di:(un our now ruf) syd) u.run u.luk tyl)
?~(vyr ~ u.vyr)
::
++ stay `vase`!>(ruf)
--

349
arvo/dill.hoon Normal file
View File

@ -0,0 +1,349 @@
::
:: dill (4d), terminal handling
::
|= pit=vase
^- vane :: kernel instrument
=| $: dug=(map duct yard)
== ::
|= [now=@da eny=@ sky=||(* (unit))] :: current invocation
^? :: opaque core
|% :: poke/peek pattern
++ beat :: process move
|= [wru=(unit writ) tea=wire hen=duct fav=curd]
=> .(fav ((hard card) fav))
^- [p=(list move) q=vane]
?: ?=(%flog -.fav)
:_ ..^$
%+ turn (~(tap by dug) *(list ,[p=duct q=yard]))
|=([a=duct b=yard] [wru [/d a] p.fav])
=+ ^= yar ^- yard
=+ yar=(~(get by dug) hen)
?^ yar u.yar
[& [80 ~ *blot] ~]
=| mos=(list move)
=+ wip=|
=< yerk:leap
|%
++ beep (curb [[%bel ~] ~]) :: send beep
++ curb :: send blits
|= wab=(list blit)
^+ +>
?~ wab +>
+>(mos [[~ hen [%blit (flop wab)]] mos])
::
++ edit :: change the bed
|= bed=bead
^+ +>
=. q.q.yar [~ bed]
%- curb
:~ [%hop (add pol.bed bus.bed)]
:- %lin
%+ weld pot.bed
?- buy.bed
%none but.bed
%text but.bed
%pass `(list ,@)`(runt [(lent but.bed) '*'] ~)
==
==
::
++ fume :: print tank, prefix
|= [pef=@tD tac=tank]
^+ +>
=+ wol=(~(win re tac) 2 p.q.yar)
%- furl
%+ turn wol
|= a=tape ^- tape
?> ?=([@ @ *] a)
[pef ' ' t.t.a]
::
++ furl :: print wall
|= wol=(list tape)
^+ +>
=. +>
%- curb
%- flop
|- ^- (list blit)
?~ wol ~
[[%lin (tuba i.wol)] [%mor ~] $(wol t.wol)]
?~ q.q.yar +>
(edit(q.q.yar ~) u.q.q.yar)
::
++ gore :: move in history
|= hup=@ud
^+ +>
=+ ^= but ^- (list ,@c)
=+ byt=(~(get by hym.u.q.q.yar) hup)
?^ byt u.byt
(tuba (rip 3 (snag hup q.hyt.u.q.q.yar)))
=+ bul=(lent but)
%- edit
%= u.q.q.yar
hiz hup
hym %+ ~(put by hym.u.q.q.yar)
hiz.u.q.q.yar
but.u.q.q.yar
bus bul
bul (lent but)
but but
==
::
++ kill :: add to kill ring
|= txt=(list ,@c)
^+ +>
=> ?. =(16 p.r.q.yar) .
.(p.r.q.yar 15, r.r.q.yar (scag 15 r.r.q.yar))
%= +>
p.r.q.yar +(p.r.q.yar)
q.r.q.yar 0
r.r.q.yar [txt r.r.q.yar]
==
::
++ leap :: terminal event
|- ^+ +
?+ -.fav
+(mos :_(mos [wru hen fav]))
%noop +
::
%belt :: terminal input
?~ q.q.yar
beep
?- -.p.fav
%aro :: arrow
?- p.p.fav
%d :: down
?: =(0 hiz.u.q.q.yar)
beep
(gore (dec hiz.u.q.q.yar))
::
%l :: left
?: =(0 bus.u.q.q.yar)
beep
(edit u.q.q.yar(bus (dec bus.u.q.q.yar)))
::
%r :: right
?: =(bul.u.q.q.yar bus.u.q.q.yar)
beep
(edit u.q.q.yar(bus +(bus.u.q.q.yar)))
::
%u
=+ hup=+(hiz.u.q.q.yar)
?: =(hup p.hyt.u.q.q.yar)
beep
(gore hup)
==
::
%bac :: backspace
^+ +.$
?: =(0 bus.u.q.q.yar)
(curb `(list blit)`[[%bel ~] ~])
%- edit
%= u.q.q.yar
bus (dec bus.u.q.q.yar)
bul (dec bul.u.q.q.yar)
but
%+ weld
(scag (dec bus.u.q.q.yar) but.u.q.q.yar)
(slag bus.u.q.q.yar but.u.q.q.yar)
==
::
%ctl :: control
?+ p.p.fav
beep
%a (edit u.q.q.yar(bus 0))
%b $(fav [%belt %aro %l])
%c +.$(mos :_(mos [wru [/b /d hen] [%kill ~]]))
%d ?: ?& =(0 bul.u.q.q.yar)
=(0 bus.u.q.q.yar)
==
$(fav [%logo ~])
$(fav [%belt %del ~])
%e (edit u.q.q.yar(bus bul.u.q.q.yar))
%f $(fav [%belt %aro %r])
%k ?: =(bul.u.q.q.yar bus.u.q.q.yar)
beep
=> .(+.$ (kill (slag bus.u.q.q.yar but.u.q.q.yar)))
%- edit
%= u.q.q.yar
bul bus.u.q.q.yar
but (scag bus.u.q.q.yar but.u.q.q.yar)
==
%l +.$(mos :_(mos [~ hen %blit [[%clr ~] ~]]))
%n $(fav [%belt %aro %d])
%p $(fav [%belt %aro %u])
%u ?: =(0 bus.u.q.q.yar)
beep
=> .(+.$ (kill (scag bus.u.q.q.yar but.u.q.q.yar)))
%- edit
%= u.q.q.yar
bus 0
bul (sub bul.u.q.q.yar bus.u.q.q.yar)
but (slag bus.u.q.q.yar but.u.q.q.yar)
==
%w +.$(mos :_(mos [wru [/b /d hen] [%limn ~]]))
%x +.$(mos :_(mos [wru [/b /d hen] [%ling ~]]))
%y ?: =(0 p.r.q.yar)
beep
$(fav [%belt %txt (snag q.r.q.yar r.r.q.yar)])
==
::
%del :: delete
?: =(bul.u.q.q.yar bus.u.q.q.yar)
beep
%- edit
%= u.q.q.yar
bul (dec bul.u.q.q.yar)
but
%+ weld
(scag bus.u.q.q.yar but.u.q.q.yar)
(slag +(bus.u.q.q.yar) but.u.q.q.yar)
==
::
%met :: meta
?+ p.p.fav
beep
%y
?: =(0 p.r.q.yar)
beep
=+ dol=(snag q.r.q.yar r.r.q.yar)
=+ leo=(lent dol)
?. (gte bus.u.q.q.yar leo)
beep
=+ pey=(sub bus.u.q.q.yar leo)
?. =(dol (swag [pey leo] but.u.q.q.yar))
beep
=. q.r.q.yar ?:(=(p.r.q.yar +(q.r.q.yar)) 0 +(q.r.q.yar))
=+ ney=(snag q.r.q.yar r.r.q.yar)
=+ lye=(lent ney)
%- edit
%= u.q.q.yar
bus (sub (add bus.u.q.q.yar lye) leo)
bul (sub (add bul.u.q.q.yar lye) leo)
but %+ weld
(scag pey but.u.q.q.yar)
%+ weld
`(list ,@c)`ney :: XX weird fuse-loop
(slag bus.u.q.q.yar but.u.q.q.yar)
==
==
::
%ret :: return
=+ jab=(rap 3 (tufa but.u.q.q.yar))
%= +.$
q.q.yar ~
r.yar
?: |(=(%$ jab) =(%pass buy.u.q.q.yar))
r.yar
%+ ~(put by r.yar)
hux.u.q.q.yar
[p.hyt.u.q.q.yar [jab +.q.hyt.u.q.q.yar]]
::
mos
:* [~ [/b /d hen] [%hail ~]]
[~ hen [%bbye ~]]
[wru [/b /d hen] [%line jab]]
[~ hen [%blit [[%mor ~] ~]]]
mos
==
==
::
%txt :: text keys
=+ let=(lent p.p.fav)
%- edit
%= u.q.q.yar
bus (add let bus.u.q.q.yar)
bul (add let bul.u.q.q.yar)
but
;: weld
(scag bus.u.q.q.yar but.u.q.q.yar)
p.p.fav
(slag bus.u.q.q.yar but.u.q.q.yar)
==
==
==
::
%blew +.$(p.q.yar p.p.fav) :: window size
%boot
%= +.$
mos
:_(mos [wru [[%b ~] [%d tea] hen] p.fav])
==
::
%crud :: error trace
=. q.fav [[%leaf (trip p.fav)] q.fav]
|- ^+ +.^$
?~ q.fav +.^$
(fume:$(q.fav t.q.fav) '!' i.q.fav)
::
%helo :: trigger prompt
%- edit
=| bed=bead
=+ ^= hyt ^- hist
=+ hyt=(~(get by r.yar) p.fav)
?~(hyt *hist u.hyt)
=+ zon=(tuba r.q.fav)
=+ zow=(lent zon)
%= bed
bul zow
bus zow
but zon
buy p.q.fav
hux p.fav
hiz 0
hyt [+(p.hyt) [%$ q.hyt]]
pot q.q.fav
pol (lent q.q.fav)
==
::
?(%hail %make %loin %sith)
+.$(mos :_(mos [wru [/b /d hen] fav]))
::
%note ?.(p.yar +.$ (fume p.fav q.fav)) :: debug message
%save :: write a file
%= +.$
mos :_(mos [wru hen `card`[%blit [%sav p.fav q.fav] ~]])
==
::
%tell (furl (turn p.fav |=(a=@t (trip a)))) :: wall of text
%text $(fav [%talk %leaf p.fav]) :: simple message
%talk (furl (~(win re p.fav) 0 p.q.yar)) :: program output
%warn (fume '~' [%leaf p.fav]) :: system message
%wipe +.$(wip &) :: delete old
==
::
++ yerk :: complete core
^- [p=(list move) q=_..^$]
:- (flop mos)
..^$(dug ?.(wip (~(put by dug) hen yar) (~(del by dug) hen)))
--
::
++ come
|= old=vase
^- vane
~|(%load-nest-dill !!)
::
++ doze
|= [now=@da hen=duct]
^- (unit ,@da)
~
::
++ flee stay
++ load
|= new=vase
^- vane
?. (~(nest ut -:!>(dug)) & p.new)
(come new)
%_ ..^$
dug ((map duct yard) q.new)
==
::
++ raze
^- vane
..$(dug ~)
::
++ scry
|= [our=ship ren=@tas his=ship syd=disc lot=coin tyl=path]
^- (unit)
~
::
++ stay `vase`!>(dug)
--

166
arvo/eyre.hoon Normal file
View File

@ -0,0 +1,166 @@
::
:: eyre (4e), http servant
::
|= pit=vase
^- vane :: kernel instrument
=> =~
|%
++ bolo :: eyre state
$: wig=(map duct (list rout)) :: server routes
ged=duct :: client interface
giv=[p=@ud q=(map ,@ud duct)] :: incoming requests
ask=[p=@ud q=(map ,@ud ,[p=duct q=hiss])] :: outgoing requests
kes=(map duct ,@ud) :: outgoing requests
==
::
++ ecco :: eat headers
|= hed=(list ,[p=@t q=@t])
=+ mah=*math
|- ^- math
?~ hed mah
=+ cus=(cass (rip 3 p.i.hed))
=+ zeb=(~(get by mah) cus)
$(hed t.hed, mah (~(put by mah) cus ?~(zeb [q.i.hed ~] [q.i.hed u.zeb])))
::
++ hone :: host match
|= [fro=host too=host] ^- ?
?- -.fro
| =(too fro)
&
?& ?=(& -.too)
|- ^- ?
?~ p.too &
?~ p.fro |
?: !=(i.p.too i.p.fro) |
$(p.too t.p.too, p.fro t.p.fro)
==
==
::
++ loot :: match route
|= [uri=purl rut=rout]
^- (unit scud)
?. |- ^- ?
?~ p.rut |
=(i.p.rut `host`r.p.uri)
~
=+ tac=*path
|- ^- (unit scud)
?~ q.rut
:- ~
:- :(weld (flop q.q.uri) tac s.rut)
`scar`[p.uri (flop tac) p.q.uri s.rut]
?: |(?=(~ q.q.uri) !=(i.q.rut i.q.q.uri))
~
$(q.rut t.q.rut, q.q.uri t.q.q.uri, tac [i.q.rut tac])
--
. ==
=| bolo
|= [now=@da eny=@ sky=||(* (unit))] :: activate
^? :: opaque core
|% ::
++ beat :: process move
|= [wru=(unit writ) tea=wire hen=duct fav=curd]
=> .(fav ((hard card) fav))
^- [p=(list move) q=vane]
?+ -.fav
[[[wru hen fav] ~] ..^$]
::
%band :: set/clear route
[~ ..^$(wig ?~(q.fav (~(del by wig) hen) (~(put by wig) hen q.fav)))]
::
%born
[~ ..^$(ged hen)] :: XX retry all gets, abort all puts
::
%crud
[[[wru [/d hen] %flog fav] ~] ..^$]
::
%that :: response by us
=+ neh=(need (~(get by q.giv) p.fav))
:_ ..^$(q.giv (~(del by q.giv) p.fav))
:_ ~
:+ ~ neh
:- %thou
^- httr
?- -.q.fav
%mid [200 ~[content-type/(moon p.q.fav)] [~ q.q.fav]]
%ham [200 ~[content-type/'text/html'] [~ (tact (xmlt p.q.fav ~))]]
%raw p.q.fav
==
::
%them :: outgoing request
?~ p.fav
=+ sud=(need (~(get by kes) hen))
:- [[~ ged [%thus sud ~]] ~]
..^$(q.ask (~(del by q.ask) sud), kes (~(del by kes) hen))
:- [[~ ged [%thus p.ask p.fav]] ~]
%= ..^$
p.ask +(p.ask)
q.ask (~(put by q.ask) p.ask hen u.p.fav)
kes (~(put by kes) hen p.ask)
==
::
%they :: response to us
=+ kas=(need (~(get by q.ask) p.fav))
:- [[~ p.kas [%thou q.fav]] ~]
..^$(q.ask (~(del by q.ask) p.kas))
::
%this :: request to us
=+ ryp=`quri`(rash q.r.fav zest:epur)
=+ mah=(ecco r.r.fav)
=+ ^= pul ^- purl
?- -.ryp
& ?>(=(p.fav p.p.p.ryp) p.ryp)
| =+ hot=(~(get by mah) %host)
?> ?=([~ @ ~] hot)
[[p.fav (rash i.u.hot thor:epur)] p.ryp q.ryp]
==
=+ het=`hate`[pul (shaf %this q.fav) [p.r.fav mah s.r.fav]]
=+ gew=`(list ,[p=duct q=(list rout)])`(~(tap by wig) ~)
=+ ^= faw
|- ^- (list ,[p=duct q=scud])
?~ gew ~
=+ mor=$(gew t.gew)
=+ ^= woy
|- ^- (list scud)
?~ q.i.gew ~
=+ mor=$(q.i.gew t.q.i.gew)
=+ lut=(loot pul i.q.i.gew)
?~(lut mor [u.lut mor])
?~ woy mor
:: ?^ t.woy [[[~ hen [%thou 500 ~ ~]] ~] ..^^$]
[[p.i.gew i.woy] mor]
?~ faw [[[~ hen [%thou 404 ~ ~]] ~] ..^$]
:: ?^ t.faw [[[~ hen [%thou 500 ~ ~]] ~] ..^$]
:- [[~ p.i.faw `card`[%thee p.giv [q.i.faw r.pul] *cred r.het]] ~]
..^$(p.giv +(p.giv), q.giv (~(put by q.giv) p.giv hen))
==
::
++ come
|= old=vase
^- vane
~|(%load-nest-eyre !!)
::
++ doze
|= [now=@da hen=duct]
^- (unit ,@da)
~
::
++ flee stay
++ load
|= new=vase
^- vane
?. (~(nest ut -:!>(`bolo`+>-.^$)) & p.new)
(come new)
..^$(+>- (bolo q.new))
::
++ raze
^- vane
..$(+>- *bolo)
::
++ scry
|= [our=ship ren=@tas who=ship syd=disc lot=coin tyl=path]
^- (unit)
~
::
++ stay `vase`!>(`bolo`+>-.$)
--

7549
arvo/hoon.hoon Normal file

File diff suppressed because it is too large Load Diff

1831
arvo/zuse.hoon Normal file

File diff suppressed because it is too large Load Diff

195
main/bin/begin.hoon Normal file
View File

@ -0,0 +1,195 @@
!:
:: /=main=/bin/begin/hoon
::
=> .(-< `who=@p`-<)
=> .(+ =>(+ ^/===/lib/pony))
|= [est=time *]
|= arg=$|(~ [p=@p ~])
=- ^- bowl
?^ arg (fud p.arg)
%+ pomp ""
%+ (polo ~ %text "Do you have a ship and a ticket? " "yes" ~)
;~(pose (jest %yes) (just %no))
|= [* ans=@t]
?. =(%yes ans)
:_ ~
:~ [%la %leaf "Please ask curtis.yarvin@gmail.com for one."]
==
%+ (polo ~ %text "Your ship: ~" ~ ~)
fed:ag
|= [* mig=@p]
^- bowl
(fud mig)
^= fud
|= mig=@p
=+ bos=(sein mig)
?> !=(bos mig)
=< main
|%
++ looc ;~(pose alp (shim 128 255))
++ loon
%+ cook
|= all=(list ,@t)
|- ^- @t
?~ all %$
?~ t.all i.all
(cat 3 i.all (cat 3 ' ' $(all t.all)))
(most ace (cook |=(a=(list ,@) (rap 3 a)) (plus looc)))
::
++ main
^- bowl
=+ ran=(clan mig)
=+ ^= cow
|- ^- @ud
?- ran
%czar 256
%king (mul 255 $(ran %czar))
%duke (mul 65.535 $(ran %king))
%earl (mul (dec (bex 32)) $(ran %duke))
%pawn (sub (bex 128) $(ran %earl))
==
=+ ^= ves ^- tape
?- ran
%czar "carriers"
%king "cruisers"
%duke "destroyers"
%earl "yachts"
%pawn "submarines"
==
=+ gup=(scow %p mig)
%+ pomp ""
%+ pomp "Launching {gup}, one of {<cow>} Urbit {ves}..."
%+ pomp ""
%+ pomp " If I did not build for myself"
%+ pomp " for whom should I build?"
%+ pomp ""
%+ pomp " -- Bunting, _Chomei at Toyama_"
%+ pond ^:@/===doc%/warning/txt
%+ (polo ~ %text "Your ticket: ~" ~ ~)
fed:ag
|= [* tic=@p]
%+ pond ^:@/===doc%/entropy/txt
%+ (polo ~ %pass "Entropy: " ~ ~)
(boss 256 (more gon qit))
|= [* tey=@]
=. tey (shax tey)
%+ pomp "Entropy check: {<`@p`(mug tey)>}"
%+ pond ^:@/===doc%/language/txt
%+ (polo ~ %text "Language: " "en" ~)
%+ sear
|= [a=@ b=@]
^- (unit ,@ta)
=+ c=(cat 3 a b)
=+(d=(glon c) ?~(d ~ [~ c]))
;~(plug low low)
|= [* lag=lang]
%+ pomp ""
%+ pomp "Okay, we'll be speaking {(need (glon lag))}."
^- bowl
?. ?=(%duke ran)
%+ (polo ~ %text "Name: " ~ ~)
(boss 256 (more gon qit))
|= [now=@da nam=@]
(moss now tic tey lag (gcos [ran nam]))
%+ pond ^:@/===doc%/identity/txt
%+ (polo ~ %text "Form: %" "lady" ~)
;~ pose
(jest %anon)
(jest %band)
(jest %crew)
(jest %dept)
(jest %fair)
(jest %holy)
(jest %home)
(jest %lady)
(jest %lord)
(jest %punk)
==
|= [now=@da fom=@t]
?+ fom !!
%anon (moss now tic tey lag [%duke %anon ~])
%punk
%+ (polo ~ %text "Handle: " ~ ~)
(boss 256 (plus alp))
|= [now=@da puc=@t]
(moss now tic tey lag [%duke %punk puc])
::
?(%band %crew %dept %fair %home %holy)
%- moon
|= [* gov=govt]
%+ (polo ~ %text "Name: " ~ ~)
loon
|= [now=@da nam=@t]
(moss now tic tey lag [%duke (what fom `corp`[nam gov])])
::
?(%lord %lady)
%+ pond ^:@/===doc%/person/txt
%+ (polo ~ %text "Year you were born: " "19" ~)
dim:ag
|= [* yar=@]
%- moon
|= [* gov=govt]
%+ pond ^:@/===doc%/name/txt
%+ (polo ~ %text "First name: " ~ ~)
loon
|= [* fis=@t]
%+ (polo ~ %text "Middle name (or blank): " ~ ~)
;~(pose (stag ~ loon) (easy ~))
|= [* mid=(unit ,@t)]
%+ (polo ~ %text "Nickname/handle (or blank): " ~ ~)
;~(pose (stag ~ loon) (easy ~))
|= [* nik=(unit ,@t)]
%+ (polo ~ %text "Last name: " ~ ~)
loon
|= [* las=@t]
%+ pond ^:@/===doc%/banner/txt
%+ (polo ~ %text "Banner: %" "blue" ~)
;~ pose
(jest %white)
(jest %blue)
(jest %red)
(jest %black)
(jest %orange)
==
|= [now=@da ban=@t]
=> .(ban (?(%white %blue %red %black %orange) ban))
=+ nam=`name`[fis mid nik las]
(moss now tic tey lag `gcos`[%duke %lord `whom`[yar gov ban nam]])
==
::
++ moon
|* woo=||([@da govt] bowl)
%+ pond ^:@/===doc%/location/txt
%+ (polo ~ %text "Location: " "us/94114" ~)
;~ pose
;~ plug
(cook |=([a=@ b=@] (cat 3 a b)) ;~(plug low low))
;~ pose
;~(pfix fas (plus ;~(pose hig hep nud)))
(easy ~)
==
==
(easy ~)
==
woo
::
++ moss
|= [now=@da tic=@p tey=@ ges=gens]
^- bowl
=+ bur=(shax :(mix (jam ges) tey))
%+ (posh (add ~s1 now)) ~[la/leaf/"generating 2048-bit RSA key..."]
|= now=@da
=+ loy=(brew 2.048 bur)
%- (post bos [%ta %to] [mig tic ges pub:ex:loy])
|= [now=@da rup=(unit ,*)]
:_ ~
?~ rup ~[la/leaf/"request rejected"]
=+ mac=`mace`[[0 sec:ex:loy] ~]
=+ wil=((hard (unit will)) u.rup)
?~ wil
:~ [%la %leaf "request rejected - invalid ticket"]
==
:~ [%la %leaf "request approved"]
[%xy /a `card`[%cash mig mac u.wil]]
==
--

16
main/bin/cat.hoon Normal file
View File

@ -0,0 +1,16 @@
!:
:: /=main=/toy/cat/hoon
::
|= *
|= ape=(list path)
:_ ~
:_ ~
^- gift
:+ %mu [%atom %t]
=- |- ^- (list ,@t)
?~(foz ~ (weld i.foz $(foz t.foz)))
^= foz
=| foz=(list (list ,@t))
|- ^+ foz
?~ ape ~
[(lore ((hard ,@) .^(%cx i.ape))) $(ape t.ape)]

27
main/bin/cd.hoon Normal file
View File

@ -0,0 +1,27 @@
!:
:: /=main=/bin/cd/hoon
::
=> .(-< `who=@p`-<)
|= [est=time *]
|= arg=$|(~ [p=path ~])
:_ ~
^- (list gift)
?~ arg
:~ [%cc ~]
[%cs ~]
==
?. ?=(^ p.arg) ~
?. =(i.p.arg (scot %p who)) ~|(%bad-ship !!)
?. ?=(^ t.p.arg) ~
=+ gav=(slay i.t.p.arg)
?. ?=([~ %$ %tas *] gav) ~|(%bad-desk !!)
:- [%ck q.p.u.gav]
?. ?=(^ t.t.p.arg) ~
=+ gov=(slay i.t.t.p.arg)
:- :- %cc
?+ gov ~|(%bad-case !!)
[~ %$ %da *] ?:(=(est q.p.u.gov) ~ [~ %da q.p.u.gov])
[~ %$ %ud *] [~ %ud q.p.u.gov]
[~ %$ %tas *] [~ %tas q.p.u.gov]
==
[[%cs t.t.t.p.arg] ~]

15
main/bin/diff.hoon Normal file
View File

@ -0,0 +1,15 @@
!:
:: /=main=/toy/cat/hoon
::
|= *
|= [del=path dev=path ~]
:_ ~
:_ ~
^- gift
=+ [hel=(lore ((hard ,@) .^(%cx del))) hev=(lore ((hard ,@) .^(%cx dev)))]
=+ dis=(loss hel hev)
=+ puc=(lusk hel hev dis)
=+ rev=(lurk hel puc)
=+ ver=(lurk hev (berk puc))
?> &(=(rev hev) =(ver hel))
[%la >puc<]

6
main/bin/echo.hoon Normal file
View File

@ -0,0 +1,6 @@
!:
:: /=main=/toy/echo/hoon
::
|= *
|= tan=(list tank)
[(turn tan |=(a=tank [%la a])) ~]

23
main/bin/env.hoon Normal file
View File

@ -0,0 +1,23 @@
!:
:: /=main=/bin/env/hoon
::
=> .(- [who=`@p`-< how=`path`->])
|= [est=time eny=@uw]
|= arg=(list)
^- bowl
:_ ~
=+ ^= voy ^- (list tape)
:~ "who: {<who>}"
"how: {<how>}"
"est: {<est>}"
"eny: {<eny>}"
==
::
=+ ^= gar
=+ nix=1
|- ^- (list tape)
?~ arg ~
:_ $(arg t.arg, nix +(nix))
"arg: {(pave !>(nix))}: {(pave !>(i.arg))}"
::
(turn (weld voy gar) |=(a=tape [%la %leaf a]))

9
main/bin/hello.hoon Normal file
View File

@ -0,0 +1,9 @@
::
:: /=main=/bin/hello/hoon
::
|= *
|= [planet=@ta ~]
^- bowl
:_ ~ :_ ~
:- %$
!>("hello, {(trip planet)}.")

21
main/bin/hi.hoon Normal file
View File

@ -0,0 +1,21 @@
!:
:: /=main=/toy/hi/hoon
::
|= *
|= [bud=@p ebb=$|(~ [tex=tape ~])]
^- bowl
:- ~
:- ~
:- ^- (list slip)
:~ [/foo/bar [%yo bud %hi ?~(ebb '' (rap 3 tex.ebb))]]
==
|= [now=@da pax=path nut=note]
?> =(/foo/bar pax)
?> ?=(%yo -.nut)
:- ?: =(%good q.nut)
~
:_ ~
:- %ha
:- %leaf
"hi: {<p.nut>}.{<p.p.r.nut>} spurned {<q.r.nut>}/{<q.p.r.nut>}/{<r.r.nut>}"
~

10
main/bin/hupdate.hoon Normal file
View File

@ -0,0 +1,10 @@
!:
:: /=main=/bin/hupdate/hoon
::
=> .(-< `who=@p`-<)
|= *
|= ~
:_ ~
=+ bos=(sein who)
:~ [%xy /c [%pull bos %arvo ~[%arvo]]]
==

9
main/bin/label.hoon Normal file
View File

@ -0,0 +1,9 @@
!:
:: /=main=/bin/label/hoon
::
|= *
|= [syd=@tas lab=@tas ~]
^- bowl
:_ ~
:~ [%ok syd %| lab]
==

13
main/bin/ls.hoon Normal file
View File

@ -0,0 +1,13 @@
!:
:: /=main=/bin/ls/hoon
::
|= *
|= [pax=path ~]
:_ ~
^- (list gift)
=+ lon=((hard arch) .^(%cy pax))
?: =(~ r.lon) ~
:_ ~
:- %la
:+ %rose [" " "" ""]
(turn (~(tap by r.lon) ~) |=([a=@ta b=*] [%leaf (trip a)]))

7
main/bin/none.hoon Normal file
View File

@ -0,0 +1,7 @@
!:
:: /=main=/bin/none/hoon
::
|= *
|= *
^- bowl
[~ ~]

41
main/bin/nusolid.hoon Normal file
View File

@ -0,0 +1,41 @@
!:
:: /=main=/bin/solid/hoon
::
=> .(- [who=`@p`-< how=`path`->])
|= [est=time eny=@uw]
|= arg=*
=+ ^= lok ^- case
?: =(~ arg) [%da est]
?> =(~ +.arg)
((hard case) -.arg)
=+ cav=(scot (dime lok))
=+ top=`path`[(scot %p who) %arvo cav ~]
=+ pax=`path`(weld top `path`[%hoon ~])
~& %solid-start
=+ gen=(reck pax)
~& %solid-parsed
=+ ken=q:(~(mint ut %noun) %noun gen)
~& %solid-compiled
=+ ^= all
=+ all=.*(0 ken)
=+ ^= vay ^- (list ,[p=@tas q=@tas])
:~ [%$ %zuse]
[%a %ames]
[%b %behn]
[%c %clay]
[%d %dill]
[%e %eyre]
==
|- ^+ all
?~ vay all
=+ pax=(weld top `path`[q.i.vay ~])
=+ txt=((hard ,@) .^(%cx (weld pax `path`[%hoon ~])))
=+ sam=[est `ovum`[[%gold ~] [%veer p.i.vay pax txt]]]
~& [%solid-veer i.vay]
=+ gat=.*(all .*(all [0 42]))
=+ nex=+:.*([-.gat [sam +>.gat]] -.gat)
$(vay t.vay, all nex)
:_ ~ :_ ~
=+ pac=(jam [ken all])
~& %solid-finished
[%xx %save [%urbit %pill ~] pac]

19
main/bin/pope.hoon Normal file
View File

@ -0,0 +1,19 @@
!:
:: /=main=/bin/pope/hoon
::
=> .(+ =>(+ ^/===/lib/pony))
|= [est=time *]
|= [who=@p ~]
^- bowl
%+ (polo ~ %pass "passphrase: " ~)
(boss 256 (more gon qit))
|= [now=@da fra=@]
%+ (posh (add ~s1 now))
~[la/leaf/"generating carrier {(scow %p who)} (#{(scow %ud who)})"]
|= now=@da
:_ ~
=+ bur=(shax (add who (shax fra)))
=+ arc=(brew 2.048 bur)
:~ [%la %leaf "generator: {(scow %uw bur)}"]
[%la %leaf "fingerprint: {(scow %uw fig:ex:arc)}"]
==

41
main/bin/ram.hoon Normal file
View File

@ -0,0 +1,41 @@
!:
:: /=main=/bin/ram/hoon
::
=> .(- `[who=@p how=path]`-)
|= *
|= ape=(list path)
=+ ^= maw ^- (list slip)
:~ [~ %$ %noun]
==
:- ~ :- ~
:- maw
|= [now=@da pax=path nut=note]
^- bowl
?+ -.nut [~ ~ maw ..$]
%$
?~ p.nut [~ ~]
=| giv=(list gift)
|- ^- bowl
?: |(?=(~ ape) ?=(~ q.u.p.nut))
[giv ~ maw ..^$]
=+ pax=i.ape
?> ?=([@ @ @ *] pax)
?> &(=(i.pax (scot %p who)) =(i.t.t.pax (scot %da now)))
%= $
ape t.ape
giv
:_ giv
^- gift
:+ %ok i.t.pax
^- nori
:- %&
^- soba
:_ ~
:- t.t.t.pax
^- miso
=+ fil=(file pax)
?~ fil
[%ins i.q.u.p.nut]
[%mut %a %a u.fil i.q.u.p.nut]
==
==

12
main/bin/rat.hoon Normal file
View File

@ -0,0 +1,12 @@
!:
:: /=main=/bin/rat/hoon
::
|= *
|= ape=(list path)
:_ ~
:_ ~
^- gift
:+ %mu %noun
|- ^- (list)
?~ ape ~
[.^(%cx i.ape) $(ape t.ape)]

25
main/bin/reboot.hoon Normal file
View File

@ -0,0 +1,25 @@
!:
:: /=main=/fun/reboot/hoon
::
=> .(- `[who=@p how=path]`-)
|= [est=time eny=@uw]
|= arg=*
=+ ^= lok ^- case
?: =(~ arg) [%da est]
?> =(~ +.arg)
((hard case) -.arg)
=+ pre=`path`[(scot %p who) %arvo ~(rent co %$ (dime lok)) ~]
=+ ^= vay ^- (list ,[p=@tas q=@tas])
:~ [%$ %zuse]
[%a %ames]
[%b %batz]
[%c %clay]
[%d %dill]
[%e %eyre]
==
:_ ~
%+ turn vay
|= [saw=@tas nam=@tas]
=+ pax=(weld pre `path`[nam ~])
=+ txt=.^(%cx (weld pax `path`[%hoon ~]))
[%xx [%veer saw pax txt]]

9
main/bin/reload.hoon Normal file
View File

@ -0,0 +1,9 @@
!:
:: /=main=/toy/veer/hoon
::
=> .(- `[who=@p how=path]`-)
|= [est=time *]
|= [nam=@tas ~]
=+ tip=(end 3 1 nam)
=+ pax=[(scot %p who) %arvo (scot %da est) nam %hoon ~]
[[[%xx [%veer ?:(=('z' tip) %$ tip) pax (,@ .^(%cx pax))]] ~] ~]

35
main/bin/reset.hoon Normal file
View File

@ -0,0 +1,35 @@
!:
:: /=main=/fun/reset/hoon
::
=> .(-< `who=@p`-<)
|= [est=time *]
|= arg=*
=+ ^= lok ^- case
?: =(~ arg) [%da est]
?> =(~ +.arg)
((hard case) -.arg)
=+ cav=(scot (dime lok))
=+ top=`path`[(scot %p who) %arvo cav ~]
=+ pax=`path`(weld top `path`[%hoon ~])
~& %reset-start
=+ gen=(reck pax)
~& %reset-parsed
=+ ken=q:(~(mint ut %noun) %noun gen)
=+ all=.*(0 ken)
~& %reset-compiled
:_ ~
:- [%xx %volt all]
^- (list gift)
=+ ^= vay ^- (list ,[p=@tas q=@tas])
:~ [%$ %zuse]
[%a %ames]
[%b %batz]
[%c %clay]
[%d %dill]
[%e %eyre]
==
%+ turn vay
|= [a=@tas b=@tas]
=+ pax=(weld top `path`[b ~])
=+ txt=((hard ,@) .^(%cx (weld pax `path`[%hoon ~])))
`gift`[%xx %veer a pax txt]

22
main/bin/set.hoon Normal file
View File

@ -0,0 +1,22 @@
!:
:: /=main=/bin/set/hoon
::
|= *
|= [nam=@tas ~]
=+ ^= rod ^- (list slip)
:~ [~ %$ %noun]
==
:- ~ :- ~
:- rod
|= [now=@da pax=path nut=note]
^- bowl
?> ?=(%$ -.nut)
?~ p.nut
:_ ~
:~ [%va nam ~]
==
?~ q.u.p.nut
[~ ~ rod ..$]
:_ ~
:~ [%va nam ~ p.u.p.nut -.q.u.p.nut]
==

41
main/bin/solid.hoon Normal file
View File

@ -0,0 +1,41 @@
!:
:: /=main=/bin/solid/hoon
::
=> .(- `[who=@p how=path]`-)
|= [est=time eny=@uw]
|= arg=*
=+ ^= lok ^- case
?: =(~ arg) [%da est]
?> =(~ +.arg)
((hard case) -.arg)
=+ cav=(scot (dime lok))
=+ top=`path`[(scot %p who) %arvo cav ~]
=+ pax=`path`(weld top `path`[%hoon ~])
~& %solid-start
=+ gen=(reck pax)
~& %solid-parsed
=+ ken=q:(~(mint ut %noun) %noun gen)
~& %solid-compiled
=+ ^= all
=+ all=.*(0 ken)
=+ ^= vay ^- (list ,[p=@tas q=@tas])
:~ [%$ %zuse]
[%a %ames]
[%b %batz]
[%c %clay]
[%d %dill]
[%e %eyre]
==
|- ^+ all
?~ vay all
=+ pax=(weld top `path`[q.i.vay ~])
=+ txt=((hard ,@) .^(%cx (weld pax `path`[%hoon ~])))
=+ sam=[est `ovum`[[%gold ~] [%veer p.i.vay pax txt]]]
~& [%solid-veer i.vay]
=+ gat=.*(all .*(all [0 42]))
=+ nex=+:.*([-.gat [sam +>.gat]] -.gat)
$(vay t.vay, all nex)
:_ ~ :_ ~
=+ pac=(jam [ken all])
~& %solid-finished
[%xx %save [%urbit %pill ~] pac]

6
main/bin/sys.hoon Normal file
View File

@ -0,0 +1,6 @@
!:
:: /=main=/toy/sys/hoon
::
|= *
|= [pax=path fav=card ~]
[[[%xy pax fav] ~] ~]

27
main/bin/ticket.hoon Normal file
View File

@ -0,0 +1,27 @@
!:
:: /=main=/bin/ticket/hoon
::
=> .(-< `who=@p`-<)
|= [est=time *]
|= arg=*
^- bowl
:_ ~
=+ ^= fir ^- [p=@p q=@ud]
?: ?=([@ ~] arg)
[-.arg 1]
?: ?=([@ @ ~] arg)
[-.arg +<.arg]
~|(%ticket-arg !!)
?> &(=(who (sein p.fir)) =(who (sein (add p.fir (dec q.fir)))))
=+ ^= sep ^- @
=+ mir=(clan p.fir)
?+ mir ~|(%ticket-clan !!)
%king (bex 8)
%duke (bex 16)
%earl (bex 32)
==
|- ^- (list gift)
?: =(0 q.fir) ~
=+ tic=(,@p .^(%a (scot %p who) %tick (scot %da est) (scot %p p.fir) ~))
:- [%la %leaf "{<p.fir>}: {<tic>}"]
$(p.fir (add sep p.fir), q.fir (dec q.fir))

12
main/bin/update.hoon Normal file
View File

@ -0,0 +1,12 @@
!:
:: /=main=/bin/update/hoon
::
=> .(-< `who=@p`-<)
|= *
|= ~
:_ ~
=+ bos=(sein who)
:~ [%xy /c [%pull bos %main ~[%main]]]
[%xy /c [%pull bos %spec ~[%spec]]]
[%xy /c [%pull bos %arvo ~[%arvo]]]
==

18
main/bin/with.hoon Normal file
View File

@ -0,0 +1,18 @@
!:
:: /=main=/bin/with/hoon
::
|= [est=@da *]
|= arg=(list path)
^- bowl
:_ ~
^- (list gift)
=< abet
|%
++ abet ?:(=(~ arg) [[%sc ~] ~] (turn arg |=(a=path `gift`[%sc ~ (with a)])))
++ with
|= pax=path ^- skit
?> ?=([@ @ @ *] pax)
:+ ?:(=((scot %da est) i.t.t.pax) ~ [~ i.t.t.pax])
[i.pax i.t.pax ~]
t.t.t.pax
--

23
main/bin/ye.hoon Normal file
View File

@ -0,0 +1,23 @@
!:
:: /=main=/toy/ye/hoon
::
=> .(-< `who=@p`-<)
|= *
|= [ebb=$|(~ [tex=tape ~])]
=+ bud=(sein who)
^- bowl
:- ~
:- ~
:- ^- (list slip)
:~ [/foo/bar [%yo bud %ye ?~(ebb '' (rap 3 tex.ebb))]]
==
|= [now=@da pax=path nut=note]
?> =(/foo/bar pax)
?> ?=(%yo -.nut)
:- ?: =(%good q.nut)
~
:_ ~
:- %ha
:- %leaf
"hi: {<p.nut>}.{<p.p.r.nut>} spurned {<q.r.nut>}/{<q.p.r.nut>}/{<r.r.nut>}"
~

24
main/doc/begin/banner.txt Normal file
View File

@ -0,0 +1,24 @@
One basic human instinct is the urge to form political tribes.
In a network that fights this need, these tribes form anyway and
they form badly. Urbit designs them into the infrastructure.
Inspired by the Qing Dynasty, you'll align yourself with one of
five colored "banners" - %red, %blue, %orange, %black or %white.
Political discourse across tribal boundaries is almost always an
antisocial act - less communication, than symbolic violence. In
Urbit, messages marked political stay within your own banner;
your friends in other banners simply won't see them. Between
banners, politics doesn't erode apolitical relationships; inside
each banner, political discourse is harmonious and productive.
Pick a banner by the adjective you feel best describes you:
%red far left: radical, anarchist
%blue center-left: moderate, liberal
%orange center-right: conservative, libertarian
%black far right: traditionalist, reactionary
Or if digital agitation isn't your cup of tea, choose %white, and
your Urbit experience will remain politics-free.

View File

@ -0,0 +1,4 @@
Enter a passphrase or other unusual text. You (or your enemies)
can regenerate your ship from this entropy.

2
main/doc/begin/govt.txt Normal file
View File

@ -0,0 +1,2 @@
Enter

View File

@ -0,0 +1,14 @@
Please select one of the pre-chosen forms:
%lady female-identified individual
%lord male-identified individual
%punk opaque handle
%anon totally anonymous
%home family
%crew corporation
%band creative collective
%fair nonprofit
%dept government agency
%holy religious institution

View File

@ -0,0 +1,6 @@
What language would your ship rather speak? Enter it as a
two-letter (ISO 639-1) code, like "en" for English. Whatever
language you pick, it'll all be English now, but in future
we'll be more sensitive to your needs.

View File

@ -0,0 +1,5 @@
Where are you? This is totally optional, but we'd like to
know your vague general location. You can enter nothing at
all, just a country code, or country and postal code.

5
main/doc/begin/name.txt Normal file
View File

@ -0,0 +1,5 @@
Please tell us your name - and please make it a real name.
Pseudonyms are totally cool, but please use %punk. Middle
name and nickname are optional. Ünicode is encouraged.

19
main/doc/begin/person.txt Normal file
View File

@ -0,0 +1,19 @@
You've selected a personal identity. For a %lord or a %lady,
please use your real name only. If you'd prefer a fictitious
handle, you can hit ^C and start over as a %punk. Or you can
use %anon and go by your ship name alone.
As a real person, we're going to ask you for a little bit of
personal information - not enough to compromise your privacy,
just enough to make everyone on Urbit feel like a neighbor.
What we're going to ask you for is information that's (a)
public (would be obvious, or at least easy to guess, for
someone who met you in person); (b) durable (doesn't change
often); and (c) relevant (helps you connect with friends).
For example, we'll ask for the year (not day) you were born,
because your age is easy to guess in person, doesn't change,
and has a big effect on how people perceive you.

2
main/doc/begin/ship.txt Normal file
View File

@ -0,0 +1,2 @@

View File

@ -0,0 +1,2 @@
You should already have a ticket (invitation code).

View File

@ -0,0 +1,5 @@
Let's configure your identity. Warning - it's nontrivial to
change this data once you've sent it to the server. If you enter
something wrong, hit ^C to cancel, then run the program again.

162
main/lib/hume.hoon Normal file
View File

@ -0,0 +1,162 @@
!:
:: application standard library
::
=>
|% :: models
++ cron ?(%day %hour %minute %none %second) :: wake frequency
++ lamp :: simple web app
$_ ^? |% :: opaque object
++ give :: serve
|= [now=@da fig=weev] :: time, request
:- p=*(list gift) :: act
q=*(unit ,[p=(list slip) q=lamp]) :: request/continue
:: ::
++ miss :: redirect?
|= [pac=pact ced=cred] :: test and apply
^- (unit purl) ::
~ ::
-- ::
++ lump ,[p=path q=mime r=octs] :: submitted data
++ user ?(%born %came %died %left) :: user event
++ wick vase :: vase of lamp
++ weev :: web event
$% [%cron p=cron] :: wakeup
[%form p=pact q=quay] :: posted form
[%note p=path q=note] :: extrinsic note
[%post p=pact q=mime q=octs] :: non-form post
[%putt p=pact q=(list lump)] :: put
[%user p=user] :: user event
== ::
-- ::
|% :: functions
++ lunt :: web framework
|= :* who=ship :: owner
:: msg=tape :: prompt
ped=cron :: wake frequency
rut=(list rout) :: routes to
ras=wick :: server state
==
^- bowl
=+ ^= hup ^- (list slip)
:~ [/ [%ht rut]]
:: [/ [%up %none msg]]
==
:- *(list gift)
:- ~
:- hup
|= [now=@da pax=path nut=note]
^- bowl
=+ [saw=*(list gift) ask=*(list slip)]
=< zing:wist
|%
++ send :: dispatch event
|= bax=weev
^+ +>
=+ sam=!>([now bax])
=+ gat=(slap ras [%cnbc %give])
=+ pro=(slam gat sam)
=+ [wax=(slot 2 pro) hin=(slot 3 pro)]
=. saw (weld ((hard (list gift)) q.wax) saw)
?: =(~ q.hin)
+>.$
=+ [vis=(slot 6 hin) lym=(slot 7 hin)]
=+ ^= gin ^- (list slip)
%+ turn ((hard (list slip)) q.vis)
|=(a=slip [[%lunt p.a] q.a])
%= +>.$
ask (weld ((hard (list slip)) q.vis) ask)
q.ras q.lym
==
::
++ pass :: try redirect
|= [pac=pact ced=cred]
^- (unit purl)
=+ sam=!>([pac ced])
=+ gat=(slap ras [%cnbc %miss])
=+ pro=(slam gat sam)
?: =(~ q.pro) ~
=+ vur=(slot 3 pro)
[~ ((hard purl) q.vur)]
::
++ post :: handle post
|= [rid=@ud zab=scab ced=cred mot=moth]
^+ +>
?> ?=(^ r.mot)
=+ cot=(need (~(get by q.mot) %content-type))
=+ ^= guz ^- (unit quay)
?. =(cot ~['application/x-www-form-urlencoded']) ~
=+ vex=((full yquy:epur) [1 1] (trip q.u.r.mot))
?~ q.vex ~
[~ p.u.q.vex]
%- send
?~ guz
[%post p.p.zab /application/octet-stream u.r.mot] :: XX parse cot
[%form p.p.zab u.guz]
::
++ went :: handle get
|= [rid=@ud zab=scab ced=cred mot=moth]
^+ +>
=+ sek=(roil [who now (shax (mix (sham zab) now)) ced] zab ras)
=+ ^= rep
:+ %th rid
?~ sek
[%raw [404 ~ [~ (tact "http error 404 at {<now>}")]]]
u.sek
+>.$(saw [rep saw])
::
++ wist :: handle note
^+ .
?. ?=(%ht -.nut)
?> ?=([%lunt *] pax)
(send [%note t.pax nut])
=> ?:(=(%post p.s.nut) (post +.nut) .)
?> ?=(%ht -.nut)
(went +.nut)
::
++ zing :: resolve
^- bowl
[saw [~ (weld ask hup) ..$]]
--
::
++ roil
|= [mad=scad zab=scab ras=wick]
^- (unit love)
=+ cag=`path`(flop p.p.zab)
?> ?=(^ cag)
=+ syd=i.cag
=+ lok=~(rent co ~ %da q.mad)
=+ hox=~(rent co ~ %p p.mad)
=+ tem=`path`[hox syd lok %web t.cag]
=< veen
|%
++ drem
|= axt=@ta
^- (unit love)
=+ arc=((hard arch) .^(%cy tem))
?: (~(has by r.arc) axt)
=+ dat=((hard ,@) .^(%cx (weld tem `path`[axt ~])))
:- ~
:+ %mid
?+ axt [%application %octet-stream ~]
%html [%text %html ~]
%txt [%text %plain ~]
%css [%text %css ~]
%js [%text %javascript ~]
==
[(met 3 dat) dat]
?. (~(has by r.arc) %hoon) ~
:- ~
=+ vez=(vang & [hox syd lok t.cag])
=+ dat=((hard ,@) .^(%cx (weld tem `path`[%hoon ~])))
=+ gen=(scan (trip dat) (full (ifix [gay gay] tall:vez)))
=+ pro=(slam (slam (slap ras gen) !>(mad)) !>(zab))
((hard love) q.pro)
::
++ dunt
^- (unit love)
(drem %html)
::
++ veen
?~(r.q.p.zab dunt (drem u.r.q.p.zab))
--
--

121
main/lib/pony.hoon Normal file
View File

@ -0,0 +1,121 @@
!:
:: /=main=/lib/pony/hoon
::
|%
++ polo :: prompt
|= [gim=(list gift) pim=prom pro=tape def=tape use=tape]
|* [rul=_rule woo=||([@da *] bowl)]
^- bowl
:- gim :- ~
:- :~ [[%polo ~] [%up pim pro def]]
==
|= [now=@da pax=path nut=note]
^- bowl
?> &(=([%polo ~] pax) ?=(%up -.nut))
=+ rey=(rush p.nut rul)
?~ rey
:- [[%la %leaf ?~(use "invalid response" use)] ~]
:- ~
[[[[%polo ~] [%up pim pro def]] ~] ..$]
(woo now u.rey)
::
++ pomo |=([gud=gift bol=bowl] [[gud p.bol] q.bol])
++ pomp |=([tix=tape bol=bowl] (pomo la/leaf/tix bol))
++ pond :: show text block
|= [lub=@ bol=bowl]
^- bowl
:_(q.bol (weld (turn (lore lub) |=(a=@t la/leaf/(trip a))) p.bol))
::
++ posh :: pause until
|= end=@da
|= [gim=(list gift) wop=||(@da bowl)]
^- bowl
:- gim :- ~
:- ^- (list slip)
:~ [~ %wa end]
==
|= [now=@da pax=path nut=note]
(wop now)
::
++ post :: request/response
|= [him=@p [cho=@ta chu=@ta] msg=*]
|= woo=||([@da (unit ,*)] bowl)
^- bowl
=+ leg="waiting for {(scow %p him)}"
:- ~ :- ~
:- ^- (list slip)
:~ [/request [%yo him cho msg]]
[/response [%oy chu]]
[/prompt [%up %none leg ~]]
==
|= [now=@da pax=path nut=note]
^- bowl
?+ -.nut !!
%oy (woo now s.nut)
%yo
?. =(%good q.nut) (woo now ~)
:- ~ :- ~
:_ ..$
^- (list slip)
:~ [/response [%oy chu]]
[/prompt [%up %none leg ~]]
==
==
::
++ pour
|= $: est=@da
dyz=(list ,[p=@tas q=[p=ship q=disc r=moat]])
wop=||([@da (map ,@tas ,[p=(unit ,@ud) q=(list frog)])] bowl)
==
^- bowl
?~ dyz (wop est ~)
=+ :* zyd=(~(gas by *(map ,@tas ,[p=ship q=disc r=moat])) dyz)
fyx=*(map ,@tas ,[p=(unit ,@ud) q=(list frog)])
==
=< apex
|%
++ apex
^- bowl
?~ zyd done
:- ~ :- ~
:- bite
|= [now=@da how=path wat=note]
?> ?=([%eg *] wat)
?> ?=([%pull @ ~] how)
apex:(bice(est now) i.t.how p.wat)
::
++ bice
|= [cyt=@tas rot=riot]
^+ +>
?~ rot
~& [%bice-done cyt]
+>(zyd (~(del by zyd) cyt))
?> ?=(%ud -.q.p.u.rot)
=+ geb=(need (~(get by zyd) cyt))
=+ saq=(need (~(get by fyx) cyt))
%= +>.$
zyd
%+ ~(put by zyd) cyt
?> =(+(p.p.r.geb) p.q.p.u.rot)
geb(p.r q.p.u.rot)
::
fyx
%+ ~(put by fyx) cyt
:- ?~(p.saq [~ p.q.p.u.rot] p.saq)
[((hard frog) r.u.rot) q.saq]
==
::
++ bite
^- (list slip)
=+ who=?>(?=(^ zyd) p.n.zyd)
:- `slip`[/prod [%up %none "waiting for <who> at <est>..." ~]]
=+ fuh=(~(tap by zyd) ~)
%+ turn fuh
|= [a=@tas b=[p=ship q=disc r=moat]]
`slip`[[%pl a ~] %es p.b q.b [%| r.b]]
::
++ done
^- bowl
(wop est fyx)
--
--

42
spec/nock/5.txt Normal file
View File

@ -0,0 +1,42 @@
1 Structures
A noun is an atom or a cell. An atom is any natural number.
A cell is an ordered pair of nouns.
2 Reductions
nock(a) *a
[a b c] [a [b c]]
?[a b] 0
?a 1
+[a b] +[a b]
+a 1 + a
=[a a] 0
=[a b] 1
=a =a
/[1 a] a
/[2 a b] a
/[3 a b] b
/[(a + a) b] /[2 /[a b]]
/[(a + a + 1) b] /[3 /[a b]]
/a /a
*[a [b c] d] [*[a b c] *[a d]]
*[a 0 b] /[b a]
*[a 1 b] b
*[a 2 b c] *[*[a b] *[a c]]
*[a 3 b] ?*[a b]
*[a 4 b] +*[a b]
*[a 5 b] =*[a b]
*[a 6 b c d] *[a 2 [0 1] 2 [1 c d] [1 0] 2 [1 2 3] [1 0] 4 4 b]
*[a 7 b c] *[a 2 b 1 c]
*[a 8 b c] *[a 7 [[7 [0 1] b] 0 1] c]
*[a 9 b c] *[a 7 c 2 [0 1] 0 b]
*[a 10 [b c] d] *[a 8 c 7 [0 3] d]
*[a 10 b c] *[a c]
*a *a

9
try/bin/fib.hoon Normal file
View File

@ -0,0 +1,9 @@
!:
:: /=try=/bin/fib/hoon
::
|= *
|= [num=@ud ~]
:_ ~ :_ ~
:- %$
!> %. num
|=(x=@ ?:((lth x 2) 1 (add $(x (dec x)) $(x (sub x 2)))))

41
try/bin/game.hoon Normal file
View File

@ -0,0 +1,41 @@
!:
:: /=try=/bin/game/hoon
::
=> .(- `[who=@p how=path]`-)
=> .(+ =>(+ ^/=main=/hume))
|= [est=time eny=@uw]
|= [neighbor=tape ~]
^- bowl
=+ messages=*(list ,@t)
%- lunt
:* who
%none
:- :~ :* :~ [%& /localhost]
[%| .127.0.0.1]
==
/game
(shas %game eny)
/try
==
==
^- vase
!> |%
++ give
|= [now=@da fig=weev]
^- [p=(list gift) q=(unit ,[p=(list slip) q=_+>.$])]
?+ -.fig
[~[la/leaf/"give other {<fig>}"] ~]
::
%form
=+ msg=(~(get by q.fig) %msg)
?~ msg
[~[la/leaf/"give odd form {<q.fig>}"] ~]
[~ [~ ~ +>.$(messages [u.msg messages])]]
==
::
++ miss
|= [pac=pact ced=cred]
^- (unit purl)
~
--
==

4
try/bin/goodbye.hoon Normal file
View File

@ -0,0 +1,4 @@
|= *
|= [planet=tape ~]
:_ ~ :_ ~
[%$ !>("hasta la vista, {planet}.")]

6
try/bin/infinite.hoon Normal file
View File

@ -0,0 +1,6 @@
|= *
|= *
=+ a=1
|- ^- bowl
?: =(0 a) [~ ~]
$(a +(a))

7
try/bin/memory.hoon Normal file
View File

@ -0,0 +1,7 @@
|= *
|= *
=+ a=1
=| b=(list)
|- ^- bowl
?: =(0 a) [~ ~]
$(a +(a), b [(bex (bex 13)) b])

7
try/bin/overflow.hoon Normal file
View File

@ -0,0 +1,7 @@
!:
|= *
|= *
=+ a=1
|- ^- bowl
?: =(0 a) [~ ~]
$(a +(a))

26
try/bin/reverse.hoon Normal file
View File

@ -0,0 +1,26 @@
!:
:: /=try=/bin/reverse/hoon
::
|= *
|= ~
:- ~ :- ~
:- ^- (list slip)
:~ [~ %$ %atom %t]
==
|= [now=@da pax=path nut=note]
^- bowl
?+ -.nut !!
%$
?~ p.nut
[~ ~]
=+ liz=((hard (list ,@t)) q.u.p.nut)
:- ^- (list gift)
:~ :+ %mu [%atom %t]
(turn liz |=(a=@t (rap 3 (flop (trip a)))))
==
:- ~
:- ^- (list slip)
:~ [~ %$ %atom %t]
==
..$
==

10
try/bin/sleep.hoon Normal file
View File

@ -0,0 +1,10 @@
!:
=> .(+ =>(+ ^/=main=/pony))
|= [est=@da *]
|= [sle=@dr ~]
^- bowl
%+ (posh (add est sle)) ~[la/leaf/"sleeping for {(scow %dr sle)}..."]
|= now=@da
:_ ~
:~ [%la %leaf "slept."]
==

31
try/bin/tiff.hoon Normal file
View File

@ -0,0 +1,31 @@
!:
:: /=try=/toy/diff/hoon
::
|= [who=seat est=time eny=@uw was=path]
|= ~
:_ ~
=< main
|%
++ main
^- (list gift)
=+ pod=test
|- ^- (list gift)
?~ pod ~
=+ dis=(loss p.i.pod q.i.pod)
?> =((lurk p.i.pod (lusk p.i.pod q.i.pod dis)) q.i.pod)
:- [%la %leaf "{p.i.pod} to {q.i.pod}: loss {dis}"]
$(pod t.pod)
::
++ fake
=+ ram=(shax eny)
=+ inx=0
|- ^- tape
?: =(inx 128) ~
[[(add 'a' (end 0 2 ram))] $(inx +(inx), ram (rsh 0 2 ram))]
::
++ test
=+ inx=0
|- ^- (list ,[p=tape q=tape])
?: =(inx 32) ~
[[fake(eny (add 1 eny)) fake(eny (add 2 eny))] $(inx +(inx), eny (add 3 eny))]
--

10
try/bin/zero.hoon Normal file
View File

@ -0,0 +1,10 @@
!:
|= *
|= ~
^- bowl
:_ ~
=+ inx=0
|- ^- (list gift)
?: =(inx 256) ~
:_ $(inx +(inx))
[%la %leaf "0 :: {(scow %ud inx)}, {(scow %p inx)}"]

5
try/lib/diff.hoon Normal file
View File

@ -0,0 +1,5 @@
!:
:: /=try=/nub/diff/hoon
::
|%
--

20
try/web/game/fun.hoon Normal file
View File

@ -0,0 +1,20 @@
!:
|= mad=[who=@p now=@da eny=@uw ced=cred]
|= zab=[sud=scud quy=quay]
^- love
:- %ham
:~ %html
:~ %body
+"urbit: {neighbor} ready at {<now.mad>}."
::
:- %ul
|- ^- marl
?~ messages ~
:_ $(messages t.messages)
~[%li +"someone said: {(trip i.messages)}"]
::
:~ ~[%form action/"fun" method/"post"]
-"message: {%[%input type/"text" name/"msg"]}"
==
==
==

1
try/web/hello/bar.html Normal file
View File

@ -0,0 +1 @@
<html><body>urbit: born to serve</body></html>

5
try/web/hello/moo.holw Normal file
View File

@ -0,0 +1,5 @@
|= mad=[who=@p now=@da eny=@uw ced=cred]
|= zab=[sec=oryx quy=quay sud=scud]
^- love
:- %ham
html/~[body/~"urbit: {neighbor} prepared to serve at {<now.mad>}"]

12
try/web/hello/posty.holw Normal file
View File

@ -0,0 +1,12 @@
|= mad=[who=@p now=@da eny=@uw ced=cred]
|= zab=[sec=oryx quy=quay sud=scud]
^- love
:- %ham
:~ %html
:~ %body
+"urbit: {neighbor} ready at {<now.mad>}."
:~ ~[%form action/"query.html" method/"get"]
-"message: {%[%input type/"text" name/"msg"]}"
==
==
==

9
try/web/hello/query.holw Normal file
View File

@ -0,0 +1,9 @@
|= mad=[who=@p now=@da eny=@uw ced=cred]
|= zab=[sec=oryx quy=quay sud=scud]
^- love
~& [%query quy.zab]
:- %ham
:~ %html
:- %body
~"urbit: {neighbor} got query {<quy.zab>}."
==