4j: Parsing (Bases and Base Digits)

+ab

Primitive parser engine

A core containing numeric parser primitives.

Source

++  ab
  |%

Examples

> ab
<36.ecc 414.gly 100.xkc 1.ypj %164>

+bix:ab

Parse hex pair

Parsing +rule. Parses a pair of base-16 digits. Used in escapes.

Source

++  bix  (bass 16 (stun [2 2] six))

Examples

> (scan "07" bix:ab)
7
> (scan "51" bix:ab)
81
> (scan "a3" bix:ab)
163

+fem:ab

Parse base58check char

Parse a single base58check character.

Source

++  fem  (sear |=(a=@ (cha:fa a)) aln)

Examples

> (scan "6" fem:ab)
5

> (scan "Z" fem:ab)
32

> (scan "j" fem:ab)
42

+haf:ab

Parse non-doz phonetic pair

Parsing +rule. Parses an atom of aura @pE, a phrase of two bytes encoded phonetically. If the leading syllable is doz (0), parsing will fail.

Source

++  haf  (bass 256 ;~(plug tep tiq (easy ~)))

Examples

> `@p`(scan "sampel" haf:ab)
~sampel

> `@p`(scan "dozpel" haf:ab)
{1 4}
syntax error

+hef:ab

Parse non-dozzod phonetic pair

Parsing +rule. Parses an atom of aura @pE without leading ~ or .~, a phrase of two bytes encoded phonetically. If it's dozzod, parsing will fail.

Source

++  hef  %+  sear  |=(a=@ ?:(=(a 0) ~ (some a)))
         %+  bass  256
         ;~(plug tip tiq (easy ~))

Examples

> `@p`(scan "sampel" hef:ab)
~sampel

> `@p`(scan "dozpel" hef:ab)
~pel

> `@p`(scan "dozzod" hef:ab)
{1 7}
syntax error

+hif:ab

Parse phonetic pair

Parsing +rule. Parses an atom of aura @pE, without leading ~ or .~. A phrase of two bytes encoded phonetically.

Source

++  hif  (boss 256 ;~(plug tip tiq (easy ~)))

Examples

> `@p`(scan "doznec" hif:ab)
~nec

> `@p`(scan "pittyp" hif:ab)
~pittyp

+hof:ab

Parse 2-4 @q phonetic pairs

Parsing +rule. Parses an atom of aura @q (non-scrambled @p), without leading ~ or .~, of between two and four phrases.

Source

++  hof  (bass 0x1.0000 ;~(plug hef (stun [1 3] ;~(pfix hep hif))))

Example

> `@q`(scan "sampel-palnet" hof:ab)
.~sampel-palnet

> `@q`(scan "sampel-sampel-palnet" hof:ab)
.~sampel-sampel-palnet

> `@q`(scan "sampel-sampel-sampel-palnet" hof:ab)
.~sampel-sampel-sampel-palnet

+huf:ab

Parse 1-4 @q phonetic pairs

Parsing +rule. Parses an atom of aura @q (non-scrambled @p), without leading ~ or .~, of between one and four phrases.

Source

++  huf  (bass 0x1.0000 ;~(plug hef (stun [0 3] ;~(pfix hep hif))))

Examples

> `@q`(scan "sampel" huf:ab)
.~sampel

> `@q`(scan "sampel-palnet" huf:ab)
.~sampel-palnet

> `@q`(scan "sampel-sampel-palnet" huf:ab)
.~sampel-sampel-palnet

> `@q`(scan "sampel-sampel-sampel-palnet" huf:ab)
.~sampel-sampel-sampel-palnet

+hyf:ab

Parse four @q phonetic pairs

Parsing +rule. Parses an atom of aura @q (non-scrambled @p), without leading ~ or .~, of exactly four phrases.

Source

++  hyf  (bass 0x1.0000 ;~(plug hif (stun [3 3] ;~(pfix hep hif))))

Examples

> `@q`(scan "sampel-sampel-sampel-palnet" hyf:ab)
.~sampel-sampel-sampel-palnet

+pev:ab

Parse 1-5 @uv base-32 chars

Parsing +rule. Parses one to five @uv base-32 digits without the leading 0v or leading zeros.

Source

++  pev  (bass 32 ;~(plug sev (stun [0 4] siv)))

Examples

> `@uv`(scan "du3ja" pev:ab)
0vdu3ja

> `@uv`(scan "3ja" pev:ab)
0v3ja

> `@uv`(scan "a" pev:ab)
0va

+pew:ab

Parse 1-5 @uw base-64 chars

Parsing +rule. Parses one to five @uw base-64 digits without the leading 0w or leading zeros.

Source

++  pew  (bass 64 ;~(plug sew (stun [0 4] siw)))

Examples

> `@uw`(scan "6U0gP" pew:ab)
0w6U0gP

> `@uw`(scan "gP" pew:ab)
0wgP

> `@uw`(scan "P" pew:ab)
0wP

+piv:ab

Parse 5 @uv base-32 chars

Parsing +rule. Parses exactly five @uv base-32 digits without the leading 0v or leading zeros.

Source

++  piv  (bass 32 (stun [5 5] siv))

Examples

> `@uv`(scan "du3ja" piv:ab)
0vdu3ja

> `@uv`(scan "u3ja" piv:ab)
{1 5}
syntax error

+piw:ab

Parse 5 @uw base-64 chars

Parsing +rule. Parses exactly five @uw base-64 digits without the leading 0w or leading zeros.

Source

++  piw  (bass 64 (stun [5 5] siw))

Examples

> `@uw`(scan "6U0gP" piw:ab)
0w6U0gP

> `@uw`(scan "U0gP" piw:ab)
{1 5}
syntax error

+qeb:ab

Parse 1-4 binary digits

Parsing +rule. Parses a binary number of up to 4 digits in length without a leading zero.

Source

++  qeb  (bass 2 ;~(plug seb (stun [0 3] sib)))

Examples

> `@ub`(scan "1010" qeb:ab)
0b1010

> `@ub`(scan "10" qeb:ab)
0b10

> `@ub`(scan "1" qeb:ab)
0b1

> `@ub`(scan "0" qeb:ab)
{1 1}
syntax error

+qex:ab

Parse 1-4 hex digits

Parsing +rule. Parses a hexadecimal number of up to 4 digits in length without a leading zero.

Source

++  qex  (bass 16 ;~(plug sex (stun [0 3] hit)))

Examples

> `@ux`(scan "beef" qex:ab)
0xbeef

> `@ux`(scan "ef" qex:ab)
0xef

> `@ux`(scan "f" qex:ab)
0xf

+qib:ab

Parse 4 binary

Parsing +rule. Parses exactly four binary digits - may have leading zeros.

Source

++  qib  (bass 2 (stun [4 4] sib))

Examples

> `@ub`(scan "0001" qib:ab)
0b1

> `@ub`(scan "1001" qib:ab)
0b1001

> `@ub`(scan "1" qib:ab)
{1 2}
syntax error

+qix:ab

Parse 4 hex

Parsing +rule. Parses exactly four hexadecimal digits - may have leading zeros.

Source

++  qix  (bass 16 (stun [4 4] six))

Examples

> `@ux`(scan "beef" qix:ab)
0xbeef

> `@ux`(scan "0000" qix:ab)
0x0

> `@ux`(scan "ef" qix:ab)
{1 3}
syntax error

+seb:ab

Parse 1

Parsing +rule. Parses the number 1.

Source

++  seb  (cold 1 (just '1'))

Examples

> (scan "1" seb:ab)
1

> (scan "2" seb:ab)
{1 1}
syntax error

+sed:ab

Parse decimal

Parsing +rule. Parses a nonzero decimal digit.

Source

++  sed  (cook |=(a=@ (sub a '0')) (shim '1' '9'))

Examples

> (scan "5" sed:ab)
5

> (scan "0" sed:ab)
{1 1}
syntax error

+sev:ab

Parse base-32

Parsing +rule. Parses a nonzero base-32 digit.

Source

++  sev  ;~(pose sed sov)

Examples

> `@uv`(scan "2" sev:ab)
0v2

> `@uv`(scan "j" sev:ab)
0vj

> `@uv`(scan "0" sev:ab)
{1 1}
syntax error

+sew:ab

Parse base-64

Parsing +rule. Parses a nonzero base-64 digit.

Source

++  sew  ;~(pose sed sow)

Examples

> `@uw`(scan "I" sew:ab)
0wI

> `@uw`(scan "2" sew:ab)
0w2

> `@uw`(scan "0" sew:ab)
{1 1}
syntax error

+sex:ab

Parse hex

Parsing +rule. Parses a non-zero hexadecimal digit.

Source

++  sex  ;~(pose sed sox)

Examples

> `@ux`(scan "a" sex:ab)
0xa

> `@ux`(scan "2" sex:ab)
0x2

> `@ux`(scan "0" sex:ab)
{1 1}
syntax error

+sib:ab

Parse binary

Parsing +rule. Parses a binary digit.

Source

++  sib  (cook |=(a=@ (sub a '0')) (shim '0' '1'))

Examples

> `@ub`(scan "1" sib:ab)
0b1

> `@ub`(scan "0" sib:ab)
0b0

+sid:ab

Parse decimal

Parsing +rule. Parses a decimal digit.

Source

++  sid  (cook |=(a=@ (sub a '0')) (shim '0' '9'))

Examples

> (scan "5" sid:ab)
5

> (scan "0" sid:ab)
0

+siv:ab

Parse base-32

Parsing +rule. Parses a base-32 digit.

Source

++  siv  ;~(pose sid sov)

Examples

> `@uv`(scan "r" siv:ab)
0vr

> `@uv`(scan "5" siv:ab)
0v5

> `@uv`(scan "0" siv:ab)
0v0

+siw:ab

Parse base-64

Parsing +rule. Parses a base-64 digit.

Source

++  siw  ;~(pose sid sow)

Examples

> `@uw`(scan "M" siw:ab)
0wM

> `@uw`(scan "0" siw:ab)
0w0

> `@uw`(scan "c" siw:ab)
0wc

+six:ab

Parse hex

Parsing +rule. Parses a hexadecimal digit.

Source

++  six  ;~(pose sid sox)

Examples

> `@ux`(scan "e" six:ab)
0xe

> `@ux`(scan "0" six:ab)
0x0

+sov:ab

Parse @uv base-32 letter

Parsing +rule. Parses a @uv base-32 letter (but not a number).

Source

++  sov  (cook |=(a=@ (sub a 87)) (shim 'a' 'v'))

Examples

> `@uv`(scan "c" sov:ab)
0vc

> `@uv`(scan "j" sov:ab)
0vj

> `@uv`(scan "5" sov:ab)
{1 1}
syntax error

+sow:ab

Parse @uw base-64 letter/symbol

Parsing +rule. Parses a base-64 letter/symbol (but not number).

Source

++  sow  ;~  pose
           (cook |=(a=@ (sub a 87)) (shim 'a' 'z'))
           (cook |=(a=@ (sub a 29)) (shim 'A' 'Z'))
           (cold 62 (just '-'))
           (cold 63 (just '~'))
         ==

Examples

> `@uw`(scan "M" sow:ab)
0wM

> `@uw`(scan "5" sow:ab)
{1 1}
syntax error

+sox:ab

Parse hex letter

Parsing +rule. Parses a hexadecimal letter (but not number).

Source

++  sox  (cook |=(a=@ (sub a 87)) (shim 'a' 'f'))

Examples

> `@ux`(scan "e" sox:ab)
0xe

> `@ux`(scan "5" sox:ab)
{1 1}
syntax error

+ted:ab

Parse 1-999 decimal

Parsing +rule. Parses a decimal number of up to 3 digits without a leading zero.

Source

++  ted  (bass 10 ;~(plug sed (stun [0 2] sid)))

Examples

> (scan "214" ted:ab)
214

> (scan "2" ted:ab)
2

> (scan "2161" ted:ab)
{1 4}
syntax error

+tep:ab

Parse non-doz leading phonetic byte

Parsing +rule. Parses the leading phonetic byte , which represents a syllable. Fails if it is doz.

Source

++  tep  (sear |=(a=@ ?:(=(a 'doz') ~ (ins:po a))) til)

Examples

> (scan "sam" tep:ab)
4

> (scan "wic" tep:ab)
99

+tip:ab

Leading phonetic byte

Parsing +rule. Parses the leading phonetic byte, which represents a syllable.

Source

++  tip  (sear |=(a=@ (ins:po a)) til)

Examples

> (scan "doz" tip:ab)
0

> (scan "pit" tip:ab)
242

+tiq:ab

Trailing phonetic syllable

Parsing +rule. Parses the trailing phonetic byte, which represents a syllable.

Source

++  tiq  (sear |=(a=@ (ind:po a)) til)

Examples

> (scan "zod" tiq:ab)
0
> (scan "nec" tiq:ab)
1

+tid:ab

Parse 3 decimal digits

Parsing +rule. Parses exactly three decimal digits.

Source

++  tid  (bass 10 (stun [3 3] sid))

Examples

> (scan "013" tid:ab)
13

> (scan "999" tid:ab)
999

> (scan "99" tid:ab)
{1 3}
syntax error

+til:ab

Parse 3 lowercase

Parsing +rule. Parses exactly three lowercase letters.

Source

++  til  (boss 256 (stun [3 3] low))

Examples

> `@t`(scan "mer" til:ab)
'mer'

> `@t`(scan "me" til:ab)
{1 3}
syntax error

+urs:ab

Parse knot characters

Parsing rule. Parses characters from an atom of the knot aura @ta.

Source

++  urs  %+  cook
           |=(a=tape (rap 3 ^-((list @) a)))
         (star ;~(pose nud low hep dot sig cab))

Examples

> `@ta`(scan "asa-lom_tak" urs:ab)
~.asa-lom_tak

+urt:ab

Parse knot without underscores

Parsing +rule. Parses all characters of the knot aura @ta except for cab, _.

Source

++  urt  %+  cook
           |=(a=tape (rap 3 ^-((list @) a)))
         (star ;~(pose nud low hep dot sig))

Examples

> `@ta`(scan "asa-lom.t0k" urt:ab)
~.asa-lom.t0k

+voy:ab

Parse bas, soq, or bix

Parsing +rule. Parses an escaped backslash, single quote, or hex pair byte.

Source

++  voy  ;~(pfix bas ;~(pose bas soq bix))

Examples

> (scan "\\\\" voy:ab)
'\\'

> (scan "\\'" voy:ab)
'\''

> (scan "\\0a" voy:ab)
'\0a'

+ag

Top-level atom parser engine

A core containing top-level atom parsers.

Source

++  ag
  |%

+ape:ag

Parse 0 or rule

Parser modifier. Parses 0 or the sample rule fel.

Accepts

fel is a +rule.

Produces

A +rule.

Source

++  ape  |*(fel=rule ;~(pose (cold 0 (just '0')) fel))

Examples

> (scan "0" (ape:ag (cold 2 (just '2'))))
0

> (scan "2" (ape:ag (cold 2 (just '2'))))
2

> (scan "3" (ape:ag (cold 2 (just '2'))))
{1 1}
syntax error

+bay:ag

Parses binary number

Parsing +rule. Parses a binary number without a leading zero.

Source

++  bay  (ape (bass 16 ;~(plug qeb:ab (star ;~(pfix dog qib:ab)))))

Examples

> `@ub`(scan "101.1100.0011.1010" bay:ag)
0b101.1100.0011.1010

+bip:ag

Parse IPv6

Parsing rule. Parses a @is, an IPv6 address.

Source

++  bip  =+  tod=(ape qex:ab)
         (bass 0x1.0000 ;~(plug tod (stun [7 7] ;~(pfix dog tod))))

Examples

> `@is`(scan "0.0.ea.3e6c.0.0.0.0" bip:ag)
.0.0.ea.3e6c.0.0.0.0

+dem:ag

Parse decimal with dots

Parsing +rule. Parses a decimal number that includes dot separators.

Source

++  dem  (ape (bass 1.000 ;~(plug ted:ab (star ;~(pfix dog tid:ab)))))

Examples

> (scan "52" dem:ag)
52
> (scan "13.507" dem:ag)
13.507

+dim:ag

Parse decimal number

Parsing rule. Parses a decimal number without a leading zero.

Source

++  dim  (ape dip)

Examples

> (scan "52" dim:ag)
52

> (scan "0" dim:ag)
0

> (scan "13507" dim:ag)
13.507

> (scan "013507" dim:ag)
{1 2}
syntax error

+dum:ag

Parse decimal with leading 0

Parsing rule. Parses a decmial number with leading zeroes.

Source

++  dum  (bass 10 (plus sid:ab))

Examples

> (scan "52" dum:ag)
52
> (scan "0000052" dum:ag)
52
> (scan "13507" dim:ag)
13.507

+fed:ag

Parse phonetic base

Parsing rule. Parses an atom of aura @p, the phonetic base.

Source

++  fed  %+  cook  fynd:ob
         ;~  pose
           %+  bass  0x1.0000.0000.0000.0000          ::  oversized
             ;~  plug
               huf:ab
               (plus ;~(pfix doh hyf:ab))
             ==
           hof:ab                                     ::  planet or moon
           haf:ab                                     ::  star
           tiq:ab                                     ::  galaxy
         ==

Examples

> `@p`(scan "zod" fed:ag)
~zod

> `@p`(scan "sampel" fed:ag)
~sampel

> `@p`(scan "sampel-palnet" fed:ag)
~sampel-palnet

> `@p`(scan "sampel-palnet-sampel-palnet" fed:ag)
~sampel-palnet-sampel-palnet

> `@p`(scan "tillyn-nillyt-tasfyn-partyv--novweb-talrud-talmud-sonfyr" fed:ag)
~tillyn-nillyt-tasfyn-partyv--novweb-talrud-talmud-sonfyr

+feq:ag

Parse @q phonetic base

Parsing rule. Parses an atom of aura @q (an unscrambled @p).

Source

++  feq  %+  cook  |=(a=(list @) (rep 4 (flop a)))
         ;~  plug
           ;~(pose hif:ab tiq:ab)
           (star ;~(pfix dof hif:ab))
         ==

Examples

> `@q`(scan "sampel" feq:ag)
.~sampel

> `@q`(scan "sampel-palnet" feq:ag)
.~sampel-palnet

> `@q`(scan "sampel-sampel-palnet" feq:ag)
.~sampel-sampel-palnet

> `@q`(scan "sampel-palnet-sampel-palnet" feq:ag)
.~sampel-palnet-sampel-palnet

> `@q`(scan "sampel-sampel-sampel-sampel-palnet-sampel-palnet" feq:ag)
.~sampel-sampel-sampel-sampel-palnet-sampel-palnet

+fim:ag

Parse base58check

Parse a base58check value, check checksum, and return decoded value sans-checksum. If the checksum check fails, parsing will fail.

Source

++  fim  (sear den:fa (bass 58 (plus fem:ab)))

Examples

With valid checksum:

> (enc:fa 0xdead.beef)
0xdead.beef.938b.8b0c
> (c-co:co 0xdead.beef.938b.8b0c)
"eFGDJSVvRHd"
> `@ux`(scan "eFGDJSVvRHd" fim:ag)
0xdead.beef

With invalid checksum:

> (c-co:co 0xdead.beef.ffff)
"2utUWE41U"
> `@ux`(scan "2utUWE41U" fim:ag)
{1 10}
syntax error

+hex:ag

Parse hex

Parsing +rule. Parses a hexadecimal number

Source

++  hex  (ape (bass 0x1.0000 ;~(plug qex:ab (star ;~(pfix dog qix:ab)))))

Examples

> `@ux`(scan "4" hex:ag)
0x4

> `@ux`(scan "1a" hex:ag)
0x1a

> `@ux`(scan "3.ac8d" hex:ag)
0x3.ac8d

+lip:ag

Parse IPv4 address

Parsing +rule. Parses an IPv4 address.

Source

++  lip  =+  tod=(ape ted:ab)
         (bass 256 ;~(plug tod (stun [3 3] ;~(pfix dog tod))))

Examples

> `@if`(scan "127.0.0.1" lip:ag)
.127.0.0.1

+mot:ag

Parse numerical month

Parse a numerical month (1-12).

Source

++  mot  ;~  pose
           ;~  pfix
             (just '1')
             (cook |=(a=@ (add 10 (sub a '0'))) (shim '0' '2'))
           ==
           sed:ab
         ==

Examples

> (scan "0" mot:ag)
{1 1}
syntax error

> (scan "1" mot:ag)
1

> (scan "6" mot:ag)
6

> (scan "12" mot:ag)
12

> (scan "13" mot:ag)
{1 2}
syntax error

+viz:ag

Parse Base-32 with dots

Parsing +rule. Parses a Base-32 number with dot separators.

Source

++  viz  (ape (bass 0x200.0000 ;~(plug pev:ab (star ;~(pfix dog piv:ab)))))

Examples

> `@uv`(scan "e2.ol4pm" viz:ag)
0ve2.ol4pm

+vum:ag

Parse base-32 string

Parsing +rule. Parses a raw base-32 string (without dots).

Source

++  vum  (bass 32 (plus siv:ab))

Examples

> `@uv`(scan "e2ol4pm" vum:ag)
0ve2.ol4pm

+wiz:ag

Parse base-64

Parsing +rule. Parses a base-64 number.

Source

++  wiz  (ape (bass 0x4000.0000 ;~(plug pew:ab (star ;~(pfix dog piw:ab)))))

Examples

> `@uw`(scan "e2O.l4Xpm" wiz:ag)
0we2O.l4Xpm

+mu

Core used to scramble 16-bit atoms

A door that contains arms that are used to scramble two atoms, top and bot. Used especially in the phonetic base to disguise the relationship between a planet and its star.

Accepts

top is an atom.

bot is an atom.

Source

++  mu
  |_  [top=@ bot=@]

+zag:mu

Add bottom into top

Produces the cell of top and bot with top scrambled to the result of adding bot to top modulo 16. Used to scramble the name of a planet.

Accepts

top & bot are atoms, and are the sample of +mu.

Produces

A (pair @ @).

Source

++  zag  [p=(end 4 (add top bot)) q=bot]

Examples

> `[@ux @ux]`~(zag mu 0x20e0 0x201)
[0x22e1 0x201]

+zig:mu

Subtract bottom from top

The inverse of +zag. Produces the cell of top and bot with top unscrambled. The unscrambled top is the sum of the sample top and the 16-bit complement of bot. Used to unscramble the name of the planet.

Accepts

top & bot are atoms, and are the sample of +mu.

Produces

A (pair @ @).

Source

++  zig  [p=(end 4 (add top (sub 0x1.0000 bot))) q=bot]

Examples

> `[@ux @ux]`~(zig mu 0x22e1 0x201)
[0x20e0 0x201]

+zug:mu

Concatenate into atom

Produces the concatenation of top and bot. Used to assemble a planet name.

Accepts

top & bot are atoms, and are the sample of +mu.

Produces

An atom.

Source

++  zug  (mix (lsh 4 top) bot)

Examples

> `@ux`~(zug mu 0x22e1 0x201)
0x22e1.0201

+ne

Digit rendering engine

A door containing arms that render digits at bases 10, 16, 32, and 64.

Accepts

tig is an $atom.

Source

++  ne
  |_  tig=@

+c:ne

Render base58check

Render a single base58check character.

Accepts

tig is an $atom, and is the sample of +ne.

Produces

An atom.

Source

++  c  (cut 3 [tig 1] key:fa)

Examples

> `@t`~(c ne 7)
'8'

> `@t`~(c ne 27)
'U'

> `@t`~(c ne 57)
'z'

> `@t`~(c ne 58)
''

+d:ne

Render decimal

Renders a decimal digit as an atom of an ACII byte value.

Accepts

tig is an $atom, and is the sample of +ne.

Produces

An atom.

Source

++  d  (add tig '0')

Examples

> `@t`~(d ne 7)
'7'

+x:ne

Render hex

Renders a hexadecimal digit as an atom of an ASCII byte value.

Accepts

tig is an $atom, and is the sample of +ne.

Produces

An atom.

Source

++  x  ?:((gte tig 10) (add tig 87) d)

Examples

> `@t`~(x ne 7)
'7'

> `@t`~(x ne 14)
'e'

+v:ne

Render base-32

Renders a base-32 digit as an atom of an ASCII byte value.

Accepts

tig is an $atom, and is the sample of +ne.

Produces

An atom.

Source

++  v  ?:((gte tig 10) (add tig 87) d)

Examples

> `@t`~(v ne 7)
'7'

> `@t`~(v ne 14)
'e'

> `@t`~(v ne 25)
'p'

+w:ne

Render base-64

Renders a base-64 digit as an atom of an ASCII byte value.

Accepts

tig is an $atom, and is the sample of +ne.

Produces

An atom.

Source

++  w  ?:(=(tig 63) '~' ?:(=(tig 62) '-' ?:((gte tig 36) (add tig 29) x)))

Examples

> `@t`~(w ne 7)
'7'

> `@t`~(w ne 14)
'e'

> `@t`~(w ne 25)
'p'

> `@t`~(w ne 52)
'Q'

> `@t`~(w ne 61)
'Z'

> `@t`~(w ne 63)
'~'

> `@t`~(w ne 62)
'-'

Last updated