urbit/gen/cram.hoon

983 lines
30 KiB
Plaintext
Raw Normal View History

2017-07-16 03:59:57 +03:00
::
2017-07-24 09:19:53 +03:00
:::: hoon/cram/gen
2017-07-16 03:59:57 +03:00
::
2017-07-24 22:21:53 +03:00
:: 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.
::
2017-07-25 01:49:59 +03:00
:: tldr: ++cram is indent-oriented. indent 2 spaces for
2017-07-24 22:21:53 +03:00
:: a dynamic interpolation, 4 spaces for example code, 6
:: spaces for a blockquote and 8 spaces for verse. separate
2017-07-25 01:49:59 +03:00
:: every semantic block by a blank line. use - for
:: unordered lists, + for ordered lists.
::
2017-07-24 22:21:53 +03:00
:: 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
2017-07-25 01:49:59 +03:00
:: hoon expression prefixed with # is a code literal.
2017-07-24 22:21:53 +03:00
::
:: (++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.)
2017-07-25 02:00:44 +03:00
::
2017-07-25 01:55:57 +03:00
|%
++ dynamic
|%
++ mane $@(@tas {@tas @tas}) :: XML name+space
++ manx {g/marx c/marl} :: XML node
++ marl (list $^(manx tuna)) :: XML node list
++ mart (list {n/mane v/(list beer)}) :: XML attributes
++ marx {n/mane a/mart} :: XML tag
++ tuna {?($tape $manx $marl $call) p/twig}
--
::
++ freeze
|= manx:dynamic ^- manx
:- [n.g (turn a.g freeze-mart)]
%+ turn c
|=(a/=>(dynamic $^(manx tuna)) ?@(-.a !! (freeze a)))
::
++ freeze-mart
|= {n/mane v/(list beer)} ^- {mane tape}
[n (turn v |=(a/beer ?^(a !! a)))]
::
::+|
::
++ steam
|= manx:dynamic ^- twig:manx
:- [(steam-mane n.g) %conl (turn a.g steam-mart)]
!.
2017-07-25 01:55:57 +03:00
|- ^- twig:marl
?~ c [%conl ~]
?- -.i.c
^ [(steam i.c) $(c t.c)]
$manx [p.i.c $(c t.c)]
$tape [[%nub p.i.c] $(c t.c)]
$call [%call p.i.c [$(c t.c)]~]
$marl [%per [p.i.c $(c t.c)] cons-twig]
==
::
++ cons-twig ^- twig
!,(*twig =>([a b]=. |-(?~(a b [-.a $(a +.a)]))))
:::+ %per [%name 2+[%a %b] $+1] :: => [a b]=.
:::* %loop :: |-
:: %ifno /a wing+/b :: ?~ a b
:: [wing+/[&+2]/a make+[/[%$] [/a /[&+3]/a]~]] :: [-.a $(a +.a)]
::==
::
++ steam-mane
|= a/mane ^- twig
?@(a [%rock %tas a] [[%rock %tas -.a] [%rock %tas +.a]])
::
++ steam-mart
|= {n/mane v/(list beer)}
[(steam-mane n) %knit v]
::
::+|
::
++ beet $@ @ :: advanced embed
$% {$a p/twig} :: take tape
{$b p/twig} :: take manx
{$c p/twig} :: take marl
{$d p/twig} :: take $-(marl marl)
{$e p/twig q/(list tuna)} :: element literal
== ::
::
++ tuna :: tagflow
$% {$a p/twig} :: plain text
{$b p/twig} :: single tag
{$c p/twig} :: simple list
{$d p/twig} :: dynamic list
{$e p/twig q/(list tuna)} :: element
{$f p/(list tuna)} :: subflow
== ::
::
++ sail :: xml template
|= tol/? =| lin/?
|%
++ ape :: product twig
%+ cook
|= tum/tuna ^- twig
?: ?=({$e *} tum)
[p.tum (sag q.tum)]
(sag tum ~)
amp
::
++ amp :: entry point
;~(pfix sem ?:(tol bam bat))
::
++ bam :: tall top
%+ knee *tuna |. ~+
;~ pose
(stag %f ;~(pfix (plus ace) (cook rab puv)))
(stag %e ;~(plug hag nal))
(stag %e hul)
(stag %f nup)
;~(pfix tis (stag %f nol))
;~(pfix hep (stag %a ;~(pfix gap tall)))
;~(pfix lus (stag %b ;~(pfix gap tall)))
;~(pfix tar (stag %c ;~(pfix gap tall)))
;~(pfix cen (stag %d ;~(pfix gap tall)))
(easy [%f [%a [%knit 10 ~]] ~])
==
::
++ bat :: wide outer top
%+ knee *tuna |. ~+
;~ pose
(stag %f nup)
(stag %f ped)
(stag %e ;~(plug hig lif))
==
::
++ bet :: wide inner top
%+ knee *tuna |. ~+
;~ pose
bat
;~(pfix hep (stag %a wide))
;~(pfix lus (stag %b wide))
;~(pfix tar (stag %c wide))
;~(pfix cen (stag %d wide))
==
::
++ fry :: mane as twig
%+ cook
|= {a/@tas b/(unit @tas)}
?~ b
[%rock %tas a]
[[%rock %tas a] [%rock %tas u.b]]
;~(plug sym ;~(pose (stag ~ ;~(pfix cab sym)) (easy ~)))
::
++ hag :: script or style
%+ cook |=(a/twig a)
;~ plug
(stag %rock (stag %tas ;~(pose (jest %script) (jest %style))))
(stag %conl jaw)
==
::
++ hig :: simple head
(cook |=({a/twig b/(list twig)} [a %conl b]) hog)
::
++ hog :: tag head
%+ cook
|= hug
^- {twig (list twig)}
=- [a (welp - ?~(c d [[[%rock %tas p.c] q.c] d]))]
=- (~(tap by -))
%. |=(e/(list tank) [%knit ~(ram re %rose [" " `~] e)])
=< ~(run by (reel b .))
|= {e/{p/term q/term} f/(jar twig tank)}
(~(add ja f) [%rock %tas p.e] [%leaf (trip q.e)])
;~ plug
fry
=- (star ;~(plug - sym))
;~(pose (cold %class dot) (cold %id hax))
=- ;~(pose ;~(plug - (stag %knit soil)) (easy ~))
;~(pose (cold %href fas) (cold %src pat))
;~ pose
%+ ifix [pel per]
%+ more ;~(plug com ace)
;~(plug fry ;~(pfix ace wide))
::
(easy ~)
==
==
::
++ hoy :: tall attributes
%- star
;~ pfix ;~(plug gap tis)
;~(plug fry ;~(pfix gap tall))
==
::
++ hug :: head shape
$: a/twig :: XX translation
b/(list {@tas @tas})
c/$@($~ {p/@tas q/twig})
d/(list twig)
==
::
++ hul :: tall preface
%+ cook
|= {a/{p/twig q/(list twig)} b/(list twig) c/(list tuna)}
^- {twig (list tuna)}
[[p.a %conl (weld q.a b)] c]
;~(plug hog hoy nol)
::
++ jaw :: wide attributes
;~ pose
%+ ifix [pel per]
%+ more ;~(plug com ace)
;~(plug fry ;~(pfix ace wide))
::
(easy ~)
==
::
++ lif :: wide elements
%+ cook |=(a/(list tuna) a)
;~(pose ;~(pfix col pep) (cold ~ sem) (easy ~))
::
++ luf :: wide elements
%+ cook |=(a/(list tuna) a)
(star ;~(pfix ace bet))
::
++ nal :: unescaped tall tail
%+ cook |=(a/(list tuna) a)
%+ ifix [gap ;~(plug gap duz)]
%+ most gap
;~ pfix sem
;~ pose
;~ pfix ace
%+ cook
|= a/tape
[%a %knit (weld a `tape`[`@`10 ~])]
(star (shim 32 255))
==
(easy [%a %knit `@`10 ~])
==
==
::
++ nol :: tall tail
?> tol
%+ cook |=(a/(list tuna) a)
;~ pose
(cold ~ sem)
;~(pfix col pep(tol |))
;~(pfix ;~(plug col ace) (cook rab(tol |) puv))
(ifix [gap ;~(plug gap duz)] (most gap amp))
==
::
++ nup :: wide quote
%+ cook |=(a/(list tuna) a)
;~ pose
;~(less (jest '"""') (ifix [doq doq] (cook rab puv)))
(inde (ifix [(jest '"""\0a') (jest '\0a"""')] (cook rab puv(lin |))))
==
::
++ pab (ifix [kel ker] ;~(plug hig luf)) :: bracketed element
++ ped :: wide flow
%+ cook |=(a/(list tuna) a)
(ifix [pel per] (more ace bet))
::
++ pep :: wrapped tuna
%+ cook |=(a/(list tuna) a)
;~ pose
ped
(ifix [pel per] (more ace bet))
(cook |=(@t [%a %knit (trip +<)]~) qut)
;~ plug
bat
(easy ~)
==
==
::
++ puv :: wide+tall flow
%+ cook |=(a/(list beet) a)
%- star
;~ pose
;~(pfix bas ;~(pose (mask "-+*%;\{") bas doq bix:ab))
;~(pfix hep (stag %a sump))
;~(pfix lus (stag %b sump))
;~(pfix tar (stag %c sump))
;~(pfix cen (stag %d sump))
;~(pfix sem (stag %e pab(tol |)))
;~(less bas kel ?:(tol fail doq) prn)
?:(lin fail ;~(less (jest '\0a"""') (just '\0a')))
(stag %a sump)
==
::
++ rab :: beet to tuna
|= reb/(list beet)
^- (list tuna)
=| {sim/(list @) tuz/(list tuna)}
|- ^- (list tuna)
?~ reb
=. sim
?. tol sim
[10 |-(?~(sim sim ?:(=(32 i.sim) $(sim t.sim) sim)))]
?~(sim tuz [[%a %knit (flop sim)] tuz])
?@ i.reb
$(reb t.reb, sim [i.reb sim])
=+ zut=$(reb t.reb, sim ~)
?~ sim [i.reb zut]
[[%a %knit (flop sim)] i.reb zut]
::
++ sag :: tuna to twig
|= lut/(list tuna)
^- twig
:- %conp
|- ^- (list twig)
?~ lut [[%rock %n ~] ~]
?- -.i.lut
$a [[%nub p.i.lut] $(lut t.lut)]
$b [p.i.lut $(lut t.lut)]
$c :_ ~
:+ %lace `twig`[p.i.lut [%conp $(lut t.lut)]]
:+ %new [%base %cell]
:- %core
^- (map term foot)
:_ [~ ~]
=+ sug=[[%& 12] ~]
:+ %$ %elm
:^ %ifno sug
[%make sug [[[[%& 1] ~] [%$ 13]] ~]]
[%make sug [[[[%& 3] ~] [%make [%$ ~] [[sug [%$ 25]] ~]]] ~]]
$d [[%call p.i.lut [%conp $(lut t.lut)] ~] ~]
$e [[p.i.lut ^$(lut [[%f q.i.lut] ~])] $(lut t.lut)]
$f $(lut (weld p.i.lut t.lut))
==
--
2017-07-25 01:55:57 +03:00
--
2017-07-25 01:50:39 +03:00
|= pax/path
2017-07-24 02:00:45 +03:00
=< (test pax)
2017-07-16 03:59:57 +03:00
=> |%
2017-07-18 04:07:47 +03:00
++ item (pair mite (list flow)) :: xml node generator
2017-07-16 03:59:57 +03:00
++ colm @ud :: column
2017-07-21 06:19:22 +03:00
++ flow manx :: node or generator
2017-07-18 04:07:47 +03:00
++ mite :: context
$? $down :: outer embed
$list :: unordered list
$lime :: list item
$lord :: ordered list
2017-07-19 06:19:27 +03:00
$poem :: verse
2017-07-18 04:07:47 +03:00
$bloc :: blockquote
$code :: preformatted code
2017-07-21 06:19:22 +03:00
$head :: heading
2017-07-19 06:19:27 +03:00
$expr :: dynamic expression
2017-07-21 06:19:22 +03:00
== ::
2017-07-16 03:59:57 +03:00
++ trig :: line style
2017-07-25 01:49:59 +03:00
$: col/@ud :: start column
2017-07-16 03:59:57 +03:00
$= sty :: style
$? $fini :: terminator
$done :: end of input
2017-07-16 03:59:57 +03:00
$lint :: + line item
$lite :: - line item
$head :: # heading
$text :: anything else
== == ::
2017-07-21 06:19:22 +03:00
++ graf :: input fragment
2017-07-24 09:19:53 +03:00
$% {$bold p/(list graf)} :: *bold*
{$talc p/(list graf)} :: _italics_
{$quod p/(list graf)} :: "double quote"
2017-07-22 09:56:21 +03:00
{$code p/tape} :: code literal
{$text p/tape} :: text symbol
2017-07-24 09:19:53 +03:00
{$link p/(list graf) q/tape} :: URL
2017-07-21 06:19:22 +03:00
==
2017-07-16 03:59:57 +03:00
--
!.
2017-07-25 01:49:59 +03:00
|% ::
2017-07-24 02:00:45 +03:00
++ 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)
=* txt (zing (turn src |=(@t (weld (rip 3 +<) `tape`~[`@`10]))))
=/ vex (cram [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)}"
(poxo ;;(manx q:(slap =>(..onan !>(~)) (steam p.u.q.vex))))
2017-07-24 02:00:45 +03:00
:: ::
++ cram :: parse unmark
2017-07-16 03:59:57 +03:00
|= {naz/hair los/tape}
2017-07-22 09:56:21 +03:00
^- (like flow)
2017-07-16 03:59:57 +03:00
::
2017-07-25 01:49:59 +03:00
:: state of the parsing loop. we maintain a construction
2017-07-24 22:21:53 +03:00
:: 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.
::
2017-07-18 04:07:47 +03:00
:: err: error position
2017-07-16 03:59:57 +03:00
:: col: current control column
:: hac: stack of items under construction
:: cur: current item under construction
2017-07-20 07:48:00 +03:00
:: lub: current block being read in
2017-07-16 03:59:57 +03:00
::
2017-07-18 04:07:47 +03:00
=| err/(unit hair)
=/ col q.naz
2017-07-16 03:59:57 +03:00
=| hac/(list item)
2017-07-20 07:48:00 +03:00
=/ cur/item [%down ~]
2017-07-16 03:59:57 +03:00
=| lub/(unit (pair hair (list tape)))
2017-07-18 04:07:47 +03:00
=< $:line
2017-07-16 03:59:57 +03:00
|%
:: ::
2017-07-20 07:48:00 +03:00
++ $ :: resolve
2017-07-22 09:56:21 +03:00
^- (like flow)
2017-07-20 07:48:00 +03:00
:: if error position is set, produce error
2017-07-16 03:59:57 +03:00
::
2017-07-20 07:48:00 +03:00
?. =(~ err) [+.err ~]
:: all data was consumed
2017-07-16 03:59:57 +03:00
::
2017-07-20 07:48:00 +03:00
=- [naz `[- [naz los]]]
2017-07-22 09:56:21 +03:00
|- ^- flow
2017-07-20 07:48:00 +03:00
:: fold all the way to top
2017-07-16 03:59:57 +03:00
::
2017-07-22 09:56:21 +03:00
?~ hac fine
2017-07-20 07:48:00 +03:00
$(..^$ fold)
2017-07-16 03:59:57 +03:00
:: ::
++ back :: column retreat
2017-07-20 07:48:00 +03:00
|= luc/@ud
2017-07-18 04:07:47 +03:00
^+ +>
2017-07-20 07:48:00 +03:00
?: =(luc col) +>
:: nex: next backward step that terminates this context
::
=/ nex/@ud
?- p.cur
2017-07-24 09:19:53 +03:00
$down 2
2017-07-21 06:19:22 +03:00
$head 0
2017-07-20 07:48:00 +03:00
$expr 2
$list 0
$lime 2
$lord 0
$poem 8
$code 4
$bloc 6
==
?: (gth nex (sub col luc))
:: indenting pattern violation
::
2017-07-24 09:19:53 +03:00
..^$(col luc, err `[p.naz luc])
=. ..^$ fold
$(col (sub col nex))
2017-07-16 03:59:57 +03:00
:: ::
2017-07-20 07:48:00 +03:00
++ fine :: item to flow
^- flow
2017-07-24 09:19:53 +03:00
?: ?=($head p.cur)
?> ?=({* $~} q.cur)
i.q.cur
=- [[- ~] (flop q.cur)]
2017-07-20 07:48:00 +03:00
?+ p.cur !!
2017-07-24 09:19:53 +03:00
$down %div
2017-07-20 07:48:00 +03:00
$list %ul
$lord %ol
$lime %li
$bloc %bq
$code %pre
==
:: ::
++ fold ^+ . :: complete and pop
?~ hac .
%= .
hac t.hac
cur [p.i.hac [fine q.i.hac]]
==
:: ::
++ snap :: capture raw line
2017-07-16 03:59:57 +03:00
=| nap/tape
2017-07-20 07:48:00 +03:00
|- ^+ [nap +>]
:: no unterminated lines
::
?~ los [~ +>(err `naz)]
2017-07-25 01:49:59 +03:00
?: =(`@`10 i.los)
2017-07-20 07:48:00 +03:00
:: consume newline
::
:_ +>(los t.los, naz [+(p.naz) 1])
:: trim trailing spaces
::
2017-07-25 01:49:59 +03:00
|- ^- tape
?: ?=({$' ' *} nap)
$(nap t.nap)
2017-07-20 07:48:00 +03:00
(flop nap)
2017-07-21 06:19:22 +03:00
:: save byte and repeat
::
2017-07-20 07:48:00 +03:00
$(los t.los, q.naz +(q.naz), nap [i.los nap])
2017-07-16 03:59:57 +03:00
:: ::
2017-07-18 04:07:47 +03:00
++ skip +:snap :: discard line
2017-07-19 06:19:27 +03:00
++ look :: inspect line
^- (unit trig)
2017-07-20 07:48:00 +03:00
?~ los
`[q.naz %done]
2017-07-20 07:48:00 +03:00
?: =(`@`10 i.los)
~
?: =(' ' i.los)
look(los t.los, q.naz +(q.naz))
2017-07-21 06:19:22 +03:00
:+ ~ q.naz
2017-07-20 07:48:00 +03:00
?: =('\\' i.los)
%fini
2017-07-24 09:19:53 +03:00
?: ?& =('#' i.los)
|- ^- ?
?~ t.los |
?: =(' ' i.t.los) &
?: =('#' i.t.los) $(t.los t.t.los)
|
==
2017-07-20 07:48:00 +03:00
%head
?: ?=({$'-' $' ' *} los)
%lite
2017-07-21 06:19:22 +03:00
?: ?=({$'+' $' ' *} los)
2017-07-20 07:48:00 +03:00
%lint
%text
:: ::
++ cape :: xml-escape
::FIXME p sure this is redundant with native manx escaping
2017-07-20 07:48:00 +03:00
|= tex/tape
^- tape
?~ tex tex
=+ $(tex t.tex)
?+ i.tex [i.tex -]
$34 ['&' 'q' 'u' 'o' 't' ';' -]
$38 ['&' 'a' 'm' 'p' ';' -]
2017-07-24 09:19:53 +03:00
$39 ['&' 'a' 'p' 'o' 's' ';' -]
2017-07-20 07:48:00 +03:00
$60 ['&' 'l' 't' ';' -]
$62 ['&' 'g' 't' ';' -]
==
:: ::
2017-07-22 09:56:21 +03:00
++ clue :: tape to xml
|= tex/tape
^- manx
[[%$ [%$ tex] ~] ~]
:: ::
++ cash :: escaped fence
|* tem/rule
;~ sfix
%- star
=+ ;~(pose bas tem)
2017-07-25 01:49:59 +03:00
;~ pose
2017-07-24 09:19:53 +03:00
(cold ' ' whit)
;~(pose ;~(less - prn) ;~(pfix bas -))
==
2017-07-22 09:56:21 +03:00
::
tem
==
:: ::
2017-07-24 09:19:53 +03:00
++ cool :: reparse
|* $: :: fex: primary parser
:: sab: secondary parser
2017-07-22 09:56:21 +03:00
::
fex/rule
sab/rule
==
|= {naz/hair los/tape}
^+ *sab
2017-07-25 01:49:59 +03:00
::
2017-07-22 09:56:21 +03:00
:: vex: fenced span
::
=/ vex/(like tape) (fex naz los)
?~ q.vex vex
2017-07-25 01:49:59 +03:00
::
2017-07-22 09:56:21 +03:00
:: hav: reparse full fenced text
::
=/ hav ((full sab) [naz p.u.q.vex])
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: reparsed error position is always at start
2017-07-22 09:56:21 +03:00
::
2017-07-24 09:19:53 +03:00
?~ q.hav [naz ~]
2017-07-25 01:49:59 +03:00
::
2017-07-22 09:56:21 +03:00
:: the complete span with the main product
::
:- p.vex
`[p.u.q.hav q.u.q.vex]
:: ::
++ echo :: hoon literal
2017-07-24 09:19:53 +03:00
|* sab/rule
2017-07-22 09:56:21 +03:00
|= {naz/hair los/tape}
^- (like tape)
:: vex: result of parsing wide twig
::
2017-07-24 09:19:53 +03:00
=/ vex (sab naz los)
2017-07-22 09:56:21 +03:00
:: use result of expression parser
::
?~ q.vex vex
2017-07-25 01:49:59 +03:00
=- [p.vex `[- q.u.q.vex]]
2017-07-22 09:56:21 +03:00
:: but replace payload with bytes consumed
::
|- ^- tape
?: =(q.q.u.q.vex los) ~
?~ los ~
[i.los $(los +.los)]
:: ::
2017-07-24 09:19:53 +03:00
++ word :: flow parser
%+ knee *(list graf) |. ~+
2017-07-22 09:56:21 +03:00
;~ pose
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: whitespace
::
(cold [%text " "]~ whit)
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: ordinary word
::
%+ cook |=(graf [+< ~])
(stag %text ;~(plug ;~(pose low hig) (star ;~(pose nud low hig hep))))
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: naked \escape
::
%+ cook |=(@ [%text [+< ~]]~)
;~(pfix bas ;~(less ace prn))
2017-07-25 01:49:59 +03:00
::
2017-07-22 09:56:21 +03:00
:: *bold literal*
::
2017-07-24 09:19:53 +03:00
%+ cook |=(graf [+< ~])
(stag %bold ;~(pfix tar (cool (cash tar) work)))
2017-07-25 01:49:59 +03:00
::
2017-07-22 09:56:21 +03:00
:: _italic literal_
::
2017-07-24 09:19:53 +03:00
%+ cook |=(graf [+< ~])
(stag %talc ;~(pfix cab (cool (cash cab) work)))
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: "quoted text"
::
%+ cook |=(graf [+< ~])
(stag %quod ;~(pfix doq (cool (cash doq) work)))
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: `classic markdown quote`
2017-07-22 09:56:21 +03:00
::
2017-07-24 09:19:53 +03:00
%+ cook |=(graf [+< ~])
(stag %code ;~(pfix tec (cash tec)))
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: #twig
::
%+ cook |=(graf [+< ~])
(stag %code ;~(pfix hax (echo wide:vast)))
2017-07-25 01:49:59 +03:00
::
2017-07-22 09:56:21 +03:00
:: ++arm
::
2017-07-24 09:19:53 +03:00
%+ cook |=(graf [+< ~])
2017-07-22 09:56:21 +03:00
(stag %code ;~(plug lus lus low (star ;~(pose nud low hep))))
2017-07-25 01:49:59 +03:00
::
2017-07-22 09:56:21 +03:00
:: [arbitrary *content*](url)
::
2017-07-24 09:19:53 +03:00
%+ cook |=(graf [+< ~])
2017-07-22 09:56:21 +03:00
%+ stag %link
;~ plug
2017-07-24 09:19:53 +03:00
;~(pfix sel (cool (cash ser) work))
2017-07-22 09:56:21 +03:00
;~(pfix gay ;~(pfix pel (cash per)))
==
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: direct hoon constant
::
%+ cook |=(graf [+< ~])
%+ stag %code
%- echo
;~ pose
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))
==
2017-07-25 01:49:59 +03:00
::
2017-07-24 09:19:53 +03:00
:: just a byte
2017-07-22 09:56:21 +03:00
::
2017-07-24 09:19:53 +03:00
(cook |=(@ [%text [+< ~]]~) ;~(less ace prn))
2017-07-22 09:56:21 +03:00
==
:: ::
2017-07-24 09:19:53 +03:00
++ work :: indefinite flow
%+ cook
|=((list (list graf)) (zing +<))
(star word)
:: ::
2017-07-22 09:56:21 +03:00
++ down :: parse inline flow
%+ knee *(list manx) |. ~+
=- (cook - work)
2017-07-25 02:00:44 +03:00
:: collect raw flow into xml tags
::
|= gaf/(list graf)
^- (list manx)
:: nap: collected words
:: max: collected tags
::
=< main
|%
++ main
^- marl
?~ gaf ~
?. ?=($text -.i.gaf)
(weld (item i.gaf) $(gaf t.gaf))
::
:: fip: accumulate text blocks
=/ fip/(list tape) [p.i.gaf]~
|- ^- marl
?~ 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
2017-07-25 02:00:44 +03:00
^- (list manx)
?- -.nex
$text !! :: handled separately
$bold [[%b ~] ^$(gaf p.nex)]~
$talc [[%i ~] ^$(gaf p.nex)]~
$code [[%code ~] ;/((cape p.nex)) ~]~
2017-07-25 02:00:44 +03:00
$quod :: smart quotes
::
%= ^$
2017-07-25 02:00:44 +03:00
gaf
:- [%text (tufa ~-~201c. ~)]
2017-07-25 02:00:44 +03:00
%+ weld p.nex
`(list graf)`[%text (tufa ~-~201d. ~)]~
2017-07-25 02:00:44 +03:00
==
$link [[%a [%href (cape q.nex)] ~] ^$(gaf p.nex)]~
2017-07-25 02:00:44 +03:00
==
--
2017-07-22 09:56:21 +03:00
:: ::
2017-07-24 02:00:45 +03:00
++ para :: paragraph
2017-07-24 09:19:53 +03:00
%+ cook
2017-07-25 01:49:59 +03:00
|=((list manx) [[%p ~] +<]~)
;~(pfix gay down) ::REVIEW does this mean comments work?
2017-07-24 02:00:45 +03:00
:: ::
2017-07-22 09:56:21 +03:00
++ whit :: whitespace
(cold ' ' (plus ;~(pose (just ' ') (just `@`10))))
2017-07-25 01:49:59 +03:00
::
2017-07-22 09:56:21 +03:00
++ head :: parse heading
2017-07-21 06:19:22 +03:00
%+ cook
|= a/manx ^- marl
=. a.g.a :_(a.g.a [%id (sanitize-to-id c.a)])
[a]~
2017-07-25 02:00:44 +03:00
::
;~ plug
2017-07-22 09:56:21 +03:00
::
:: # -> 1 -> %h1, ### -> 3 -> %h3, etc
:(cook |=(a/@u /(crip "h{<a>}")) lent (stun [1 6] hax))
2017-07-25 02:00:44 +03:00
::
;~(pfix whit down)
==
:: ::
++ sanitize-to-id
|= a/(list manx) ^- tape
2017-07-25 02:00:44 +03:00
=- %- zing
%+ turn `(list tape)`(flop -)
|= tape ^- tape
%+ turn `tape`+<
|= @tD
^- @tD
?: ?| &((gte +< 'a') (lte +< 'z'))
&((gte +< '0') (lte +< '9'))
==
+<
?: &((gte +< 'A') (lte +< 'Z'))
(add 32 +<)
'-'
:: collect all text in header flow
::
=| ges/(list tape)
|- ^- (list tape)
?~ a ges
2017-07-25 02:00:44 +03:00
%= $
a t.a
2017-07-25 02:00:44 +03:00
ges
?: ?=({{$$ {$$ *} $~} $~} i.a)
2017-07-25 02:00:44 +03:00
:: capture text
::
[v.i.a.g.i.a ges]
2017-07-25 02:00:44 +03:00
:: descend into children
::
$(a c.i.a)
2017-07-22 09:56:21 +03:00
==
2017-07-21 06:19:22 +03:00
:: ::
2017-07-20 07:48:00 +03:00
++ made :: compose block
2017-07-25 01:49:59 +03:00
^+ .
2017-07-20 07:48:00 +03:00
:: empty block, no action
::
?~ lub .
:: if block is preformatted code
::
?: ?=($code p.cur)
:: add blank line between blocks
::
=. q.cur
?~ q.cur q.cur
:_(q.cur ;/("\0a"))
2017-07-20 07:48:00 +03:00
%= .
2017-07-25 01:49:59 +03:00
q.cur
2017-07-20 07:48:00 +03:00
%+ weld
%+ turn
q.u.lub
|= tape ^- flow
:: each line is text data with its newline
::
;/((weld (slag (dec col) +<) "\0a"))
2017-07-20 07:48:00 +03:00
q.cur
==
:: if block is verse
::
?: ?=($poem p.cur)
:: add break between stanzas
::
=. q.cur ?~(q.cur q.cur [[[%br ~] ~] q.cur])
%= .
2017-07-25 01:49:59 +03:00
q.cur
2017-07-20 07:48:00 +03:00
%+ weld
%+ turn
q.u.lub
|= tape ^- flow
:: each line is a paragraph
::
:- [%p ~]
:_ ~
;/((weld (slag (dec col) +<) "\0a"))
2017-07-20 07:48:00 +03:00
q.cur
==
2017-07-24 02:00:45 +03:00
:: yex: block recomposed, with newlines
::
2017-07-24 09:19:53 +03:00
=/ yex/tape
=/ hel (flop q.u.lub)
|- ^- tape
?~ hel ~
?~ t.hel i.hel
(weld i.hel `tape`[`@`10 $(hel t.hel)])
:: XX live expressions stubbed out
2017-07-20 07:48:00 +03:00
::
?: ?=($expr p.cur)
!!
2017-07-21 06:19:22 +03:00
:: vex: parse of paragraph
2017-07-20 07:48:00 +03:00
::
2017-07-22 09:56:21 +03:00
=/ vex/(like (list manx))
2017-07-24 02:00:45 +03:00
:: either a one-line header or a paragraph
2017-07-22 09:56:21 +03:00
::
2017-07-24 02:00:45 +03:00
%.([p.u.lub yex] ?:(?=($head p.cur) head para))
2017-07-21 06:19:22 +03:00
:: if error, propagate correctly
::
?~ q.vex ..$(err `p.vex)
2017-07-24 09:19:53 +03:00
:: finish tag if it's a header
::
=< ?. =(%head p.cur) ..$ fold
:: save good result, clear buffer
2017-07-21 06:19:22 +03:00
::
2017-07-24 09:19:53 +03:00
..$(lub ~, q.cur (weld p.u.q.vex q.cur))
2017-07-25 01:49:59 +03:00
:: ::
2017-07-18 04:07:47 +03:00
++ line ^+ . :: body line loop
2017-07-16 03:59:57 +03:00
:: abort after first error
::
2017-07-19 06:19:27 +03:00
?: !=(~ err) .
2017-07-16 03:59:57 +03:00
:: pic: profile of this line
::
=/ pic look
:: if line is blank
::
2017-07-19 06:19:27 +03:00
?~ pic
2017-07-16 03:59:57 +03:00
:: break section
::
2017-07-19 06:19:27 +03:00
line:made:skip
2017-07-16 03:59:57 +03:00
:: line is not blank
::
=> .(pic u.pic)
2017-07-18 04:07:47 +03:00
:: if end of input, complete
2017-07-16 03:59:57 +03:00
::
?: ?=($done sty.pic)
2017-07-18 04:07:47 +03:00
..$(q.naz col.pic)
:: if end marker behind current column
2017-07-16 03:59:57 +03:00
::
?: &(?=($fini sty.pic) (lth col.pic col))
2017-07-18 04:07:47 +03:00
:: retract and complete
2017-07-16 03:59:57 +03:00
::
2017-07-18 04:07:47 +03:00
(back(q.naz (add 2 col.pic)) col.pic)
2017-07-19 06:19:27 +03:00
:: bal: inspection copy of lub, current section
::
=/ bal lub
2017-07-18 04:07:47 +03:00
:: if within section
2017-07-16 03:59:57 +03:00
::
2017-07-19 06:19:27 +03:00
?^ bal
2017-07-18 04:07:47 +03:00
:: detect bad block structure
2017-07-16 03:59:57 +03:00
::
2017-07-21 06:19:22 +03:00
?: ?| :: only one line in a heading
::
=(%head p.cur)
2017-07-18 04:07:47 +03:00
?: ?=(?($code $poem $expr) p.cur)
2017-07-21 06:19:22 +03:00
:: literals need to end with a blank line
::
2017-07-18 04:07:47 +03:00
(lth col.pic col)
2017-07-21 06:19:22 +03:00
:: text flows must continue aligned
::
2017-07-19 06:19:27 +03:00
|(!=(%text sty.pic) !=(col.pic col))
2017-07-18 04:07:47 +03:00
==
..$(err `[p.naz col.pic])
:: accept line and continue
2017-07-25 01:49:59 +03:00
::
2017-07-20 07:48:00 +03:00
=^ nap ..$ snap
2017-07-19 06:19:27 +03:00
line(lub bal(q.u [nap q.u.bal]))
2017-07-18 04:07:47 +03:00
:: if column has retreated, adjust stack
2017-07-16 03:59:57 +03:00
::
2017-07-24 09:19:53 +03:00
=. ..$ ?. (lth col.pic col) ..$ (back col.pic)
2017-07-18 04:07:47 +03:00
:: dif: columns advanced
2017-07-19 06:19:27 +03:00
:: erp: error position
2017-07-16 03:59:57 +03:00
::
2017-07-18 04:07:47 +03:00
=/ dif (sub col.pic col)
2017-07-19 06:19:27 +03:00
=/ erp [p.naz col.pic]
2017-07-18 04:07:47 +03:00
=. col col.pic
:: nap: take first line
::
=^ nap ..$ snap
:: execute appropriate paragraph form
::
2017-07-19 19:53:34 +03:00
=< line:abet:apex
2017-07-18 04:07:47 +03:00
|%
2017-07-25 01:49:59 +03:00
:: ::
2017-07-18 04:07:47 +03:00
++ abet :: accept line
..$(lub `[naz nap ~])
:: ::
2017-07-19 06:19:27 +03:00
++ apex ^+ . :: by column offset
2017-07-18 04:07:47 +03:00
?+ dif fail
$0 apse
$2 expr
$4 code
$6 bloc
$8 poem
==
:: ::
2017-07-19 06:19:27 +03:00
++ apse ^+ . :: by prefix style
2017-07-18 04:07:47 +03:00
?- sty.pic
$fini !!
2017-07-18 04:07:47 +03:00
$head head
$lite lite
$lint lint
$text text
==
:: ::
++ bloc apse:(push %bloc) :: blockquote line
2017-07-19 06:19:27 +03:00
++ fail .(err `erp) :: set error position
2017-07-20 07:48:00 +03:00
++ push |=(mite %_(+> hac [cur hac], cur [+< ~])) :: push context
2017-07-18 04:07:47 +03:00
++ expr (push %expr) :: hoon expression
++ code (push %code) :: code literal
++ poem (push %poem) :: verse literal
2017-07-21 06:19:22 +03:00
++ head (push %head) :: heading
2017-07-18 04:07:47 +03:00
++ lent :: list entry
|= ord/?
2017-07-19 06:19:27 +03:00
^+ +>
2017-07-18 04:07:47 +03:00
:: erase list marker
::
=. nap =+(+(col) (runt [- ' '] (slag - nap)))
:: indent by 2
::
=. col (add 2 col)
:: can't switch list types
::
?: =(?:(ord %list %lord) p.cur) fail
2017-07-20 07:48:00 +03:00
:: push list item
::
%. %lime
=< push
:: push list context, unless we're in list
2017-07-18 04:07:47 +03:00
::
=+ ?:(ord %lord %list)
2017-07-20 07:48:00 +03:00
?: =(- p.cur) ..push (push -)
2017-07-18 04:07:47 +03:00
::
++ lint (lent &) :: numbered list
++ lite (lent |) :: unnumbered list
++ text :: plain text
2017-07-19 06:19:27 +03:00
^+ .
2017-07-21 06:19:22 +03:00
:: only in lists, fold
2017-07-18 04:07:47 +03:00
::
?. ?=(?($list $lord) p.cur) .
2017-07-21 06:19:22 +03:00
.($ fold)
2017-07-18 04:07:47 +03:00
--
2017-07-16 03:59:57 +03:00
--
2017-07-18 04:07:47 +03:00
--