mirror of
https://github.com/ilyakooo0/urbit.git
synced 2024-12-01 11:33:41 +03:00
Merge branch 'nozap'
This commit is contained in:
commit
c396584886
59
gen/cram.hoon
Normal file
59
gen/cram.hoon
Normal file
@ -0,0 +1,59 @@
|
||||
::
|
||||
:::: hoon/cram/gen
|
||||
::
|
||||
:: test generator for the cram markdown syntax
|
||||
::
|
||||
:: todo: integrate with ++sail and embed in hoon compiler
|
||||
::
|
||||
:: ++cram is a simple markdown-inspired parser that makes
|
||||
:: common html tropes easy to type. you can think of ++cram
|
||||
:: as "rational markdown" or "markdown with syntax errors."
|
||||
:: a document format should be easy to type and read, but
|
||||
:: that doesn't mean it can't or have rigorous syntax.
|
||||
::
|
||||
:: tldr: ++cram is indent-oriented. indent 2 spaces for
|
||||
:: a dynamic interpolation, 4 spaces for example code, 6
|
||||
:: spaces for a blockquote and 8 spaces for verse. separate
|
||||
:: every semantic block by a blank line. use - for
|
||||
:: unordered lists, + for ordered lists.
|
||||
::
|
||||
:: markdown link syntax works. * means bold, _ means
|
||||
:: italics, "" inserts smart quotes. all enclosed
|
||||
:: strings are reparsed; escape the terminator within
|
||||
:: the string, eg, *star \* in bold text*.
|
||||
::
|
||||
:: markdown `literal` syntax is supported, but all hoon
|
||||
:: constants are automatically marked as code. also, any
|
||||
:: hoon expression prefixed with # is a code literal.
|
||||
::
|
||||
:: (++cram is a valid hoon parsing rule, but it does a lot
|
||||
:: of custom processing internally, since the language is
|
||||
:: context-sensitive. we use a context-sensitive parser
|
||||
:: to cut the lines into blocks, then reparse flow blocks
|
||||
:: with normal hoon rules. multipass parsing is the tax
|
||||
:: humans have to pay for simple but human-friendly syntax.)
|
||||
::
|
||||
::|= inp/cord
|
||||
::=< (steam-marl (rash inp apex:(sail &)))
|
||||
=< |=(pax/path (test pax))
|
||||
|% ::
|
||||
++ test :: test text parsing
|
||||
|= pax/path
|
||||
^- tape
|
||||
::
|
||||
:: src: text file as (list cord)
|
||||
:: txt: source as tape with newlines
|
||||
:: vex: parsing result
|
||||
::
|
||||
=/ src .^(wain %cx pax)
|
||||
=. src ['---' src]
|
||||
=/ txt (zing (turn src |=(@t (weld (rip 3 +<) `tape`~[`@`10]))))
|
||||
=/ vex (cram:vast [1 1] txt)
|
||||
::
|
||||
:: print result as error or xml text
|
||||
?~ q.vex
|
||||
"syntax error: line {(scow %ud p.p.vex)}, column {(scow %ud q.p.vex)}"
|
||||
?: [freeze=|] (poxo (snag 1 ~(shut ap p.u.q.vex)))
|
||||
(poxo ;;(manx q:(slap !>(..zuse) p.u.q.vex)))
|
||||
::
|
||||
--
|
1823
lib/vast2.hoon
Normal file
1823
lib/vast2.hoon
Normal file
File diff suppressed because it is too large
Load Diff
24
mar/umd.hoon
Normal file
24
mar/umd.hoon
Normal file
@ -0,0 +1,24 @@
|
||||
::
|
||||
:::: /hoon/umd/mar
|
||||
::
|
||||
/? 310
|
||||
::
|
||||
|_ mud/@t
|
||||
++ grow
|
||||
|%
|
||||
++ mime [/text/x-unmark (taco mud)]
|
||||
++ txt
|
||||
(lore mud)
|
||||
++ elem
|
||||
^- manx
|
||||
[/div ~(shut ap %xml (rash mud fenced:cram:vast))]
|
||||
--
|
||||
++ grab
|
||||
|%
|
||||
++ mime |=({p/mite q/octs} q.q)
|
||||
++ noun @t
|
||||
++ txt role
|
||||
--
|
||||
++ grad %txt
|
||||
++ garb /down
|
||||
--
|
@ -8,8 +8,18 @@
|
||||
==
|
||||
=, format
|
||||
=, html
|
||||
::
|
||||
|%
|
||||
++ script-safe
|
||||
!.
|
||||
|= a/tape ^- tape
|
||||
?~ a a
|
||||
?. ?=({$'<' $'/' *} a) [i.a $(a t.a)]
|
||||
['<' '\\' '/' $(a t.t.a)]
|
||||
--
|
||||
::
|
||||
^- marl
|
||||
=/ tree (en-json (pairs:enjs data+dat sein+dat-sen ~))
|
||||
=/ tree (script-safe (en-json (pairs:enjs data+dat sein+dat-sen ~)))
|
||||
;= ;script(type "text/javascript"): window.tree = {tree}
|
||||
;div#tree;
|
||||
==
|
||||
|
690
sys/hoon.hoon
690
sys/hoon.hoon
@ -4293,8 +4293,8 @@
|
||||
?. =(10 -.res) [-.res $(res +.res)]
|
||||
(welp [`@t`10 (trip lev)] $(res +.res))
|
||||
::
|
||||
++ ifix
|
||||
|* {fel/{rule rule} hof/rule}
|
||||
++ ifix :: prefix and suffix
|
||||
|* {fel/{rule rule} hof/rule} :: surround hof
|
||||
~! +<
|
||||
~! +<:-.fel
|
||||
~! +<:+.fel
|
||||
@ -9880,6 +9880,672 @@
|
||||
?~ 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 %xmn [%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{<a>}")) 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
|
||||
@ -10699,14 +11365,18 @@
|
||||
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
|
||||
|
3
web/unmark/1.txt
Normal file
3
web/unmark/1.txt
Normal file
@ -0,0 +1,3 @@
|
||||
The quick *brown fox* jumped over #(add 2 2)
|
||||
their owner's "extremely lazy" dogs.
|
||||
|
3
web/unmark/10.txt
Normal file
3
web/unmark/10.txt
Normal file
@ -0,0 +1,3 @@
|
||||
;style:'#test-style {transform: skew(25deg)}'
|
||||
|
||||
### Test style
|
12
web/unmark/11.txt
Normal file
12
web/unmark/11.txt
Normal file
@ -0,0 +1,12 @@
|
||||
;+
|
||||
;>
|
||||
foo *some style*
|
||||
|
||||
outdent
|
||||
|
||||
;= ;div; ==
|
||||
|
||||
;=
|
||||
moar markdown
|
||||
==
|
||||
|
11
web/unmark/2.txt
Normal file
11
web/unmark/2.txt
Normal file
@ -0,0 +1,11 @@
|
||||
The quick brown fox jumped _over
|
||||
the_ extremely lazy dogs.
|
||||
|
||||
Then a horse arrived. It was extremely angry.
|
||||
Outside, two bears [were fighting](http://google.com) each other.
|
||||
|
||||
Also present at the scene were:
|
||||
|
||||
- an Armenian.
|
||||
|
||||
Everything was soon back to normal.
|
52
web/unmark/3.txt
Normal file
52
web/unmark/3.txt
Normal file
@ -0,0 +1,52 @@
|
||||
#(add 2 2) is a hoon expression
|
||||
|
||||
un*bearably*
|
||||
|
||||
0b1100
|
||||
|
||||
---
|
||||
|
||||
|
||||
## This is a header
|
||||
|
||||
The quick brown fox jumped over
|
||||
the extremely lazy dogs.
|
||||
|
||||
Then a horse arrived. It was extremely angry.
|
||||
Outside, two bears [were fighting](http://google.com) each other.
|
||||
|
||||
Also present at _the intense %hoon scene_ were:
|
||||
|
||||
- an Armenian.
|
||||
|
||||
- a haberdasher.
|
||||
|
||||
A haberdasher is someone who makes hats. There are quite
|
||||
a few kinds of hats:
|
||||
|
||||
- fedoras
|
||||
|
||||
- borsalinos
|
||||
|
||||
- sombreros
|
||||
|
||||
- baseball caps
|
||||
|
||||
All these devices will protect your bald spot from the rain.
|
||||
|
||||
It is _sometimes difficult_ to be a bald man when it's raining.
|
||||
|
||||
We sometimes speak in %hoon We also say 0xdead.beef things like ~ and #`@`2.
|
||||
|
||||
We don't care if we sound funny, and sometimes we !@#$%%#^? cuss.
|
||||
|
||||
```
|
||||
We also sometimes put
|
||||
in
|
||||
code
|
||||
looks
|
||||
|
||||
like
|
||||
this.
|
||||
```
|
||||
|
18
web/unmark/4.txt
Normal file
18
web/unmark/4.txt
Normal file
@ -0,0 +1,18 @@
|
||||
## A digital home base
|
||||
|
||||
What you need is a digital home base. What is that computer? Is
|
||||
it (a) your phone, (b) your browser, (c) your PC or laptop, (d)
|
||||
your AWS instance, (e) your RasPi or other custom home computer?
|
||||
|
||||
Here are three obvious features your digital home base needs.
|
||||
(1) it should be infinitely secure and persistent -- at the level
|
||||
of Amazon S3, Gmail, your bank, etc. (2) it should be a server,
|
||||
not just a client. (3) it should be usable by ordinary people.
|
||||
|
||||
Everything except (d) falls far short of (1) and/or (2). (d)
|
||||
falls far short of (3).
|
||||
|
||||
The missing piece is a practical _personal server_ -- a virtual
|
||||
computer in the cloud, with persistence guarantees comparable to
|
||||
cloud storage services, that's as completely yours as a RasPi.
|
||||
|
6
web/unmark/6.txt
Normal file
6
web/unmark/6.txt
Normal file
@ -0,0 +1,6 @@
|
||||
*brown fox* ;{s "ignoreme"} ;{a(name "foo")} jumped over
|
||||
|
||||
;div#test: hello world
|
||||
|
||||
- - foo
|
||||
- bar
|
37
web/unmark/8.txt
Normal file
37
web/unmark/8.txt
Normal file
@ -0,0 +1,37 @@
|
||||
> xyz
|
||||
abc
|
||||
|
||||
```
|
||||
code at the beginning of the line
|
||||
```
|
||||
|
||||
zyxxy
|
||||
|
||||
> bar
|
||||
|
||||
poe
|
||||
m
|
||||
|
||||
> baz
|
||||
> bal
|
||||
|
||||
- - bleh
|
||||
- blah
|
||||
+ one
|
||||
+ two
|
||||
|
||||
1
|
||||
|
||||
> > bel
|
||||
> what did you just say about me
|
||||
|
||||
...
|
||||
|
||||
```
|
||||
code
|
||||
still code?
|
||||
```
|
||||
|
||||
> > foo
|
||||
|
||||
not-code
|
1
web/unmark/9.txt
Normal file
1
web/unmark/9.txt
Normal file
@ -0,0 +1 @@
|
||||
> - + ;div.test: nesting
|
89
web/unmark/all.hoon
Normal file
89
web/unmark/all.hoon
Normal file
@ -0,0 +1,89 @@
|
||||
:: Render all %%/{@u}.txt test cases
|
||||
::
|
||||
:::: /hoon/all/unmark/web
|
||||
::
|
||||
/- down, markdown
|
||||
/+ vast2
|
||||
::
|
||||
/= cor /^ (list {@ud wain})
|
||||
/: /%%/ /_ @ud /txt/
|
||||
/= mad /: /%%/cm-spec /down/
|
||||
::
|
||||
|%
|
||||
++ rolt |=(a/wall `tape`?~(a ~ ?~(t.a i.a :(weld i.a "\0a" $(a t.a)))))
|
||||
++ wush
|
||||
|= {wid/@u tan/tang} ^- tape
|
||||
(rolt (zing (turn tan |=(a/tank (wash 0^wid a)))))
|
||||
::
|
||||
++ mads
|
||||
|= a/wain ^- marl
|
||||
=/ try (mule |.(~(shut ap (rash (nule ';>' a) apex:(sail &):vast2))))
|
||||
?- -.try
|
||||
$& p.try
|
||||
$| ;= ;div
|
||||
;h3: ERROR
|
||||
;pre: {(wush 120 p.try)}
|
||||
== == ==
|
||||
::
|
||||
++ split-on
|
||||
=| hed/wain
|
||||
|= {mid/@t all/wain} ^+ [hed all]
|
||||
?~ all !!
|
||||
?: =(mid i.all) [(flop hed) t.all]
|
||||
$(all t.all, hed :_(hed i.all))
|
||||
::
|
||||
++ strip
|
||||
|= a/manx ^- manx
|
||||
:_ (turn c.a ..$)
|
||||
?+ g.a g.a
|
||||
{@ {$id *} *} g.a(a t.a.g.a)
|
||||
{$$ {$$ *} $~}
|
||||
=< g.a(v.i.a (tufa (turn (tuba v.i.a.g.a) .)))
|
||||
|=(b/@c `@`?+(b b $~-~201c. '"', $~-~201d. '"'))
|
||||
==
|
||||
--
|
||||
::
|
||||
^- manx
|
||||
;ul
|
||||
;li
|
||||
;h2: Core
|
||||
;ul
|
||||
;* ^- marl
|
||||
%+ turn cor
|
||||
|= {num/@u txt/wain}
|
||||
;li: ;{p -[<num>]} *{(mads txt)} ;{hr}
|
||||
==
|
||||
==
|
||||
;li
|
||||
;h2: CommonMark
|
||||
;ol
|
||||
;* ?: [disabled=&] ; DISABLED
|
||||
^- marl
|
||||
%+ murn `down`mad
|
||||
|= a/elem:markdown
|
||||
?: ?=($head -.a)
|
||||
?. ?=({{$$ *} $~} q.a)
|
||||
~
|
||||
(some /(crip "h{<p.a>}") ;"{p.i.q.a}")
|
||||
?. ?=({$code ^ *} a) ~
|
||||
?. =("example" r.u.p.a) ~
|
||||
%- some
|
||||
^- manx
|
||||
|-
|
||||
=+ [inp out]=(split-on '.' q.a)
|
||||
=/ mar c:(snag 0 (mads inp))
|
||||
;li
|
||||
;pre: {(trip (role inp))}
|
||||
;p: =>
|
||||
;pre: {(trip (role out))}
|
||||
;p: vs
|
||||
;pre: {(many:poxo mar "")}
|
||||
;p
|
||||
;- =/ pox (rush (role out) many:poxa)
|
||||
?~ pox "INVALID"
|
||||
?: =(u.pox mar) "EQUIVALENT"
|
||||
?: =(u.pox (turn mar strip)) "COMPATIBLE"
|
||||
"DIVERGE"
|
||||
==
|
||||
== ==
|
||||
== ==
|
9413
web/unmark/cm-spec.md
Normal file
9413
web/unmark/cm-spec.md
Normal file
File diff suppressed because it is too large
Load Diff
348
web/unmark/doc.umd
Normal file
348
web/unmark/doc.umd
Normal file
@ -0,0 +1,348 @@
|
||||
:: :- :* title+"urbit-flavored markdown docs"
|
||||
:: author+"ted blackman"
|
||||
:: date+~2017.8.25
|
||||
:: ==
|
||||
::
|
||||
;>
|
||||
|
||||
# udon: urbit-flavored markdown
|
||||
|
||||
## overview
|
||||
|
||||
Udon is a minimal markup language for creating and rendering text documents,
|
||||
with a markdown-inspired syntax. It's integrated with the hoon programming
|
||||
language, allowing it to be used as standalone prose in its own file or inside
|
||||
a hoon source file, in which case it will be parsed into a tree of HTML nodes
|
||||
using hoon's `sail` datatype.
|
||||
|
||||
Udon is stricter than markdown and generally supports only one syntax for each
|
||||
type of HTML node it emits.
|
||||
|
||||
### headers
|
||||
|
||||
Headers in udon begin with one or more `#` characters, followed by a space. The
|
||||
number of leading `#`s corresponds to the resulting HTML element: `#` yields an
|
||||
`<h1>`, `##` yields an `<h2>`, and so on through `<h6>`.
|
||||
|
||||
Example:
|
||||
```
|
||||
### Header (h3)
|
||||
|
||||
##### Header (h5)
|
||||
```
|
||||
produces:
|
||||
|
||||
> ### Header (h3)
|
||||
|
||||
##### Header (h5)
|
||||
|
||||
### lists
|
||||
|
||||
A line beginning with a `-` or `+` followed by a space is interpreted as an
|
||||
element of a list. `-` means unordered list (`<ul>`) and `+` means ordered list
|
||||
(`<ol>`).
|
||||
|
||||
Example:
|
||||
|
||||
```
|
||||
- unordered 1
|
||||
text on newline shows up on same line
|
||||
- unordered 2\
|
||||
text on newline after `\` puts in <br> line break
|
||||
|
||||
- unordered after 1 blank line
|
||||
- nested
|
||||
- double-nested
|
||||
|
||||
+ leading '+'
|
||||
+ leading '+'
|
||||
- unordered '-'
|
||||
+ nested ordered '+' item 1
|
||||
+ nested ordered '+' item 2
|
||||
|
||||
+ ordered '+'
|
||||
+ nested item 1
|
||||
+ nested item 2
|
||||
```
|
||||
|
||||
produces:
|
||||
|
||||
> - unordered 1
|
||||
text on newline shows up on same line
|
||||
- unordered 2\
|
||||
text on newline after `\` puts in <br> line break
|
||||
|
||||
- unordered after 1 blank line
|
||||
- nested
|
||||
- double-nested
|
||||
|
||||
+ leading '+'
|
||||
+ leading '+'
|
||||
- unordered '-'
|
||||
+ nested ordered '+' item 1
|
||||
+ nested ordered '+' item 2
|
||||
|
||||
+ ordered '+'
|
||||
+ nested item 1
|
||||
+ nested item 2
|
||||
|
||||
### blockquotes
|
||||
|
||||
A section of text beginning with `> ` and indented by two spaces yields a
|
||||
`<blockquote>` element. This blockquote can itself turn contain more udon,
|
||||
including more blockquotes to render nested levels of quotation.
|
||||
|
||||
Example:
|
||||
|
||||
```
|
||||
> As Gregor Samsa awoke one morning from uneasy dreams
|
||||
he found himself _transformed_ in his bed into a *monstrous* vermin.
|
||||
```
|
||||
|
||||
produces:
|
||||
|
||||
> > As Gregor Samsa awoke one morning from uneasy dreams
|
||||
he found himself _transformed_ in his bed into a *monstrous* vermin.
|
||||
|
||||
### code blocks
|
||||
|
||||
By enclosing a block of text in `\`\`\` on their own lines
|
||||
before and after the block, the text will be treated as a code block.
|
||||
|
||||
Example:
|
||||
|
||||
```
|
||||
> ```
|
||||
(def Y (fn [f]
|
||||
((fn [x]
|
||||
(x x))
|
||||
(fn [x]
|
||||
(f (fn [y]
|
||||
((x x) y)))))))
|
||||
```
|
||||
```
|
||||
|
||||
produces:
|
||||
|
||||
> ```
|
||||
(def Y (fn [f]
|
||||
((fn [x]
|
||||
(x x))
|
||||
(fn [x]
|
||||
(f (fn [y]
|
||||
((x x) y)))))))
|
||||
```
|
||||
|
||||
### poems
|
||||
|
||||
A poem is a section of text with meaningful newlines. Normally in udon,
|
||||
newlines are treated as spaces and do not create a new line of text. If you
|
||||
want to embed text where newlines are retained, then indent the text by
|
||||
question with eight spaces.
|
||||
|
||||
Example:
|
||||
```
|
||||
A shape with lion body and the head of a man,
|
||||
A gaze blank and pitiless as the sun,
|
||||
Is moving its slow thighs, while all about it
|
||||
Reel shadows of the indignant desert birds.
|
||||
```
|
||||
produces:
|
||||
> A shape with lion body and the head of a man,
|
||||
A gaze blank and pitiless as the sun,
|
||||
Is moving its slow thighs, while all about it
|
||||
Reel shadows of the indignant desert birds.
|
||||
|
||||
### sail expressions
|
||||
|
||||
It's possible to use udon as an HTML templating language akin to
|
||||
PHP, ERB, JSP, or Handlebars templates. This facility derives
|
||||
in part from the support for embedding hoon code inside the markup.
|
||||
There are two ways to do embed hoon in udon: inline expressions and sail.
|
||||
[Sail](https://urbit.org/fora/posts/~2017.7.6..21.27.00..bebb~/)
|
||||
is a DSL within hoon for creating XML nodes, including HTML. It can
|
||||
be used directly within udon to provide scripting capability and also to
|
||||
provide more fine-grained control over the resulting HTML.
|
||||
|
||||
Example:
|
||||
```
|
||||
;=
|
||||
;p
|
||||
;strong: Don't panic!
|
||||
;br;
|
||||
;small: [reactive publishing intensifies]
|
||||
==
|
||||
==
|
||||
```
|
||||
|
||||
produces:
|
||||
> ;=
|
||||
;p
|
||||
;strong: Don't panic!
|
||||
;br;
|
||||
;small: [reactive publishing intensifies]
|
||||
==
|
||||
==
|
||||
|
||||
_Note:
|
||||
[urbit's web publishing system](https://urbit.org/docs/arvo/web-apps/)
|
||||
currently does not apply `<style>` elements or element attributes,
|
||||
which are supported in sail syntax. Future versions of the publishing
|
||||
system will rectify this._
|
||||
|
||||
### horizontal rules
|
||||
|
||||
`---` on its own line produces an `<hr>` element, the 'horizontal rule'.
|
||||
This is rendered as a horizontal line the width of its containing paragraph.
|
||||
|
||||
Example:
|
||||
```
|
||||
Above the line
|
||||
---
|
||||
Below the line
|
||||
```
|
||||
> :: produces:\
|
||||
Above the line
|
||||
---
|
||||
Below the line
|
||||
|
||||
### inline markup
|
||||
|
||||
In addition to the above, udon includes several options for marking up
|
||||
inline text.
|
||||
|
||||
##### bold
|
||||
|
||||
Enclose some text in asterisks to boldly render it inside a `<b>` element.
|
||||
|
||||
Example:
|
||||
```
|
||||
The first rule of tautology club is
|
||||
*the first rule of tautology club*.
|
||||
```
|
||||
produces:\
|
||||
|
||||
> The first rule of tautology club is
|
||||
*the first rule of tautology club*.
|
||||
|
||||
##### italics
|
||||
|
||||
Surrounding text with `_` on each side will cause it to appear
|
||||
in italics, using an <i> element.
|
||||
|
||||
Example:
|
||||
```
|
||||
Bueller? _Bueller?_
|
||||
```
|
||||
|
||||
produces:
|
||||
|
||||
Bueller? _Bueller?_
|
||||
|
||||
##### double quote
|
||||
|
||||
Text enclosed in double quotes (`"`) will be rendered with
|
||||
opening and closing quotes.
|
||||
|
||||
Example:
|
||||
```
|
||||
"Yes," he said. "That is the way with him."
|
||||
```
|
||||
produces:\
|
||||
|
||||
"Yes," he said. "That is the way with him."
|
||||
|
||||
##### backslash escape
|
||||
|
||||
A backslash directly before a word (with no spaces) will be interpreted
|
||||
as an escape character, causing it to be rendered raw.
|
||||
|
||||
Example:
|
||||
```
|
||||
Here is some *bold* text.
|
||||
Here is some \*not bold\* text.
|
||||
```
|
||||
produces:
|
||||
|
||||
Here is some *bold* text.
|
||||
Here is some \*not bold\* text.
|
||||
|
||||
##### trailing backslash
|
||||
|
||||
A backslash at the end of a line inserts a line break (`<br>`)
|
||||
after that line. This contrasts with the normal udon behavior of
|
||||
converting newlines to spaces.
|
||||
|
||||
Example:
|
||||
```
|
||||
I wonder how long each line
|
||||
will be if I put backslashes\
|
||||
at the ends of the lines.
|
||||
```
|
||||
produces:
|
||||
|
||||
I wonder how long each line
|
||||
will be if I put backslashes\
|
||||
at the ends of the lines.
|
||||
|
||||
##### inline code literal
|
||||
|
||||
Enclosing some text in ``` characters will cause it to be displayed as code,
|
||||
inside a <code> element with monospace font and a different background color.
|
||||
|
||||
Example:
|
||||
```
|
||||
`*[a 2 b c] -> *[*[a b] *[a c]]` is like lisp's `apply`.
|
||||
```
|
||||
produces:\
|
||||
|
||||
`*[a 2 b c] -> *[*[a b] *[a c]]` is like lisp's `apply`.
|
||||
|
||||
Also, using the `++` prefix before a word will cause the word
|
||||
to be rendered as code, since that's the standard notation
|
||||
for an arm in hoon.
|
||||
|
||||
Example:
|
||||
```
|
||||
The udon parser is part of ++vast.
|
||||
```
|
||||
produces:\
|
||||
|
||||
The udon parser is part of ++vast.
|
||||
|
||||
##### hoon constants
|
||||
|
||||
Hoon has several syntactic forms for literals (numbers, strings, dates, etc.)
|
||||
that can be used in udon as well. They will appear inside a <code> element like
|
||||
inline code.
|
||||
|
||||
Example:
|
||||
|
||||
```
|
||||
~2017.8.29 \
|
||||
0xdead.beef \
|
||||
%term
|
||||
```
|
||||
|
||||
produces:\
|
||||
|
||||
~2017.8.29 \
|
||||
0xdead.beef \
|
||||
%term
|
||||
|
||||
##### url
|
||||
|
||||
To insert a hyperlink, put the text content of the link in `[]` brackets
|
||||
followed by the destination URL in `()` parentheses. Note that the text
|
||||
of the displayed link can contain markdown styling.
|
||||
|
||||
Example:
|
||||
|
||||
```
|
||||
A [hoon `core`](https://urbit.org/docs/hoon/concepts/#-core-object)
|
||||
is similar to an object in a traditional programming langauge.
|
||||
```
|
||||
produces:\
|
||||
|
||||
A [hoon `core`](https://urbit.org/docs/hoon/concepts/#-core-object)
|
||||
is similar to an object in a traditional programming langauge.
|
8
web/unmark/test.hoon
Normal file
8
web/unmark/test.hoon
Normal file
@ -0,0 +1,8 @@
|
||||
:- ;>
|
||||
indented
|
||||
indented
|
||||
|
||||
:- ;= ;>
|
||||
==
|
||||
;= ;> some *markdown*
|
||||
==
|
Loading…
Reference in New Issue
Block a user