4e: Parsing (Combinators)
+bend
+bend
Conditional composer.
Parsing composer: connects the $edge
.vex
with the subsequent $rule
.sab
as an optional suffix, using gate .raq
to compose or reject its result. If there is no suffix, or if the suffix fails to be composed with the current result, the current result is produced. Used to map a group of $rule
s to a specified output.
Accepts
.raq
is a gate.
.sab
is a rule.
.vex
is an edge.
Produces
A $rule
.
Source
++ bend
~/ %bend
=+ raq=|*([a=* b=*] [~ u=[a b]])
|@
++ $
~/ %fun
|* [vex=edge sab=rule]
?~ q.vex
vex
=+ yit=(sab q.u.q.vex)
=+ yur=(last p.vex p.yit)
?~ q.yit
[p=yur q=q.vex]
=+ vux=(raq p.u.q.vex p.u.q.yit)
?~ vux
[p=yur q=q.vex]
[p=yur q=[~ u=[p=u.vux q=q.u.q.yit]]]
--
Examples
> (;~((bend |=([a=char b=char] ?.(=(a b) ~ (some +(a))))) prn prn) [1 1] "qs")
[p=[p=1 q=3] q=[~ u=[p=113 q=[p=[p=1 q=2] q="s"]]]]
> (;~((bend |=([a=char b=char] ?.(=(a b) ~ (some +(a))))) prn prn) [1 1] "qqq")
[p=[p=1 q=3] q=[~ u=[p=114 q=[p=[p=1 q=3] q="q"]]]]
> `@t`(scan "aa" ;~((bend |=([a=char b=char] ?.(=(a b) ~ (some +(a))))) prn prn))
'b'
> (scan "ba" ;~((bend |=([a=char b=char] ?.(=(a b) ~ (some +(a))))) prn prn))
{1 3}
syntax error
> `(unit @tas)`(scan "" ;~((bend) (easy ~) sym))
~
> `(unit @tas)`(scan "sep" ;~((bend) (easy ~) sym))
[~ %sep]
+comp
+comp
Arbitrary compose.
Parsing composer: connects the $edge
.vex
with a following $rule
.sab
, combining the contents of .vex
with the result of .sab
using a binary gate .raq
. Used to fold over the results of several $rule
s.
Accepts
.raq
is a gate that accepts a cell of two $noun
s, .a
and .b
, and produces a cell of two $noun
s.
.vex
is an edge.
.sab
is a rule.
Produces
A $rule
.
Source
++ comp
~/ %comp
=+ raq=|*([a=* b=*] [a b])
|@
++ $
~/ %fun
|* [vex=edge sab=rule]
~! +<
?~ q.vex
vex
=+ yit=(sab q.u.q.vex)
=+ yur=(last p.vex p.yit)
?~ q.yit
[p=yur q=q.yit]
[p=yur q=[~ u=[p=(raq p.u.q.vex p.u.q.yit) q=q.u.q.yit]]]
--
Examples
> (scan "123" ;~((comp |=([a=@ud b=@ud] (add a b))) dit dit dit))
6
> (scan "12" ;~((comp |=([a=@ud b=@ud] (add a b))) dit dit dit))
{1 3}
syntax error
+fail
+fail
Never parse.
Produces an $edge
at the same text position ($hair
) with a failing result (q=~
).
Accepts
.tub
is a $nail
.
Produces
An $edge
.
Source
++ fail |=(tub=nail [p=p.tub q=~])
Examples
> (fail [[1 1] "abc"])
[p=[p=1 q=1] q=~]
> (fail [[p=1.337 q=70] "Parse me, please?"])
[p=[p=1.337 q=70] q=~]
+glue
+glue
Skip delimiter.
Parsing composer: connects an $edge
.vex
with a following $rule
.sab
by parsing the $rule
.bus
(the delimiting symbol) and throwing out the result.
Accepts
.bus
is a $rule
.
.vex
is an $edge
.
.sab
is a $rule
.
Produces
A $rule
.
Source
++ glue
~/ %glue
|* bus=rule
~/ %fun
|* [vex=edge sab=rule]
(plug vex ;~(pfix bus sab))
Examples
> `[@ud @tas @tas]`(scan "200|mal|bon" ;~((glue bar) dem sym sym))
[200 %mal %bon]
> `[@ud @t @tas]`(scan "200|;|bon" ;~((glue bar) dem mic sym))
[200 ';' %bon]
+less
+less
Parse unless.
Parsing composer: if an $edge
.vex
reflects a success, fail. Otherwise, connect .vex
with the following $rule
.
Accepts
.vex
is an $edge
.
.sab
is a $rule
.
Produces
An $edge
.
Source
++ less
|* [vex=edge sab=rule]
?~ q.vex
=+ roq=(sab)
[p=(last p.vex p.roq) q=q.roq]
(fail +<.sab)
Examples
> (scan "sas-/lo" (star ;~(less lus bar prn)))
"sas-/lo"
> (scan "sas-/l+o" (star ;~(less lus bar prn)))
! {1 8}
! exit
> (scan "sas|-/lo" (star ;~(less lus bar prn)))
! {1 5}
! exit
+pfix
+pfix
Discard first rule.
Parsing composer: connects an $edge
.vex
with two subsequent $rule
s, ignoring the result of the first and producing the result of the second.
Accepts
.vex
is an $edge
.
.sab
is a $rule
.
Produces
An $edge
.
Source
++ pfix
~/ %pfix
|* sam=[vex=edge sab=rule]
%. sam
(comp |*([a=* b=*] b))
Examples
> `@t`(scan "%him" ;~(pfix cen sym))
'him'
> (scan "+++10" ;~(pfix (star lus) dem))
10
+plug
+plug
Parse to tuple.
Parsing composer: connects an $edge
.vex
with a following $rule
.sab
, producing a cell of both the results. See also: the monad applicator ;~
for a more detailed explanation.
Accepts
.vex
is an $edge
.
.sab
is a $rule
.
Produces
An $edge
.
Source
++ plug
~/ %plug
|* [vex=edge sab=rule]
?~ q.vex
vex
=+ yit=(sab q.u.q.vex)
=+ yur=(last p.vex p.yit)
?~ q.yit
[p=yur q=q.yit]
[p=yur q=[~ u=[p=[p.u.q.vex p.u.q.yit] q=q.u.q.yit]]]
Examples
> (scan "1..20" ;~(plug dem dot dot dem))
[1 '.' '.' 20]
+pose
+pose
Parse options.
Parsing composer: if .vex
reflects a failure, connect it with the following $rule
.sab
. See also: the monad applicator ;~
Accepts
.vex
is an $edge
.
.sab
is a $rule
.
Produces
An $edge
.
Source
++ pose
~/ %pose
|* [vex=edge sab=rule]
?~ q.vex
=+ roq=(sab)
[p=(last p.vex p.roq) q=q.roq]
vex
Examples
> `@t`(scan "+" ;~(pose lus tar cen))
'+'
> `@t`(scan "*" ;~(pose lus tar cen))
'*'
> `@t`(scan "%" ;~(pose lus tar cen))
'%'
> `@t`(scan "-" ;~(pose lus tar cen))
! {1 1}
! exit
+sfix
+sfix
Discard second rule.
Parsing composer: connects $edge
.vex
with two subsequent $rule
s returning the result of the first and discarding the result of the second.
Accepts
.vex
is an $edge
.
.sab
is a $rule
.
Produces
An $edge
.
Source
++ sfix
~/ %sfix
|* sam=[vex=edge sab=rule]
%. sam
(comp |*([a=* b=*] a))
Examples
> `@t`(scan "him%" ;~(sfix sym cen))
'him'
> (scan "10+++" ;~(sfix dem (star lus)))
q=10
+simu
+simu
First and second.
Parsing composer: if an $edge
.vex
reflects a failure, fail. Otherwise, connect .vex
with the following $rule
.
Accepts
.vex
is an $edge
.
.sab
is a $rule
.
Produces
An $edge
.
Source
++ simu
|* [vex=edge sab=rule]
?~ q.vex
vex
=+ roq=(sab)
roq
Examples
> (scan "~zod" scat:vast)
[%dtzy p=%p q=0]
> (scan "%zod" scat:vast)
[%dtzz p=%tas q=6.582.138]
> (scan "%zod" ;~(simu cen scat:vast))
[%dtzz p=%tas q=6.582.138]
> (scan "~zod" ;~(simu cen scat:vast))
! {1 1}
! exit
Last updated