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
  • $abel
  • $alas
  • $atom
  • $aura
  • $base
  • $woof
  • $chum
  • $coil
  • $garb
  • $poly
  • $foot
  • $link
  • $crib
  • $help
  • $limb
  • $null
  • $onyx
  • $opal
  • $pica
  • $palo
  • $plat
  • $pock
  • $port
  • $spec
  • $tent
  • $tiki
  • $skin
  • $tome
  • $tope
  • +hoot
  • +$beer:hoot
  • +$mane:hoot
  • +$manx:hoot
  • +$marl:hoot
  • +$mart:hoot
  • +$marx:hoot
  • +$mare:hoot
  • +$maru:hoot
  • +$tuna:hoot
  • $hoon
  • $tyre
  • $tyke
  • $nock
  • $note
  • $type
  • $tony
  • $tine
  • $tool
  • $tune
  • $typo
  • $vase
  • $vise
  • $vial
  • $vair
  • $vein
  • $sect
  • $whit
  • $what
  • $wing
  • $block
  • $result
  • $thunk
  • $doss
  • $moan
  • $hump
Edit on GitHub
  1. Hoon
  2. Standard Library

4o: Molds

$abel

Original sin: type

Old type, same as the new type.

Source

+$  abel  typo

Examples

> *abel
#t/*

$alas

Alias list

This is the type used in %brcb (|_ door) hoon type for +* alias arms.

Source

+$  alas  (list (pair term hoon))

$atom

Just an atom

This is the same as @.

Source

+$  atom  @

Examples

> *atom
0

> `atom`'foo'
7.303.014

$aura

'type' of atom

By convention, a short name for a category of atom. aura is circularly defined, with @ta being the aura of the ASCII subset commonly used in urbit.

Source

+$  aura  @ta

Examples

See also: +$base, aura reference

> `aura`'ux'
~.ux

$base

Base type

A base type that nouns are built from. A base is either a noun, atom with aura, cell, boolean, null, or an empty set.

Source

+$  base            ::  base mold
  $@  $?  %noun     ::  any noun
          %cell     ::  any cell
          %flag     ::  loobean
          %null     ::  ~ == 0
          %void     ::  empty set
      ==            ::
  [%atom p=aura]    ::  atom

Examples

> *base
%void

> (ream '=|(^ !!)')
[%tsbr p=[%base p=%cell] q=[%zpzp ~]]

$woof

Simple embed

An atom or some hoon.

Source

+$  woof  $@(@ [~ p=hoon])

Examples

> *woof
0

> `woof`[~ %base p=%cell]
[~ p=[%base p=%cell]]

> `woof`'foo'
7.303.014

$chum

Jet hint information

Jet hint information that must be present in the body of a ~/ or ~% rune. A chum can optionally contain a kelvin version, jet vendor, and version number.

Source

+$  chum  $?  lef=term                                  ::  jet name
              [std=term kel=@]                          ::  kelvin version
              [ven=term pro=term kel=@]                 ::  vendor and product
              [ven=term pro=term ver=@ kel=@]           ::  all of the above
          ==                                            ::

Examples

> `chum`'hi'
lef=%hi

> (ream '~/(%lob.314 !!)')
[%sgfs p=[std=%lob kel=314] q=[%zpzp ~]]

$coil

Tuple of core information

Variance p, subject type q, and r: optional compiled nock, and arms. Used as an intermediate step during compilation and converted to a core.

Source

+$  coil  $:  p=garb                               ::  name, wet=dry, vary
              q=type                               ::  context
              r=(pair seminoun (map term tome))    ::  chapters
          ==                                       ::

$garb

Core metadata

A triple of an optional name, polarity (wet/dry), and variance (%iron, etc).

Source

+$  garb  (trel (unit term) poly vair)

$poly

Polarity

Whether a core is wet or dry.

Source

+$  poly  ?(%wet %dry)

$foot

Cases of arms by variance model.

Source

+$  foot  $%  [%dry p=hoon]    ::  dry arm, geometric
              [%wet p=hoon]    ::  wet arm, generic
          ==

$link

Lexical segment

Used for documentation.

Source

+$  link                               ::  lexical segment
          $%  [%chat p=term]           ::  |chapter
              [%cone p=aura q=atom]    ::  %constant
              [%frag p=term]           ::  .leg
              [%funk p=term]           ::  +arm
          ==

$crib

Summary and details

Summary and details for documentation.

Source

+$  crib  [summary=cord details=(list sect)]

$help

Documentation

Source

+$  help  [links=(list link) =crib]

$limb

Wing element

Reference into subject by tree address or name.

Source

+$  limb  $@  term                                      ::  wing element
          $%  [%& p=axis]                               ::  by geometry
              [%| p=@ud q=(unit term)]                  ::  by name
          ==                                            ::

Examples

> (ream '^^$')
[%wing p=~[[%.n p=2 q=[~ %$]]]]

$null

Null, nil, etc

Just ~.

Source

+$  null  ~

Examples

> *null
~

$onyx

Arm activation

Source

+$  onyx  (list (pair type foot))

$opal

Wing match

Arm or leg of a wing.

Source

+$  opal                                            ::  limb match
          $%  [%& p=type]                           ::  leg
              [%| p=axis q=(set [p=type q=foot])]   ::  arm
          ==                                        ::

$pica

Prose or code

A (pair ? cord). If %.y it's prose and if %.n it's code. Used in documentation.

Source

+$  pica  (pair ? cord)

$palo

Wing trace, match

A $vein and a $opal.

Source

+$  palo  (pair vein opal)

$plat

%hoon, %type, %nock or %tank

Source

+$  plat
          $?  %hoon
              %type
              %nock
              %tank
          ==

$pock

Changes

Source

+$  pock  (pair axis nock)

$port

Successful wing match

Source

+$  port  (each palo (pair type nock))

$spec

Structure definition AST.

Source

+$  spec                                                ::  structure definition
          $~  [%base %null]                             ::
          $%  [%base p=base]                            ::  base type
              [%dbug p=spot q=spec]                     ::  set debug
              [%leaf p=term q=@]                        ::  constant atom
              [%like p=wing q=(list wing)]              ::  reference
              [%loop p=term]                            ::  hygienic reference
              [%made p=(pair term (list term)) q=spec]  ::  annotate synthetic
              [%make p=hoon q=(list spec)]              ::  composed spec
              [%name p=term q=spec]                     ::  annotate simple
              [%over p=wing q=spec]                     ::  relative to subject
          ::                                            ::
              [%bcgr p=spec q=spec]                     ::  $>, filter: require
              [%bcbc p=spec q=(map term spec)]          ::  $$, recursion
              [%bcbr p=spec q=hoon]                     ::  $|, verify
              [%bccb p=hoon]                            ::  $_, example
              [%bccl p=[i=spec t=(list spec)]]          ::  $:, tuple
              [%bccn p=[i=spec t=(list spec)]]          ::  $%, head pick
              [%bcdt p=spec q=(map term spec)]          ::  $., read-write core
              [%bcgl p=spec q=spec]                     ::  $<, filter: exclude
              [%bchp p=spec q=spec]                     ::  $-, function core
              [%bckt p=spec q=spec]                     ::  $^, cons pick
              [%bcls p=stud q=spec]                     ::  $+, standard
              [%bcfs p=spec q=(map term spec)]          ::  $/, write-only core
              [%bcmc p=hoon]                            ::  $;, manual
              [%bcpm p=spec q=hoon]                     ::  $&, repair
              [%bcsg p=hoon q=spec]                     ::  $~, default
              [%bctc p=spec q=(map term spec)]          ::  $`, read-only core
              [%bcts p=skin q=spec]                     ::  $=, name
              [%bcpt p=spec q=spec]                     ::  $@, atom pick
              [%bcwt p=[i=spec t=(list spec)]]          ::  $?, full pick
              [%bczp p=spec q=(map term spec)]          ::  $!, opaque core
          ==                                            ::

Examples

> *spec
[%base p=%null]

> `spec`[%bccl ~[leaf+ud+1 leaf+ud+2]]
[%bccl p=[i=[%leaf p=%ud q=1] t=~[[%leaf p=%ud q=2]]]]

$tent

Model builder

Source

+$  tent
          $%  [%| p=wing q=tent r=(list spec)]    ::  ~(p q r...)
              [%& p=(list wing)]                  ::  a.b:c.d
          ==                                      ::

$tiki

Test case

This is used when compiling ?- expressions and similar.

Source

+$  tiki                                                ::  test case
          $%  [%& p=(unit term) q=wing]                 ::  simple wing
              [%| p=(unit term) q=hoon]                 ::  named wing
          ==                                            ::

$skin

Texture

This type is used for faces and similar by the compiler.

Source

+$  skin                             ::  texture
          $@  =term                  ::  name/~[term %none]
          $%  [%base =base]          ::  base match
              [%cell =skin =skin]    ::  pair
              [%dbug =spot =skin]    ::  trace
              [%leaf =aura =atom]    ::  atomic constant
              [%help =help =skin]    ::  describe
              [%name =term =skin]    ::  apply label
              [%over =wing =skin]    ::  relative to
              [%spec =spec =skin]    ::  cast to
              [%wash depth=@ud]      ::  strip faces
          ==                         ::

$tome

Core chapter

This type is used by the compiler for the contents of arms in cores.

Source

+$  tome  (pair what (map term hoon))

$tope

Topographic type

Describes the structure of a noun.

Source

+$  tope              ::  topographic type
  $@  $?  %&          ::  cell or atom
          %|          ::  atom
      ==              ::
  (pair tope tope)    ::  cell

Examples

> *tope
%.n

> `tope`[%| %&]
[p=%.n q=%.y]

+hoot

Hoon tools

Container core for internally-used XML structure types. XML structure types you'd typically use directly are defined in Standard Library section 5e.

Source

++  hoot
  |%

+$beer:hoot

Simple embed

Either a tape element or interpolated hoon expression in an XML attribute.

Source

+$  beer  $@(char [~ p=hoon])

+$mane:hoot

XML name+space

XML tag name and optional namespace.

Source

+$  mane  $@(@tas [@tas @tas])

Examples

> (en-xml:html ;foo;)
"<foo></foo>"

> (en-xml:html ;foo_bar;)
"<foo:bar></foo:bar>"

> `manx:hoot`;foo_bar;
[g=[n=[%foo %bar] a=~] c=~]

> `mane:hoot`n.g:`manx`;foo_bar;
[%foo %bar]

> `mane:hoot`n.g:`manx:hoot`;foo;
%foo

+$manx:hoot

Dynamic XML node

An XML element which may contain text, attributes, and other elements.

g is a $marx:hoot (a tag) and c is a $marl:hoot (its contents).

Source

+$  manx  $~([[%$ ~] ~] [g=marx c=marl])

Examples

> *manx:hoot
[g=[n=%$ a=~] c=~

> `manx:hoot`;foo;
[g=[n=%foo a=~] c=~]

> (en-xml:html `manx:hoot`;foo;)
"<foo></foo>"

> =a ^-  manx:hoot
     ;foo
       ;bar: abc
       ;baz
         ;xxx: hello
       ==
     ==

> a
[ g=[n=%foo a=~]
    c
  ~[
    [ g=[n=%bar a=~]
      c=~[[g=[n=%$ a=~[[n=%$ v="abc"]]] c=~]]
    ]
    [ g=[n=%baz a=~]
        c
      ~[
        [ g=[n=%xxx a=~]
          c=~[[g=[n=%$ a=~[[n=%$ v="hello"]]] c=~]]
        ]
      ]
    ]
  ]
]

> (en-xml:html a)
"<foo><bar>abc</bar><baz><xxx>hello</xxx></baz></foo>"

+$marl:hoot

Dynamic XML nodes

A list of XML nodes - maybe with interpolation and recursion. See $tuna:hoot.

Source

+$  marl  (list tuna)

Examples

> *marl
~

> ^-  marl:hoot
  ;=
    ;foo: abc
    ;bar: def
  ==
~[
  [g=[n=%foo a=~] c=~[[g=[n=%$ a=~[[n=%$ v=~['a' 'b' 'c']]]] c=~]]]
  [g=[n=%bar a=~] c=~[[g=[n=%$ a=~[[n=%$ v=~['d' 'e' 'f']]]] c=~]]]
]

> %-  en-xml:html
  ;baz
    ;=
      ;foo: abc
      ;bar: def
    ==
  ==
"<baz><foo>abc</foo><bar>def</bar></baz>"

+$mart:hoot

Dynamic XML attributes

A list of atributes for an XML tag. For each list item, n is a $mane:hoot (an attribute name with optional namespace) and v is a (list beer:hoot) (the attribute itself, maybe with interpolated hoon).

Source

+$  mart  (list [n=mane v=(list beer)])

Examples

> *mart:hoot
~

> `manx:hoot`;foo.bar;
[g=[n=%foo a=~[[n=%class v=~['b' 'a' 'r']]]] c=~]

> `mart:hoot`a.g:`manx:hoot`;foo.bar;
~[[n=%class v=~['b' 'a' 'r']]]

> (en-xml:html ;foo.bar;)
"<foo class=\"bar\"></foo>"

+$marx:hoot

Dynamic XML tag

An XML tag with optional attributes. n is a $mane:hoot (the tag name with optional namespace) and a is a $mart:hoot (any XML attributes).

Source

+$  marx  $~([%$ ~] [n=mane a=mart])

Examples

> `manx:hoot`;foo.bar;
[g=[n=%foo a=~[[n=%class v=~['b' 'a' 'r']]]] c=~]

> `marx:hoot`g:`manx:hoot`;foo.bar;
[n=%foo a=~[[n=%class v=~['b' 'a' 'r']]]]

> (en-xml:html ;foo.bar;)
"<foo class=\"bar\"></foo>"

+$mare:hoot

Node or nodes

If %.y, a $manx:hoot (single XML node). If %.n, a $marl:hoot (list of XML nodes).

Source

+$  mare  (each manx marl)

Examples

> *mare:hoot
[%.y p=[g=[n=%$ a=~] c=~]]

> `mare:hoot`[%.y ;foo.bar;]
[%.y p=[g=[n=%foo a=~[[n=%class v=~['b' 'a' 'r']]]] c=~]]

> `mare:hoot`[%.n ~[;foo.bar; ;baz;]]
[%.n p=~[[g=[n=%foo a=~[[n=%class v=~['b' 'a' 'r']]]] c=~] [g=[n=%baz a=~] c=~]]]

+$maru:hoot

Interpolation or nodes

If %.y, a $tuna:hoot. If %.n, a $marl:hoot.

Source

+$  maru  (each tuna marl)

+$tuna:hoot

Maybe interpolation

Kinds of nodes. Either an ordinary $manx:hoot, or else a plain tape, a $marl:hoot, or a function call.

Source

+$  tuna
    $~  [[%$ ~] ~]
    $^  manx
    $:  ?(%tape %manx %marl %call)
        p=hoon
    ==

$hoon

Hoon AST

See the Rune section of the Hoon reference for details of what many of these relate to.

Source

+$  hoon                                                ::
  $~  [%zpzp ~]
  $^  [p=hoon q=hoon]                                   ::
  $%                                                    ::
    [%$ p=axis]                                         ::  simple leg
  ::                                                    ::
    [%base p=base]                                      ::  base spec
    [%bust p=base]                                      ::  bunt base
    [%dbug p=spot q=hoon]                               ::  debug info in trace
    [%eror p=tape]                                      ::  assembly error
    [%hand p=type q=nock]                               ::  premade result
    [%note p=note q=hoon]                               ::  annotate
    [%fits p=hoon q=wing]                               ::  underlying ?=
    [%knit p=(list woof)]                               ::  assemble string
    [%leaf p=(pair term @)]                             ::  symbol spec
    [%limb p=term]                                      ::  take limb
    [%lost p=hoon]                                      ::  not to be taken
    [%rock p=term q=*]                                  ::  fixed constant
    [%sand p=term q=*]                                  ::  unfixed constant
    [%tell p=(list hoon)]                               ::  render as tape
    [%tune p=$@(term tune)]                             ::  minimal face
    [%wing p=wing]                                      ::  take wing
    [%yell p=(list hoon)]                               ::  render as tank
    [%xray p=manx:hoot]                                 ::  ;foo; templating
  ::                                            ::::::  cores
    [%brbc sample=(lest term) body=spec]                ::  |$
    [%brcb p=spec q=alas r=(map term tome)]             ::  |_
    [%brcl p=hoon q=hoon]                               ::  |:
    [%brcn p=(unit term) q=(map term tome)]             ::  |%
    [%brdt p=hoon]                                      ::  |.
    [%brkt p=hoon q=(map term tome)]                    ::  |^
    [%brhp p=hoon]                                      ::  |-
    [%brsg p=spec q=hoon]                               ::  |~
    [%brtr p=spec q=hoon]                               ::  |*
    [%brts p=spec q=hoon]                               ::  |=
    [%brpt p=(unit term) q=(map term tome)]             ::  |@
    [%brwt p=hoon]                                      ::  |?
  ::                                            ::::::  tuples
    [%clcb p=hoon q=hoon]                               ::  :_ [q p]
    [%clkt p=hoon q=hoon r=hoon s=hoon]                 ::  :^ [p q r s]
    [%clhp p=hoon q=hoon]                               ::  :- [p q]
    [%clls p=hoon q=hoon r=hoon]                        ::  :+ [p q r]
    [%clsg p=(list hoon)]                               ::  :~ [p ~]
    [%cltr p=(list hoon)]                               ::  :* p as a tuple
  ::                                            ::::::  invocations
    [%cncb p=wing q=(list (pair wing hoon))]            ::  %_
    [%cndt p=hoon q=hoon]                               ::  %.
    [%cnhp p=hoon q=hoon]                               ::  %-
    [%cncl p=hoon q=(list hoon)]                        ::  %:
    [%cntr p=wing q=hoon r=(list (pair wing hoon))]     ::  %*
    [%cnkt p=hoon q=hoon r=hoon s=hoon]                 ::  %^
    [%cnls p=hoon q=hoon r=hoon]                        ::  %+
    [%cnsg p=wing q=hoon r=(list hoon)]                 ::  %~
    [%cnts p=wing q=(list (pair wing hoon))]            ::  %=
  ::                                            ::::::  nock
    [%dtkt p=spec q=hoon]                               ::  .^  nock 11
    [%dtls p=hoon]                                      ::  .+  nock 4
    [%dttr p=hoon q=hoon]                               ::  .*  nock 2
    [%dtts p=hoon q=hoon]                               ::  .=  nock 5
    [%dtwt p=hoon]                                      ::  .?  nock 3
  ::                                            ::::::  type conversion
    [%ktbr p=hoon]                                      ::  ^|  contravariant
    [%ktdt p=hoon q=hoon]                               ::  ^.  self-cast
    [%ktls p=hoon q=hoon]                               ::  ^+  expression cast
    [%kthp p=spec q=hoon]                               ::  ^-  structure cast
    [%ktpm p=hoon]                                      ::  ^&  covariant
    [%ktsg p=hoon]                                      ::  ^~  constant
    [%ktts p=skin q=hoon]                               ::  ^=  label
    [%ktwt p=hoon]                                      ::  ^?  bivariant
    [%kttr p=spec]                                      ::  ^*  example
    [%ktcl p=spec]                                      ::  ^:  filter
  ::                                            ::::::  hints
    [%sgbr p=hoon q=hoon]                               ::  ~|  sell on trace
    [%sgcb p=hoon q=hoon]                               ::  ~_  tank on trace
    [%sgcn p=chum q=hoon r=tyre s=hoon]                 ::  ~%  general jet hint
    [%sgfs p=chum q=hoon]                               ::  ~/  function j-hint
    [%sggl p=$@(term [p=term q=hoon]) q=hoon]           ::  ~<  backward hint
    [%sggr p=$@(term [p=term q=hoon]) q=hoon]           ::  ~>  forward hint
    [%sgbc p=term q=hoon]                               ::  ~$  profiler hit
    [%sgls p=@ q=hoon]                                  ::  ~+  cache=memoize
    [%sgpm p=@ud q=hoon r=hoon]                         ::  ~&  printf=priority
    [%sgts p=hoon q=hoon]                               ::  ~=  don't duplicate
    [%sgwt p=@ud q=hoon r=hoon s=hoon]                  ::  ~?  tested printf
    [%sgzp p=hoon q=hoon]                               ::  ~!  type on trace
  ::                                            ::::::  miscellaneous
    [%mcts p=marl:hoot]                                 ::  ;=  list templating
    [%mccl p=hoon q=(list hoon)]                        ::  ;:  binary to nary
    [%mcfs p=hoon]                                      ::  ;/  [%$ [%$ p ~] ~]
    [%mcgl p=spec q=hoon r=hoon s=hoon]                 ::  ;<  bind
    [%mcsg p=hoon q=(list hoon)]                        ::  ;~  kleisli arrow
    [%mcmc p=spec q=hoon]                               ::  ;;  normalize
  ::                                            ::::::  compositions
    [%tsbr p=spec q=hoon]                               ::  =|  push bunt
    [%tscl p=(list (pair wing hoon)) q=hoon]            ::  =:  q w= p changes
    [%tsfs p=skin q=hoon r=hoon]                        ::  =/  typed variable
    [%tsmc p=skin q=hoon r=hoon]                        ::  =;  =/(q p r)
    [%tsdt p=wing q=hoon r=hoon]                        ::  =.  r with p as q
    [%tswt p=wing q=hoon r=hoon s=hoon]                 ::  =?  conditional =.
    [%tsgl p=hoon q=hoon]                               ::  =<  =>(q p)
    [%tshp p=hoon q=hoon]                               ::  =-  =+(q p)
    [%tsgr p=hoon q=hoon]                               ::  =>  q w=subject p
    [%tskt p=skin q=wing r=hoon s=hoon]                 ::  =^  state machine
    [%tsls p=hoon q=hoon]                               ::  =+  q w=[p subject]
    [%tssg p=(list hoon)]                               ::  =~  hoon stack
    [%tstr p=(pair term (unit spec)) q=hoon r=hoon]     ::  =*  new style
    [%tscm p=hoon q=hoon]                               ::  =,  overload p in q
  ::                                            ::::::  conditionals
    [%wtbr p=(list hoon)]                               ::  ?|  loobean or
    [%wthp p=wing q=(list (pair spec hoon))]            ::  ?-  pick case in q
    [%wtcl p=hoon q=hoon r=hoon]                        ::  ?:  if=then=else
    [%wtdt p=hoon q=hoon r=hoon]                        ::  ?.  ?:(p r q)
    [%wtkt p=wing q=hoon r=hoon]                        ::  ?^  if p is a cell
    [%wtgl p=hoon q=hoon]                               ::  ?<  ?:(p !! q)
    [%wtgr p=hoon q=hoon]                               ::  ?>  ?:(p q !!)
    [%wtls p=wing q=hoon r=(list (pair spec hoon))]     ::  ?+  ?-  w=default
    [%wtpm p=(list hoon)]                               ::  ?&  loobean and
    [%wtpt p=wing q=hoon r=hoon]                        ::  ?@  if p is atom
    [%wtsg p=wing q=hoon r=hoon]                        ::  ?~  if p is null
    [%wthx p=skin q=wing]                               ::  ?#  if q matches p
    [%wtts p=spec q=wing]                               ::  ?=  if q matches p
    [%wtzp p=hoon]                                      ::  ?!  loobean not
  ::                                            ::::::  special
    [%zpcm p=hoon q=hoon]                               ::  !,
    [%zpgr p=hoon]                                      ::  !>
    [%zpgl p=spec q=hoon]                               ::  !<
    [%zpmc p=hoon q=hoon]                               ::  !;
    [%zpts p=hoon]                                      ::  !=
    [%zppt p=(list wing) q=hoon r=hoon]                 ::  !@
    [%zpwt p=$@(p=@ [p=@ q=@]) q=hoon]                  ::  !?
    [%zpzp ~]                                           ::  !!
  ==                                                    ::

Examples

> *hoon
[%zpzp ~]

> `hoon`(ream '|=([a=@ b=@] [b a])')
[ %brts
    p
  [ %bccl
      p
    [ i=[%bcts p=term=%a q=[%base p=[%atom p=~.]]]
      t=~[[%bcts p=term=%b q=[%base p=[%atom p=~.]]]]
    ]
  ]
  q=[%cltr p=~[[%wing p=~[%b]] [%wing p=~[%a]]]]
]

$tyre

List, term hoon

Associative list of term hoon, used in jet hint processing.

Source

+$  tyre  (list [p=term q=hoon])                        ::

$tyke

List of 'maybe' hoons

List of unit hoon, or gaps left to be inferred, in path parsing. When you use a path such as /=base=/gen/code the path is in fact a tyke, where the = are inferred from your current path.

Source

+$  tyke  (list (unit hoon))

$nock

Virtual nock.

See the Nock documentation for details.

Source

+$  nock  $^  [p=nock q=nock]                      ::  autocons
          $%  [%1 p=*]                             ::  constant
              [%2 p=nock q=nock]                   ::  compose
              [%3 p=nock]                          ::  cell test
              [%4 p=nock]                          ::  increment
              [%5 p=nock q=nock]                   ::  equality test
              [%6 p=nock q=nock r=nock]            ::  if, then, else
              [%7 p=nock q=nock]                   ::  serial compose
              [%8 p=nock q=nock]                   ::  push onto subject
              [%9 p=@ q=nock]                      ::  select arm and fire
              [%10 p=[p=@ q=nock] q=nock]          ::  edit
              [%11 p=$@(@ [p=@ q=nock]) q=nock]    ::  hint
              [%12 p=nock q=nock]                  ::  grab data from sky
              [%0 p=@]                             ::  axis select
          ==                                       ::

Examples

> !=([+(.) 20 -<])
[[4 0 1] [1 20] 0 4]

> (nock !=([+(.) 20]))
[p=[%4 p=[%0 p=1]] q=[%1 p=20]]

$note

Type annotation

Used for documentation.

Source

+$  note                                             ::  type annotation
          $%  [%help p=help]                         ::  documentation
              [%know p=stud]                         ::  global standard
              [%made p=term q=(unit (list wing))]    ::  structure
          ==                                         ::

$type

Hoon type type

Source

+$  type  $~  %noun                                ::
          $@  $?  %noun                            ::  any nouns
                  %void                            ::  no noun
              ==                                   ::
          $%  [%atom p=term q=(unit @)]            ::  atom / constant
              [%cell p=type q=type]                ::  ordered pair
              [%core p=type q=coil]                ::  object
              [%face p=$@(term tune) q=type]       ::  namespace
              [%fork p=(set type)]                 ::  union
              [%hint p=(pair type note) q=type]    ::  annotation
              [%hold p=type q=hoon]                ::  lazy evaluation
          ==                                       ::

Examples

> `type`[%cell [%atom %ud ~] [%atom %ud ~]]
#t/[@ud @ud]

$tony

$tone done right

An intermediate Nock computation result. Similar to a $toon but without a rendered stack trace.

Source

+$  tony                               ::  ++tone done right
          $%  [%0 p=tine q=*]          ::  success
              [%1 p=(set)]             ::  blocks
              [%2 p=(list [@ta *])]    ::  error ~_s
          ==                           ::

$tine

Partial noun

Source

+$  tine                            ::  partial noun
          $@  ~                     ::  open
          $%  [%& p=tine q=tine]    ::  half-blocked
              [%| p=(set)]          ::  fully blocked
          ==                        ::

$tool

Type decoration

Source

+$  tool  $@(term tune)

$tune

Complex

Source

+$  tune                                  ::  complex
          $~  [~ ~]                       ::
          $:  p=(map term (unit hoon))    ::  aliases
              q=(list hoon)               ::  bridges
          ==                              ::

$typo

Old type

Same as $type

Source

+$  typo  type

$vase

Type-value pair

Typed data. A $vase is used wherever typed data is explicitly worked with.

Source

+$  vase  [p=type q=*]

Examples

> *vase
[#t/* q=0]

> !>([2 2])
[#t/[@ud @ud] q=[2 2]]

> !>('foo')
[#t/@t q=7.303.014]

$vise

Old vase

Same as a $vase.

Source

+$  vise  [p=typo q=*]

$vial

co/contra/in/bi

Covariant, contravariant, invariant, bivariant.

Source

+$  vial  ?(%read %rite %both %free)

$vair

in/contra/bi/co

Core variance.

  • %gold - invariant payload.

  • %iron - contravariant sample.

  • %lead - bivariant sample.

  • %zinc - covariant sample.

See the Hoon School lesson on type polymorphism for more details.

Source

+$  vair  ?(%gold %iron %lead %zinc)

$vein

Search trace

Noun search trace.

Source

+$  vein  (list (unit axis))

$sect

Paragraph

Used in documentation.

Source

+$  sect  (list pica)

$whit

Documentation

Source

+$  whit                                                ::
          $:  lab=(unit term)                           ::  label
              boy=(unit (pair cord (list sect)))        ::  body
              def=(map term (pair cord (list sect)))    ::  definitions
              use=(set term)                            ::  defs used
          ==                                            ::

$what

Help slogan/section

Source

+$  what  (unit (pair cord (list sect)))

$wing

Search path

Address in subject. A $wing is a path to a value in the subject. A term alone is the trivial case of a $wing.

Source

+$  wing  (list limb)

Examples

> (ream 'a.+.c')
[%wing p=~[%a [%.y p=3] %c]]

> (wing +:(ream 'a.+.c'))
~[%a [%.y p=3] %c]

$block

Abstract identity of resource awaited

Source

+$  block
  path

$result

Internal interpreter result

Source

+$  result
  $@(~ seminoun)

$thunk

Fragment constructor

Source

+$  thunk
  $-(@ud (unit noun))

$doss

Profiling

Source

+$  doss
  $:  mon=moan               ::  sample count
      hit=(map term @ud)     ::  hit points
      cut=(map path hump)    ::  cut points
  ==

$moan

Profiling: sample metric

Source

+$  moan         ::  sample metric
  $:  fun=@ud    ::  samples in C
      noc=@ud    ::  samples in nock
      glu=@ud    ::  samples in glue
      mal=@ud    ::  samples in alloc
      far=@ud    ::  samples in frag
      coy=@ud    ::  samples in copy
      euq=@ud    ::  samples in equal
  ==             ::

$hump

Profiling

Source

+$  hump
  $:  mon=moan              ::  sample count
      out=(map path @ud)    ::  calls out of
      inn=(map path @ud)    ::  calls into
  ==

Previous4n: VirtualizationNext5a: Compiler Utilities

Last updated 1 day ago