From 242ed3e57db2ee6d02a072dfc7b673735093eb63 Mon Sep 17 00:00:00 2001 From: Elliot Glaysher Date: Thu, 16 Nov 2017 11:09:03 -0800 Subject: [PATCH 1/2] Partial redo of hoon.hoon --- sys/hoon.hoon | 906 +++++++++++++++++++++++++++++++++++++++++++++----- 1 file changed, 818 insertions(+), 88 deletions(-) diff --git a/sys/hoon.hoon b/sys/hoon.hoon index 056fc59319..e6ec693022 100644 --- a/sys/hoon.hoon +++ b/sys/hoon.hoon @@ -1,16 +1,15 @@ :: :: :::: /sys/hoon :: :: :: -~> %slog.[0 leaf+"hoon-assembly"] =< ride => %143 => :: :: :::: 0: version stub :: :: :: ~% %k.143 ~ ~ :: +!: |% -++ foo 0 -++ hoon + +++ hoon-version + -- => :: :: :::: 1: layer one :: @@ -20,32 +19,45 @@ :: 1c: molds and mold builders :: :: ~% %one + ~ +:> # %base +:> +:> basic mathematical operations |% -++ foo 0 -:: :: -:::: 1a: unsigned arithmetic :: - :: -++ add :: unsigned addition +:> # %math +:> unsigned arithmetic ++| +++ add ~/ %add - |= {a/@ b/@} + :> unsigned addition + :> + :> a: the augend + :> b: the added + |= [a=@ b=@] + :> the addend ^- @ ?: =(0 a) b $(a (dec a), b +(b)) :: -++ dec :: unsigned decrement +++ dec ~/ %dec - |= a/@ + :> unsigned decrement by one. + |= a=@ ~_ leaf+"decrement-underflow" ?< =(0 a) =+ b=0 + :> decremented integer |- ^- @ ?: =(a +(b)) b $(b +(b)) :: -++ div :: unsigned divide +++ div ~/ %div - =+ [a=`@`1 b=`@`1] - |. + :> unsigned divide + :> + :> a: dividend + :> b: divisor + |: [a=`@`1 b=`@`1] + :> quotient ^- @ ~_ leaf+"divide-by-zero" ?< =(0 b) @@ -54,32 +66,64 @@ ?: (lth a b) c $(a (sub a b), c +(c)) :: -++ dvr :: divide w/remainder +++ dvr ~/ %dvr - |= {a/@ b/@} - ^- {p/@ q/@} + :> unsigned divide with remainder + :> + :> a: dividend + :> b: divisor + |= [a=@ b=@] + :> p: quotient + :> q: remainder + ^- [p=@ q=@] [(div a b) (mod a b)] :: -++ gte :: unsigned greater/eq +++ gte ~/ %gte - |= {a/@ b/@} + :> unsigned greater than or equals + :> + :> returns whether {a >= b}. + :> + :> a: left hand operand (todo: name) + :> b: right hand operand + |= [a=@ b=@] + :> greater than or equal to? ^- ? !(lth a b) :: -++ gth :: unsigned greater +++ gth ~/ %gth - |= {a/@ b/@} + :> unsigned greater than + :> + :> returns whether {a > b} + :> + :> a: left hand operand (todo: name) + :> b: right hand operand + |= [a=@ b=@] + :> greater than? ^- ? !(lte a b) :: -++ lte :: unsigned less/eq +++ lte ~/ %lte - |= {a/@ b/@} + :> unsigned less than or equals + :> + :> returns whether {a >= b}. + :> + :> a: left hand operand (todo: name) + :> b: right hand operand + |= [a=@ b=@] + :> less than or equal to? |(=(a b) (lth a b)) :: -++ lth :: unsigned less +++ lth ~/ %lth - |= {a/@ b/@} + :> unsigned less than + :> + :> a: left hand operand (todo: name) + :> b: right hand operand + |= [a=@ b=@] + :> less than? ^- ? ?& !=(a b) |- @@ -88,48 +132,67 @@ $(a (dec a), b (dec b)) == == == :: -++ max :: unsigned maximum +++ max ~/ %max - |= {a/@ b/@} + :> unsigned maximum + |= [a=@ b=@] + :> the maximum ^- @ ?: (gth a b) a b :: -++ min :: unsigned minimum +++ min ~/ %min - |= {a/@ b/@} + :> unsigned minimum + |= [a=@ b=@] + :> the minimum ^- @ ?: (lth a b) a b :: -++ mod :: unsigned modulus +++ mod ~/ %mod + :> unsigned modulus + :> + :> a: dividend + :> b: divisor |: [a=`@`1 b=`@`1] + :> the remainder ^- @ ?< =(0 b) (sub a (mul b (div a b))) :: -++ mul :: unsigned multiply +++ mul ~/ %mul + :> unsigned multiplication + :> + :> a: multiplicand + :> b: multiplier |: [a=`@`1 b=`@`1] + :> product ^- @ =+ c=0 |- ?: =(0 a) c $(a (dec a), c (add b c)) :: -++ sub :: subtract +++ sub ~/ %sub + :> unsigned subtraction + :> + :> a: minuend + :> b: subtrahend |= {a/@ b/@} ~_ leaf+"subtract-underflow" + :> difference ^- @ ?: =(0 b) a $(a (dec a), b (dec b)) -:: :: -:::: 1b: tree addressing :: - :: :: - :: cap, mas, peg :: - :: +:: +:> # %tree +:> +:> tree addressing ++| ++ cap :: fragment head ~/ %cap |= a/@ @@ -207,7 +270,6 @@ :: ~% %two + ~ |% -++ foo 0 :: :: :::: 2a: unit logic :: :: :: @@ -1542,15 +1604,12 @@ :: :: :: ++ ly :: list from raw noun - |* a/* le:nl :: ++ my :: map from raw noun - |* a/* my:nl :: ++ sy :: set from raw noun - |* a/* si:nl :: ++ nl @@ -1634,6 +1693,17 @@ =+ gol=(han fud) ?.(=(gol fud) ~ [~ gol]) :: +++ slog :: deify printf + =| pri/@ :: priority level + |= a/tang ^+ same :: .= ~&(%a 1) + ?~(a same ~>(%slog.[pri i.a] $(a t.a))) :: ((slog ~[>%a<]) 1) +:: :: +++ mean :: crash with trace + |= a/tang + ^+ !! + ?~ a !! + ~_(i.a $(a t.a)) +:: ++ tail |*(^ ,:+<+) :: get tail ++ test |=(^ =(+<- +<+)) :: equality :: @@ -1769,7 +1839,6 @@ :: :: ~% %tri + ~ |% -++ foo 0 :: :::: 3a: signed and modular ints :: :: :: @@ -3490,7 +3559,6 @@ %show show == |% -++ foo 0 :: :::: 4a: exotic bases :: @@ -5692,7 +5760,6 @@ %ut ut == |% -++ foo 0 :: :::: 5a: compiler utilities :: @@ -6808,8 +6875,8 @@ :: {$zpwt *} ?: ?: ?=(@ p.gen) - (lte hoon p.gen) - &((lte hoon p.p.gen) (gte hoon q.p.gen)) + (lte hoon-version p.gen) + &((lte hoon-version p.p.gen) (gte hoon-version q.p.gen)) q.gen ~_(leaf+"hoon-version" !!) :: @@ -8508,7 +8575,6 @@ :: ref/span == - ~+ :: :span: subject refurbished to reference namespace :: ^- span @@ -8587,8 +8653,8 @@ ?=(?($noun $void {?($atom $core) *}) ref) == done - ~_ (dunk 'redo: dext: sut') - ~_ (dunk(sut ref) 'redo: dext: ref') + :: ~_ (dunk 'redo: dext: sut') + :: ~_ (dunk(sut ref) 'redo: dext: ref') ?- sut ?($noun $void {?($atom $core) *}) :: reduce reference and reassemble leaf @@ -8660,8 +8726,8 @@ =/ lov =/ lov dear ?~ lov - ~_ (dunk 'redo: dear: sut') - ~_ (dunk(sut ref) 'redo: dear: ref') + :: ~_ (dunk 'redo: dear: sut') + :: ~_ (dunk(sut ref) 'redo: dear: ref') ~& [%wec wec] !! (need lov) @@ -9205,16 +9271,9 @@ %^ cat 3 %~ rent co :+ %$ %ud - |- ^- @ - ?- q.s.q.sut - $~ 0 - {* $~ $~} 1 - {* $~ *} +($(q.s.q.sut r.q.s.q.sut)) - {* * $~} +($(q.s.q.sut l.q.s.q.sut)) - {* * *} .+ %+ add - $(q.s.q.sut l.q.s.q.sut) - $(q.s.q.sut r.q.s.q.sut) - == == + %- ~(rep by (~(run by q.s.q.sut) |=(tomb ~(wyt by q)))) + |=([[@ a=@u] b=@u] (add a b)) + == %^ cat 3 ?-(p.q.sut $gold '.', $iron '|', $lead '?', $zinc '&') =+ gum=(mug q.s.q.sut) @@ -9881,6 +9940,671 @@ ?~ sim [i.reb $(reb t.reb, sim ~)] [;/((flop sim)) i.reb $(reb t.reb, sim ~)] -- + :: + ++ cram :: parse unmark + => |% + ++ item (pair mite marl:twig) :: xml node generator + ++ colm @ud :: column + ++ flow marl:twig :: node or generator + ++ mite :: context + $? $down :: outer embed + $rule :: horizontal ruler + $list :: unordered list + $lime :: list item + $lord :: ordered list + $poem :: verse + $bloc :: blockquote + $code :: preformatted code + $head :: heading + $expr :: dynamic expression + == :: + ++ trig :: line style + $: col/@ud :: start column + sty/trig-style :: style + == :: + ++ trig-style :: type of parsed line + $? $done :: end of input + $rule :: --- horizontal ruler + $lint :: + line item + $lite :: - line item + $head :: # heading + $bloc :: > block-quote + $expr :: ;sail expression + $text :: anything else + == :: + ++ graf :: paragraph element + $% {$bold p/(list graf)} :: *bold* + {$talc p/(list graf)} :: _italics_ + {$quod p/(list graf)} :: "double quote" + {$code p/tape} :: code literal + {$text p/tape} :: text symbol + {$link p/(list graf) q/tape} :: URL + {$expr p/tuna:twig} :: interpolated hoon + == + -- + =< apex + |% + ++ apex + =; fel |=(nail (fel +<)) + :(stag %xray [%div ~] fenced) + :: + ++ fenced + :: + :: top: original indentation level + :: + |= {{@u top/@u} tape} + %+ pfix (hrul:parse +<) + |= nail ^- (like marl:twig) + ~($ main top +<) + :: + ++ main + :: + :: state of the parsing loop. we maintain a construction + :: stack for elements and a line stack for lines in the + :: current block. a blank line causes the current block + :: to be parsed and thrown in the current element. when + :: the indent column retreats, the element stack rolls up. + :: + :: err: error position + :: col: current control column + :: hac: stack of items under construction + :: cur: current item under construction + :: lub: current block being read in + :: + =| err/(unit hair) + =| col/@ud + =| hac/(list item) + =/ cur/item [%down ~] + =| lub/(unit (pair hair (list tape))) + |_ {top/@ud naz/hair los/tape} + :: + ++ $ :: resolve + ^- (like flow) + => line + :: + :: if error position is set, produce error + ?. =(~ err) [+.err ~] + :: + :: all data was consumed + =- [naz `[- [naz los]]] + => made + |- ^- flow + :: + :: fold all the way to top + ?~ hac fine + $(..^$ fold) + :: + ::+| + :: + ++ cur-indent + ?- p.cur + $down 2 + $rule 0 + $head 0 + $expr 2 + $list 0 + $lime 2 + $lord 0 + $poem 8 + $code 4 + $bloc 2 + == + :: + ++ back :: column retreat + |= luc/@ud + ^+ +> + ?: =(luc col) +> + :: + :: nex: next backward step that terminates this context + =/ nex/@ud cur-indent ::REVIEW code and poem blocks are handled elsewhere + ?: (gth nex (sub col luc)) + :: + :: indenting pattern violation + ::~& indent-pattern-violation+[p.cur nex col luc] + ..^$(col luc, err `[p.naz luc]) + =. ..^$ fold + $(col (sub col nex)) + :: + ++ fine :: item to flow + ^- flow + ?: ?=(?($down $head $expr) p.cur) + (flop q.cur) + =- [[- ~] (flop q.cur)]~ + ?- p.cur + $rule %hr + $list %ul + $lord %ol + $lime %li + $code %pre + $poem %div ::REVIEW actual container element? + $bloc %blockquote + == + :: + ++ fold ^+ . :: complete and pop + ?~ hac . + %= . + hac t.hac + cur [p.i.hac (concat-code (weld fine q.i.hac))] + == + :: + ++ concat-code :: merge continuous pre + |= a/flow + ?~ a a + ?. ?=({$pre *} -.i.a) a + |- + ?~ t.a a + ?. ?=({$pre $~} -.i.t.a) a + :: add blank line between blocks + $(t.a t.t.a, c.i.a (welp c.i.t.a ;/("\0a") c.i.a)) + :: + ++ snap :: capture raw line + =| nap/tape + |- ^+ [nap +>] + :: + :: no unterminated lines + ?~ los + ::~& %unterminated-line + [~ +>(err `naz)] + ?. =(`@`10 i.los) + ?: (gth col q.naz) + ?. =(' ' i.los) + ::~& expected-indent+[col naz los] + [~ +>(err `naz)] + $(los t.los, q.naz +(q.naz)) + :: + :: save byte and repeat + $(los t.los, q.naz +(q.naz), nap [i.los nap]) + :: + :: consume newline + :_ +>(los t.los, naz [+(p.naz) 1]) + :: + :: trim trailing spaces + |- ^- tape + ?: ?=({$' ' *} nap) + $(nap t.nap) + (flop nap) + :: + ++ skip :: discard line + |- ^+ + + :: + :: no unterminated lines + ?~ los + ::~& %unterminated-line + +(err `naz) + ?. =(`@`10 i.los) + :: + :: eat byte and repeat + $(los t.los) + :: + :: consume newline + +(los t.los, naz [+(p.naz) 1]) + :: + ++ look :: inspect line + ^- (unit trig) + (wonk (look:parse naz los)) + :: + ++ made :: compose block + ^+ . + :: + :: empty block, no action + ?~ lub . + :: + :: if block is preformatted code + ?: ?=($code p.cur) + =- fold(lub ~, q.cur (weld - q.cur), col (sub col 4)) + %+ turn q.u.lub + |= tape ^- mars + :: + :: each line is text data with its newline + ;/("{+<}\0a") + :: + :: if block is verse + ?: ?=($poem p.cur) + :: + :: add break between stanzas + =. q.cur ?~(q.cur q.cur [[[%br ~] ~] q.cur]) + =- fold(lub ~, q.cur (weld - q.cur), col (sub col 8)) + %+ turn q.u.lub + |= tape ^- manx + :: + :: each line is a paragraph + :- [%p ~] + :_ ~ + ;/("{+<}\0a") + :: + :: yex: block recomposed, with newlines + =/ yex/tape + (zing (turn (flop q.u.lub) |=(a/tape (runt [(dec col) ' '] "{a}\0a")))) + :: + :: vex: parse of paragraph + =/ vex/(like marl:twig) + :: + :: either a one-line header or a paragraph + %. [p.u.lub yex] + %- full + ?- p.cur + $rule =<(;~(pfix (punt whit) hrul) parse) + $expr expr:parse + $head head:parse + @ para:parse + == + :: + :: if error, propagate correctly + ?~ q.vex ..$(err `p.vex) + :: + :: finish tag if it's a header or rule + =< ?:(?=(?($head $rule) p.cur) fold ..$) + :: + :: save good result, clear buffer + ..$(lub ~, q.cur (weld p.u.q.vex q.cur)) + :: + ++ line ^+ . :: body line loop + :: + =. col ?~(col top col) + :: + :: abort after first error + ?: !=(~ err) . + :: + :: pic: profile of this line + =/ pic look + :: + :: if line is blank + ?~ pic + :: + :: break section + line:made:skip + :: + :: line is not blank + => .(pic u.pic) + :: + :: if end of input, complete + ?: |(?=($done sty.pic) (lth col.pic top)) + ..$(q.naz col.pic) + :: + :: bal: inspection copy of lub, current section + =/ bal lub + :: + :: if within section + ?~ bal (new-container pic) + :: + :: detect unspaced new containers + ?: ?& ?=(?($down $lime $bloc) p.cur) + |(!=(%text sty.pic) (gth col.pic col)) + == + (new-container:made pic) + :: + :: first line of container is legal + ?~ q.u.bal + =^ nap ..$ snap + line(lub bal(q.u [nap q.u.bal])) + :: + :: detect bad block structure + ?. ?- p.cur + :: + :: can't(/directly) contain text + ?($lord $list) ~|(bad-leaf-container+p.cur !!) + :: + :: only one line in a header/break + ?($head $rule) | + :: + :: literals need to end with a blank line + ?($code $poem $expr) (gte col.pic col) + :: + :: text flows must continue aligned + ?($down $list $lime $lord $bloc) =(col.pic col) + == + ::~& bad-block-structure+[p.cur col col.pic] + ..$(err `[p.naz col.pic]) + :: + :: accept line and continue + =^ nap ..$ snap + line(lub bal(q.u [nap q.u.bal])) + :: + ++ new-container :: enter list/quote + |= pic/trig + :: + :: if column has retreated, adjust stack + =. +>.$ ?. (lth col.pic col) +>.$ (back col.pic) + :: + :: dif: columns advanced + :: erp: error position + :: + =/ dif (sub col.pic col) + =/ erp [p.naz col.pic] + =. col col.pic + :: + :: execute appropriate paragraph form + =< line:abet:apex + |% + :: + ++ abet :: accept line + :: + :: nap: take first line + ..$(lub `[naz ~]) + :: + ++ apex ^+ . :: by column offset + ?+ dif fail :: + $0 apse :: unindented forms + $4 (push %code) :: code literal + $8 (push %poem) :: verse literal + == + :: + ++ apse ^+ . :: by prefix style + ?- sty.pic + $done !! :: blank + $rule (push %rule) :: horizontal ruler + $head (push %head) :: heading + $bloc (entr %bloc) :: blockquote line + $expr (entr %expr) :: hoon expression + $lite (lent %list) :: unnumbered list + $lint (lent %lord) :: numbered list + $text text :: anything else + == + :: + ++ fail .(err `erp) :: set error position + ++ push |=(mite +>(hac [cur hac], cur [+< ~])):: push context + ++ entr :: enter container + |= typ/mite + ^+ +> + :: + :: indent by 2 + =. col (add 2 col) + :: + :: "parse" marker + =. los (slag (sub col q.naz) los) + =. q.naz col + :: + (push typ) + :: + ++ lent :: list entry + |= ord/?($lord $list) + ^+ +> + :: can't switch list types + ?: =(?-(ord $list %lord, $lord %list) p.cur) + fail + :: + :: push list item + =< (entr %lime) + :: + :: push list context, unless we're in list + ?:(=(ord p.cur) ..push (push ord)) + :: + ++ text :: plain text + ^+ . + :: + :: only in lists, fold + ?. ?=(?($list $lord) p.cur) . + .(^$ fold) + -- + -- + :: + ++ parse :: individual parsers + |% + ++ look :: classify line + %+ cook |=(a/(unit trig) a) + ;~ pfix (star ace) + %+ here + |=({a/pint b/?($~ trig-style)} ?~(b ~ `[q.p.a b])) + ;~ pose + (full (easy %done)) :: end of input + (cold ~ (just `@`10)) :: blank line + (cold %rule ;~(plug hep hep hep)) :: --- horizontal ruler + (cold %head ;~(plug (star hax) ace)) :: # heading + (cold %lite ;~(plug hep ace)) :: - line item + (cold %lint ;~(plug lus ace)) :: + line item + (cold %bloc ;~(plug gar ace)) :: > block-quote + (cold %expr sem) :: ;sail expression + (easy %text) :: anything else + == + == + :: + ++ cash :: escaped fence + |* tem/rule + %- echo + %- star + ;~ pose + whit + ;~(plug bas tem) + ;~(less tem prn) + == + :: + ++ cool :: reparse + |* $: :: fex: primary parser + :: sab: secondary parser + :: + fex/rule + sab/rule + == + |= {naz/hair los/tape} + ^+ *sab + :: + :: vex: fenced span + =/ vex/(like tape) (fex naz los) + ?~ q.vex vex + :: + :: hav: reparse full fenced text + =/ hav ((full sab) [naz p.u.q.vex]) + :: + :: reparsed error position is always at start + ?~ q.hav [naz ~] + :: + :: the complete span with the main product + :- p.vex + `[p.u.q.hav q.u.q.vex] + :: + ::REVIEW surely there is a less hacky "first or after space" solution + ++ easy-sol :: parse start of line + |* a/* + |= b/nail + ?: =(1 q.p.b) ((easy a) b) + (fail b) + :: + ++ echo :: hoon literal + |* sab/rule + |= {naz/hair los/tape} + ^- (like tape) + :: + :: vex: result of parsing wide twig + =/ vex (sab naz los) + :: + :: use result of expression parser + ?~ q.vex vex + =- [p.vex `[- q.u.q.vex]] + :: + :: but replace payload with bytes consumed + |- ^- tape + ?: =(q.q.u.q.vex los) ~ + ?~ los ~ + [i.los $(los +.los)] + :: + ++ word :: flow parser + %+ knee *(list graf) |. ~+ + %+ cook |=(a/?(graf (list graf)) ?+(a a {@ *} [a]~)) + ;~ pose + :: + :: ordinary word + :: + %+ stag %text + ;~(plug ;~(pose low hig) (star ;~(pose nud low hig hep))) + :: + :: naked \escape + :: + (stag %text ;~(pfix bas (cook trip ;~(less ace prn)))) + :: + :: *bold literal* + :: + (stag %bold (ifix [tar tar] (cool (cash tar) work))) + :: + :: _italic literal_ + :: + (stag %talc (ifix [cab cab] (cool (cash cab) work))) + :: + :: "quoted text" + :: + (stag %quod (ifix [doq doq] (cool (cash doq) work))) + :: + :: `classic markdown quote` + :: + (stag %code (ifix [tec tec] (cash tec))) + :: + :: ++arm + :: + (stag %code ;~(plug lus lus low (star ;~(pose nud low hep)))) + :: + :: [arbitrary *content*](url) + :: + %+ stag %link + ;~ (glue (punt whit)) + (ifix [sel ser] (cool (cash ser) work)) + (ifix [pel per] (cash per)) + == + :: + :: #twig + :: + ;~ plug + (stag %text ;~(pose (cold " " whit) (easy-sol ~))) + (stag %code ;~(pfix hax (echo wide))) + ;~(simu whit (easy ~)) + == + :: + :: direct hoon constant + :: + ;~ plug + (stag %text ;~(pose (cold " " whit) (easy-sol ~))) + :: + %+ stag %code + %- echo + ;~ pose + ::REVIEW just copy in 0x... parsers directly? + ;~(simu ;~(plug (just '0') alp) bisk:so) + :: + tash:so + ;~(pfix dot perd:so) + ;~(pfix sig ;~(pose twid:so (easy [%$ %n 0]))) + ;~(pfix cen ;~(pose sym buc pam bar qut nuck:so)) + == + :: + ;~(simu whit (easy ~)) + == + :: + :: whitespace + :: + (stag %text (cold " " whit)) + :: + :: {interpolated} sail + :: + (stag %expr inline-embed:(sail |)) + :: + :: just a byte + :: + (stag %text (cook trip ;~(less ace prn))) + == + :: + ++ work (cook zing (star word)) :: indefinite flow + :: + ++ down :: parse inline flow + %+ knee *flow |. ~+ + =- (cook - work) + :: + :: collect raw flow into xml tags + |= gaf/(list graf) + ^- flow + =< main + |% + ++ main + ^- flow + ?~ gaf ~ + ?. ?=($text -.i.gaf) + (weld (item i.gaf) $(gaf t.gaf)) + :: + :: fip: accumulate text blocks + =/ fip/(list tape) [p.i.gaf]~ + |- ^- flow + ?~ t.gaf [;/((zing (flop fip))) ~] + ?. ?=($text -.i.t.gaf) + [;/((zing (flop fip))) ^$(gaf t.gaf)] + $(gaf t.gaf, fip :_(fip p.i.t.gaf)) + :: + ++ item + |= nex/graf + ^- flow ::CHECK can be tuna:twig? + ?- -.nex + $text !! :: handled separately + $expr [p.nex]~ + $bold [[%b ~] ^$(gaf p.nex)]~ + $talc [[%i ~] ^$(gaf p.nex)]~ + $code [[%code ~] ;/(p.nex) ~]~ + $quod :: + :: smart quotes + %= ^$ + gaf + :- [%text (tufa ~-~201c. ~)] + %+ weld p.nex + `(list graf)`[%text (tufa ~-~201d. ~)]~ + == + $link [[%a [%href q.nex] ~] ^$(gaf p.nex)]~ + == + -- + :: + ++ hrul :: empty besides fence + (cold ~ ;~(plug hep hep hep (star hep) (just '\0a'))) + :: + ++ para :: paragraph + %+ cook + |=(a/flow ?~(a ~ [[%p ~] a]~)) + ;~(pfix (punt whit) down) + :: + ++ expr :: expression + %+ ifix [(punt whit) (punt whit)] :: whitespace surround + => (sail &) :: tall-form + (cook drop-top top-level) :: list of tags + :: + :: + ++ whit :: whitespace + (cold ' ' (plus ;~(pose (just ' ') (just '\0a')))) + :: + ++ head :: parse heading + %+ cook + |= a/manx:twig ^- marl:twig + =. a.g.a :_(a.g.a [%id (sanitize-to-id c.a)]) + [a]~ + :: + ;~ plug + :: + :: # -> 1 -> %h1, ### -> 3 -> %h3, etc + :(cook |=(a/@u /(crip "h{}")) lent (stun [1 6] hax)) + :: + ;~(pfix whit down) + == + :: + ++ sanitize-to-id :: # text into elem id + |= a/(list tuna:twig) ^- tape + =; raw/tape + %+ turn raw + |= @tD + ^- @tD + ?: ?| &((gte +< 'a') (lte +< 'z')) + &((gte +< '0') (lte +< '9')) + == + +< + ?: &((gte +< 'A') (lte +< 'Z')) + (add 32 +<) + '-' + :: + :: collect all text in header flow + |- ^- tape + ?~ a ~ + %+ weld + ^- tape + ?- i.a + {{$$ {$$ *} $~} $~} :: text node contents + (murn v.i.a.g.i.a |=(a/beer:twig ?^(a ~ (some a)))) + {^ *} $(a c.i.a) :: concatenate children + {@ *} ~ :: ignore interpolation + == + $(a t.a) + -- + -- ++ scab %+ cook |= a/(list wing) ^- twig @@ -9896,6 +10620,8 @@ :~ :- '_' ;~(pfix cab (stag %bccb wide)) + :- ',' + ;~(pfix com (stag %bcsm wide)) :- '$' ;~ pose ;~ pfix buc @@ -9939,13 +10665,13 @@ (stag %bcwt ;~(pfix wut (ifix [pel per] (most ace wyde)))) (cold [%base %bean] wut) == + :- '~' + (cold [%base %null] sig) :- '^' ;~ pose scab (cold [%base %cell] ket) == - :- '.' - scab :- ['a' 'z'] ;~ pose (stag %bcts ;~(plug sym ;~(pfix ;~(pose fas tis) wyde))) @@ -9960,8 +10686,8 @@ :~ :- ',' ;~ pose + ;~(pfix com wyde) (stag %wing rope) - ;~(pfix com (stag %ktsg wide)) == :- '!' ;~ pose @@ -10007,10 +10733,10 @@ :- '(' (stag %cnhp (ifix [pel per] (most ace wide))) :- '{' - (stag %bccl (ifix [kel ker] (most ace wide))) + (stag %bccl (ifix [kel ker] (most ace wyde))) :- '*' ;~ pose - (stag %bunt ;~(pfix tar wide)) + (stag %bunt ;~(pfix tar wyde)) (cold [%base %noun] tar) == :- '@' @@ -10059,7 +10785,7 @@ (stag %dtts ;~(pfix tis (ifix [pel per] ;~(glam wide wide)))) :- '?' ;~ pose - (stag %bcwt ;~(pfix wut (ifix [pel per] (most ace wide)))) + (stag %bcwt ;~(pfix wut (ifix [pel per] (most ace wyde)))) (cold [%base %bean] wut) == :- '[' @@ -10078,7 +10804,7 @@ ;~ pfix tar (stag %kthp (stag [%base %noun] ;~(pfix tec wide))) == - (stag %kthp ;~(plug wide ;~(pfix tec wide))) + (stag %kthp ;~(plug wyde ;~(pfix tec wide))) (stag %ktls ;~(pfix lus ;~(plug wide ;~(pfix tec wide)))) (cook |=(a/twig [[%rock %n ~] a]) wide) == @@ -10189,7 +10915,7 @@ ['.' (runo dot %brdt [~ ~] expa)] ['-' (runo hep %brhp [~ ~] expa)] ['^' (runo ket %brkt [~ ~] expx)] - ['~' (runo sig %brsg [~ ~] expb)] + ['~' (runo sig %brsg [~ ~] exqc)] ['*' (runo tar %brtr [~ ~] exqc)] ['=' (runo tis %brts [~ ~] exqc)] ['?' (runo wut %brwt [~ ~] expa)] @@ -10199,15 +10925,15 @@ ;~ pfix buc %- stew ^. stet ^. limo - :~ ['@' (rune pat %bcpt expb)] + :~ ['@' (rune pat %bcpt exqb)] ['_' (rune cab %bccb expa)] - [':' (rune col %bccl exps)] - ['%' (rune cen %bccn exps)] - ['^' (rune ket %bckt expb)] - ['-' (rune hep %bchp expb)] - ['=' (rune tis %bcts expg)] - ['?' (rune wut %bcwt exps)] - [';' (rune sem %bcsm expa)] + [':' (rune col %bccl exqs)] + ['%' (rune cen %bccn exqs)] + ['^' (rune ket %bckt exqb)] + ['-' (rune hep %bchp exqb)] + ['=' (rune tis %bcts exqg)] + ['?' (rune wut %bcwt exqs)] + [';' (rune sem %bcsm exqa)] == == :- '%' @@ -10510,7 +11236,7 @@ %+ sear :: |= a/(map @ tomb) :: ^- (unit (map @ tomb)) :: - =* fir (~(got by a) 0) :: + =+ fir=(~(got by a) 0) :: ?: (~(has by q.fir) %$) :: %$ in first chapter ~ :: [~ u=a] :: @@ -10519,6 +11245,7 @@ ++ expz |.(loaf(bug &)) :: twig with tracing :: root contents :: + ++ exqa |.(loan) :: one twig ++ exqb |.(;~(gunk loan loan)) :: two roots ++ exqc |.(;~(gunk loan loaf)) :: root then twig ++ exqs |.((butt hunk)) :: closed gapped roots @@ -10696,15 +11423,19 @@ apex:docs fel apse:docs - == - ++ tall %+ knee *twig :: full tall form - |.(~+((wart (wrap ;~(pose (norm | &) long lute apex:(sail &)))))) - ++ till %+ knee *root :: full tall form - |.(~+((wart (wrap ;~(pose (norm & &) scad))))) - ++ wide %+ knee *twig :: full wide form - |.(~+((wart ;~(pose (norm | |) long apex:(sail |))))) - ++ wyde %+ knee *root :: full wide form - |.(~+((wart ;~(pose (norm & |) scad)))) + == + ++ tall :: full tall form + %+ knee *twig + |.(~+((wart (wrap ;~(pose (norm | &) cram long lute apex:(sail &)))))) + ++ till :: mold tall form + %+ knee *root + |.(~+((wart (wrap ;~(pose (norm & &) scad))))) + ++ wide :: full wide form + %+ knee *twig + |.(~+((wart ;~(pose (norm | |) long apex:(sail |))))) + ++ wyde :: mold wide form + %+ knee *root + |.(~+((wart ;~(pose (norm & |) scad)))) ++ wart |* zor/rule %+ here @@ -10716,7 +11447,6 @@ ++ vest ~/ %vest |= tub/nail - ~| %vest ^- (like twig) %. tub %- full From b490c945c66683d9c9df3dfc3b56aafcc14a888d Mon Sep 17 00:00:00 2001 From: Elliot Glaysher Date: Thu, 16 Nov 2017 14:54:32 -0800 Subject: [PATCH 2/2] Stylize layer one of hoon.hoon, make # work in most cases. --- app/dojo.hoon | 6 +- sys/hoon.hoon | 165 +++++++++++++++++++++++++++++++++++++++++--------- 2 files changed, 142 insertions(+), 29 deletions(-) diff --git a/app/dojo.hoon b/app/dojo.hoon index 19874be8a2..0cbd34c2ca 100644 --- a/app/dojo.hoon +++ b/app/dojo.hoon @@ -671,7 +671,7 @@ ?: !=(i.t.topics u.p.p.q.i.tombs) :: this isn't the topic. $(tombs t.tombs) - `[%chapter (trip i.t.topics) q.p.q.i.tombs p.sut q.sut p.i.tombs] + `[%chapter (trip i.t.topics) q.p.q.i.tombs sut q.sut p.i.tombs] :: {$face *} ?. ?=(term q.p.sut) @@ -909,7 +909,7 @@ :> the computed arm documentation and the product documentation. ^- {what what} =+ foot-span=(~(play ut sut) p.f) - =+ raw-product=(what-from-span foot-span) + =/ raw-product/what (what-from-span foot-span) =/ product-product/what ?. ?=({$core *} foot-span) ~ @@ -917,6 +917,8 @@ (what-from-span inner-span) :- ?~ arm-doc + ?~ raw-product + product-product raw-product arm-doc ?~ arm-doc diff --git a/sys/hoon.hoon b/sys/hoon.hoon index 0a20cfdbc4..a6ec48506e 100644 --- a/sys/hoon.hoon +++ b/sys/hoon.hoon @@ -182,7 +182,7 @@ :> :> a: minuend :> b: subtrahend - |= {a/@ b/@} + |= [a=@ b=@] ~_ leaf+"subtract-underflow" :> difference ^- @ @@ -193,9 +193,13 @@ :> :> tree addressing +| -++ cap :: fragment head +++ cap ~/ %cap - |= a/@ + :> tree head + :> + :> tests whether an `a` is in the head or tail of a noun. produces %2 if it + :> is within the head, or %3 if it is within the tail. + |= a=@ ^- ?($2 $3) ?- a $2 %2 @@ -204,9 +208,13 @@ * $(a (div a 2)) == :: -++ mas :: fragment body +++ mas ~/ %mas - |= a/@ + :> axis within head/tail + :> + :> computes the axis of `a` within either the head or tail of a noun + :> (depends whether `a` lies within the the head or tail). + |= a=@ ^- @ ?- a $1 !! @@ -215,10 +223,14 @@ * (add (mod a 2) (mul $(a (div a 2)) 2)) == :: -++ peg :: fragment compose +++ peg ~/ %peg - |= {a/@ b/@} + :> axis within axis + :> + :> computes the axis of {b} within axis {a}. + |= [a=@ b=@] ?< =(0 a) + :> a composed axis ^- @ ?- b $1 a @@ -226,26 +238,125 @@ $3 +((mul a 2)) * (add (mod b 2) (mul $(b (div b 2)) 2)) == -:: :: -:::: 1c: ideal containers :: - :: :: - :: -++ ache |*({a/mold b/mold} $%({$| p/b} {$& p/a})) :: a or b, b default -++ bloq @ :: bitblock, eg 3=byte -++ each |*({a/mold b/mold} $%({$& p/a} {$| p/b})) :: a or b, a default -++ gate $-(* *) :: generic mold -++ list |*(a/mold $@($~ {i/a t/(list a)})) :: nullterminated list -++ lone |*(a/mold p/a) :: 1-tuple -++ mold gate :: normalizing gate -++ pair |*({a/mold b/mold} {p/a q/b}) :: 2-tuple -++ pole |*(a/mold $@($~ {a (pole a)})) :: faceless list -++ qual |* {a/mold b/mold c/mold d/mold} :: 4-tuple - {p/a q/b r/c s/d} :: -++ quip |*({a/mold b/mold} {(list a) b}) :: list-with for sip -++ trap |*(a/mold _|?(*a)) :: producer -++ tree |*(a/mold $@($~ {n/a l/(tree a) r/(tree a)})) :: binary tree -++ trel |*({a/mold b/mold c/mold} {p/a q/b r/c}) :: 3-tuple -++ unit |*(a/mold $@($~ {$~ u/a})) :: maybe +:: +:> # %containers +:> +:> the most basic of data types ++| +++ bloq + :> blocksize + :> + :> a blocksize is the power of 2 size of an atom. ie, 3 is a byte as 2^3 is + :> 8 bits. + @ +:: +++ each +:: todo: do i add "mold generator:" to the following? + :> either {a} or {b}, defaulting to {a}. + :> + :> mold generator: produces a discriminated fork between two types, + :> defaulting to {a}. + |*({a/mold b/mold} $%({$& p/a} {$| p/b})) +:: +++ gate + :> function + :> + :> a core with one arm, `$`--the empty name--which transforms a sample noun + :> into a product noun. If used dryly as a type, the subject must have a + :> sample type of `*`. + $-(* *) +:: +++ list + :> null-terminated list + :> + :> mold generator: produces a mold of a null-terminated list of the + :> homogeneous type {a}. + |*(a/mold $@($~ {i/a t/(list a)})) +:: +++ lone + :> single item tuple + :> + :> mold generator: puts the face of `p` on the passed in mold. + |*(a/mold p/a) +:: +++ mold + :> normalizing gate + :> + :> actually a type alias for gate. + gate +:: +++ pair + :> dual tuple + :> + :> mold generator: produces a tuple of the two types passed in. + :> + :> a: first type, labeled {p} + :> b: second type, labeled {q} + |*({a/mold b/mold} {p/a q/b}) +:: +++ pole + :> faceless list + :> + :> like ++list, but without the faces {i} and {t}. + :> + :> a: a mold for the item type. + |*(a/mold $@($~ {a (pole a)})) +:: +++ qual + :> quadruple tuple + :> + :> mold generator: produces a tuple of the four types passed in. + :> + :> a: first type, labeled {p} + :> b: second type, labeled {q} + :> c: third type, labeled {r} + :> d: fourth type, labeled {s} + |* {a/mold b/mold c/mold d/mold} + {p/a q/b r/c s/d} +:: +++ quip + :> pair of list of first and second + :> + :> a common pattern in hoon code is to return a ++list of changes, along with + :> a new state. + :> + :> a: type of list item + :> b: type of returned state + |*({a/mold b/mold} {(list a) b}) +:: +++ trap + :> a core with one arm `$` + :> + :> a: return type of the `$` arm. + |*(a/mold _|?(*a)) +:: +++ tree + :> tree mold generator + :> + :> a `++tree` can be empty, or contain a node of a type and + :> left/right sub `++tree` of the same type. pretty-printed with `{}`. + :> + :> a: type of tree node + |*(a/mold $@($~ {n/a l/(tree a) r/(tree a)})) :: binary tree +:: +++ trel + :> triple tuple + :> + :> mold generator: produces a tuple of the three types passed in. + :> + :> a: first type, labeled {p} + :> b: second type, labeled {q} + :> c: third type, labeled {r} + |*({a/mold b/mold c/mold} {p/a q/b r/c}) +:: +++ unit + :> maybe + :> + :> mold generator: either `~` or `[~ u=a]` where `a` is the + :> type that was passed in. + :> + :> a: type when non-null + |*(a/mold $@($~ {$~ u/a})) -- => :: :: :::: 2: layer two ::