4m: Formatting Functions

+scot

Render dime as cord

Renders a dime mol as a cord.

Accepts

mol is a $dime.

Produces

A $cord.

Source

++  scot
  ~/  %scot
  |=(mol=dime ~(rent co %$ mol))

Examples

> (scot %p ~pillyt)
~.~pillyt

> `@t`(scot %p ~pillyt)
'~pillyt'

> `@t`(scot %ux 0x12)
'0x12'

> `@t`(scot %if .127.0.0.1)
'.127.0.0.1'

> `@t`(scot %ta ~.asd_a)
'~.asd_a'

+scow

Render dime as tape

Renders a dime mol as a tape.

Accepts

mol is a $dime.

Produces

A $tape.

Source

++  scow
  ~/  %scow
  |=(mol=dime ~(rend co %$ mol))

Examples

> (scow %p ~pillyt)
"~pillyt"

> (scow %ux 0x12)
"0x12"

> (scow %if .127.0.0.1)
".127.0.0.1"

> (scow %ta ~.asd_a)
"~.asd_a"

+slat

Curried slaw

Produces a $gate that parses a $knot txt to a +unit containing the atom of the aura specified by mod. The +unit will be null if parsing failed.

Accepts

mod is a $knot.

txt is a $cord.

Produces

A (unit @).

Source

++  slat  |=(mod=@tas |=(txt=@ta (slaw mod txt)))

Examples

> `(unit @p)`((slat %p) '~pillyt')
[~ ~pillyt]

> `(unit @ux)`((slat %ux) '0x12')
[~ 0x12]

> `(unit @if)`((slat %if) '.127.0.0.1')
[~ .127.0.0.1]

> `(unit @ta)`((slat %ta) '~.asd_a')
[~ ~.asd_a]

+slav

Demand: parse cord with input aura

Parses a cord txt to an atom of the aura specificed by mod. Crashes if it fails to parse.

Accepts

mod is a $term

txt is a $knot.

Produces

an atom.

Source

++  slav  |=([mod=@tas txt=@ta] (need (slaw mod txt)))

Examples

> `@p`(slav %p '~pillyt')
~pillyt

> `@p`(slav %p '~pillam')
! exit

> `@ux`(slav %ux '0x12')
0x12

> `@ux`(slav %ux '0b10')
! exit

> `@if`(slav %if '.127.0.0.1')
.127.0.0.1

> `@if`(slav %if '.fe80.0.0.202')
! exit

> `@ta`(slav %ta '~.asd_a')
~.asd_a

> `@ta`(slav %ta '~~asd-a')
! exit

+slaw

Parse cord to input aura

Parses a cord txt to a +unit containing the atom of the aura specified by mod. The +unit is null if parsing failed.

Accepts

mod is a $term.

txt is a $knot.

Produces

A (unit @).

Source

++  slaw
  ~/  %slaw
  |=  [mod=@tas txt=@ta]
  ^-  (unit @)
  ?+    mod
      ::  slow fallback case to the full slay
      ::
      =+  con=(slay txt)
      ?.(&(?=([~ %$ @ @] con) =(p.p.u.con mod)) ~ [~ q.p.u.con])
  ::
      %da
    (rush txt ;~(pfix sig (cook year when:so)))
  ::
      %p
    (rush txt ;~(pfix sig fed:ag))
  ::
      %ud
    (rush txt dem:ag)
  ::
      %ux
    (rush txt ;~(pfix (jest '0x') hex:ag))
  ::
      %uv
    (rush txt ;~(pfix (jest '0v') viz:ag))
  ::
      %ta
    (rush txt ;~(pfix ;~(plug sig dot) urs:ab))
  ::
      %tas
    (rush txt sym)
  ==

Examples

> `(unit @p)`(slaw %p '~pillyt')
[~ ~pillyt]

> `(unit @p)`(slaw %p '~pillam')
~

> `(unit @ux)`(slaw %ux '0x12')
[~ 0x12]

> `(unit @ux)`(slaw %ux '0b10')
~

> `(unit @if)`(slaw %if '.127.0.0.1')
[~ .127.0.0.1]

> `(unit @if)`(slaw %if '.fe80.0.0.202')
~

> `(unit @ta)`(slaw %ta '~.asd_a')
[~ ~.asd_a]

> `(unit @ta)`(slaw %ta '~~asd-a')
~

+slay

Parse cord to coin

Parses a cord txt to the unit of a $coin.

Accepts

txt is a @ta.

Produces

A (unit coin).

Source

++  slay
  |=  txt=@ta  ^-  (unit coin)
  =+  ^=  vex
      ?:  (gth 0x7fff.ffff txt)                         ::  XX  petty cache
        ~+  ((full nuck:so) [[1 1] (trip txt)])
      ((full nuck:so) [[1 1] (trip txt)])
  ?~  q.vex
    ~
  [~ p.u.q.vex]

Examples

> (slay '~pillyt')
[~ [%$ p=[p=~.p q=13.184]]]

> (slay '0x12')
[~ [%$ p=[p=~.ux q=18]]]

> (slay '.127.0.0.1')
[~ [%$ p=[p=~.if q=2.130.706.433]]]

> (slay '!')
~

+smyt

Render path as tank

Renders the path bon as a $tank, which is used for pretty-printing.

Accepts

bon is a $path.

Produces

A $tank.

Source

++  smyt
  |=  bon=path  ^-  tank
  :+  %rose  [['/' ~] ['/' ~] ~]
  (turn bon |=(a=@ [%leaf (trip a)]))

Examples

> (smyt %)
[ %rose
  p=[p="/" q="/" r=""]
    q
  ~[
    [%leaf p="~zod"]
    [%leaf p="base"]
    [%leaf p="~2022.1.6..14.22.14..40bf"]
  ]
]

> (smyt /as/les/top)
[ %rose
  p=[p="/" q="/" r=""]
  q=~[[%leaf p="as"] [%leaf p="les"] [%leaf p="top"]]
]

+spat

Render path as cord

Renders a path pax as cord.

Accepts

pax is a $path.

Produces

A $cord.

Source

++  spat  |=(pax=path (crip (spud pax)))

Examples

> (spat %)
'/~zod/base/~2022.1.6..14.23.31..e367'

> (spat %/lib)
'/~zod/base/~2022.1.6..14.23.43..829e/lib'

> (spat /as/les/top)
'/as/les/top'

+spud

Render path as tape

Renders a path pax as tape.

Accepts

pax is a $path.

Produces

A $tape.

Source

++  spud  |=(pax=path ~(ram re (smyt pax)))

Examples

> (spud %)
"/~zod/base/~2022.1.6..14.24.35..cddf"

> (spud %/lib)
"/~zod/base/~2022.1.6..14.24.43..3efb/lib"

> (spud /as/les/top)
"/as/les/top"

+stab

Parse cord to path

Parses a cord zep to a static $path. Crashes if it fails to parse.

Accepts

zep is a @t.

Produces

A $path, or crash.

Source

++  stab  |=(zep=@t `$path`(rash zep stap))

Examples

> (stab '/as/lek/tor')
/as/lek/tor

+stap

Path parser

Parsing +rule. Parses a $path, used internally by +stab.

Source

++  stap
  %+  sear
    |=  p=path
    ^-  (unit path)
    ?:  ?=([~ ~] p)  `~
    ?.  =(~ (rear p))  `p
    ~
  ;~(pfix fas (most fas urs:ab))

Examples

> (scan "/foo/bar/baz" stap)
/foo/bar/baz

Last updated