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
  • +bake
  • +fand
  • +find
  • +flop
  • +gulf
  • +homo
  • +into
  • +join
  • +lent
  • +levy
  • +lien
  • +limo
  • +murn
  • +oust
  • +reap
  • +rear
  • +reel
  • +roll
  • +scag
  • +skid
  • +skim
  • +skip
  • +slag
  • +snag
  • +snap
  • +snip
  • +snoc
  • +sort
  • +spin
  • +spun
  • +swag
  • +turn
  • +weld
  • +welp
  • +zing
Edit on GitHub
  1. Hoon
  2. Standard Library

2b: List Logic

+bake

Note: This function isn't specifically a list function but is included in section 2b of the standard library so is documented here for completeness.

Convert wet gate f to a dry gate by specifying argument mold a.

+bake is a wet gate that takes a wet gate and produces a dry gate.

Accepts

f is a gate.

a is a mold.

Produces

A dry gate whose sample type is a.

Source

++  bake
  |*  [f=gate a=mold]
  |=  arg=a
  (f arg)

Examples

> =wet-gate |*(a=* [a a])
> (wet-gate 42)
[42 42]
> (wet-gate ['foo' 'bar'])
[['foo' 'bar'] 'foo' 'bar']
> =dry-gate (bake wet-gate @ud)
> (dry-gate 42)
[42 42]
> (dry-gate ['foo' 'bar'])
-need.@ud
-have.[@t @t]
nest-fail

+fand

All indices in list

Produces the indices of all occurrences of nedl in hstk as a list of atoms.

Accepts

nedl is a list.

hstk is a list.

Produces

A list.

Source

++  fand
  ~/  %fand
  |=  [nedl=(list) hstk=(list)]
  =|  i=@ud
  =|  fnd=(list @ud)
  |-  ^+  fnd
  =+  [n=nedl h=hstk]
  |-
  ?:  |(?=(~ n) ?=(~ h))
    (flop fnd)
  ?:  =(i.n i.h)
    ?~  t.n
      ^$(i +(i), hstk +.hstk, fnd [i fnd])
    $(n t.n, h t.h)
  ^$(i +(i), hstk +.hstk)

Examples

> (fand ~[3] ~[1 2 3])
~[2]
> (fand ~[4] ~[1 2 3])
~
> (fand ~['a'] "cbabab")
~[2 4]
> (fand "ba" "cbabab")
~[1 3]

+find

First index in list

Produces the index of the first occurrence of nedl in hstk as the unit of an atom.

Accepts

nedl is a list.

hstk is a list.

Produces

The unit of an atom.

Source

++  find
  ~/  %find
  |=  [nedl=(list) hstk=(list)]
  =|  i=@ud
  |-   ^-  (unit @ud)
  =+  [n=nedl h=hstk]
  |-
  ?:  |(?=(~ n) ?=(~ h))
     ~
  ?:  =(i.n i.h)
    ?~  t.n
      `i
    $(n t.n, h t.h)
  ^$(i +(i), hstk +.hstk)

Examples

> (find [3]~ ~[1 2 3])
[~ u=2]
> (find [4]~ ~[1 2 3])
~
> (find ['c']~ "cbabab")
[~ u=0]
> (find "ab" "cbabab")
[~ u=2]
> (find "bab" "cbabab")
[~ u=1]

+flop

Reverse

Produces the list a in reverse order.

Accepts

a is a list.

Produces

A list.

Source

++  flop
  ~/  %flop
  |*  a=(list)
  =>  .(a (homo a))
  ^+  a
  =+  b=`_a`~
  |-
  ?~  a  b
  $(a t.a, b [i.a b])

Examples

> =a [1 2 3 ~]
> (flop a)
~[3 2 1]
> (flop (flop a))
~[1 2 3]

+gulf

List from range

Produces a list composed of each consecutive integer starting from a and ending with b. a and b are themselves included.

Accepts

a is an atom.

b is an atom.

Produces

a list.

Source

++  gulf
  |=  [a=@ b=@]
  ?>  (lte a b)
  |-  ^-  (list @)
  ?:(=(a +(b)) ~ [a $(a +(a))])

Examples

> (gulf 1 6)
~[1 2 3 4 5 6]
> `(list @t)`(gulf 99 106)
<|c d e f g h i j|>

+homo

Homogenize

Produces a list whose type is a fork of all the contained types in the list a. Used when you want to make all the types of the elements of a list the same.

Accepts

a is a list.

Produces

a list.

Source

++  homo
  |*  a=(list)
  ^+  =<  $
    |@  ++  $  ?:(*? ~ [i=(snag 0 a) t=$])
    --
  a

Examples

> lyst
[i=1 t=[i=97 t=[i=2 t=[i=98 t=[i=[~ u=10] t=~]]]]]
> (homo lyst)
~[1 97 2 98 [~ u=10]]
> =a (limo [1 2 3 ~])
> a
[i=1 t=[i=2 t=[i=3 t=~]]]
> (homo a)
~[1 2 3]

+into

Insert item at index

Accepts a list a, an atom b, and a noun c, producing the list of a with the item c inserted at index b.

Accepts

a is a list.

b is a atom.

c is a noun.

Produces

the list of a with the item c inserted at index b.

Source

++  into
  ~/  %into
  |*  [a=(list) b=@ c=*]
  ^+  a
  (weld (scag b a) [c (slag b a)])

Examples

> (into (limo ~[2 3 4]) 1 11)
~[2 11 3 4]

+join

Constructs a new list, placing sep between every element of lit.

Accepts

sep is a noun.

lit is a list.

Produces

a list.

Source

++  join
  |*  [sep=* lit=(list)]
  =.  sep  `_?>(?=(^ lit) i.lit)`sep
  ?~  lit  ~
  =|  out=(list _?>(?=(^ lit) i.lit))
  |-  ^+  out
  ?~  t.lit
    (flop [i.lit out])
  $(out [sep i.lit out], lit t.lit)

Examples

> (join ' ' "hoon")
"h o o n"
> (join 0 `(list @)`~[1 2 3])
~[1 0 2 0 3]

+lent

List length

Produces the length of any list a as an atom.

Accepts

a is a list.

Produces

an atom.

Source

++  lent
  ~/  %lent
  |=  a=(list)
  ^-  @
  =+  b=0
  |-
  ?~  a  b
  $(a t.a, b +(b))

Examples

> (lent [1 2 3 4 ~]))
4
> (lent [1 'a' 2 'b' (some 10) ~])
5

+levy

Logical "and" on list

Computes the Boolean logical "and" on the results of gate b applied to each individual element in list a.

Accepts

a is a list.

b is a gate.

Produces

A boolean.

Source

++  levy
  ~/  %levy
  |*  [a=(list) b=$-(* ?)]
  |-  ^-  ?
  ?~  a  &
  ?.  (b i.a)  |
  $(a t.a)

Examples

> =a |=(a=@ (lte a 1))
> (levy `(list @)`[0 1 2 1 ~] a)
%.n
> =a |=(a=@ (lte a 3))
> (levy `(list @)`[0 1 2 1 ~] a)
%.y

+lien

Logical "or" on list

Computes the Boolean logical "or" on the results of applying gate b to every element of ++list a.

Accepts

a is a list.

b is a gate.

Source

++  lien
  ~/  %lien
  |*  [a=(list) b=$-(* ?)]
  |-  ^-  ?
  ?~  a  |
  ?:  (b i.a)  &
  $(a t.a)

Examples

> =a |=(a=@ (gte a 1))
> (lien `(list @)`[0 1 2 1 ~] a)
%.y
> =a |=(a=@ (gte a 3))
> (lien `(list @)`[0 1 2 1 ~]) a)
%.n

+limo

List Constructor

Turns a null-terminated tuple into a list.

Accepts

a is a null-terminated tuple.

Produces

A ++list.

Source

++  limo
  |*  a=*
  ^+  =<  $
    |@  ++  $  ?~(a ~ ?:(*? [i=-.a t=$] $(a +.a)))
    --
  a

Examples

> (limo [1 2 3 ~])
[i=1 t=[i=2 t=[i=3 t=~]]]

+murn

Maybe transform

Passes each member of list a to gate b, which must produce a unit. Produces a new list with all the results that do not produce ~.

Accepts

a is a list.

b is a gate that produces a unit.

Produces

A list.

Source

++  murn
  ~/  %murn
  |*  [a=(list) b=$-(* (unit))]
  =>  .(a (homo a))
  |-  ^-  (list _?>(?=(^ a) (need (b i.a))))
  ?~  a  ~
  =/  c  (b i.a)
  ?~  c  $(a t.a)
  [+.c $(a t.a)]

Examples

> =a |=(a=@ ?.((gte a 2) ~ (some (add a 10))))
> (murn `(list @)`[0 1 2 3 ~] a)
[i=12 t=[i=13 t=~]]

+oust

Remove

Removes elements from list c beginning at inclusive index a, removing b number of elements.

Accepts

c is a list.

Produces

A ++list.

Source

++  oust
  ~/  %oust
  |*  [[a=@ b=@] c=(list)]
  (weld (scag +<-< c) (slag (add +<-< +<->) c))

Examples

> (oust [4 5] "good day, urbit!")
"good urbit!"
> (oust [2 2] `(list @)`[1 2 3 4 ~])
~[1 2]

+reap

Replicate

Replicate: produces a list containing a copies of b.

Accepts

a is an atom.

b is a noun.

Produces

A list.

Source

++  reap
  ~/  %reap
  |*  [a=@ b=*]
  |-  ^-  (list _b)
  ?~  a  ~
  [b $(a (dec a))]

Examples

> (reap 20 %a)
~[%a %a %a %a %a %a %a %a %a %a %a %a %a %a %a %a %a %a %a %a]
> (reap 5 ~s1)
~[~s1 ~s1 ~s1 ~s1 ~s1]
> `@dr`(roll (reap 5 ~s1) add)
~s5

+rear

Last item of list

Produces the last item in list a, crashing if a is null.

Accepts

a is a list.

Produces

The type of the last element in a.

Source

++  rear
  ~/  %rear
  |*  a=(list)
  ^-  _?>(?=(^ a) i.a)
  ?>  ?=(^ a)
  ?:  =(~ t.a)  i.a
  $(a t.a)

Examples

> (rear ~[1 2 3])
3
> (rear ~)
dojo: hoon expression failed

+reel

Right fold

Right fold: moves right to left across a list a, recursively slamming a binary gate b with an element from a and an accumulator, producing the final value of the accumulator.

(To "slam" means to call a gate and give it a sample/samples. In this instance, a is the list of samples that are given to the gate b.)

The initial value of the accumulator is the bunt of b's second argument (+<+). This can occasionally produce undesired behavior (see examples). If you need more control over the initial value, try making use of $_ and |:, or perhaps +spin or +spun.

Accepts

a is a list.

b is a binary gate.

Produces

The accumulator, which is a noun.

Source

++  reel
  ~/  %reel
  |*  [a=(list) b=_=>(~ |=([* *] +<+))]
  |-  ^+  ,.+<+.b
  ?~  a
    +<+.b
  (b i.a $(a t.a))

Examples

> (reel `(list @)`[1 2 3 4 5 ~] add)
15

> (reel `(list @)`[6 3 1 ~] sub)
4

> (reel `(list @)`[3 6 1 ~] sub)
! subtract-underflow
! exit

+mul's default sample is 1, so calling +reel with +mul yields the expected behavior:

> *mul
1

> (reel `(list @)`~[1 2 3 4] mul)
24

However, if you build a gate that uses +mul like so, the sample defaults to 0 since that is the bunt of @:

> (reel `(list @)`~[1 2 3 4] |=([a=@ b=@] (mul a b)))
0

We can fix this with |::

> (reel `(list @)`~[1 2 3 4] |:([a=1 b=1] (mul a b)))
24

If you check the definition of +mul, you'll see that it also utilizes this pattern.

We can check explicitly what sequence of operations +reel performs like this:

> =f |:  [l='e_l' r='e_r']
      ^-  @t
      :((cury cat 3) '(' l '*' r ')')
> (reel "abcde" f)
'(a*(b*(c*(d*(e*e_r)))))'

+roll

Left fold

Left fold: moves left to right across a list a, recursively slamming a binary gate b with an element from the list and an accumulator, producing the final value of the accumulator.

(To "slam" means to call a gate and give it a sample/samples. In this instance, a is the list of samples that are given to the gate b.)

The initial value of the accumulator is b's second argument (+<+). This can occasionally produce undesired behavior (see examples). If you need more control over the initial value, try making use of $_ and |:, or perhaps +spin or +spun.

Accepts

a is a list.

b is a binary gate.

Produces

The accumulator, which is a noun.

Source

++  roll
  ~/  %roll
  |*  [a=(list) b=_=>(~ |=([* *] +<+))]
  |-  ^+  ,.+<+.b
  ?~  a
    +<+.b
  $(a t.a, b b(+<+ (b i.a +<+.b)))

Examples

> (roll `(list @)`[1 2 3 4 5 ~] add)
q=15

> (roll `(list @)`[6 3 1 ~] sub)
! subtract-underflow
! exit

> (roll `(list @)`[1 3 6 ~] sub)
q=4

+mul's default sample is 1, so calling +roll with +mul yields the expected behavior:

> *mul
1

> (roll `(list @)`~[1 2 3 4] mul)
24

However, if you build a gate that uses +mul like so, the sample defaults to 0 since that is the bunt of @:

> (roll `(list @)`~[1 2 3 4] |=([a=@ b=@] (mul a b)))
0

We can fix this with |::

> (roll `(list @)`~[1 2 3 4] |:([a=1 b=1] (mul a b)))
24

If you check the definition of +mul, you'll see that it also utilizes this pattern.

We can check explicitly what sequence of operations +roll performs like this:

> =f |:  [l='e_l' r='e_r']
      ^-  @t
      :((cury cat 3) '(' l '*' r ')')
> (roll "abcde" f)
'(e*(d*(c*(b*(a*e_r)))))

This is in contrast to what one might expect:

> =foldl
    |*  [l=(list) f=$-([* *] *)]
    ^-  f
    ?~  l  +<-.f
    %=  $
      +<-.f  (f +<-.f i.l)
      l      t.l
      ==
> (foldl "abcde" f)
'(((((e_l*a)*b)*c)*d)*e)'

+scag

Prefix

Accepts an atom a and list b, producing the first a elements of the front of the list.

Accepts

a is an atom.

b is a list.

Produces

A list of the same type as b.

Source

++  scag
  ~/  %scag
  |*  [a=@ b=(list)]
  |-  ^+  b
  ?:  |(?=(~ b) =(0 a))  ~
  [i.b $(b t.b, a (dec a))]

Examples

> (scag 2 `(list @)`[1 2 3 4 ~])
[i=1 t=~[2]]
> (scag 10 `(list @)`[1 2 3 4 ~])
[i=1 t=~[2 3 4]]

+skid

Separate

Separates a list a into two lists - Those elements of a who produce true when slammed to gate b and those who produce %.n.

(To "slam" means to call a gate and give it a sample/samples. In this instance, a is the list of samples that are given to the gate b.)

Accepts

a is a list.

b is a gate that accepts one argument and produces a flag.

Produces

A cell of two lists.

Source

++  skid
  ~/  %skid
  |*  [a=(list) b=$-(* ?)]
  |-  ^+  [p=a q=a]
  ?~  a  [~ ~]
  =+  c=$(a t.a)
  ?:((b i.a) [[i.a p.c] q.c] [p.c [i.a q.c]])

Examples

> =a |=(a=@ (gth a 1))
> (skid `(list @)`[0 1 2 3 ~] a)
[p=[i=2 t=~[3]] q=[i=0 t=~[1]]]

+skim

Filter

Cycles through the members of a list a, passing them to a gate b and producing a list of all of the members that produce %.y. Inverse of skip.

Accepts

a is a list.

b is a gate that accepts one argument and produces a boolean.

Produces

A list.

Source

++  skim
  ~/  %skim
  |*  [a=(list) b=$-(* ?)]
  |-
  ^+  a
  ?~  a  ~
  ?:((b i.a) [i.a $(a t.a)] $(a t.a))

Examples

> =a |=(a=@ (gth a 1))
> (skim `(list @)`[0 1 2 3 ~] a)
[i=2 t=~[3]]

+skip

Except

Cycles through the members of list a, passing them to a gate b. Produces a list of all of the members that produce %.n. Inverse of skim.

Accepts

a is a list.

b is a gate that accepts one argument and produces a flag.

Produces

A list of the same type as a.

Source

++  skip
  ~/  %skip
  |*  [a=(list) b=$-(* ?)]
  |-
  ^+  a
  ?~  a  ~
  ?:((b i.a) $(a t.a) [i.a $(a t.a)])

Examples

> =a |=(a=@ (gth a 1))
> (skip `(l)`[0 1 2 3 ~]) a)
[i=0 t=[i=1 t=~]]

+slag

Suffix

Accepts an atom a and list b, producing the remaining elements from b starting at a.

Accepts

a is an atom.

b is a list.

Produces

A list of the same type as b.

Source

++  slag
  ~/  %slag
  |*  [a=@ b=(list)]
  |-  ^+  b
  ?:  =(0 a)  b
  ?~  b  ~
  $(b t.b, a (dec a))

Examples

> (slag 2 (limo [1 2 3 4 ~]))
[i=3 t=[i=4 t=~]]
> (slag 1 (limo [1 2 3 4 ~]))
[i=2 t=[i=3 t=[i=4 t=~]]]

+snag

Index

Accepts an atom a and a ++list b, producing the element at the index of aand failing if the list is null. Lists are 0-indexed.

Accepts

a is an atom.

b is a list.

Produces

Produces an element of b, or crashes if no element exists at that index.

Source

++  snag
  ~/  %snag
  |*  [a=@ b=(list)]
  |-  ^+  ?>(?=(^ b) i.b)
  ?~  b
    ~_  leaf+"snag-fail"
    !!
  ?:  =(0 a)  i.b
  $(b t.b, a (dec a))

Examples

> (snag 2 "asdf")
'd'
> (snag 0 `(list @ud)`~[1 2 3 4])
1

+snap

Replace item at index

Accepts a list a, an atom b, and a noun c, producing the list of a with the item at index b replaced with c.

Accepts

a is a list.

b is a atom.

c is a noun.

Produces

the list of a with the item at index b replaced with c.

Source

++  snap
  ~/  %snap
  |*  [a=(list) b=@ c=*]
  ^+  a
  (weld (scag b a) [c (slag +(b) a)])

Examples

> (snap (limo ~[2 3 4]) 1 11)
~[2 11 4]

+snip

Drop tail off list

Removes the last element from list a.

Accepts

a is a list.

Produces

A list.

Source

++  snip
  ~/  %snip
  |*  a=(list)
  ^+  a
  ?~  a  ~
  ?:  =(~ t.a)  ~
  [i.a $(a t.a)]

Examples

> `tape`(snip "foobar")
"fooba"
> (snip ~)
~

+snoc

Append

Accepts a ++list a and a noun b, producing the list of b appended to a.

Accepts

a is a list.

b is a noun.

Produces

Produces a list of b appended to a.

Source

++  snoc
  |*  [a=(list) b=*]
  (weld a ^+(a [b]~))

Examples

> `tape`(zing (snoc `(list tape)`~["a" "bc" "def"] "g"))
"abcdefg"
> (snoc `(list @ud)`~[1 2 3] 4)
~[1 2 3 4]

+sort

Quicksort

Quicksort: accepts a ++list a and a gate b which accepts two nouns and produces a flag. ++sort then produces a list of the elements of a, sorted according to b.

Accepts

a is a list.

b is a gate that accepts two nouns and produces a boolean.

Produces

A list

Source

++  sort  !.
  ~/  %sort
  |*  [a=(list) b=$-([* *] ?)]
  =>  .(a ^.(homo a))
  |-  ^+  a
  ?~  a  ~
  =+  s=(skid t.a |:(c=i.a (b c i.a)))
  %+  weld
    $(a p.s)
  ^+  t.a
  [i.a $(a q.s)]

Examples

> (sort `(list @)`[0 1 2 3 ~] gth)
~[3 2 1 0]

+spin

Gate to list, with state

Accepts a ++list a, some state b, and a gate c. c is called with a tuple -- the head is an element of a and the tail is the state b, and should produce a tuple of the transformed element and the (potentially modified) state b. Produces a pair where the first element is a list of the transformed elements of a, and the second element is the final value of b.

Accepts

a is a ++list.

b is a noun.

c is a gate.

Produces

A pair of a list and a noun.

Source

++  spin
  ~/  %spin
  |*  [a=(list) b=* c=_|=(^ [** +<+])]
  =>  .(c `$-([_?>(?=(^ a) i.a) _b] [_-:(c) _b])`c)
  =/  acc=(list _-:(c))  ~
  |-  ^-  (pair _acc _b)
  ?~  a
    [(flop acc) b]
  =^  res  b  (c i.a b)
  $(acc [res acc], a t.a)

Examples

> %^  spin  (limo ~[4 5 6])     ::  Trivial example -- does nothing with the state
    0
  |=([n=@ a=@] [n a])
[p=~[4 5 6] q=0]
> %^  spin  (limo ~[4 5 6])     ::  Form a pair with `p` as the index and `q` as the list element
    0
  |=([n=@ a=@] [`(pair)`[a n] +(a)])
[p=~[[p=0 q=4] [p=1 q=5] [p=2 q=6]] q=3]
> %^  spin  (reap 10 0)     :: Create 10 random numbers less than `10`
    ~(. og eny)
  |=([n=@ rng=_og] (rads:rng 10))
[p=~[7 8 6 0 1 5 4 7 9 3] q=<4.rvi {a/@uvJ <51.qyl 129.pdd 41.mac 1.ane $141>}>]

Discussion

(~(rads og eny) 2) creates a random number less than 2, seeding the RNG with entropy (eny). The head of the product is the random number, the tail is the continuation of the RNG.


+spun

Gate to list, with state

Accepts a list a and a gate b. c is internal state, initially derived by bunting the tail of the sample of gate b, instead of being passed in explicitly as in ++spin. Produces a list with the gate applied to each element of the original list. b is called with a tuple -- the head is an element of a and the tail is the state c, and should produce a tuple of the transformed element and the (potentially modified) state c.

Accepts

a is a ++list.

b is a gate.

Produces

A list.

Source

++  spun
  ~/  %spun
  |*  [a=(list) b=_|=(^ [** +<+])]
  p:(spin a +<+.b b)

Examples

> %+  spun  (limo ~[4 5 6])            ::  `p` as the index and `q` as the list element
  |=([n=@ a=@] [`(pair)`[a n] +(a)])
~[[p=0 q=4] [p=1 q=5] [p=2 q=6]]
> =l (limo ~[7 8 9])
> %+  spun  (limo ~[4 5 6])            ::  joins two lists into a list of pairs
  |=([n=@ a=@] [`(pair)`[(snag a l) n] +(a)])
~[[p=7 q=4] [p=8 q=5] [p=9 q=6]]

+swag

Infix

Similar to substr in Javascript: extracts a string infix, beginning at inclusive index a, producing b number of characters.

Accepts

a is an atom.

b is an atom.

c is a list.

Produces

A list of the same type as c.

Source

++  swag
  |*  [[a=@ b=@] c=(list)]
  (scag +<-> (slag +<-< c))

Examples

> (swag [2 5] "roly poly")
"ly po"
> (swag [2 2] (limo [1 2 3 4 ~]))
[i=3 t=[i=4 t=~]]

+turn

Gate to list

Accepts a ++list a and a gate b. Produces a list with the gate applied to each element of the original list.

Accepts

a is a list.

b is a gate.

Produces

A list.

Source

++  turn
  ~/  %turn
  |*  [a=(list) b=gate]
  =>  .(a (homo a))
  ^-  (list _?>(?=(^ a) (b i.a)))
  |-
  ?~  a  ~
  [i=(b i.a) t=$(a t.a)]

Examples

> (turn (limo [104 111 111 110 ~]) @t)
<|h o o n|>
> =a |=(a=@ (add a 4))
> (turn (limo [1 2 3 4 ~]) a)
~[5 6 7 8]

Discussion

turn is Hoon's version of 'map' in Haskell.


+weld

Concatenate

Concatenate two ++lists a and b.

Accepts

a and b are lists.

Source

++  weld
  ~/  %weld
  |*  [a=(list) b=(list)]
  =>  .(a ^.(homo a), b ^.(homo b))
  |-  ^+  b
  ?~  a  b
  [i.a $(a t.a)]

Examples

> (weld "urb" "it")
"urbit"
> (weld (limo [1 2 ~]) (limo [3 4 ~]))
~[1 2 3 4]

+welp

Perfect weld

Concatenate two ++lists a and b without losing their type information to homogenization.

Accepts

a is a list.

b is a list.

Produces

A list.

Source

++  welp
  ~/  %welp
  =|  [* *]
  |@
  ++  $
    ?~  +<-
      +<-(. +<+)
    +<-(+ $(+<- +<->))
  --

Examples

> (welp "foo" "bar")
"foobar"
> (welp ~[60 61 62] ~[%a %b %c])
[60 61 62 %a %b %c ~]

> ? (welp ~[60 61 62] ~[%a %b %c])
  [@ud @ud @ud %a %b %c %~]
[60 61 62 %a %b %c ~]
> (welp [sa+1 so+2 ~] si=3)
[[%sa 1] [%so 2] si=3]

+zing

Turns a ++list of lists into a single list by promoting the elements of each sublist into the higher.

Accepts

A list of lists.

Produces

A list.

Source

++  zing
  ~/  %zing
  =|  *
  |@
  ++  $
    ?~  +<
      +<
    (welp +<- $(+< +<+))
  --

Examples

> (zing (limo [(limo ['a' 'b' 'c' ~]) (limo ['e' 'f' 'g' ~]) (limo ['h' 'i' 'j' ~]) ~]))
~['a' 'b' 'c' 'e' 'f' 'g' 'h' 'i' 'j']
> (zing (limo [(limo [1 'a' 2 'b' ~]) (limo [3 'c' 4 'd' ~]) ~]))
~[1 97 2 98 3 99 4 100]

Previous2a: Unit LogicNext2c: Bit Arithmetic

Last updated 1 day ago