++so
Coin parser engine
Core containing arms that parse atoms encoded in strings.
Source
++ so
~% %so + ~
|%
++bisk:so
Parse aura-atom pair
Parsing rule
. Parses an @u
of any permitted base,
producing a dime
.
Source
++ bisk
~+
;~ pose
;~ pfix (just '0')
;~ pose
(stag %ub ;~(pfix (just 'b') bay:ag))
(stag %uc ;~(pfix (just 'c') fim:ag))
(stag %ui ;~(pfix (just 'i') dim:ag))
(stag %ux ;~(pfix (just 'x') hex:ag))
(stag %uv ;~(pfix (just 'v') viz:ag))
(stag %uw ;~(pfix (just 'w') wiz:ag))
==
==
(stag %ud dem:ag)
==
Examples
> (scan "25" bisk:so)
[%ud 25]
> (scan "0x12.6401" bisk:so)
[%ux 1.205.249]
++crub:so
Parse @da
, @dr
, @p
, @t
Parsing rule
. Parses any atom of any of the following auras after a leading
sig: @da
, @dr
, @p
, and @t
. Produces a dime
.
Source
++ crub
~+
;~ pose
(cook |=(det=date `dime`[%da (year det)]) when)
::
%+ cook
|= [a=(list [p=?(%d %h %m %s) q=@]) b=(list @)]
=+ rop=`tarp`[0 0 0 0 b]
|- ^- dime
?~ a
[%dr (yule rop)]
?- p.i.a
%d $(a t.a, d.rop (add q.i.a d.rop))
%h $(a t.a, h.rop (add q.i.a h.rop))
%m $(a t.a, m.rop (add q.i.a m.rop))
%s $(a t.a, s.rop (add q.i.a s.rop))
==
;~ plug
%+ most
dot
;~ pose
;~(pfix (just 'd') (stag %d dim:ag))
;~(pfix (just 'h') (stag %h dim:ag))
;~(pfix (just 'm') (stag %m dim:ag))
;~(pfix (just 's') (stag %s dim:ag))
==
;~(pose ;~(pfix ;~(plug dot dot) (most dot qix:ab)) (easy ~))
==
::
(stag %p fed:ag)
;~(pfix dot (stag %ta urs:ab))
;~(pfix sig (stag %t urx:ab))
;~(pfix hep (stag %c (cook taft urx:ab)))
==
Examples
> (scan "1926.5.12" crub:so)
[p=~.da q=170.141.184.449.747.016.871.285.095.307.149.312.000]
> ;;([%da @da] (scan "1926.5.12" crub:so))
[%da ~1926.5.12]
> (scan "s10" crub:so)
[p=~.dr q=184.467.440.737.095.516.160]
> ;;([%dr @dr] (scan "s10" crub:so))
[%dr ~s10]
> (scan "sampel" crub:so)
[%p 1.135]
> (scan ".mas" crub:so)
[%ta 7.561.581]
++nuck:so
Top-level coin parser
Parsing rule
. Switches on the first character and applies the
corresponding coin
parser.
Source
++ nuck
~/ %nuck |= a=nail %. a
%+ knee *coin |. ~+
%- stew
^. stet ^. limo
:~ :- ['a' 'z'] (cook |=(a=@ta [%$ %tas a]) sym)
:- ['0' '9'] (stag %$ bisk)
:- '-' (stag %$ tash)
:- '.' ;~(pfix dot perd)
:- '~' ;~(pfix sig ;~(pose twid (easy [%$ %n 0])))
==
Examples
> (scan "~pillyt" nuck:so)
[%$ p=[p=~.p q=13.184]]
> (scan "0x12" nuck:so)
[%$ p=[p=~.ux q=18]]
> (scan ".127.0.0.1" nuck:so)
[%$ p=[p=~.if q=2.130.706.433]]
> (scan "._20_0w25_sam__" nuck:so)
[ %many
p
~[
[%$ p=[p=~.ud q=20]]
[%$ p=[p=~.uw q=133]]
[%$ p=[p=~.tas q=7.168.371]]
]
]
++nusk:so
Parse coin literal with escapes
Parsing rule
. Parses a coin literal with escapes.
Source
++ nusk
~+
:(sear |=(a=@ta (rush a nuck)) wick urt:ab)
Examples
> ~.asd_a
~.asd_a
> ._1_~~.asd~-a__
[1 ~.asd_a]
> (scan "~~.asd~-a" nusk:so)
[%$ p=[p=~.ta q=418.212.246.369]]
++perd:so
Parsing coin literal without prefixes
Parsing rule
. Parses a dime or tuple without their respective standard
prefixes.
Source
++ perd
~+
;~ pose
(stag %$ zust)
(stag %many (ifix [cab ;~(plug cab cab)] (more cab nusk)))
==
Examples
> (scan "y" perd:so)
[%$ [%f %.y]]
> (scan "n" perd:so)
[%$ [%f %.n]]
> (scan "_20_x__" perd:so)
[%many [[%$ p=[p=~.ud q=20]] [i=[%$ p=[p=~.tas q=120]] t=~]]]
++royl:so
Parse dime float
Parsing rule
. Parses a number into a dime
float.
Source
++ royl
~+
;~ pose
(stag %rh royl-rh)
(stag %rq royl-rq)
(stag %rd royl-rd)
(stag %rs royl-rs)
==
Examples
> (scan "~3.14" royl:so)
[%rd .~3.14]
> (scan "3.14" royl:so)
[%rs .3.14]
++royl-rh:so
Parse half-precision float
Parsing rule
. Parses a @rh
.
Source
++ royl-rh (cook rylh ;~(pfix ;~(plug sig sig) (cook royl-cell royl-rn)))
Examples
> (scan "~~3.14" royl-rh:so)
.~~3.14
++royl-rq:so
Parse quad-precision float
Parsing rule
. Parses a @rq
.
Source
++ royl-rq (cook rylq ;~(pfix ;~(plug sig sig sig) (cook royl-cell royl-rn)))
Examples
> (scan "~~~3.14" royl-rq:so)
.~~~3.14
++royl-rd:so
Parse double-precision float
Parsing rule
. Parses a @rd
.
Source
++ royl-rd (cook ryld ;~(pfix sig (cook royl-cell royl-rn)))
Examples
> (scan "~3.14" royl-rd:so)
.~3.14
++royl-rs:so
Parse single-precision float
Parsing rule
. Parses a @rs
.
Source
++ royl-rs (cook ryls (cook royl-cell royl-rn))
Examples
> (scan "3.14" royl-rs:so)
.3.14
++royl-rn:so
Parse real number
Parsing rule
. Parses a real number to a ++rn
.
Source
++ royl-rn
=/ moo
|= a=tape
:- (lent a)
(scan a (bass 10 (plus sid:ab)))
;~ pose
;~ plug
(easy %d)
;~(pose (cold | hep) (easy &))
;~ plug dim:ag
;~ pose
;~(pfix dot (cook moo (plus (shim '0' '9'))))
(easy [0 0])
==
;~ pose
;~ pfix
(just 'e')
;~(plug ;~(pose (cold | hep) (easy &)) dim:ag)
==
(easy [& 0])
==
==
==
::
;~ plug
(easy %i)
;~ sfix
;~(pose (cold | hep) (easy &))
(jest 'inf')
==
==
::
;~ plug
(easy %n)
(cold ~ (jest 'nan'))
==
==
Examples
> (scan "3.14" royl-rn:so)
[%d %.y 3 [2 14] [%.y 0]]
> (scan "-3.14e-39" royl-rn:so)
[%d %.n 3 [2 14] [%.n 39]]
> (scan "3" royl-rn:so)
[%d %.y 3 [0 0] [%.y 0]]
++royl-cell:so
Convert rn to dn
Intermediate parsed float converter. Convert a
++rn
to
++dn
.
Accepts
A ++rn
.
Produces
A ++dn
.
Source
++ royl-cell
|= rn
^- dn
?. ?=([%d *] +<) +<
=+ ^= h
(dif:si (new:si f.b i.b) (sun:si d.b))
[%d a h (add (mul c.b (pow 10 d.b)) e.b)]
Examples
> (royl-cell:so (scan "3.14" royl-rn:so))
[%d s=%.y e=-2 a=314]
> (ryls (royl-cell:so (scan "3.14" royl-rn:so)))
.3.14
++tash:so
Parse signed dime
Parsing rule
. Parse a @s
to a dime
.
Source
++ tash
~+
=+ ^= neg
|= [syn=? mol=dime] ^- dime
?> =('u' (end 3 p.mol))
[(cat 3 's' (rsh 3 p.mol)) (new:si syn q.mol)]
;~ pfix hep
;~ pose
(cook |=(a=dime (neg | a)) bisk)
;~(pfix hep (cook |=(a=dime (neg & a)) bisk))
==
==
Examples
> (scan "-20" tash:so)
[p=~.sd q=39]
> ;;([%sd @sd] (scan "-20" tash:so))
[%sd -20]
> ;;([%sd @sd] (scan "--20" tash:so))
[%sd --20]
> ;;([%sx @sx] (scan "--0x2e" tash:so))
[%sx --0x2e]
++twid:so
Parse coins without ~
prefix
Parsing rule. Parses coins after a leading sig, ~
.
Source
++ twid
~+
;~ pose
%+ stag %blob
%+ sear |=(a=@ (mole |.((cue a))))
;~(pfix (just '0') vum:ag)
::
(stag %$ crub)
==
Examples
> (scan "zod" twid:so)
[%$ [%p 0]]
> (scan ".sam" twid:so)
[%$ [%ta 7.168.371]]
> (scan "0ph" twid:so)
[%blob [1 1]]
++when:so
Parse date
Parsing rule
. Parse a @da
-formatted date string (sans the leading ~
) to a
date
.
Source
++ when
~+
;~ plug
%+ cook
|=([a=@ b=?] [b a])
;~(plug dim:ag ;~(pose (cold | hep) (easy &)))
;~(pfix dot mot:ag) :: month
;~(pfix dot dip:ag) :: day
;~ pose
;~ pfix
;~(plug dot dot)
;~ plug
dum:ag
;~(pfix dot dum:ag)
;~(pfix dot dum:ag)
;~(pose ;~(pfix ;~(plug dot dot) (most dot qix:ab)) (easy ~))
==
==
(easy [0 0 0 ~])
==
==
Examples
> `date`(scan "2000.1.1..12.00.00..ffff" when:so)
[[a=%.y y=2.000] m=1 t=[d=1 h=12 m=0 s=0 f=~[0xffff]]]
++zust:so
Parse dimes from @i
, @f
, @r
or @q
Parsing rule. Parses an atom of either @if
(IP address), @f
(loobean), @r
(floating point) into a dime
. The @q
alone requires a leading ~
.
Source
++ zust
~+
;~ pose
(stag %is bip:ag)
(stag %if lip:ag)
royl
(stag %f ;~(pose (cold & (just 'y')) (cold | (just 'n'))))
(stag %q ;~(pfix sig feq:ag))
==
Examples
> (scan "~sampel" zust:so)
[%q 1.135]
> (scan "y" zust:so)
[%f %.y]
> (scan "127.0.0.1" zust:so)
[%if 2.130.706.433]
> (scan "af.0.0.0.0.e7a5.30d2.7" zust:so)
[%is 908.651.950.243.594.834.993.091.554.288.205.831]
> (scan "12.09" zust:so)
[%rs .12.09]