In the middle of internal merge.

This commit is contained in:
C. Guy Yarvin 2016-01-29 18:25:52 -08:00
parent a4e950a3a2
commit e3a0446634
23 changed files with 1606 additions and 5 deletions

View File

@ -1,6 +1,5 @@
A noun is an atom or a cell.
An atom is a natural number.
A cell is an ordered pair of nouns.
A noun is an atom or a cell. An atom is a natural number. A cell is an ordered
pair of nouns.
nock(a) *a
[a b c] [a [b c]]
@ -37,3 +36,4 @@ nock(a) *a
*[a 10 b c] *[a c]
*a *a

116
bad/ape/oct3.hoon Normal file
View File

@ -0,0 +1,116 @@
:: :: ::
:::: /hoon+oct3/ape :::::: dependencies
:: :: ::
/? 310 :: arvo version
/- sole, oct3 :: structures
/+ sole, oct3 :: libraries
[. sole oct3] :: ::
:: :: ::
:::: :::::: interfaces
!: :: ::
=> |% ::
++ axle {eye/face gam/game} :: agent state
++ card $% {$diff lime} :: update
{$quit $~} :: cancel
== ::
++ face (map bone sole-share) :: console state
++ lime $% {$sole-effect sole-effect} :: :sole update
{$oct3-update play} :: :oct3 update
== ::
++ move (pair bone card) :: cause and action
-- ::
:: :: ::
:::: :::::: past state
:: :: ::
=> |% ::
++ axon $%({$1 axle} {$0 axle-0}) :: all states
++ axle-0 {eye/face gam/game-0} :: old axle
++ game-0 {who/? box/board boo/board} :: old game
++ wake |= axon :- %1 ?- +<- $1 +<+ :: coarse upgrade
$0 [eye [who ~^~ ~ box boo]:gam]:+<+ ::
== -- ::
:: :: ::
:::: :::::: parsers
:: :: ::
=> |% ::
++ colm (cook |=(a/@ (sub a '1')) (shim '1' '3')) :: row or column
++ come ;~(plug colm ;~(pfix fas colm)) :: coordinate
++ cope |=(? ?:(+< (stag %| (cold ~ sig)) come)) :: with wait mode
-- ::
:: :: ::
:::: :::::: process core
:: :: ::
|_ $: bowl ::
moz/(list move) :: pending actions
{$1 axle} :: process state v1
== ::
:: :: ::
:::: :::::: process tools
:: :: ::
++ abet [(flop moz) .(moz ~)] :: resolve
++ bike $+(_. _+>) :: self-transformer
++ dish |=(cad/card %_(+> moz [[ost cad] moz])) :: request
++ echo |= {all/(list sink) fun/bike} =+ old=+>+<- :: publish to all
|- ^+ +>.^$ ?~ all +>.^$(+<- old) ::
=> .(ost p.i.all, src q.i.all) ::
$(all t.all, +>.^$ (fun +>.^$)) ::
++ eels (~(tap by sup)) :: all clients
++ elfs (prey /oct3 +<-) :: network clients
++ elks (prey /sole +<-) :: console clients
++ flap |= {net/bike con/bike} :: update all clients
(echo:(echo elks con) elfs net) ::
++ here ~(. go src gam) :: game core
:: :: ::
:::: :::::: server logic
:: :: ::
++ fail ?:(soul (fect %bel ~) ~|(%invalid-move !!)) :: user error
++ fect |=(sole-effect (dish %diff %sole-effect +<)) :: update console
++ fact |=(play (dish %diff %oct3-update +<)) :: update partner
++ hail |=(? tame(gam (hey:here +<))) :: toggle subscriber
++ heal |= old/axon =. +>+<+> (wake old) :: complete update
=- +>.$(gam -) ?. !=(1 +<-) gam ::
(muy:here (turn eels |=(sink q))) ::
++ kick |= point =^ dud gam ~(m at:here +<) ::
?.(dud fail wild:kind) ::
++ kind =+(res:here ?~(- + (word(gam new:here) ->))) :: move result
++ prom (fect %pro %& %oct3 voy:here) :: update prompt
++ rend (turn `wall`tab:here |=(tape txt++<)) :: table print
++ sawn (hail(eye (~(del by eye) ost)) |) :: console unsubscribe
++ seen (hail(eye (~(put by eye) ost *sole-share)) &) :: console subscribe
++ show prom:(fect %mor rend) :: update console
++ soul =+((~(get by sup) ost) ?=([~ * %sole *] -)) :: is console
++ tame (flap |=(_. (fact:+< &/gam)) |=(_. prom:+<)) :: light update
++ wild (flap |=(_. (fact:+< &/gam)) |=(_. show:+<)) :: full update
++ word |= txt/tape %+ flap :: game message
|=(_+> (fact:+< |/txt)) ::
|=(_+> (fect:+< txt+txt)) ::
:: :: ::
:::: :::::: console UI
:: :: ::
++ work :: console action
|= act/sole-action ::
=+ say=(~(got by eye) ost) ::
|^ ?+(-.act abet $det (delt +.act), $ret dive) ::
++ abet ..work(eye (~(put by eye) ost say)) :: resolve
++ cusp (cope !ept:here) :: parsing rule
++ delt |= cal/sole-change :: edit command line
=^ cul say (~(remit sole say) cal good) ::
?~(cul abet fail:(fect:abet det+u.cul)) ::
++ dive =+ (rust (tufa buf.say) (punt come)) :: apply command line
?~(- fail ?~(-> show (kick:wipe ->+))) ::
++ good |=((list @c) -:(rose (tufa +<) cusp)) :: validate input
++ wipe =^ cal say (~(transmit sole say) set+~) :: clear line
(fect:abet %det cal) ::
-- ::
:: :: ::
:::: :::::: arvo handlers
:: :: ::
++ peer-oct3 |=(* abet:tame:(hail &)) :: urbit subscribe
++ peer-sole |=(* abet:show:seen) :: console subscribe
++ poke-sole-action |=(sole-action abet:(work +<)) :: console input
++ poke-oct3-move |=(point abet:wild:(kick +<)) :: urbit move
++ prep |= (unit (pair (list move) axon)) :: update self
abet:?~(+< +> wild:(heal +<+>)) ::
++ pull-oct3 |=(* abet:(hail |)) :: urbit unsubscribe
++ pull-sole |=(* abet:sawn) :: console unsubscribe
--

139
bad/ape/oct4.hoon Normal file
View File

@ -0,0 +1,139 @@
:: :: ::
:::: /hoon+oct4/ape :::::: dependencies
:: :: ::
/? 310 :: arvo version
/- sole, oct4 :: structures
/+ sole, oct4 :: libraries
[. sole oct4] :: ::
:: :: ::
:::: :::::: interfaces
!: :: ::
=> |% ::
++ axle {eye/face rem/(unit ship) gam/game} :: agent state
++ card $% {$diff lime} :: update
{$quit $~} :: cancel
{$peer wire dock path} :: subscribe
{$poke wire dock pear} :: send move
{$pull wire dock $~} :: unsubscribe
== ::
++ face (map bone sole-share) :: console state
++ lime $% {$sole-effect sole-effect} :: :sole update
{$oct4-update play} :: :oct4 update
== ::
++ move (pair bone card) :: cause and action
++ pear {$oct4-move point} :: outgoing move
-- ::
:: :: ::
:::: :::::: past state
:: :: ::
=> |% ::
++ agon (unit {(list move) axon}) :: boot argument
++ axon $%({$1 axle} {$0 axle-0}) :: all states
++ axle-0 {eye/face gam/game-0} :: old axle
++ game-0 {who/? box/board boo/board} :: old game
++ wake |= axon :- %1 ?- +<- $1 +<+ :: coarse upgrade
$0 [eye ~ [who ~^~ ~ box boo]:gam]:+<+ ::
== -- ::
:: :: ::
:::: :::::: parsers
:: :: ::
=> |% ::
++ colm (cook |=(a/@ (sub a '1')) (shim '1' '3')) :: row or column
++ come ;~(plug colm ;~(pfix fas colm)) :: coordinate
++ comb (pick come ;~(pfix sig (punt fed:ag))) :: all command input
++ cope |=(? ?:(+< (stag %| (cold ~ sig)) comb)) :: with wait mode
-- ::
:: :: ::
:::: :::::: process core
:: :: ::
|_ $: bowl ::
moz/(list move) :: pending actions
{$1 axle} :: process state v1
== ::
:: :: ::
:::: :::::: process tools
:: :: ::
++ abet [(flop moz) .(moz ~)] :: resolve
++ bike $+(_. _+>) :: self-transformer
++ dish |=(cad/card %_(+> moz [[ost cad] moz])) :: request
++ done (echo eels |=(_. (dish:+< %quit ~))) :: cancel everyone
++ echo |= {all/(list sink) fun/bike} =+ old=+>+<- :: publish to all
|- ^+ +>.^$ ?~ all +>.^$(+<- old) ::
=> .(ost p.i.all, src q.i.all) ::
$(all t.all, +>.^$ (fun +>.^$)) ::
++ eels (~(tap by sup)) :: all clients
++ elfs (prey /oct4 +<-) :: network clients
++ elks (prey /sole +<-) :: console clients
++ emit |=(lime (dish %diff +<)) :: publish
++ flap |= {net/bike con/bike} :: update all clients
(echo:(echo elks con) elfs net) ::
++ here ~(. go src gam) :: game core
:: :: ::
:::: :::::: server logic
:: :: ::
++ fail ?:(soul (fect %bel ~) ~|(%invalid-move !!)) :: user error
++ fect |=(sole-effect (emit %sole-effect +<)) :: update console
++ fact |=(play (emit %oct4-update +<)) :: update partner
++ hail |=(? ?^(rem +> tame(gam (hey:here +<)))) :: toggle subscriber
++ harp |=(game ?:(=(gam +<) +> wild(gam +<))) :: update game
++ heal |= old/axon =. +>+<+> (wake old) :: complete update
=- +>.$(gam -) ?. !=(1 +<-) gam ::
(muy:here (turn eels |=(sink q))) ::
++ hear |=(play ?-(+<- $| (word +<+), $& (harp +<+))) :: network update
++ kick |= point =^ dud gam ~(m at:here +<) ::
?.(dud fail wild:?~(rem kind (send +>-))) ::
++ kind =+(res:here ?~(- + (word(gam new:here) ->))) :: move result
++ plan |= (unit ship) ?~ +< stop(gam new:here) :: link+unlink
?^(rem fail link(rem +<)) ::
++ plot |= (each point (unit ship)) :: apply command
?-(+<- $& (kick +<+), $| (plan +<+)) ::
++ like |*(* [/oct4 [+.rem dap] +<]) :: friend message
++ link (dish peer+(like /oct4)) :: subscribe to friend
++ prom (fect %pro %& %oct4 stat) :: update prompt
++ rend (turn `wall`tab:here |=(tape txt++<)) :: table print
++ sawn (hail(eye (~(del by eye) ost)) |) :: console unsubscribe
++ seen (hail(eye (~(put by eye) ost *sole-share)) &) :: console subscribe
++ send |=(point (dish poke+(like %oct4-move +<))) :: send move
++ show prom:(fect %mor rend) :: update console
++ soul =+((~(get by sup) ost) ?=([~ * %sole *] -)) :: is console
++ stat (weld ?~(rem ~ "@{(scow p+u.rem)}") voy:here) :: prompt line
++ stop ?~(rem done wild:(dish pull+(like ~))) :: unsubscribe
++ tame (flap |=(_. (fact:+< &/gam)) |=(_. prom:+<)) :: light update
++ wild (flap |=(_. (fact:+< &/gam)) |=(_. show:+<)) :: full update
++ with |=(? (word(rem ?:(+< rem ~)) "{<[+< src]>}")) ::
++ word |= txt/tape %+ flap :: game message
|=(_+> (fact:+< |/txt)) ::
|=(_+> (fect:+< txt+txt)) ::
:: :: ::
:::: :::::: console UI
:: :: ::
++ work :: console action
|= act/sole-action ::
=+ say=(~(got by eye) ost) ::
|^ ?+(-.act abet $det (delt +.act), $ret dive) ::
++ abet ..work(eye (~(put by eye) ost say)) :: resolve
++ cusp (cope !ept:here) :: parsing rule
++ delt |= cal/sole-change :: edit command line
=^ cul say (~(remit sole say) cal good) ::
?~(cul abet fail:(fect:abet det+u.cul)) ::
++ dive =+ (rust (tufa buf.say) (punt comb)) :: apply command line
?~(- fail ?~(-> show (plot:wipe ->+))) ::
++ good |=((list @c) -:(rose (tufa +<) cusp)) :: validate input
++ wipe =^ cal say (~(transmit sole say) set+~) :: clear line
(fect:abet %det cal) ::
-- ::
:: :: ::
:::: :::::: arvo handlers
:: :: ::
++ reap-oct4 |=({* (unit)} abet:(with =(~ +<+))) :: linked to friend
++ coup-oct4 |=({* (unit)} abet:?~(+<+ +> fail)) :: move acknowledge
++ diff-oct4-update |=({* play} abet:(hear +<+)) :: network update
++ peer-oct4 |=(* abet:tame:(hail &)) :: urbit subscribe
++ peer-sole |=(* abet:show:seen) :: console subscribe
++ poke-sole-action |=(sole-action abet:(work +<)) :: console input
++ poke-oct4-move |=(point abet:wild:(kick +<)) :: urbit move
++ prep |=(agon abet:?~(+< +> (heal +<+>))) :: load state
++ pull-oct4 |=(* abet:(hail |)) :: urbit unsubscribe
++ pull-sole |=(* abet:sawn) :: console unsubscribe
++ quit-oct4 |=(* abet:?~(rem +> wild(rem ~))) :: unlinked by friend
--

60
bad/lib/oct3.hoon Normal file
View File

@ -0,0 +1,60 @@
:: :: ::
:::: /hoon+oct3/lib :::::: dependencies
:: :: ::
/? 310 :: arvo version
/- oct3 :: structures
:: :: ::
:::: :::::: semantics
!: :: ::
[. ^oct3]
|% ::
++ icon |=(? ?:(+< 'X' 'O')) :: display at
++ bo :: per board
|_ bud/board ::
++ bit |=(@ =(1 (cut 0 [+< 1] bud))) :: moved at address
++ get |=(point (bit (off +<))) :: get point
++ jon a+(turn (gulf 0 9) |=(@ b+(bit +<))) :: to json
++ off |=(point (add x (mul 3 y))) :: bitfield address
++ set |=(point (con bud (bex (off +<)))) :: set point
++ win %- lien :_ |=(a/@ =(a (dis a bud))) :: test for win
(rip 4 0wl04h0.4A0Aw.4A00s.0e070) :: with bitmasks
-- ::
++ go :: play from
|_ {src/ship game} ::
++ at |_ point :: per point
++ g `game`+>+<+ :: game
++ k &(!|(x o) ept) :: legal move
++ m ?.(k [| g] [& g:t:?:(who y p)]) :: move
++ o (~(get bo boo) +<) :: old at o
++ p .(boo (~(set bo boo) +<), q.sag `src) :: play at o
++ t .(who !who) :: take turn
++ v ?:(x (icon &) ?:(o (icon |) '.')) :: view
++ x (~(get bo box) +<) :: old at x
++ y .(box (~(set bo box) +<), p.sag `src) :: play at x
-- ::
++ ept =+(own |(&(=(~ -) !=(oth `src)) =(`src -))) :: we can play
++ hey |=(? +>+<+(aud ((stat ship) +< src aud))) :: enter+leave
++ muy |= (list ship) ?~ +< +>+<+ :: many in audience
$(+< t.+<, aud ((stat ship) & i.+< aud)) ::
++ nam =+ ?: =(p.sag `src) ['=' (icon &) ~] :: print name
?: =(q.sag `src) ['=' (icon |) ~] ::
"" (welp (scow %p src) `tape`-) ::
++ new +<+(boo 0, box 0, who &, sag [~ ~]) :: reset game
++ oth own(who !who) :: who owns other turn
++ own ?:(who p.sag q.sag) :: who owns this turn
++ res ?. |(~(win bo box) ~(win bo boo)) :: possible result
?: =(511 (con boo box)) ::
`"tie :-(" ~ `"{<nam>} wins" ::
++ row |= y/@ :- (add y '1') %- zing :: print row
(turn (gulf 0 3) |=(@ ~[' ' ~(v at y +<)])) ::
++ str =+ [own ~[(icon who)]] ^- tape :: print player
?~(-< -> (scow %p u.-<)) ::
++ tab ~["+ 1 2 3" (row 0) (row 1) (row 2)] :: print table
++ vew =- ?: =(~ -) ~ :(weld "[" - "]") :: print watchers
=+ dow=(~(tap by aud)) |- ^- tape ::
?~ dow ~ =+ mor=$(dow t.dow) ::
:(weld nam(src p.i.dow) ?~(mor "" ", ") mor) ::
++ voy =+ ~[(icon who)] %+ weld vew :: print prompt
?.(ept " ({-}'s turn) " ": {-} (row+col): ")::
--
--

60
bad/lib/oct4.hoon Normal file
View File

@ -0,0 +1,60 @@
:: :: ::
:::: /hoon+oct4/lib :: :: dependencies
:: :: ::
/? 310 :: arvo version
/- oct4 :: structures
:: :: ::
:::: :: :: semantics
!: :: ::
[. ^oct4]
|%
++ icon |=(? ?:(+< 'X' 'O')) :: display at
++ bo :: per board
|_ bud/board ::
++ bit |=(@ =(1 (cut 0 [+< 1] bud))) :: moved at address
++ get |=(point (bit (off +<))) :: get point
++ jon a+(turn (gulf 0 9) |=(@ b+(bit +<))) :: to json
++ off |=(point (add x (mul 3 y))) :: bitfield address
++ set |=(point (con bud (bex (off +<)))) :: set point
++ win %- lien :_ |=(a/@ =(a (dis a bud))) :: test for win
(rip 4 0wl04h0.4A0Aw.4A00s.0e070) :: with bitmasks
-- ::
++ go :: play from
|_ {src/ship game} ::
++ at |_ point :: per point
++ g `game`+>+<+ :: game
++ k &(!|(x o) ept) :: legal move
++ m ?.(k [| g] [& g:t:?:(who y p)]) :: move
++ o (~(get bo boo) +<) :: old at o
++ p .(boo (~(set bo boo) +<), q.sag `src) :: play at o
++ t .(who !who) :: take turn
++ v ?:(x (icon &) ?:(o (icon |) '.')) :: view
++ x (~(get bo box) +<) :: old at x
++ y .(box (~(set bo box) +<), p.sag `src) :: play at x
-- ::
++ ept =+(own |(&(=(~ -) !=(oth `src)) =(`src -))) :: we can play
++ hey |=(? +>+<+(aud ((stat ship) +< src aud))) :: enter+leave
++ muy |= (list ship) ?~ +< +>+<+ :: many in audience
$(+< t.+<, aud ((stat ship) & i.+< aud)) ::
++ nam =+ ?: =(p.sag `src) ['=' (icon &) ~] :: print name
?: =(q.sag `src) ['=' (icon |) ~] ::
"" (welp (scow %p src) `tape`-) ::
++ new +<+(boo 0, box 0, who &, sag [~ ~]) :: reset game
++ oth own(who !who) :: who owns other turn
++ own ?:(who p.sag q.sag) :: who owns this turn
++ res ?. |(~(win bo box) ~(win bo boo)) :: possible result
?: =(511 (con boo box)) ::
`"tie :-(" ~ `"{<nam>} wins" ::
++ row |= y/@ :- (add y '1') %- zing :: print row
(turn (gulf 0 3) |=(@ ~[' ' ~(v at y +<)])) ::
++ str =+ [own ~[(icon who)]] ^- tape :: print player
?~(-< -> (scow %p u.-<)) ::
++ tab ~["+ 1 2 3" (row 0) (row 1) (row 2)] :: print table
++ vew =- ?: =(~ -) ~ :(weld "[" - "]") :: print watchers
=+ dow=(~(tap by aud)) |- ^- tape ::
?~ dow ~ =+ mor=$(dow t.dow) ::
:(weld nam(src p.i.dow) ?~(mor "" ", ") mor) ::
++ voy =+ ~[(icon who)] %+ weld vew :: print prompt
?.(ept " ({-}'s turn) " ": {-} (row+col): ")::
--
--

36
bad/mar/down.hoon Normal file
View File

@ -0,0 +1,36 @@
::
:::: /hoon+down+mar
::
/? 314
/- markdown
/+ down-jet, frontmatter
::
::::
::
[markdown .]
|_ don/down
++ grab :: convert from
|%
++ noun down :: clam from %noun
++ md
|= src/@t
=+ [atr mud]=(parse:frontmatter (lore src))
[[%meta atr] (mark:down-jet mud)]
--
::
++ grow :: convert into
|%
++ hymn :: convert to %hymn
;html
;head:title:"Untitled"
;body
;* (print:down-jet don)
==
==
++ elem :: convert to %elem
;div
;* (print:down-jet don)
==
:: ++ react elem
--
--

16
bad/mar/oct3/move.hoon Normal file
View File

@ -0,0 +1,16 @@
::
:::: /hoon+oct3-move+mar
::
/? 314
!:
::::
::
=+ point={x/@ y/@}
|_ point
::
++ grab :: convert from
|%
++ json (corl need (at ni ni ~):jo) :: reparse from %json
++ noun point :: clam from %noun
--
--

35
bad/mar/oct3/update.hoon Normal file
View File

@ -0,0 +1,35 @@
:: :: ::
:::: /hoon+oct3-update+mar :::::: dependencies
:: :: ::
/? 310 :: arvo
/- oct3 :: structures
/+ oct3 :: libraries
[. oct3 ^oct3]
!: :: ::
:::: :: :: protocol
:: :: ::
|_ play :: game
++ grab :: convert from
|%
++ noun play :: from %noun
--
++ grow :: convert to
|%
++ json ^- ^json :: to %json
~! +>-<
?: ?=({$|} +>-<)
~! +>-<
~! p
s+(crip p)
=+ she=|=(ship s+(scot %p +<))
=+ hes=|=({ship *} (she +<-))
%- jobe
:~ who+s+?:(who.p %x %o)
plx+?~(p.sag.p ~ (she u.p.sag.p))
plo+?~(q.sag.p ~ (she u.q.sag.p))
aud+a+(turn (~(tap by aud.p)) hes)
box+~(jon bo box.p)
boo+~(jon bo boo.p)
==
--
--

16
bad/mar/oct4/move.hoon Normal file
View File

@ -0,0 +1,16 @@
::
:::: /hoon+oct4-move+mar
::
/? 314
!:
::::
::
=+ point={x/@ y/@}
|_ point
::
++ grab :: convert from
|%
++ json (corl need (at ni ni ~):jo) :: reparse from %json
++ noun point :: clam from %noun
--
--

35
bad/mar/oct4/update.hoon Normal file
View File

@ -0,0 +1,35 @@
:: :: ::
:::: /hoon+oct4-update+mar :::::: dependencies
:: :: ::
/? 310 :: arvo
/- oct4 :: structures
/+ oct4 :: libraries
!: :: ::
:::: :: :: protocol
:: :: ::
[oct4 ^oct4 .]
|_ play :: game
++ grab :: convert from
|%
++ noun play :: from %noun
--
++ grow :: convert to
|%
++ json ^- ^json :: to %json
~! +>-<
?: ?=($| +>-<)
~! +>-<
~! p
s+(crip p)
=+ she=|=(ship s+(scot %p +<))
=+ hes=|=({ship *} (she +<-))
%- jobe
:~ who+s+?:(who.p %x %o)
plx+?~(p.sag.p ~ (she u.p.sag.p))
plo+?~(q.sag.p ~ (she u.q.sag.p))
aud+a+(turn (~(tap by aud.p)) hes)
box+~(jon bo box.p)
boo+~(jon bo boo.p)
==
--
--

31
bad/mar/react-snip.hoon Normal file
View File

@ -0,0 +1,31 @@
::
:::: /hoon/core/react-snip/mar
::
/? 314
/+ react
!:
::::
::
[. react]
|_ {hed/marl tal/marl}
::
++ grow :: convert to
|%
++ mime [/application/json (tact tape)]
++ tape (pojo react-snips-json)
++ elem ;div:(h1:"*{hed}" div:"*{tal}")
++ react-snip-js (crip (react-to-tape elem))
++ react-snips-json
::?> ?=([[%div ~] [[%h1 ~] *] [[%div ~] *] ~]] own) :: xx mystery fish-loop
%^ jobe
head+react-head-json
body+react-snip-json
~
::
++ react-head-json (react-to-json ;h1:"*{hed}")
++ react-snip-json (react-to-json ;div:"*{tal}")
--
++ grab |% :: convert from
++ noun manx :: clam from %noun
++ snip |=(a/{marl marl} a)
-- --

23
bad/mar/react.hoon Normal file
View File

@ -0,0 +1,23 @@
::
:::: /hoon/core/react/mar
::
/? 314
/+ react
!:
::::
::
[. react]
|_ own/manx
::
++ grow :: convert to
|%
++ tape (pojo react-json)
++ react-js (crip (react-to-tape own))
:: ++ js react-js :: convert to %js
++ react-json (react-to-json own)
++ mime [/application/json (tact tape)] :: convert to %mime
--
++ grab |% :: convert from
++ noun manx :: clam from %noun
++ elem |= a/manx a
-- --

28
bad/mar/sched.hoon Normal file
View File

@ -0,0 +1,28 @@
!:
:::: /hoon/core/sched/mar
::
|_ dat/(map @da cord)
++ grow :: convert to
|% ++ mime [/text/x-sched (tact tape)]
++ tape
(zing `wall`(turn sorted-list |=({a/@da b/cord} "{<a>} {(trip b)}\0a")))
++ elem =< ;ul: *{(turn sorted-list .)}
|= {tym/@da ite/cord} ^- manx
;li: ;{b "{<tym>}"}: {(trip ite)}
++ sorted-list
(sort (~(tap by dat)) |=({{l/@ @} {r/@ @}} (lth l r)))
--
++ grab
|% :: convert from
++ mime
|= {p/mite q/octs} ^+ dat
=< (mo (turn (lore q.q) .))
|= a/@t ^- {@da @t}
%+ rash a
;~ (glue ace)
(cook |=(a/coin ?>(?=({$~ $da @} a) `@da`q.p.a)) nuck:so)
(cook crip (star prn))
==
--
++ grad %mime
--

60
bad/mar/snip.hoon Normal file
View File

@ -0,0 +1,60 @@
::
:::: /hoon+core+elem+mar
::
/? 314
!:
|%
++ words 1
++ hedtal
=| met/marl
|= a/marl ^- {hed/marl tal/marl}
?~ a [~ ~]
?. ?=($h1 n.g.i.a)
?: ?=($meta n.g.i.a)
$(a t.a, met [i.a met])
=+ had=$(a c.i.a)
?^ -.had had
$(a t.a)
[c.i.a (weld (flop met) (limit words t.a))]
::
++ limit
|= {lim/@u mal/marl}
=< res
|- ^- {rem/@u res/marl}
?~ mal [lim ~]
?~ lim [0 ~]
=+ ^- {lam/@u hed/manx}
?: ?=(_:/(**) i.mal)
[lim :/(tay)]:(deword lim v.i.a.g.i.mal)
[rem ele(c res)]:[ele=i.mal $(mal c.i.mal)]
[rem - res]:[hed $(lim lam, mal t.mal)]
::
++ deword
|= {lim/@u tay/tape} ^- {lim/@u tay/tape}
?~ tay [lim tay]
?~ lim [0 ~]
=+ wer=(dot 1^1 tay)
?~ q.wer
[lim - tay]:[i.tay $(tay t.tay)]
=+ nex=$(lim (dec lim), tay q.q.u.q.wer)
[-.nex [(wonk wer) +.nex]]
--
::
!:
|_ {hed/marl tal/marl}
::
++ grow :: convert to
|%
++ mime
=< mime
|%
++ elem ;div:(h1:"*{hed}" div:"*{tal}") :: convert to %elem
++ hymn ;html:(head:title:"snip" body:"+{elem}") :: convert to %hymn
++ html (crip (poxo hymn)) :: convert to %html
++ mime [/text/html (taco html)] :: convert to %mime
--
--
++ grab |% :: convert from
++ noun {marl marl} :: clam from $noun
++ elem |=(a/manx (hedtal +.a))
-- --

38
bad/mar/sole/action.hoon Normal file
View File

@ -0,0 +1,38 @@
::
:::: /hoon+sole-action+mar
::
/? 314
/- sole
!:
::::
::
[sole .]
|_ sole-action
::
++ grab :: convert from
|%
++ json
|= jon/^json ^- sole-action
%- need %. jon
=> [jo ..sole-action]
|^ (fo %ret (of det+change ~))
++ fo
|* {a/term b/fist}
|=(c/json ?.(=([%s a] c) (b c) (some [a ~])))
::
++ ra
|* {a/{p/term q/fist} b/fist}
|= c/json %. c
?.(=(%a -.c) b (pe p.a (ar q.a)))
::
++ change (ot ler+(at ni ni ~) ted+(cu |*(a/* [0v0 a]) edit) ~)
++ char (cu turf so)
++ edit
%+ fo %nop
%+ ra mor+|=(json (edit +<))
(of del+ni set+(cu tuba sa) ins+(ot at+ni cha+char ~) ~)
--
::
++ noun sole-action :: clam from %noun
--
--

60
bad/mar/sole/effect.hoon Normal file
View File

@ -0,0 +1,60 @@
::
:::: /hoon+sole-effect+mar
::
/? 314
/- sole
!:
::::
::
[sole .]
|%
++ mar-sole-change :: XX dependency
|_ cha/sole-change
++ grow
|% ++ json
^- ^json
=+ cha
=< (jobe ted+(. ted) ler+a+~[(jone own.ler) (jone his.ler)] ~)
|= det/sole-edit
?- -.det
$nop [%s 'nop']
$mor [%a (turn p.det ..$)]
$del (joba %del (jone p.det))
$set (joba %set (jape (tufa p.det)))
$ins (joba %ins (jobe at+(jone p.det) cha+s+(tuft q.det) ~))
==
--
--
++ wush
|= {wid/@u tan/tang}
^- tape
=+ rolt=|=(a/wall `tape`?~(a ~ ?~(t.a i.a :(weld i.a "\0a" $(a t.a)))))
(rolt (turn (flop tan) |=(a/tank (rolt (wash 0^wid a)))))
::
--
!:
|_ sef/sole-effect
::
++ grab :: convert from
|%
++ noun sole-effect :: clam from %noun
--
++ grow
|%
++ json
^- ^json
?+ -.sef
~|(unsupported-effect+-.sef !!)
$mor [%a (turn p.sef |=(a/sole-effect json(sef a)))]
$err (joba %hop (jone p.sef))
$txt (joba %txt (jape p.sef))
$tan (joba %tan (jape (wush 160 p.sef)))
$det (joba %det json:~(grow mar-sole-change +.sef))
$pro
(joba %pro (jobe vis+b+vis.sef tag+s+tag.sef cad+(jape cad.sef) ~))
::
?($bel $clr $nex)
(joba %act %s -.sef)
==
--
--

119
bad/mar/talk/command.hoon Normal file
View File

@ -0,0 +1,119 @@
::
:::: /hoon+talk-command+mar
::
/? 314
/- talk
!:
[talk .]
|_ cod/command
::
++ grab :: convert from
|%
++ noun command :: clam from %noun
++ json
=> [jo ..command]
|= a/json ^- command
=- (need ((of -) a))
=< :~ publish+(ar thot)
review+(ar thot)
design+(ot party+so config+(mu conf) ~)
==
|%
++ op :: parse keys of map
|* {fel/rule wit/fist}
%+ cu mo
%- ci :_ (om wit)
|= a/(map cord _(need *wit))
^- (unit (list _[(wonk *fel) (need *wit)]))
(zl (turn (~(tap by a)) (head-rush fel)))
::
++ ke :: callbacks
|* {gar/* sef/_|.(fist)}
|= jon/json
^- (unit _gar)
=- ~! gar ~! (need -) -
((sef) jon)
::
++ as :: array as set
:: |*(a=fist (cu sa (ar a))) :: XX types
|* a/fist
%- cu :_ (ar a)
~(gas in *(set _(need *a)))
::
++ lake |*(a/_* $+(json (unit a)))
++ peach
|* a/{rule rule}
|= tub/nail
^- (like (each _(wonk (-.a)) _(wonk (+.a))))
%. tub
;~(pose (stag %& -.a) (stag %| +.a))
::
++ head-rush
|* a/rule
|* {b/cord c/*}
=+ nit=(rush b a)
?~ nit ~
(some [u.nit c])
::
::
++ thot
^- $+(json (unit thought))
%- ot :~
serial+(ci (slat %uv) so)
audience+audi
statement+stam
==
::
++ audi (op parn memb) :: audience
++ auri (op parn (ci (soft presence) so))
++ memb (ot envelope+lope delivery+(ci (soft delivery) so) ~)
++ lope (ot visible+bo sender+(mu (su parn)) ~)
::
++ parn
^- $+(nail (like partner))
%+ peach
;~((glue fas) ;~(pfix sig fed:ag) urs:ab)
%+ sear (soft passport)
;~((glue fas) sym urs:ab) :: XX [a-z0-9_]{1,15}
::
++ speech-or-eval $?(speech {$eval p/@t} {$mor p/(list speech-or-eval)})
++ eval
|= a/(trel @da bouquet speech-or-eval)
^- statement
%= a r ^- speech
|-
?: ?=($mor -.r.a)
[%mor (turn p.r.a |=(b/speech-or-eval ^$(r.a b)))]
?. ?=($eval -.r.a) r.a
=- [%fat tank+- %exp p.r.a]
=+ pax=[&1:% &2:% (scot %da p.a) |3:%]
p:(mule |.([(sell (slap !>(..zuse) (rain pax p.r.a)))]~))
==
::
++ stam
^- $+(json (unit statement))
%+ cu eval
(ot date+di bouquet+(as (ar so)) speech+spec ~)
::
++ spec
%+ ke *speech-or-eval |.
%- of
:~ lin+(ot say+bo txt+so ~)
url+(su aurf:urlp)
eval+so
mor+(ar spec)
:: exp+(cu |=(a=cord [a ~]) so)
:: inv+(ot ship+(su fed:ag) party+(su urs:ab) ~)
==
::
++ conf
^- $+(json (unit config))
%- ot :~
sources+(as (su parn))
caption+so
:- %cordon
(ot posture+(ci (soft posture) so) list+(as (su fed:ag)) ~)
==
--
-- --

144
bad/mar/talk/report.hoon Normal file
View File

@ -0,0 +1,144 @@
::
:::: /hoon/talk-report/mar
::
/? 314
/- talk
/+ talk
!:
[talk .]
|_ rep/report
::
++ grab :: convert from
|%
++ noun report :: clam from %noun
--
++ grow
|%
++ mime [/text/json (taco (crip (pojo json)))]
++ json
=> +
|^ %+ joba -.rep
?- -.rep
$cabal (cabl +.rep)
$house a+(turn (~(tap by +.rep)) jose)
$glyph ((jome |=(a/char a) nack) +.rep)
$grams (jobe num+(jone p.rep) tele+[%a (turn q.rep gram)] ~)
$group (jobe local+(grop p.rep) global+%.(q.rep (jome parn grop)) ~)
==
++ joce |=(a/span [%s a])
++ jose
|= {a/span b/posture c/cord}
(jobe name+[%s a] posture+[%s a] caption+[%s b] ~)
::
++ jove
|= {a/envelope b/delivery}
%- jobe :~
envelope+(jobe visible+[%b p.a] sender+?~(q.a ~ s+(parn u.q.a)) ~)
delivery+[%s b]
==
++ jope |=(a/ship (jape +:<a>)) ::[%s (crip +:(scow %p a))])
++ joke |=(a/tank [%s (role (turn (wash 0^80 a) crip))])
++ jode |=(a/time (jone (div (mul (sub a ~1970.1.1) 1.000) ~s1)))
:: ++ jase
:: |* a=,json
:: |= b=(set ,$+<.a) ^- json
:: ~! b
:: [%a (turn (~(tap in b)) a)]
::
++ jome :: stringify keys
|* {a/_cord b/_json}
|= c/(map _+<.a _+<.b)
(jobe (turn (~(tap by c)) (both a b)))
::
++ both :: cons two gates
|* {a/_* b/_*}
|=(c/_[+<.a +<.b] [(a -.c) (b +.c)])
::
::
++ nack |=(a/(set (set partner)) [%a (turn (~(tap in a)) sorc)])
++ grop (jome phon stas) :: (map ship status)
++ phon |=(a/ship (scot %p a))
++ stas |=(status (jobe presence+(joce p) human+(huma q) ~))
++ gram |=(telegram (jobe ship+(jope p) thought+(thot q) ~))
++ thot
|= thought
(jobe serial+(jape <p>) audience+(audi q) statement+(stam r) ~)
::
++ audi (jome parn jove)
++ bouq
|= a/bouquet
a+(turn (~(tap in a)) |=(b/path a+(turn b |=(c/span s+c))))
::
++ parn
|= a/partner ^- cord
?- -.a
$& (stat p.a)
$| %- crip
?- -.p.a
$twitter "{(trip -.p.a)}/{(trip p.p.a)}"
==
==
::
++ stat
|= a/station ^- cord
(crip "{<p.a>}/{(trip q.a)}")
::
++ stam
|= statement
(jobe date+(jode p) bouquet+(bouq q) speech+(spec r) ~)
::
++ spec
|= a/speech
%+ joba -.a
?+ -.a ~|(stub+-.a !!)
$lin (jobe txt+[%s q.a] say+[%b p.a] ~)
$url (joba txt+[%s (crip (earf p.a))])
$exp (joba txt+[%s p.a])
$tax (joba txt+(jape (rend-work-duty p.a)))
$app (jobe txt+[%s q.a] src+[%s p.a] ~)
$fat (jobe tor+(tors p.a) taf+$(a q.a) ~)
$mor a+(turn p.a spec)
:: %inv (jobe ship+(jope p.a) party+[%s q.a] ~)
==
::
++ tors
|= a/torso
%+ joba -.a
?- -.a
$text [%s (role +.a)]
$tank [%a (turn +.a joke)]
$name (jobe nom+s+p.a mon+$(a q.a) ~)
==
::
++ huma
|= human
%^ jobe
hand+?~(hand ~ [%s u.hand])
:- %true
?~ true ~
=+ u.true
(jobe first+[%s p] middle+?~(q ~ [%s u.q]) last+[%s r] ~)
~
::
++ cabl
|= cabal
%- jobe :~
loc+(conf loc)
ham+((jome stat conf) ham)
==
::
++ sorc
|= a/(set partner) ^- json
[%a (turn (~(tap in a)) |=(b/partner s+(parn b)))]
::
++ conf
|= config
%- jobe :~
sources+(sorc sources)
caption+[%s caption]
=- cordon+(jobe posture+[%s -.cordon] list+[%a -] ~)
(turn (~(tap in q.cordon)) jope) :: XX jase
==
--
-- --

320
bad/mar/talk/telegrams.hoon Normal file
View File

@ -0,0 +1,320 @@
::
:::: /hoon/talk-telegrams/mar
::
/? 314
/- talk
/+ talk
!:
=+ talk
|_ gam/(list telegram)
::
++ grab-work-duty => [jo work-stuff]
|^ dute
++ as
:: |*(a/fist (cu sa (ar a))) :: XX types
|* a/fist
%- cu :_ (ar a)
~(gas in *(set _(need *a)))
++ ot
|* a/(pole {@tas fist})
|= b/json
%. ((^ot a) b)
%- slog
?+ b ~
{$o *}
%+ murn `(list {@tas fist})`a
|= {c/term d/fist} ^- (unit tank)
=+ (~(get by p.b) c)
?~ - (some >[c (turn (~(tap by p.b)) head)]<)
=+ (d u)
?~ - (some >[c u]<)
~
==
++ of
|* a/(pole {@tas fist})
|= b/json
%. ((of:jo a) b)
%- slog
?+ b ~
{$o *}
%+ murn `(list {@tas fist})`a
|= {c/term d/fist} ^- (unit tank)
=+ (~(get by p.b) c)
?~ - ~
=+ (d u)
?~ - (some >[c u]<)
~
==
++ id (ci (slat %uv) so)
++ ship (su fed:ag)
++ dute
%- of :~
create+task change+(ot id+id meat+uppd ~)
archive+id update+(ot id+id version+ni her+(su fed:ag) meat+uppd ~)
==
++ task
%- ot :~
id+id 'date_created'^di
version+ni 'date_modified'^di
creator+ship doer+(mu ship)
tags+(as so) 'date_due'^(mu di)
done+(mu di) title+so
description+so discussion+(ar (ot date+di ship+ship body+so ~))
==
++ audi (as stan)
++ stan (su ;~((glue fas) ;~(pfix sig fed:ag) urs:ab))
++ uppd
%- of :~
set-doer+(mu (su fed:ag))
set-date-due+(mu di)
set-tags+(as so)
set-title+so
set-description+so
set-done+bo
add-comment+(ot ship+(su fed:ag) com+so ~)
==
--
++ grow-work-duty
=> work-stuff
=+ jope=|=(a/ship [%s (rsh 3 1 (scot %p a))])
=+ jove=|=(a/@uvI [%s (scot %uv a)])
=< |= duty
%+ joba +<-
?- +<-
$create (task tax)
$archive (jove id)
$change (jobe id+(jove id) meat+(flesh meat) ~)
$update
%- jobe :~
id+(jove id)
version+(jone version)
her+(jope her)
meat+(flesh meat)
==
==
|%
++ tags
|= a/(set @t)
[%a (turn (sort (~(tap in a)) aor) |=(b/cord s+b))]
::
++ task
|= ^task
%- jobe :~ id+[%s (scot %uv id)]
tags+(^tags tags)
doer+?~(doer ~ (jope u.doer))
title+[%s title]
creator+(jope creator)
version+(jone version)
'date_created'^(jode date-created)
'date_modified'^(jode date-modified)
description+[%s description]
=< discussion+[%a (turn discussion .)]
|=(comment (jobe date+(jode date) ship+(jope ship) body+[%s body] ~))
'date_due'^?~(date-due ~ (jode u.date-due))
done+?~(done ~ (jode u.done))
==
++ flesh
|= ^flesh
%+ joba +<-
?- +<-
$set-doer ?~(her ~ (jope u.her))
$set-date-due ?~(wen ~ (jode u.wen))
$set-tags (tags tag)
$set-title [%s til]
$set-description [%s des]
$set-done [%b don]
$add-comment (jobe ship+(jope who) com+[%s com] ~)
==
--
++ grab
|%
++ noun (list telegram)
++ mime |=(^mime (json (rash q.q apex:poja)))
++ json
=> [jo ..telegram dute=grab-work-duty]
|= a/json ^- (list telegram)
=- (need ((ar (ot ship+(su fed:ag) thought+thot ~)) a))
|%
++ of
|* a/(pole {@tas fist})
|= b/json
%. ((of:jo a) b)
%- slog
?+ b ~
{$o *}
%+ murn `(list {@tas fist})`a
|= {c/term d/fist} ^- (unit tank)
=+ (~(get by p.b) c)
?~ - ~
=+ (d u)
?~ - (some >[c u]<)
~
==
++ op :: parse keys of map
|* {fel/rule wit/fist}
%+ cu mo
%- ci :_ (om wit)
|= a/(map cord _(need *wit))
^- (unit (list _[(wonk *fel) (need *wit)]))
(zl (turn (~(tap by a)) (head-rush fel)))
::
++ as :: array as set
:: |*(a/fist (cu sa (ar a))) :: XX types
|* a/fist
%- cu :_ (ar a)
~(gas in *(set _(need *a)))
::
++ ke :: callbacks
|* {gar/* sef/_|.(fist)}
|= jon/json
^- (unit _gar)
=- ~! gar ~! (need -) -
((sef) jon)
::
++ lake |*(a/_* $+(json (unit a)))
++ head-rush
|* a/rule
|* {b/cord c/*}
=+ nit=(rush b a)
?~ nit ~
(some [u.nit c])
::
::
++ thot
^- $+(json (unit thought))
%- ot :~
serial+(ci (slat %uv) so)
audience+audi
statement+stam
==
::
++ audi (op parn memb) :: audience
++ auri (op parn (ci (soft presence) so))
++ memb (ot envelope+lope delivery+(ci (soft delivery) so) ~)
++ lope (ot visible+bo sender+(mu (su parn)) ~)
::
++ parn
^- $+(nail (like partner))
%+ pick
;~((glue fas) ;~(pfix sig fed:ag) urs:ab)
%+ sear (soft passport)
;~((glue fas) sym urs:ab) :: XX [a-z0-9_]{1,15}
::
++ stam (ot date+di bouquet+(as (ar so)) speech+spec ~)
++ spec
%+ ke *speech |. ~+
%- of :~
lin+(ot say+bo txt+so ~)
url+(ot txt+(su aurf:urlp) ~)
exp+(ot txt+so ~)
tax+(ot xat+dute ~)
app+(ot txt+so src+so ~)
fat+(ot tor+tors taf+spec ~)
ext+(ot nom+so txe+blob ~)
non+ul
:: inv+(ot ship+(su fed:ag) party+(su urs:ab) ~)
==
++ tors
%+ ke *torso |. ~+
%- of :~
name+(ot nom+so mon+tors ~)
text+(cu lore so)
tank+(ot dat+(cu (hard (list tank)) blob) ~)
==
::
++ blob (cu cue (su fel:ofis))
--
--
::
++ grow
|%
++ mime [/text/json (taco (crip (pojo json)))]
++ json
=> +
|^
:- %a
%+ turn gam
|= telegram
(jobe ship+(jope p) thought+(thot q) ~)
::
++ jove
|= {a/envelope b/delivery}
%- jobe :~
envelope+(jobe visible+[%b p.a] sender+?~(q.a ~ s+(parn u.q.a)) ~)
delivery+[%s b]
==
::
++ jope |=(a/ship (jape +:<a>)) ::[%s (crip +:(scow %p a))])
++ joke |=(a/tank [%s (role (turn (wash 0^80 a) crip))])
++ jode |=(a/time (jone (div (mul (sub a ~1970.1.1) 1.000) ~s1)))
++ jome :: stringify keys
|* {a/_cord b/_json}
|= c/(map _+<.a _+<.b)
(jobe (turn (~(tap by c)) (both a b)))
::
++ both :: cons two gates
|* {a/_* b/_*}
|=(c/_[+<.a +<.b] [(a -.c) (b +.c)])
::
++ thot
|= thought
(jobe serial+(jape <p>) audience+(audi q) statement+(stam r) ~)
::
++ audi (jome parn jove)
++ bouq
|= a/bouquet
a+(turn (~(tap in a)) |=(b/path a+(turn b |=(c/knot s+c))))
::
++ parn
|= a/partner ^- cord
?- -.a
$& (stat p.a)
$| %- crip
?- -.p.a
$twitter "{(trip -.p.a)}/{(trip p.p.a)}"
==
==
::
++ stat
|= a/station ^- cord
(crip "{<p.a>}/{(trip q.a)}")
::
++ stam
|= statement
(jobe date+(jode p) bouquet+(bouq q) speech+(spec r) ~)
::
++ spec
|= a/speech
%+ joba -.a
?+ -.a ~|(stub+-.a !!)
$lin (jobe txt+[%s q.a] say+[%b p.a] ~)
$url (joba txt+(jape (earf p.a)))
$exp (joba txt+[%s p.a])
$tax (jobe txt+(jape (rend-work-duty p.a)) xat+(grow-work-duty p.a) ~)
$app (jobe txt+[%s q.a] src+[%s p.a] ~)
$fat (jobe tor+(tors p.a) taf+$(a q.a) ~)
$ext (jobe nom+[%s p.a] txe+(jape (sifo (jam +.a))) ~)
$non ~
:: $inv (jobe ship+(jope p.a) party+[%s q.a] ~)
==
::
++ tors
|= a/torso
%+ joba -.a
?- -.a
$text [%s (role +.a)]
$tank (jobe txt+[%a (turn +.a joke)] dat+(jape (sifo (jam +.a))) ~)
$name (jobe nom+s+p.a mon+$(a q.a) ~)
==
::
--
--
::
++ grad
|%
++ form %talk-telegrams
++ diff |=((list telegram) +<)
++ pact |=((list telegram) +<)
++ join |=({(list telegram) (list telegram)} `(unit mime)`~)
--
--

104
bad/mar/work/command.hoon Normal file
View File

@ -0,0 +1,104 @@
::
:::: /hoon+command+work+mar
::
/- work
!:
::::
::
[work .]
|_ mad/command
++ grab
|% ++ noun command
++ json
=> [jo ..command]
=< (corl need (cu |=(a/command a) coma))
|%
++ as
:: |*(a/fist (cu sa (ar a))) :: XX types
|* a/fist
%- cu :_ (ar a)
~(gas in *(set _(need *a)))
++ ot
|* a/(pole {@tas fist})
|= b/json
%. ((^ot a) b)
%- slog
?+ b ~
{$o *}
%+ murn `(list {@tas fist})`a
|= {c/term d/fist} ^- (unit tank)
=+ (~(get by p.b) c)
?~ - (some >[c (turn (~(tap by p.b)) head)]<)
=+ (d u)
?~ - (some >[c u]<)
~
==
++ of
|* a/(pole {@tas fist})
|= b/json
%. ((of:jo a) b)
%- slog
?+ b ~
{$o *}
%+ murn `(list {@tas fist})`a
|= {c/term d/fist} ^- (unit tank)
=+ (~(get by p.b) c)
?~ - ~
=+ (d u)
?~ - (some >[c u]<)
~
==
++ id (ci (slat %uv) so)
++ ship (su fed:ag)
++ coma
%- of :~
new+task old+(ot id+id dif+uppd ~)
sort+(ar id)
==
++ task
%- ot :~
::index+ni
audience+audi
id+id 'date_created'^di
version+ni 'date_modified'^di
creator+ship doer+(mu ship)
tags+(as so) 'date_due'^(mu di)
done+(mu di) title+so
description+so discussion+(ar (ot date+di ship+ship body+so ~))
==
++ audi (as stan)
++ stan (su ;~((glue fas) ;~(pfix sig fed:ag) urs:ab))
++ uppd
%- of :~
doer+(of release+ul claim+ul ~)
add+(of comment+so ~)
:- %set
%- of :~
audience+audi
date-due+(mu di)
title+so
description+so
tags+(as so)
done+bo
==
==
--
--
++ grow
|%
++ elem ;pre: {(zing `wall`(turn (wash 0^120 >mad<) |=(a/tape ['\0a' a])))}
--
--
:: {new: {
:: id:'0vaof.6df9u.2agc3.d0dp1',
:: date-created:1440011611215,
:: version:1,
:: date-modified:1440011611215,
:: creator:'fyr',
:: tags:['tag'],
:: date-due:null,
:: done:false,
:: title:'Test task',
:: description:'The converter owrks right?',
:: discussion:[{date:1440011611215,ship:'sondel',body:'hi'}]
:: } }

55
bad/mar/work/report.hoon Normal file
View File

@ -0,0 +1,55 @@
::
:::: /hoon+report+work+mar
::
/- work
!:
::::
::
[work .]
|_ client
++ grow
|% ++ json
=+ jope=|=(a/ship [%s (rsh 3 1 (scot %p a))])
%- jobe :~
sort+[%a (turn sort |=(a/@uv [%s (scot %uv a)]))]
=< tasks+(jobe (turn (~(tap by tasks)) .))
|= {@ client-task}
=+ tax
:- (scot %uv id)
%- jobe :~ id+[%s (scot %uv id)]
tags+[%a (turn (^sort (~(tap in tags)) aor) |=(a/cord s+a))]
doer+?~(doer ~ (jope u.doer))
title+[%s title]
creator+(jope creator)
version+(jone version)
archived+[%b archived]
=< audience+[%a (turn (~(tap in audience)) .)]
|=(a/station:talk [%s (crip "{<p.a>}/{(trip q.a)}")])
'date_created'^(jode date-created)
'date_modified'^(jode date-modified)
description+[%s description]
=< discussion+[%a (turn discussion .)]
|=(comment (jobe date+(jode date) ship+(jope ship) body+[%s body] ~))
'date_due'^?~(date-due ~ (jode u.date-due))
done+?~(done ~ (jode u.done))
==
==
-- --
:: sort: ["0v111id" ...]
:: tasks: [ {
:: id:"0v111id"
:: tags:["str" ...]
:: doer:|("~ship" null)
:: title:"str"
:: creator:"~ship"
:: version:12345
:: archived:false
:: audience:["~ship+chan" ...]
:: date_created:1262304000000
:: date_modified:1262304000000
:: description:"str"
:: discussion:[{date:1262304000000 ship:"~ship" body:"str"} ...]
:: date_due:?(1262304000000 null)
:: done:?(1262304000000 null)
:: }
:: ...]

106
bad/mar/work/task.hoon Normal file
View File

@ -0,0 +1,106 @@
::
:::: /hoon/task/work/mar
::
/- work
!:
::::
::
[work .]
|%
++ rend
|= a/(list $@(char dime)) ^- cord
%- crip
|- ^- tape
?~ a ~
?@ i.a [i.a $(a t.a)]
(weld (scow i.a) $(a t.a))
::
++ indent |=(a/wain (turn a |=(b/cord (cat 3 ' ' b))))
::
++ undent
|* {a/wain b/$+(wain *)} ^+ [*b a]
=^ c a
|- ^- {c/wain a/wain}
?~ a [~ a]
?. =(' ' (end 3 2 i.a))
[~ a]
[[- c] a]:[(rsh 3 2 i.a) $(a t.a)]
[(b `wain`c) a]
::
++ keen |*({a/* b/rule} |=(c/nail `(like a)`(b c)))
++ parse
|* {hed/$?($~ $@(@tas tape)) tal/(pole)}
?~ hed (..$ tal)
?^ hed ;~(pfix (just (crip hed)) (..$ tal))
=- ?~(tal had ;~(plug had (..$ tal)))
=< had=(sear . nuck:so)
|= a/coin ^- (unit (odo:raid hed))
?. &(?=({$$ @ @} a) =(hed p.p.a)) ~
(some q.p.a)
::
++ advance
|* {a/wain b/rule} ^+ [(wonk *b) a]
?~(a !! ~|(i.a [(rash i.a b) t.a]))
--
!:
::::
::
|_ taz/task
++ grab
|% ++ txt
|= a/wain ^+ taz
=+ ~[id=%uv "_" date-created=%da " " version=%ud date-modified=%da]
=^ b a (advance a ;~(plug (parse -) (punt (parse " " %da ~))))
=+ [-.b `date-due/(unit @da)`+.b]
=^ tags a (undent a ~(gas in *(set cord)))
=^ title a ?~(a !! a)
=^ b a %+ advance a
;~(plug (parse %p ~) (punt (parse ">" %p ~)) (punt (parse "X" %da ~)))
=+ `{creator/@p doer/(unit @p) done/(unit @da)}`b
=^ description a (undent a role)
:* id date-created version date-modified creator
doer tags date-due done title description :: XX done
|- ^- (list comment)
?: =(~ a) ~
=^ b a (advance a (parse ship=%p " " date=%da ~))
=+ b
=^ body a (undent a role)
[[date ship body] $]
==
--
++ grow
|%
++ elem ;pre: {(zing `wall`(turn (wash 0^120 >taz<) |=(a/tape ['\0a' a])))}
++ mime [/text/x-task (taco (role txt))]
++ txt
=+ taz
=+ due=?~(date-due ~ ~[' ' da+u.date-due])
:- (rend uv+id '_' da+date-created ' ' ud+version da+date-modified due)
%+ welp (indent (sort (~(tap in tags)) aor))
:- title
=+ do=[=-(?~(doer - ['>' p+u.doer -]) ?~(done ~ ~['X' da+u.done]))]
:- (rend p+creator do)
%- zing ^- (list wain)
:- (indent (lore description))
%+ turn discussion
|= comment ^- wain
[(rend p+ship ' ' da+date ~) (indent (lore body))]
--
++ grad %txt
--
:: {id}_{date-created} {version}{date-modified}{|(" {date-due}" ~)}
:: {tag1}
:: {tag2}
:: ...
:: {title}
:: {creator}{|(">{doer}" ~)}{|("X{done}" ~)}
:: {description}
:: {more description}
:: {ship1} {date}
:: {comment}
:: {more comment}
:: {more comment}
:: {ship2} {date}
:: {comment}
:: {more comment}
:: {more comment}

View File

@ -348,7 +348,7 @@ static u3j_harm _mood__hoon__ut_burn_a[] = {{".2", u3wfu_burn}, {}};
static u3j_harm _mood__hoon__ut_conk_a[] = {{".2", u3wfu_conk}, {}};
static u3j_harm _mood__hoon__ut_crop_a[] = {{".2", u3wfu_crop}, {}};
// static u3j_harm _mood__hoon__ut_fire_a[] = {{".2", u3wfu_fire}, {}};
static u3j_harm _mood__hoon__ut_fond_a[] = {{".2", u3wfu_fond}, {}};
// static u3j_harm _mood__hoon__ut_fond_a[] = {{".2", u3wfu_fond}, {}};
static u3j_harm _mood__hoon__ut_fish_a[] = {{".2", u3wfu_fish}, {}};
static u3j_harm _mood__hoon__ut_fuse_a[] = {{".2", u3wfu_fuse}, {}};
static u3j_harm _mood__hoon__ut_mint_a[] = {{".2", u3wfu_mint}, {}};
@ -366,7 +366,7 @@ static u3j_core _mood__hoon__ut_d[] =
{ "burn", _mood__hoon__ut_burn_a },
{ "conk", _mood__hoon__ut_conk_a },
{ "crop", _mood__hoon__ut_crop_a },
{ "fond", _mood__hoon__ut_fond_a },
// { "fond", _mood__hoon__ut_fond_a },
// { "fire", _mood__hoon__ut_fire_a },
{ "fish", _mood__hoon__ut_fish_a },
{ "fuse", _mood__hoon__ut_fuse_a },