Urbit Docs
  • What is Urbit?
  • Get on Urbit
  • Build on Urbit
    • Contents
    • Environment Setup
    • Hoon School
      • 1. Hoon Syntax
      • 2. Azimuth (Urbit ID)
      • 3. Gates (Functions)
      • 4. Molds (Types)
      • 5. Cores
      • 6. Trees and Addressing
      • 7. Libraries
      • 8. Testing Code
      • 9. Text Processing I
      • 10. Cores and Doors
      • 11. Data Structures
      • 12. Type Checking
      • 13. Conditional Logic
      • 14. Subject-Oriented Programming
      • 15. Text Processing II
      • 16. Functional Programming
      • 17. Text Processing III
      • 18. Generic and Variant Cores
      • 19. Mathematics
    • App School I
      • 1. Arvo
      • 2. The Agent Core
      • 3. Imports and Aliases
      • 4. Lifecycle
      • 5. Cards
      • 6. Pokes
      • 7. Structures and Marks
      • 8. Subscriptions
      • 9. Vanes
      • 10. Scries
      • 11. Failure
      • 12. Next Steps
      • Appendix: Types
    • App School II (Full-Stack)
      • 1. Types
      • 2. Agent
      • 3. JSON
      • 4. Marks
      • 5. Eyre
      • 6. React app setup
      • 7. React app logic
      • 8. Desk and glob
      • 9. Summary
    • Core Academy
      • 1. Evaluating Nock
      • 2. Building Hoon
      • 3. The Core Stack
      • 4. Arvo I: The Main Sequence
      • 5. Arvo II: The Boot Sequence
      • 6. Vere I: u3 and the Serf
      • 7. Vere II: The Loom
      • 8. Vanes I: Behn, Dill, Kahn, Lick
      • 9. Vanes II: Ames
      • 10. Vanes III: Eyre, Iris
      • 11. Vanes IV: Clay
      • 12. Vanes V: Gall and Userspace
      • 13. Vanes VI: Khan, Lick
      • 14. Vanes VII: Jael, Azimuth
    • Runtime
      • U3
      • Conn.c Guide
      • How to Write a Jet
      • API Overview by Prefix
      • C in Urbit
      • Cryptography
      • Land of Nouns
    • Tools
      • Useful Links
      • JS Libraries
        • HTTP API
      • Docs App
        • File Format
        • Index File
        • Suggested Structure
    • Userspace
      • Command-Line App Tutorial
      • Remote Scry
      • Unit Tests
      • Software Distribution
        • Software Distribution Guide
        • Docket File
        • Glob
      • Examples
        • Building a CLI App
        • Debugging Wrapper
        • Host a Website
        • Serving a JS Game
        • Ship Monitoring
        • Styled Text
  • Urbit ID
    • What is Urbit ID?
    • Azimuth Data Flow
    • Life and Rift
    • Urbit HD Wallet
    • Advanced Azimuth Tools
    • Custom Roller Tutorial
    • Azimuth.eth Reference
    • Ecliptic.eth Reference
    • Layer 2
      • L2 Actions
      • L2 Rollers
      • L2 Roller HTTP RPC-API
      • L2 Transaction Format
  • Urbit OS
    • What is Urbit OS?
    • Base
      • Hood
      • Threads
        • Basics Tutorial
          • Bind
          • Fundamentals
          • Input
          • Output
          • Summary
        • HTTP API Guide
        • Spider API Reference
        • Strandio Reference
        • Examples
          • Child Thread
          • Fetch JSON
          • Gall
            • Poke Thread
            • Start Thread
            • Stop Thread
            • Take Facts
            • Take Result
          • Main-loop
          • Poke Agent
          • Scry
          • Take Fact
    • Kernel
      • Arvo
        • Cryptography
        • Move Trace
        • Scries
        • Subscriptions
      • Ames
        • Ames API Reference
        • Ames Cryptography
        • Ames Data Types
        • Ames Scry Reference
      • Behn
        • Behn API Reference
        • Behn Examples
        • Behn Scry Reference
      • Clay
        • Clay API Reference
        • Clay Architecture
        • Clay Data Types
        • Clay Examples
        • Clay Scry Reference
        • Filesystem Hierarchy
        • Marks
          • Mark Examples
          • Using Marks
          • Writing Marks
        • Using Clay
      • Dill
        • Dill API Reference
        • Dill Data Types
        • Dill Scry Reference
      • Eyre
        • EAuth
        • Eyre Data Types
        • Eyre External API
        • Eyre Internal API
        • Eyre Scry Reference
        • Low-Level Eyre Guide
        • Noun channels
      • Gall
        • Gall API Reference
        • Gall Data Types
        • Gall Scry Reference
      • Iris
        • Iris API Reference
        • Iris Data Types
        • Iris Example
      • Jael
        • Jael API Reference
        • Jael Data Types
        • Jael Examples
        • Jael Scry Reference
      • Khan
        • Khan API Reference
        • Khan Data Types
        • Khan Example
      • Lick
        • Lick API Reference
        • Lick Guide
        • Lick Examples
        • Lick Scry Reference
  • Hoon
    • Why Hoon?
    • Advanced Types
    • Arvo
    • Auras
    • Basic Types
    • Cheat Sheet
    • Cryptography
    • Examples
      • ABC Blocks
      • Competitive Programming
      • Emirp
      • Gleichniszahlenreihe
      • Islands
      • Luhn Number
      • Minimum Path Sum
      • Phone Letters
      • Restore IP
      • Rhonda Numbers
      • Roman Numerals
      • Solitaire Cipher
      • Water Towers
    • Generators
    • Hoon Errors
    • Hoon Style Guide
    • Implementing an Aura
    • Irregular forms
    • JSON
    • Limbs and wings
      • Limbs
      • Wings
    • Mips (Maps of Maps)
    • Parsing Text
    • Runes
      • | bar · Cores
      • $ buc · Structures
      • % cen · Calls
      • : col · Cells
      • . dot · Nock
      • / fas · Imports
      • ^ ket · Casts
      • + lus · Arms
      • ; mic · Make
      • ~ sig · Hints
      • = tis · Subject
      • ? wut · Conditionals
      • ! zap · Wild
      • Constants (Atoms and Strings)
      • --, == · Terminators
    • Sail (HTML)
    • Serialization
    • Sets
    • Standard Library
      • 1a: Basic Arithmetic
      • 1b: Tree Addressing
      • 1c: Molds and Mold-Builders
      • 2a: Unit Logic
      • 2b: List Logic
      • 2c: Bit Arithmetic
      • 2d: Bit Logic
      • 2e: Insecure Hashing
      • 2f: Noun Ordering
      • 2g: Unsigned Powers
      • 2h: Set Logic
      • 2i: Map Logic
      • 2j: Jar and Jug Logic
      • 2k: Queue Logic
      • 2l: Container from Container
      • 2m: Container from Noun
      • 2n: Functional Hacks
      • 2o: Normalizing Containers
      • 2p: Serialization
      • 2q: Molds and Mold-Builders
      • 3a: Modular and Signed Ints
      • 3b: Floating Point
      • 3c: Urbit Time
      • 3d: SHA Hash Family
      • 3e: AES encryption (Removed)
      • 3f: Scrambling
      • 3g: Molds and Mold-Builders
      • 4a: Exotic Bases
      • 4b: Text Processing
      • 4c: Tank Printer
      • 4d: Parsing (Tracing)
      • 4e: Parsing (Combinators)
      • 4f: Parsing (Rule-Builders)
      • 4g: Parsing (Outside Caller)
      • 4h: Parsing (ASCII Glyphs)
      • 4i: Parsing (Useful Idioms)
      • 4j: Parsing (Bases and Base Digits)
      • 4k: Atom Printing
      • 4l: Atom Parsing
      • 4m: Formatting Functions
      • 4n: Virtualization
      • 4o: Molds
      • 5a: Compiler Utilities
      • 5b: Macro Expansion
      • 5c: Compiler Backend & Prettyprinter
      • 5d: Parser
      • 5e: Molds and mold builders
      • 5f: Profiling support
    • Strings
    • The Engine Pattern
    • Udon (Markdown-esque)
    • Vases
    • Zuse
      • 2d(1-5): To JSON, Wains
      • 2d(6): From JSON
      • 2d(7): From JSON (unit)
      • 2e(2-3): Print & Parse JSON
      • 2m: Ordered Maps
  • Nock
    • What is Nock?
    • Decrement
    • Definition
    • Fast Hints and Jets
    • Implementations
    • Specification
  • User Manual
    • Contents
    • Running Urbit
      • Cloud Hosting
      • Home Servers
      • Runtime Reference
      • Self-hosting S3 Storage with MinIO
    • Urbit ID
      • Bridge Troubleshooting
      • Creating an Invite Pool
      • Get an Urbit ID
      • Guide to Factory Resets
      • HD Wallet (Master Ticket)
      • Layer 2 for planets
      • Layer 2 for stars
      • Proxies
      • Using Bridge
    • Urbit OS
      • Basics
      • Configuring S3 Storage
      • Dojo Tools
      • Filesystem
      • Shell
      • Ship Troubleshooting
      • Star and Galaxy Operations
      • Updates
Powered by GitBook

GitHub

  • Urbit ID
  • Urbit OS
  • Runtime

Resources

  • YouTube
  • Whitepaper
  • Awesome Urbit

Contact

  • X
  • Email
  • Gather
On this page
  • +bass
  • +boss
  • +cold
  • +cook
  • +easy
  • +fuss
  • +full
  • +funk
  • +here
  • +inde
  • +ifix
  • +jest
  • +just
  • +knee
  • +mask
  • +more
  • +most
  • +next
  • +perk
  • +plus
  • +punt
  • +sear
  • +shim
  • +slug
  • +stag
  • +star
  • +stet
  • +stew
  • +stir
  • +stun
Edit on GitHub
  1. Hoon
  2. Standard Library

4f: Parsing (Rule-Builders)

+bass

Parser modifier: LSB ordered list as atom of a base.

Accepts

wuc is an atom.

tyd is a rule.

Produces

A rule.

Source

++  bass
  |*  [wuc=@ tyd=rule]
  %+  cook
    |=  waq=(list @)
    %+  roll
      waq
    =|([p=@ q=@] |.((add p (mul wuc q))))
  tyd

Examples

> (scan "123" (bass 10 (star dit)))
q=123
> (scan "123" (bass 8 (star dit)))
q=83
> `@ub`(scan "123" (bass 8 (star dit)))
0b101.0011

+boss

Parser modifier: LSB

Ordered list as atom of a base.

Accepts

wuc is an atom.

tyd is a rule.

Produces

A rule.

Source

++  boss
  |*  [wuc=@ tyd=rule]
  %+  cook
    |=  waq=(list @)
    %+  reel
      waq
    =|([p=@ q=@] |.((add p (mul wuc q))))
  tyd

Examples

> (scan "123" (boss 10 (star dit)))
321

> `@t`(scan "bam" (boss 256 (star alp)))
'bam'

> `@ux`(scan "bam" (boss 256 (star alp)))
0x6d.6162

+cold

Replace with constant

Parser modifier. Accepts a rule sef and produces a parser that produces a constant cus, assuming sef is successful.

Accepts

cus is a constant noun.

sef is a rule.

Produces

An edge.

Source

++  cold
  ~/  %cold
  |*  [cus=* sef=rule]
  ~/  %fun
  |=  tub=nail
  =+  vex=(sef tub)
  ?~  q.vex
    vex
  [p=p.vex q=[~ u=[p=cus q=q.u.q.vex]]]

Examples

> ((cold %foo (just 'a')) [[1 1] "abc"])
[p=[p=1 q=2] q=[~ u=[p=%foo q=[p=[p=1 q=2] q="bc"]]]]

> ((cold %foo (just 'a')) [[1 1] "bc"])
[p=[p=1 q=1] q=~]

+cook

Apply gate

Parser modifier. Produces a parser that takes a (successful) result of a rule sef and slams it through poq.

Accepts

poq is a gate.

sef is a rule.

Produces

An rule.

Source

++  cook
  ~/  %cook
  |*  [poq=gate sef=rule]
  ~/  %fun
  |=  tub=nail
  =+  vex=(sef tub)
  ?~  q.vex
    vex
  [p=p.vex q=[~ u=[p=(poq p.u.q.vex) q=q.u.q.vex]]]

Examples

> ((cook ,@ud (just 'a')) [[1 1] "abc"])
[p=[p=1 q=2] q=[~ u=[p=97 q=[p=[p=1 q=2] q="bc"]]]]

> ((cook ,@tas (just 'a')) [[1 1] "abc"])
[p=[p=1 q=2] q=[~ u=[p=%a q=[p=[p=1 q=2] q="bc"]]]]

> ((cook |=(a=@ +(a)) (just 'a')) [[1 1] "abc"])
[p=[p=1 q=2] q=[~ u=[p=98 q=[p=[p=1 q=2] q="bc"]]]]

> ((cook |=(a=@ `@t`+(a)) (just 'a')) [[1 1] "abc"])
[p=[p=1 q=2] q=[~ u=[p='b' q=[p=[p=1 q=2] q="bc"]]]]

+easy

Always parse

Parser generator. Produces a parser that succeeds with given noun huf without consuming any text.

Accepts

huf is a noun.

Produces

A rule.

Source

++  easy
  ~/  %easy
  |*  huf=*
  ~/  %fun
  |=  tub=nail
  ^-  (like _huf)
  [p=p.tub q=[~ u=[p=huf q=tub]]]

Examples

> ((easy %foo) [[1 1] "abc"])
[p=[p=1 q=1] q=[~ [p=%foo q=[p=[p=1 q=1] q="abc"]]]]

> ((easy %foo) [[1 1] "bc"])
[p=[p=1 q=1] q=[~ [p=%foo q=[p=[p=1 q=1] q="bc"]]]]

> ((easy 'a') [[1 1] "bc"])
[p=[p=1 q=1] q=[~ [p='a' q=[p=[p=1 q=1] q="bc"]]]]

+fuss

Has A or B?

If string sic is parsed: %.y. If string non is parsed: %.n. Otherwise, fail.

Accepts

sic is a @t.

non is a @t.

Produces

A rule.

Source

++  fuss
  |=  [sic=@t non=@t]
  ;~(pose (cold %& (jest sic)) (cold %| (jest non)))

Examples

> (rash 'foo' (fuss 'foo' 'bar'))
%.y

> (rash 'bar' (fuss 'foo' 'bar'))
%.n

> (rash 'baz' (fuss 'foo' 'bar'))
{1 3}
syntax error

+full

Parse to end

Parser modifier. Accepts a rule sef, and produces a parser that succeeds only when the tape of tub is fully consumed using sef.

Accepts

sef is a rule.

Produces

A rule.

Source

++  full
  |*  sef=rule
  |=  tub=nail
  =+  vex=(sef tub)
  ?~(q.vex vex ?:(=(~ q.q.u.q.vex) vex [p=p.vex q=~]))

Examples

> ((full (just 'a')) [[1 1] "ab"])
[p=[p=1 q=2] q=~]

> ((full (jest 'ab')) [[1 1] "ab"])
[p=[p=1 q=3] q=[~ u=[p='ab' q=[p=[p=1 q=3] q=""]]]]

> ((full ;~(plug (just 'a') (just 'b'))) [[1 1] "ab"])
[p=[p=1 q=3] q=[~ u=[p=['a' 'b'] q=[p=[p=1 q=3] q=""]]]]

+funk

Add to tape

Parser modifier: prepend text to tape before applying parser.

Accepts

pre is a tape

sef is a rule

Produces

A rule.

Source

++  funk
  |*  [pre=tape sef=rule]
  |=  tub=nail
  (sef p.tub (weld pre q.tub))

Examples

> ((funk "abc prefix-" (jest 'abc')) [[1 1] "to be parsed"])
[p=[p=1 q=4] q=[~ [p='abc' q=[p=[p=1 q=4] q=" prefix-to be parsed"]]]]

> ((funk "parse" (just 'a')) [[1 4] " me"])
[p=[p=1 q=4] q=~]

+here

Place-based apply

Parser modifier. Similar to ++cook in that it produces a parser that takes a (successful) result of sef and slams it through hez. hez accepts a pint a and a noun b, which is what the parser parsed.

Accepts

hez is a gate.

sef is a rule

Produces

A rule.

Source

++  here
  ~/  %here
  =+  [hez=|=([a=pint b=*] [a b]) sef=*rule]
  |@
  ++  $
    ~/  %fun
    |=  tub=nail
    =+  vex=(sef tub)
    ?~  q.vex
      vex
    [p=p.vex q=[~ u=[p=(hez [p.tub p.q.u.q.vex] p.u.q.vex) q=q.u.q.vex]]]
  --

Examples

> (scan "abc" (star alf))
"abc"

> (scan "abc" (here |*(^ +<) (star alf)))
[[[p=1 q=1] p=1 q=4] "abc"]

> (scan "abc" (star (here |*(^ +<) alf)))
~[[[[p=1 q=1] p=1 q=2] ~~a] [[[p=1 q=2] p=1 q=3] ~~b] [[[p=1 q=3] p=1 q=4] ~~c]]

+inde

Indentation block

Apply rule to indented block starting at current column number, omitting the leading whitespace.

Accepts

sef is a rule.

Produces

A rule.

Source

++  inde  |*  sef=rule
  |=  nail  ^+  (sef)
  =+  [har tap]=[p q]:+<
  =+  lev=(fil 3 (dec q.har) ' ')
  =+  eol=(just `@t`10)
  =+  =-  roq=((star ;~(pose prn ;~(sfix eol (jest lev)) -)) har tap)
      ;~(simu ;~(plug eol eol) eol)
  ?~  q.roq  roq
  =+  vex=(sef har(q 1) p.u.q.roq)
  =+  fur=p.vex(q (add (dec q.har) q.p.vex))
  ?~  q.vex  vex(p fur)
  =-  vex(p fur, u.q -)
  :+  &3.vex
    &4.vex(q.p (add (dec q.har) q.p.&4.vex))
  =+  res=|4.vex
  |-  ?~  res  |4.roq
  ?.  =(10 -.res)  [-.res $(res +.res)]
  (welp [`@t`10 (trip lev)] $(res +.res))

Examples

> `tape`(scan "   foo\0a   bar" ;~(pfix ace ace ace (inde (star ;~(pose prn (just '\0a'))))))
"foo\0abar"

Discussion

Note the amount of indentation whitespace to be stripped from the beginning of each line is determined by the value of q (the column) in the hair when ++inde is first called. This means something like the pfix expression in the example above is necessary to set the level of indentation. Additionally, the rule given to ++inde must consume the whole line including the line ending.


+ifix

Infix

Parser modifier: surround with pair of rules, the output of which is discarded.

Accepts

fel is a pair of rules.

hof is a rule.

Produces

A rule.

Source

++  ifix
  |*  [fel=[rule rule] hof=rule]
  ~!  +<
  ~!  +<:-.fel
  ~!  +<:+.fel
  ;~(pfix -.fel ;~(sfix hof +.fel))

Examples

> (scan "-40-" (ifix [hep hep] dem))
40

> (scan "4my4" (ifix [dit dit] (star alf)))
"my"

+jest

Match a cord

Match and consume a cord.

Accepts

daf is a @t.

Produces

A rule.

Source

++  jest
  |=  daf=@t
  |=  tub=nail
  =+  fad=daf
  |-  ^-  (like @t)
  ?:  =(`@`0 daf)
    [p=p.tub q=[~ u=[p=fad q=tub]]]
  ?:  |(?=(~ q.tub) !=((end 3 daf) i.q.tub))
    (fail tub)
  $(p.tub (lust i.q.tub p.tub), q.tub t.q.tub, daf (rsh 3 daf))

Examples

> ((jest 'abc') [[1 1] "abc"])
[p=[p=1 q=4] q=[~ [p='abc' q=[p=[p=1 q=4] q=""]]]]

> (scan "abc" (jest 'abc'))
'abc'

> (scan "abc" (jest 'acb'))
! {1 2}
! 'syntax-error'
! exit

> ((jest 'john doe') [[1 1] "john smith"])
[p=[p=1 q=6] q=~]

> ((jest 'john doe') [[1 1] "john doe"])
[p=[p=1 q=9] q=[~ [p='john doe' q=[p=[p=1 q=9] q=""]]]]

+just

Match a char

Match and consume a single character.

Accepts

daf is a char

Produces

A rule.

Source

++  just
  ~/  %just
  |=  daf=char
  ~/  %fun
  |=  tub=nail
  ^-  (like char)
  ?~  q.tub
    (fail tub)
  ?.  =(daf i.q.tub)
    (fail tub)
  (next tub)

Examples

> ((just 'a') [[1 1] "abc"])
[p=[p=1 q=2] q=[~ [p='a' q=[p=[p=1 q=2] q="bc"]]]]

> (scan "abc" (just 'a'))
! {1 2}
! 'syntax-error'
! exit

> (scan "a" (just 'a'))
'a'

> (scan "%" (just '%'))
'%'

+knee

Recursive parsers

Used for recursive parsers, which would otherwise be infinite when compiled.

Accepts

gar is a noun.

sef is a gate that accepts a rule

Produces

A rule.

Source

++  knee
  =|  [gar=* sef=_|.(*rule)]
  |@  ++  $
        |=  tub=nail
        ^-  (like _gar)
        ((sef) tub)
  --

Examples

> |-(;~(plug prn ;~(pose $ (easy ~))))
! rest-loop
! exit

> |-(;~(plug prn ;~(pose (knee *tape |.(^$)) (easy ~))))
< 1.obo
  [ c=c=tub=[p=[p=@ud q=@ud] q=""]
      b
    < 1.bes
      [ c=tub=[p=[p=@ud q=@ud] q=""]
        b=<1.tnv [tub=[p=[p=@ud q=@ud] q=""] <1.ktu [daf=@tD <414.fvk 101.jzo 1.ypj %164>]>]>
        a=<1.fvg [tub=[p=[p=@ud q=@ud] q=""] <1.khu [[les=@ mos=@] <414.fvk 101.jzo 1.ypj %164>]>]>
        v=<414.fvk 101.jzo 1.ypj %164>
      ]
    >
      a
    ... 450 lines omitted ...
  ]
>

> (scan "abcd" |-(;~(plug prn ;~(pose (knee *tape |.(^$)) (easy ~)))))
['a' "bcd"]

+mask

Match char

Parser generator. Matches the next character if it is in a list of characters.

Accepts

bud is a list of char

Produces

A rule.

Source

++  mask
  ~/  %mask
  |=  bud=(list char)
  ~/  %fun
  |=  tub=nail
  ^-  (like char)
  ?~  q.tub
    (fail tub)
  ?.  (lien bud |=(a=char =(i.q.tub a)))
    (fail tub)
  (next tub)

Examples

> (scan "a" (mask "cba"))
'a'

> ((mask "abc") [[1 1] "abc"])
[p=[p=1 q=2] q=[~ [p='a' q=[p=[p=1 q=2] q="bc"]]]]

> ((mask "abc") [[1 1] "bbc"])
[p=[p=1 q=2] q=[~ [p='b' q=[p=[p=1 q=2] q="bc"]]]]

> ((mask "abc") [[1 1] "dbc"])
[p=[p=1 q=1] q=~]

+more

Parse list with delimiter

Parser modifier: Parse a list of matches using a delimiter rule.

Accepts

bus is a rule.

fel is a rule.

Produces

A rule.

Source

++  more
  |*  [bus=rule fel=rule]
  ;~(pose (most bus fel) (easy ~))

Examples

> (scan "" (more ace dem))
~

> (scan "40 20" (more ace dem))
[40 [i=20 t=~]]

> (scan "40 20 60 1 5" (more ace dem))
[40 [i=20 t=~[60 1 5]]]

+most

Parse list of at least one match

Parser modifier: parse a list of at least one match using a delimiter rule.

Accepts

bus is a rule.

fel is a rule.

Produces

A rule.

Source

++  most
  |*  [bus=rule fel=rule]
  ;~(plug fel (star ;~(pfix bus fel)))

Examples

> (scan "40 20" (most ace dem))
[40 [i=20 t=~]]

> (scan "40 20 60 1 5" (most ace dem))
[40 [i=20 t=~[60 1 5]]]

> (scan "" (most ace dem))
! {1 1}
! exit

+next

Consume char

Consume any character, producing it as a result.

Accepts

tub is a nail

Produces

An edge.

Source

++  next
  |=  tub=nail
  ^-  (like char)
  ?~  q.tub
    (fail tub)
  =+  zac=(lust i.q.tub p.tub)
  [zac [~ i.q.tub [zac t.q.tub]]]

Examples

> (next [[1 1] "ebc"])
[p=[p=1 q=2] q=[~ [p='e' q=[p=[p=1 q=2] q="bc"]]]]

> (next [[1 1] "john jumps jones"])
[p=[p=1 q=2] q=[~ [p='j' q=[p=[p=1 q=2] q="ohn jumps jones"]]]]

+perk

Parse cube fork

Given a, a list of @tas, match any one in the list and produce it. Note the list should not be a list type, but just a null-terminated cell like ~[%foo %bar %baz]. The type produced will be a union of the items in the given list, so you can use a ?- expression on the output.

Accepts

a is a (pole @tas).

Produces

A rule.

Source

++  perk
  |*  a=(pole @tas)
  ?~  a  fail
  ;~  pose
    (cold -.a (jest -.a))
    $(a +.a)
  ==

Examples

> (scan "foo" (perk ~[%foo %bar]))
%foo

> (scan "bar" (perk ~[%foo %bar]))
%bar

> (scan "baz" (perk ~[%foo %bar]))
{1 3}
syntax error

+plus

List of at least one match.

Parser modifier: parse list of at least one match.

Accepts

fel is a rule.

Produces

A rule.

Source

++  plus  |*(fel=rule ;~(plug fel (star fel)))          ::

Examples

> (scan ">>>>" (cook lent (plus gar)))
4

> (scan "-  - " (plus ;~(pose ace hep)))
['-' [i=' ' t=~[' ' '-' ' ']]]

> `tape`(scan "-  - " (plus ;~(pose ace hep)))
"-  - "

> `(pole ,@t)`(scan "-  - " (plus ;~(pose ace hep)))
['-' [' ' [' ' ['-' [' ' ~]]]]]

+punt

Unitized parse

Either successfully apply rule a and produce a unit of the result, or produce ~.

Accepts

a is a rule.

Produces

A rule.

Source

++  punt  |*([a=rule] ;~(pose (stag ~ a) (easy ~)))

Example

> ((punt (jest 'foo')) 1^1 "foo")
[p=[p=1 q=4] q=[~ u=[p=[~ 'foo'] q=[p=[p=1 q=4] q=~]]]]

> ((punt (jest 'foo')) 1^1 "bar")
[p=[p=1 q=1] q=[~ [p=~ q=[p=[p=1 q=1] q="bar"]]]]

+sear

Conditional cook

Conditional cook. Slams the result through a gate that produces a unit; if that unit is empty, fail.

Accepts

pyq is a gate that produces a unit.

sef is a rule.

Produces

A rule.

Source

++  sear
  |*  [pyq=$-(* (unit)) sef=rule]
  |=  tub=nail
  =+  vex=(sef tub)
  ?~  q.vex
    vex
  =+  gey=(pyq p.u.q.vex)
  ?~  gey
    [p=p.vex q=~]
  [p=p.vex q=[~ u=[p=u.gey q=q.u.q.vex]]]

Examples

> ((sear |=(a=* ?@(a (some a) ~)) (just 'a')) [[1 1] "abc"])
[p=[p=1 q=2] q=[~ u=[p=97 q=[p=[p=1 q=2] q="bc"]]]]

> ((sear |=(* ~) (just 'a')) [[1 1] "abc"])
[p=[p=1 q=2] q=~]

+shim

Char in range

Match characters (char) within a range.

Accepts

les is an atom.

mos is an atom.

Produces

A rule.

Source

++  shim
  ~/  %shim
  |=  [les=@ mos=@]
  ~/  %fun
  |=  tub=nail
  ^-  (like char)
  ?~  q.tub
    (fail tub)
  ?.  ?&((gte i.q.tub les) (lte i.q.tub mos))
    (fail tub)
  (next tub)

Examples

> `tape`(rash 'abc' (plus (shim 'a' 'z')))
"abc"

> `tape`(rash 'ABC' (plus (shim 'a' 'z')))
{1 1}
syntax error

+slug

Use gate to parse delimited list

Parser modifier: By composing with a gate, parse a delimited list of matches.

Accepts

raq is a binary gate.

bus is a rule.

fel is a rule.

Produces

A rule.

Source

++  slug
  |*  raq=_=>(~ |*([a=* b=*] [a b]))
  |*  [bus=rule fel=rule]
  ;~((comp raq) fel (stir +<+.raq raq ;~(pfix bus fel)))

Examples

> (scan "20+5+110" ((slug add) lus dem))
135

> `@t`(scan "a b c" ((slug |=(a=[@t @t] (cat 3 a))) ace alp))
'abc'

+stag

Add label

Add a label to an edge parsed by a rule.

Accepts

gob is a noun.

sef is a rule.

Produces

A rule.

Source

++  stag
  ~/  %stag
  |*  [gob=* sef=rule]
  ~/  %fun
  |=  tub=nail
  =+  vex=(sef tub)
  ?~  q.vex
    vex
  [p=p.vex q=[~ u=[p=[gob p.u.q.vex] q=q.u.q.vex]]]

Examples

> (rash 'abc' (stag %foo (jest 'abc')))
[%foo 'abc']

+star

List of matches

Parser modifier: parse list of matches.

Accepts

fel is a rule.

Produces

A rule.

Source

++  star
  |*  fel=rule
  (stir `(list _(wonk *fel))`~ |*([a=* b=*] [a b]) fel)

Examples

> (scan "aaaaa" (just 'a'))
! {1 2}
! 'syntax-error'
! exit

> (scan "aaaaa" (star (just 'a')))
"aaaaa"

> (scan "abcdef" (star (just 'a')))
! {1 2}
! 'syntax-error'
! exit

> (scan "abcabc" (star (jest 'abc')))
<|abc abc|>

> (scan "john smith" (star (shim 0 200)))
"john smith"

+stet

Add faces

Add faces [p q] to range-parser pairs in a list. Typically used in combination with ++stew.

Accepts

leh is a list of range-parsers.

Produces

A (list [p=?(@ [@ @]) q=rule]).

Source

++  stet
  |*  leh=(list [?(@ [@ @]) rule])
  |-
  ?~  leh
    ~
  [i=[p=-.i.leh q=+.i.leh] t=$(leh t.leh)]

Examples

> =rule %-  stew
        %-  stet
        %-  limo
        :~
          [['a' 'z'] (cook |=(a=@ (sub a 32)) alp)]
          [['A' 'Z'] (cook |=(a=@ (add a 32)) alp)]
        ==

> `tape`(rash 'fooBARbaz' (star rule))
"FOObarBAZ"

+stew

Switch by first char

Parser generator. From an associative list of characters or character ranges to rules, construct a map, and parse tapes only with rules associated with a range that the tape's first character falls in.

Accepts

leh is a (list [p=?(@ [@ @]) q=rule]), where p is a char or char range.

Produces

A rule.

Source

++  stew                                                ::  switch by first char
  ~/  %stew
  |*  leh=(list [p=?(@ [@ @]) q=rule])                  ::  char+range keys
  =+  ^=  wor                                           ::  range complete lth
      |=  [ort=?(@ [@ @]) wan=?(@ [@ @])]
      ?@  ort
        ?@(wan (lth ort wan) (lth ort -.wan))
      ?@(wan (lth +.ort wan) (lth +.ort -.wan))
  =+  ^=  hel                                           ::  build parser map
      =+  hel=`(tree _?>(?=(^ leh) i.leh))`~
      |-  ^+  hel
      ?~  leh
        ~
      =+  yal=$(leh t.leh)
      |-  ^+  hel
      ?~  yal
        [i.leh ~ ~]
      ?:  (wor p.i.leh p.n.yal)
        =+  nuc=$(yal l.yal)
        ?>  ?=(^ nuc)
        ?:  (mor p.n.yal p.n.nuc)
          [n.yal nuc r.yal]
        [n.nuc l.nuc [n.yal r.nuc r.yal]]
      =+  nuc=$(yal r.yal)
      ?>  ?=(^ nuc)
      ?:  (mor p.n.yal p.n.nuc)
        [n.yal l.yal nuc]
      [n.nuc [n.yal l.yal l.nuc] r.nuc]
  ~%  %fun  ..^$  ~
  |=  tub=nail
  ?~  q.tub
    (fail tub)
  |-
  ?~  hel
    (fail tub)
  ?:  ?@  p.n.hel
        =(p.n.hel i.q.tub)
      ?&((gte i.q.tub -.p.n.hel) (lte i.q.tub +.p.n.hel))
    ::  (q.n.hel [(lust i.q.tub p.tub) t.q.tub])
    (q.n.hel tub)
  ?:  (wor i.q.tub p.n.hel)
    $(hel l.hel)
  $(hel r.hel)

Examples

> =rule %-  stew
        %-  stet
        %-  limo
        :~
          [['a' 'z'] (cook |=(a=@ (sub a 32)) alp)]
          [['A' 'Z'] (cook |=(a=@ (add a 32)) alp)]
        ==

> `tape`(rash 'fooBARbaz' (star rule))
"FOObarBAZ"

+stir

Parse repeatedly

Parse with rule as many times as possible, and fold over results with a binary gate.

Accepts

rud is a noun.

raq is a gate that takes two nouns and produces a cell.

fel is a rule.

Produces

A rule.

Source

++  stir
  ~/  %stir
  |*  [rud=* raq=_=>(~ |*([a=* b=*] [a b])) fel=rule]
  ~/  %fun
  |=  tub=nail
  ^-  (like _rud)
  ::
  ::  lef: successful interim parse results (per .fel)
  ::  wag: initial accumulator (.rud in .tub at farthest success)
  ::
  =+  ^=  [lef wag]
    =|  lef=(list _(fel tub))
    |-  ^-  [_lef (pair hair [~ u=(pair _rud nail)])]
    =+  vex=(fel tub)
    ?~  q.vex
      :-  lef
      [p.vex [~ rud tub]]
    $(lef [vex lef], tub q.u.q.vex)
  ::
  ::  fold .lef into .wag, combining results with .raq
  ::
  %+  roll  lef
  |=  _[vex=(fel tub) wag=wag]  :: q.vex is always (some)
  ^+  wag
  :-  (last p.vex p.wag)
  [~ (raq p.u.+.q.vex p.u.q.wag) q.u.q.wag]

Examples

> (scan "abc" (stir *@ add prn))
294

> (roll "abc" add)
294

+stun

Parse several times

Parse bounded number of times.

Accepts

lig is a cell of atoms ([@ @]) indicating the bounds.

fel is a rule.

Produces

A rule.

Source

++  stun
  ~/  %stun
  |*  [lig=[@ @] fel=rule]
  |=  tub=nail
  ^-  (like (list _(wonk (fel))))
  ?:  =(0 +.lig)
    [p.tub [~ ~ tub]]
  =+  vex=(fel tub)
  ?~  q.vex
    ?:  =(0 -.lig)
      [p.vex [~ ~ tub]]
    vex
  =+  ^=  wag  %=  $
                 -.lig  ?:(=(0 -.lig) 0 (dec -.lig))
                 +.lig  ?:(=(0 +.lig) 0 (dec +.lig))
                 tub  q.u.q.vex
               ==
  ?~  q.wag
    wag
  [p.wag [~ [p.u.q.vex p.u.q.wag] q.u.q.wag]]

Examples

> ((stun [5 10] prn) [1 1] "aquickbrownfoxran")
[p=[p=1 q=11] q=[~ [p="aquickbrow" q=[p=[p=1 q=11] q="nfoxran"]]]]

> ((stun [5 10] prn) [1 1] "aquickbro")
[p=[p=1 q=10] q=[~ [p="aquickbro" q=[p=[p=1 q=10] q=""]]]]

> ((stun [5 10] prn) [1 1] "aqui")
[p=[p=1 q=5] q=~]

Previous4e: Parsing (Combinators)Next4g: Parsing (Outside Caller)

Last updated 1 day ago