volume 1, Hoon Structures ========================= ------------------------------------------------------------------------ ### ++abel ++ abel typo :: original sin: type Biblical names in hoon are primarily aliases for the compiler. See also: `++typo` ~zod/try=> *abel %void ------------------------------------------------------------------------ ### ++axis ++ axis ,@ :: tree address A Nock axis inside a noun. After the leading 1, in binary, a 1 signfies right and 0 left. See also: `++clue`, `++limb`, `++slot`, `++peg`, and Section 2fC ~zod/try=> *axis 0 ~zod/try=> :: 0 is not actually a valid axis ~zod/try=> [[4 5] 6 7] [[4 5] 6 7] ~zod/try=> `axis`0b110 6 ------------------------------------------------------------------------ ### ++also ++ also ,[p=term q=wing r=type] :: alias XX unused? ------------------------------------------------------------------------ ### ++base ++ base ?([%atom p=odor] %noun %cell %bean %null) :: axils, @ * ^ ? ~ A base type that nouns are built from. Either a noun, a cell, loobean or null labelled with an odor. See also: `++tile`, `++twig` ~zod/try=> *base %null ~zod/try=> (ream '=|(^ !!)') [%tsbr p=[%axil p=%cell] q=[%zpzp ~]] ~zod/try=> :: p.p is a ++base ~zod/try=> (ream '=|(@t !!)') [%tsbr p=[%axil p=[%atom p=~.t]] q=[%zpzp ~]] ~zod/try=> (ream '=|(? !!)') [%tsbr p=[%axil p=%bean] q=[%zpzp ~]] ------------------------------------------------------------------------ ### ++bean ++ bean ,? :: 0=&=yes, 1=|=no The Urbit version of a boolean, which we call a loobean. 0 or & is "yes", 1 or | is "no". ~zod/try=> *bean %.y ~zod/try=> `bean`& %.y ~zod/try=> `bean`| %.n ------------------------------------------------------------------------ ### ++beer ++ beer $|(@ [~ p=twig]) :: simple embed Used to build tapes internally. See also: `++phax`, `++scat`, section 2fD ~zod/try=> `beer`'as' 29.537 ~zod/try=> `beer`[~ (ream 'lan')] [~ p=[%cnzz p=~[%lan]]] ------------------------------------------------------------------------ ### ++beet ++ beet $| @ :: advanced embed $% [%a p=twig] :: take tape [%b p=twig] :: take manx [%c p=twig] :: take marl [%d p=twig] :: take $+(marl marl) [%e p=twig q=(list tuna)] :: element literal == :: Cases for XML interpolation. Used internally. See also: `++sail`, section 2fD ------------------------------------------------------------------------ ### ++bloq ++ bloq ,@ :: blockclass Atom representing a blocksize, by convention expressed as a power of 2. See also: section 2cA ~zod/try=> :: ++met measures how many bloqs long an atom is ~zod/try=> (met 3 256) 2 ~zod/try=> :: 256 is 2 bloqs of 2^3 ------------------------------------------------------------------------ ### ++calf ++ calf ,[p=(map ,@ud wine) q=wine] :: Encodes cyclical backreferences in types. Used in pretty printing. See also: `++wine`, `++dole`, `++doge`, `++dish`, section 2fC ~zod/try=> `calf`[~ %atom %ta] [p={} q=[%atom p=%ta]] ~zod/try=> `calf`~(dole ut p:!>(*^)) [p={} q=[%plot p=~[%noun %noun]]] ~zod/try=> `calf`~(dole ut p:!>($:|-(?(~ [* $])))) [ p={[p=1 q=[%pick p=~[[%pear p=%n q=0] [%plot p=~[%noun [%stop p=1]]]]]]} q=[%stop p=1] ] ------------------------------------------------------------------------ ### ++char ++ char ,@tD :: UTF-8 byte A single character. Odor `@tD` designates a single Unicode byte. All parsers consume `++tape` (a list of `++char`). See also: `++tape`, `++lust`, `++just`, `++mask`, chapter 2f ~zod/try=> *char ~~ ~zod/try=> (char 97) ~~a ------------------------------------------------------------------------ ### ++chub ++ chub :: registered battery $: p=(pair chum tyre) :: definition q=* :: battery r=(unit (pair axis chub)) :: parent == :: Used by the compiler (implicitly by `%sgcn`) to attach jets. See also: Section 2fB. ------------------------------------------------------------------------ ### ++chum ++ 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 == :: 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 major.minor version number. XX there's a ++chum in zuse that's politely causing this not to work See also: `++twig`, `++clue` ~zod/try=> `chum`'hi' lef=%hi ~zod/try=> (ream '~/(%lob.314 !!)') [%sgfs p=[std=%lob kel=314] q=[%zpzp ~]] ------------------------------------------------------------------------ ### ++clue ++ clue ,[p=axis q=chum r=tyre] :: battery definition Used by compiler to attach jets. XX implementation does not currenlty match docs See also: section 2fB ------------------------------------------------------------------------ ### ++coil ++ coil $: p=?(%gold %iron %lead %zinc) :: core type q=type :: r=[p=?(~ ^) q=(map term foot)] :: == :: Core information tuple: variance, subject type, optional compiled nock, and arms. Used as an intermediate step within Section 2fB. Converted by `++core` to %core type. See also: `++core`, Section 2fB ------------------------------------------------------------------------ ### ++coin ++ coin $% [%$ p=dime] :: [%blob p=*] :: [%many p=(list coin)] :: == :: Noun literal syntax cases: atoms, jammed nouns, and nestable tuples. Parsed and printed using `++so` and `++co` cores in Section 2eL respectively. See also: `++so`, `++co`, Section 2eL, `++dime` ~zod/try=> `coin`(need (slay '~s1')) [%$ p=[p=~.dr q=18.446.744.073.709.551.616]] ~zod/try=> `coin`(need (slay '0x2b59')) [%$ p=[p=~.ux q=11.097]] ~zod/try=> ~(rend co [%many ~[[%$ %ud 1] [%$ %tas 'a'] [%$ %s -2]]]) "._1_a_-2__" ~zod/try=> ._1_a_-2__ [1 %a -2] ~zod/try=> `@uv`(jam [3 4]) 0v2cd1 ~zod/try=> (slay '~02cd1') [~ [%blob p=[3 4]]] ~zod/try=> ~02cd1 [3 4] ------------------------------------------------------------------------ ### ++cord ++ cord ,@t :: text atom (UTF-8) One of Hoon's two string types (the other being `++tape`). A cord is an atom of UTF-8 text. `++trip` and `++crip` convert between cord and `++tape` Odor `@t` designates a Unicode atom, little-endian: the first character in the text is the low byte. See also: `++trip`, `++crip`, Section 2eJ ~zod/try=> `@ux`'foobar' 0x7261.626f.6f66 ~zod/try=> `@`'urbit' 499.984.265.845 ~zod/try=> (cord 499.984.265.845) 'urbit' ------------------------------------------------------------------------ ### ++date ++ date ,[[a=? y=@ud] m=@ud t=tarp] :: parsed date A point in time. A loobean designating AD or BC, a year atom, a month atom, and a `++tarp`, which is a day atom and a time. See also: `++year`, `++yore`, Section 2cH, `++stud`, `++dust`, Section 3bc ~zod/try=> `date`(yore ~2014.6.6..21.09.15..0a16) [[a=%.y y=2.014] m=6 t=[d=6 h=21 m=9 s=15 f=~[0xa16]]] ------------------------------------------------------------------------ ### ++dime ++ dime ,[p=@ta q=@] :: Odor-atom pair, used in `++coin`. Convenience methods `++scot` and `++scow` (in Section 2eL) print dimes as cords/tapes, `++slat`, `++slav`, and `++slaw` are used to parse atoms of specific odor. See also: `++so`, `++co`, Section 2eL, `++coin` ~zod/try=> +>:(slay '0x123') p=[p=~.ux q=291] ------------------------------------------------------------------------ ### ++dram ++ dram $% [| p=(map ,@tas dram)] :: simple unix dir [& p=@ud q=@] :: == :: The structure of a unix filesystem tree. A `++dram` is one of two cases: `|` a directory - a map of names to deeper tree structures, `&` a file - a numbered atom of data. XX Unused ------------------------------------------------------------------------ ### ++each ++ each |*([a=$+(* *) b=$+(* *)] $%([& p=a] [| p=b])) :: either a or b Tile generator: produces a dicriminated fork between two types. ~zod/try=> :type; *(each cord time) [%.y p=''] {[%.y p=@t] [%.n p=@da]} ------------------------------------------------------------------------ ### ++edge ++ edge ,[p=hair q=(unit ,[p=* q=nail])] :: parsing output Parsing location metadata: optional result and parsing continuation. See also: Section 2eD, `++rule` ~zod/try=> *edge [p=[p=0 q=0] q=~] ~zod/try=> (tall:vast [1 1] "a b") [p=[p=1 q=2] q=[~ [p=[%cnzz p=~[%a]] q=[p=[p=1 q=2] q=" b"]]]] ------------------------------------------------------------------------ ### ++foot ++ foot $% [%ash p=twig] :: dry arm, geometric [%elm p=twig] :: wet arm, generic [%oak ~] :: XX not used [%yew p=(map term foot)] :: XX not used == :: Cases of arms by variance model. See also: `++ap`, `++ut`, Section 2fB, Section 2fC ~zod/try=> *foot [%yew p={}] ~zod/try=> (ream '|% ++ $ foo --') [%brcn p={[p=%$ q=[%ash p=[%cnzz p=~[%foo]]]]}] ~zod/try=> +<+:(ream '|% ++ $ foo --') t=~[%ash %cnzz %foo] ~zod/try=> (foot +<+:(ream '|% ++ $ foo --')) [%ash p=[%cnzz p=~[%foo]]] ~zod/try=> (foot +<+:(ream '|% +- $ foo --')) [%elm p=[%cnzz p=~[%foo]]] ------------------------------------------------------------------------ ### ++gate ++ gate $+(* *) :: general gate An core with one arm, `$`, which transforms a sample noun into a product noun. If used dryly as a type, subject must have a sample type of `*`. See also: `++lift`, `++cork`, Core Language Doc ~zod/try=> *gate <1|mws [* <101.jzo 1.ypj %164>]> ~zod/try=> `gate`|=(* 0) <1|mws [* <101.jzo 1.ypj %164>]> ~zod/try=> (|=(a=* [a 'b']) 'c') [99 'b'] ~zod/try=> (`gate`|=(a=* [a 'b']) 'c') [99 98] ------------------------------------------------------------------------ ### ++hair ++ hair ,[p=@ud q=@ud] :: parsing trace A pair of two `@ud` used in parsing indicating line and column number. See also: `++last`, Section 2eB ~zod/try=> *hair [p=0 q=0] ~zod/try=> `hair`[1 1] :: parsing starts at [1 1] as a convention. [p=1 q=1] ~zod/try=> ((plus ace) [1 1] " --") [p=[p=1 q=4] q=[~ u=[p=[~~. " "] q=[p=[p=1 q=4] q="--"]]]] ~zod/try=> `hair`p:((plus ace) [1 1] " --") [p=1 q=4] ------------------------------------------------------------------------ ### ++like ++ like |* a=_,* :: generic edge |= b=_`*`[(hair) ~] :: :- p=(hair -.b) :: ^= q :: ?@ +.b ~ :: :- ~ :: u=[p=(a +>-.b) q=[p=(hair -.b) q=(tape +.b)]] :: Tile generator for an `++edge`. `++like` generates an `++edge` with a parsed result set to a specific type. See also: `++easy`, `++just`/`++jest`, `++knee`, `++mask`, `++shim`, `++stir`, `++stun`, Section 2eC ~zod/try=> *(like char) [p=[p=0 q=0] q=~] ~zod/try=> (ace [1 1] " a") [p=[p=1 q=2] q=[~ [p=~~. q=[p=[p=1 q=2] q="a"]]]] ~zod/try=> `(like char)`(ace [1 1] " a") [p=[p=1 q=2] q=[~ [p=~~. q=[p=[p=1 q=2] q="a"]]]] ~zod/try=> `(like ,@)`(ace [1 1] " a") [p=[p=1 q=2] q=[~ [p=32 q=[p=[p=1 q=2] q="a"]]]] ------------------------------------------------------------------------ ### ++limb ++ limb $|(term $%([%& p=axis] [%| p=@ud q=term])) :: XX move to `++ut` Reference into subject by name/axis See also: section 2fC-2fD ~zod/try=> (ream '^^$') [%cnzz p=~[[%.n p=2 q=%$]]] ~zod/try=> (limb &2:(ream '^^$')) [%.n p=2 q=%$] ~zod/try=> (limb &2:(ream '^^^$')) [%.n p=3 q=%$] ------------------------------------------------------------------------ ### ++line ++ line ,[p=[%leaf p=odor q=@] q=tile] :: %kelp case XX move to `++ut` Dicriminated union unionee XX Used in compilation and grammar, section 2fC-2fD ~zod/try=> (ream '$%([1 a] [%2 b])') [ %bccm p [ %kelp p [ i=[p=[%leaf p=~.ud q=1] q=[%herb p=[%cnzz p=~[%a]]]] t=~[[p=[%leaf p=~.ud q=2] q=[%herb p=[%cnzz p=~[%b]]]]] ] ] ] ~zod/try=> &3:(ream '$%([1 a] [%2 b])') p=[p=[%leaf p=%ud q=1] q=[%herb p=[%cnzz p=~[%a]]]] ~zod/try=> (line &3:(ream '$%([1 a] [%2 b])')) [p=[%leaf p=~.ud q=1] q=[%herb p=[%cnzz p=~[%a]]]] ------------------------------------------------------------------------ ### ++list ++ list |* a=_,* :: null-term list $|(~ [i=a t=(list a)]) :: Tile generator. `++list` generates a tile of a null-termanated list of homogenous type. See also: `++turn`, `++snag`, section 2bB. ~zod/try=> *(list) ~ ~zod/try=> `(list ,@)`"abc" ~[97 98 99] ~zod/try=> (snag 0 "abc") ~~a ------------------------------------------------------------------------ ### ++lone ++ lone |*(a=$+(* *) ,p=a) :: just one thing XX unused Tile generator. `++lone` puts face of `p` on something. ------------------------------------------------------------------------ ### ++mane ++ mane $|(@tas [@tas @tas]) :: XML name/space An XML name (tag name or attribute name) with an optional namespace. Parsed by `++name`:poxa, rendered by `++name`:poxo. See also: `++sail` doc, Section 3bD ~zod/try=> *mane %$ ~zod/try=> `mane`n.g:`manx`;div:namespace; %div ~zod/try=> `mane`n.g:`manx`;div_namespace; [%div %namespace] ------------------------------------------------------------------------ ### ++manx ++ manx ,[g=marx c=marl] :: XML node XML node. Parsed by `++apex`:poxa, rendered by `++poxo`, section 3bD See also: `++sail` doc, Section 3bD ------------------------------------------------------------------------ ### ++marl ++ marl (list manx) :: XML node list List of XML nodes. Parsed within `++apex`:poxa, rendered by `++many`:poxo, section 3bD See also: `++sail` doc ------------------------------------------------------------------------ ### ++mars ++ mars ,[t=[n=%$ a=[i=[n=%$ v=tape] t=~]] c=~] :: XML cdata XML CDATA. Implicitly produced by `++chrd`:poxa See also: `++sail` doc ------------------------------------------------------------------------ ### ++mart ++ mart (list ,[n=mane v=tape]) :: XML attributes List of XML attributes. Each `++mart` is a list of pairs of `++mane` and `++tape`. Parsed by `++attr`:poxa, rendered by `++attr`:poxo, section 3bD See also: `++sail` doc ------------------------------------------------------------------------ ### ++marx ++ marx ,[n=mane a=mart] :: XML tag XML tag. A `++marx` is a pair of a tag name, `++mane` and a list of attributes, `++mart`. Parsed by `++head`:poxa, rendered within `++poxo`, section 3bD See also: `++sail` doc ------------------------------------------------------------------------ ### ++metl ++ metl ?(%gold %iron %zinc %lead) :: core variance XX move to `++ut` See also: `++coil` ------------------------------------------------------------------------ ### ++noun ++ noun ,* :: any noun Used nowhere XX ~zod/try=> `noun`~[1 2 3] [1 2 3 0] ------------------------------------------------------------------------ ### ++null ++ null ,~ :: null, nil, etc Used nowhere XX ~zod/try=> :type; *null ~ %~ ------------------------------------------------------------------------ ### ++odor ++ odor ,@ta :: atom format By convetion, a short name for a category of atom. `++odor` is circularly defined, `@ta` being the `++odor` of the ASCII subset commonly used in urbit. See also: `++base`, odor reference ~zod/try=> `odor`%ux ~.ux ------------------------------------------------------------------------ ### ++tarp ++ tarp ,[d=@ud h=@ud m=@ud s=@ud f=(list ,@ux)] :: parsed time The remaining part of a `++date`: day, hour, minute, second and a list of `@ux` for precision. See also: `++date`, `++yell`/`++yule`, Section 2cH ~zod/try=> -<- ~2014.9.20..00.43.33..b52a ~zod/try=> :: the time is always in your context at -<- ~zod/try=> (yell -<-) [d=106.751.991.820.278 h=0 m=43 s=39 f=~[0x54d1]] ~zod/try=> (yell ~d20) [d=20 h=0 m=0 s=0 f=~] ------------------------------------------------------------------------ ### ++time ++ time ,@da :: galactic time The `@da` odor designates an absolute date atom. See also: `++date`, odor reference ~zod/try=> `time`-<- ~2014.9.25..20.01.47..eeac ~zod/try=> :: the time is always in your context at -<- ~zod/try=> `time`~2014.1.1 ~2014.1.1 ------------------------------------------------------------------------ ### ++tree ++ tree |* a=_,* :: binary tree $|(~ [n=a l=(tree a) r=(tree a)]) :: Tile generator. A `++tree` can be empty, or contain a node of a type and left/right sub `++tree`s of the same type. Pretty-printed with `{}`. ~zod/try=> `(tree ,[@ tape])`[[1 "hi"] [[2 "bye"] ~ ~] ~] {[2 "bye"] [1 "hi"]} ------------------------------------------------------------------------ ### ++nail ++ nail ,[p=hair q=tape] :: parsing input Location in parsed text, and remainder of it. Indicates parsing position and remaining text to be parsed. See also: `++roll` ~zod/try=> +<:;~(plug cab cab) c=tub=[p=[p=0 q=0] q=""] ~zod/try=> :: tub is a ++nail ------------------------------------------------------------------------ ### ++numb ++ numb ,@ :: just a number Used nowhere XX ------------------------------------------------------------------------ ### ++pair ++ pair |*([a=$+(* *) b=$+(* *)] ,[p=a q=b]) :: just a pair Tile generator. Produces a tuple of two of the types passed in. ~zod/try=> *(pair bean cord) [p=%.y q=''] ------------------------------------------------------------------------ ### ++pass ++ pass ,@ :: public key Atom alias. Used primarily in crypto. See also: `++acru`, `++crua`, `++crub` ------------------------------------------------------------------------ ### ++path ++ path (list span) :: filesys location A filesystem path. A `++path` is a list of `++span`, `@ta`. Used in `%clay` and `%eyre` extensively. ~zod/try=> `path`"abc" /a/b/c ------------------------------------------------------------------------ ### ++pint ++ pint ,[p=[p=@ q=@] q=[p=@ q=@]] :: line/column range A parsing range, mostly used for stacktraces. A `++pint` is a pair of hairs indicating from - to. ~zod/try=> !:(!!) ! /~zod/try/~2014.9.20..01.22.04..52e3/:<[1 4].[1 6]> ~zod/try=> :: !! always produces a crash ~zod/try=> `pint`[[1 4] [1 6]] [p=[p=1 q=4] q=[p=1 q=6]] ------------------------------------------------------------------------ ### ++pole ++ pole |* a=_,* :: nameless list $|(~ [a (pole a)]) :: A `++list` without the faces. A `++pole` is a null-terminated typle without the `i=` and `t=`. ~zod/try=> `(pole char)`"asdf" [~~a [~~s [~~d [~~f ~]]]] ------------------------------------------------------------------------ ### ++port ++ port $: p=axis :: $= q :: $% [%& p=type] :: [%| p=axis q=(list ,[p=type q=foot])] :: == :: == :: XX move to `++ut` Type and location of core-shaped thing? XX Compiler Internals ~zod/try=> *port [p=0 q=[%.y p=%void]] ------------------------------------------------------------------------ ### ++post ++ post $: p=axis :: $= q :: $% [0 p=type] :: [1 p=axis q=(list ,[p=type q=foot])] :: [2 p=twin q=type] :: == :: == :: XX move to `++ut` Type and location of possibly core-shaped thing? XX Compiler Internals ~zod/try=> *post [p=0 q=[%0 p=%void]] ------------------------------------------------------------------------ ### ++prop ++ prop $: p=axis :: $= q :: [p=?(~ axis) q=(list ,[p=type q=foot])] :: == :: XX move to `++ut` Verified core-shaped thing? XX Compiler Internals ~zod/try=> *prop [p=0 q=[p=~ q=~]] ------------------------------------------------------------------------ ### ++qual ++ qual |* [a=$+(* *) b=$+(* *) c=$+(* *) d=$+(* *)] :: just a quadruple ,[p=a q=b r=c s=d] :: Tile generator. A `++qual` is a tuple of four of the types passed in.. ~zod/try=> *(qual date time tape cord) [p=[[a=%.y y=0] m=0 t=[d=0 h=0 m=0 s=0 f=~]] q=~292277024401-.1.1 r="" s=''] ------------------------------------------------------------------------ ### ++rege ++ rege $| ?(%dote %ende %sart %empt %boun %bout) :: parsed regex $% [%lite p=char] :: literal [%pair p=rege q=rege] :: ordering [%capt p=rege q=@u] :: capture group [%brac p=@] :: p is 256 bitmask [%eith p=rege q=rege] :: either [%mant p=rege] :: greedy 0 or more [%plls p=rege] :: greedy 1 or more [%betw p=rege q=@u r=@u] :: between q and r [%bint p=rege q=@u] :: min q [%bant p=rege q=@u] :: exactly q [%manl p=rege] :: lazy 0 or more [%plll p=rege] :: lazy 1 or more [%betl p=rege q=@u r=@u] :: between q and r lazy [%binl p=rege q=@u] :: min q lazy == :: Regular expressions. `++rege` defines the cases of a regex. See also: `++rexp`, `++repg`, `++pars` ~zod/try=> (pars "[a-z]") [~ [%brac p=10.633.823.807.823.001.954.701.781.295.154.855.936]] ~zod/try=> (rexp "[a-z]" "abc1") [~ [~ {[p=0 q="a"]}]] ------------------------------------------------------------------------ ### ++ring ++ ring ,@ :: private key Atom alias, used primarily in crypto. See also: `++acru`, `++crua`, `++crub`. ------------------------------------------------------------------------ ### ++rule ++ rule |=(tub=nail `edge`[p.tub ~ ~ tub]) :: parsing rule Parsing rule. `++rule` is an empty parsing rule, but it is used to check that parsing rules match this with `_`. See also: `++cold`, Section 2eC ~zod/try=> *rule [p=[p=0 q=0] q=[~ [p=0 q=[p=[p=0 q=0] q=""]]]] ~zod/try=> ^+(rule [|=(a=nail [p.a ~])]:|6) <1.dww [tub=[p=[p=@ud q=@ud] q=""] <101.jzo 1.ypj %164>]> ~zod/try=> (^+(rule [|=(a=nail [p.a ~ u=['a' a]])]:|6) [1 1] "hi") [p=[p=1 q=1] q=[~ [p=97 q=[p=[p=1 q=1] q="hi"]]]] ~zod/try=> ([|=(a=nail [p.a ~ u=['a' a]])]:|6 [1 1] "hi") [[p=1 q=1] ~ u=['a' p=[p=1 q=1] q="hi"]] ------------------------------------------------------------------------ ### ++span ++ span ,@ta :: text-atom (ASCII) A restricted text atom for canonical atom syntaxes. The prefix is `~.`. There are no escape sequences except `~~`, which means `~`, and `~-`, which means `_`. `-` and `.` encode themselves. No other characters besides numbers and lowercase letters are permitted. ~zod/try=> *span ~. ~zod/try=> `@t`~.foo 'foo' ~zod/try=> `@t`~.foo.bar 'foo.bar' ~zod/try=> `@t`~.foo~~bar 'foo~bar' ~zod/try=> `@t`~.foo~-bar 'foo_bar' ~zod/try=> `@t`~.foo-bar 'foo-bar' ------------------------------------------------------------------------ ### ++spot ++ spot ,[p=path q=pint] :: range in file Stack trace line. A `++spot` is what we print after crashing. See also: `++pint` ~zod/try=> :into /=main=/bin/fail/hoon '!: !!' + /~zod/main/359/bin/fail/hoon ~zod/try=> :fail ! /~zod/main/~2014.9.22..18.40.56..ef04/bin/fail/:<[1 5].[1 7]> ! exit ------------------------------------------------------------------------ ### ++tang ++ tang (list tank) :: general error Unused XX ------------------------------------------------------------------------ ### ++tank ++ tank $% [%leaf p=tape] :: printing formats $: %palm :: p=[p=tape q=tape r=tape s=tape] :: q=(list tank) :: == :: $: %rose :: delimeted list p=[p=tape q=tape r=tape] :: mid open close q=(list tank) :: == :: == Pretty-printing structure. A `++tank` is one of three cases. A `%leaf` is just a string. A `%palm` is XX need more information. A `%rose` is a list of `++tank` delimted by the strings in `p`. ~zod/try=> >(bex 20) (bex 19)< [%rose p=[p=" " q="[" r="]"] q=~[[%leaf p="1.048.576"] [%leaf p="524.288"]]] ~zod/try=> (wash [0 80] >(bex 20) (bex 19)<) :: at 80 cols <<"[1.048.576 524.288]">> ~zod/try=> (wash [0 15] >(bex 20) (bex 19)<) :: at 15 cols (two lines) <<"[ 1.048.576" " 524.288" "]">> ~zod/try=> [(bex 150) (bex 151)] :: at 80 cols [ 1.427.247.692.705.959.881.058.285.969.449.495.136.382.746.624 2.854.495.385.411.919.762.116.571.938.898.990.272.765.493.248 ] ------------------------------------------------------------------------ ### ++tape ++ tape (list char) :: like a string One of Hoon's two string types, the other being `++cord`. A tape is a list of chars. ~zod/try=> `(list ,char)`"foobar" "foobar" ~zod/try=> `(list ,@)`"foobar" ~[102 111 111 98 97 114] ------------------------------------------------------------------------ ### ++term ++ term ,@tas :: Hoon ASCII subset A restricted text atom for Hoon constants. The only characters permitted are lowercase ASCII, - except as the first or last character, and 0-9 except as the first character. The syntax for `@tas` is the text itself, always preceded by `%`. This means a term is always cubical. The empty `@tas` has a special syntax, `$`: ~zod/try=> *term %$ ~zod/try=> %dead-fish9 %dead-fish9 ~zod/try=> -:!>(%dead-fish9) [%cube p=271.101.667.197.767.630.546.276 q=[%atom p=%tas]] ------------------------------------------------------------------------ ### ++tiki ++ tiki :: test case $% [& p=(unit term) q=wing] :: simple wing [| p=(unit term) q=twig] :: named wing == :: XX move to `++ut` A `++wing` or `++twig`. ~zod/try=> (ream '=+ a=4 ?-(a @ ~)') [ %tsls p=[%ktts p=p=%a q=[%dtzy p=%ud q=4]] q [ %wthz p=[%.y p=~ q=~[%a]] q=~[[p=[%axil p=[%atom p=~.]] q=[%bczp p=%null]]] ] ] ~zod/try=> (ream '=+ a=4 ?-(4 @ ~)') [ %tsls p=[%ktts p=p=%a q=[%dtzy p=%ud q=4]] q [ %wthz p=[%.n p=~ q=[%dtzy p=%ud q=4]] q=~[[p=[%axil p=[%atom p=~.]] q=[%bczp p=%null]]] ] ] ------------------------------------------------------------------------ ### ++tile See the Tile section of the Hoon Reference. ------------------------------------------------------------------------ ### ++toga ++ toga :: face control $| p=term :: two togas $% [0 ~] :: no toga [1 p=term q=toga] :: deep toga [2 p=toga q=toga] :: cell toga == :: XX move to `++ut` and rune doc (for \^= examples) A face, or tree of faces. A `++toga` is applied to anything assigned using `^=`. ~zod/try=> a=1 a=1 ~zod/try=> (ream 'a=1') [%ktts p=p=%a q=[%dtzy p=%ud q=1]] ~zod/try=> [a b]=[1 2 3] [a=1 b=[2 3]] ~zod/try=> (ream '[a b]=[1 2 3]') [ %ktts p=[%2 p=p=%a q=p=%b] q=[%cltr p=~[[%dtzy p=%ud q=1] [%dtzy p=%ud q=2] [%dtzy p=%ud q=3]]] ] ~zod/try=> [a ~]=[1 2 3] [a=1 2 3] ~zod/try=> (ream '[a ~]=[1 2 3]') [ %ktts p=[%2 p=p=%a q=[%0 ~]] q=[%cltr p=~[[%dtzy p=%ud q=1] [%dtzy p=%ud q=2] [%dtzy p=%ud q=3]]] ] ------------------------------------------------------------------------ ### ++trap ++ trap ,_|.(_*) :: makes perfect sense A trap is a core with one arm `++$`. See also: `|.` ~zod/try=> *trap <1.mws 101.jzo 1.ypj %164> ~zod/try=> (*trap) 0 ~zod/try=> (|.(42)) 42 ------------------------------------------------------------------------ ### ++trel ++ trel |* [a=$+(* *) b=$+(* *) c=$+(* *)] :: just a triple ,[p=a q=b r=c] :: Tile generator. `++trel` is a tuple of three of the types passed in. ~zod/try=> *(trel ,@ud ,@t ,@s) [p=0 q='' r=--0] ------------------------------------------------------------------------ ### ++tuna ++ tuna :: tagflow $% [%a p=twig] :: plain text [%b p=twig] :: single tag [%c p=twig] :: simple list [%d p=twig] :: dynamic list [%e p=twig q=(list tuna)] :: element [%f p=(list tuna)] :: subflow == :: An XML template tree. Leaf %a contains plain-text, %b an empty tag, %c a static list, %d a dynamic list, %e a full node element containing a twig and a list of tuna, and %f is a empty node. See also: `++sail` ------------------------------------------------------------------------ ### ++twig See Twig section of Hoon reference ------------------------------------------------------------------------ ### ++tine ++ tine (list ,[p=tile q=twig]) :: Switch statement cases. In `?-`, for example, your list of cases is a `++tine`. See also: `++twig` ~zod/try=> (ream '?-(!! @ |, ^ &)') [ %wthz p=[%.n p=~ q=[%zpzp ~]] q ~[ [p=[%axil p=[%atom p=~.]] q=[%dtzy p=%f q=1]] [p=[%axil p=%cell] q=[%dtzy p=%f q=0]] ] ] ~zod/try=> (tine |2:(ream '?-(!! @ |, ^ &)')) ~[ [p=[%axil p=[%atom p=~.]] q=[%dtzy p=%f q=1]] [p=[%axil p=%cell] q=[%dtzy p=%f q=0]] ] ------------------------------------------------------------------------ ### ++tusk ++ tusk (list twig) :: Variable-arity expression list. In `:*`, for example, your contents are a `++tusk`. See also: `++twig` ~zod/try=> (ream '[1 2 3]') [%cltr p=~[[%dtzy p=%ud q=1] [%dtzy p=%ud q=2] [%dtzy p=%ud q=3]]] ~zod/try=> (tusk +:(ream '[1 2 3]')) ~[[%dtzy p=%ud q=1] [%dtzy p=%ud q=2] [%dtzy p=%ud q=3]] ------------------------------------------------------------------------ ### ++tyre ++ tyre (list ,[p=term q=twig]) :: Associative list of term to twig, used in jet hint processing. See also: `++twig` ------------------------------------------------------------------------ ### ++tyke ++ tyke (list (unit twig)) :: List of twigs, or gaps left to be inferred, in path parsing. When you use a path such as `/=main=/pub/src/doc` the path is in fact a `++tyke`, where the `=` are inferred from your current path. ~zod/try=> (scan "/==as=" porc:vast) [0 ~[~ ~ [~ [%dtzy p=%tas q=29.537]] ~]] ~zod/try=> `tyke`+:(scan "/==as=" porc:vast) ~[~ ~ [~ [%dtzy p=%tas q=29.537]] ~] ------------------------------------------------------------------------ ### ++tram ++ tram (list ,[p=wing q=twig]) :: List of changes by location in context. When using `%=`, for example, the list of changes is a `++tram`. See also: `++twig` ~zod/try=> (ream '$(a 1, b 2)') [ %cnts p=~[%$] q=~[[p=~[%a] q=[%dtzy p=%ud q=1]] [p=~[%b] q=[%dtzy p=%ud q=2]]] ] ~zod/try=> (tram +:(ream '$(a 1, b 2)')) ~[[p=~ q=[% p=0]] [p=~[%a] q=[%dtzy p=%ud q=1]] [p=~[%b] q=[%dtzy p=%ud q=2]]] ------------------------------------------------------------------------ ### ++nock ++ nock $& [p=nock q=nock] :: autocons $% [%0 p=@] :: axis select [%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] :: hint [%11 p=nock] :: grab data from sky == :: See Nock doc ~zod/try=> !=([+(.) 20 -<]) [[4 0 1] [1 20] 0 4] ~zod/try=> (nock !=([+(.) 20])) [p=[%4 p=[%0 p=1]] q=[%1 p=20]] ------------------------------------------------------------------------ ### ++tone ++ tone $% [%0 p=*] :: success [%1 p=(list)] :: blocks [%2 p=(list ,[@ta *])] :: error ~_s == :: Intermediate Nock computation result. Similar to `++toon`, but stack trace is not yet rendered. ~zod/try=> (mink [[20 21] 0 3] ,~) [%0 p=21] ~zod/try=> (mink [[0] !=(.^(cy//=main/1))] ,~) [%1 p=~[[31.075 1.685.027.454 1.852.399.981 49 0]]] ~zod/try=> (path [31.075 1.685.027.454 1.852.399.981 49 0]) /cy/~zod/main/1 ~zod/try=> (mink [[1 2] !=(~|(%hi +(.)))] ,~) [%2 p=~[[~.yelp 26.984]]] ~zod/try=> (mink [[1 2] !=(!:(+(.)))] ,~) [ %2 p ~[ [ ~.spot [ [ 1.685.027.454 7.959.156 \/159.445.990.350.374.058.574.398.238.344.143.957.205.628.479.572.65\/ 8.112.403.878.526 \/ \/ 0 ] [1 20] 1 24 ] ] ] ] ------------------------------------------------------------------------ ### ++toon ++ toon $% [%0 p=*] :: success [%1 p=(list)] :: blocks [%2 p=(list tank)] :: stack trace == :: Nock computation result. Either success (`%0`), a block with list of requests blocked on (`%1`), or failure with stack trace (`%2`). ~zod/try=> (mock [[20 21] 0 3] ,~) [%0 p=21] ~zod/try=> (mock [[0] !=(.^(cy//=main/1))] ,~) [%1 p=~[[31.075 1.685.027.454 1.852.399.981 49 0]]] ~zod/try=> (path [31.075 1.685.027.454 1.852.399.981 49 0]) /cy/~zod/main/1 ~zod/try=> (mock [[1 2] !=(!:(+(.)))] ,~) [%2 p=~[[%leaf p="/~zod/try/~2014.9.23..18.34.32..d3c5/:<[1 20].[1 24]>"]]] ------------------------------------------------------------------------ ### ++tune ++ tune $% [%0 p=vase] :: [%1 p=(list)] :: [%2 p=(list ,[@ta *])] :: == :: XX Unused Probably typed `tone`? ------------------------------------------------------------------------ ### ++twin ++ twin ,[p=term q=wing r=axis s=type] :: alias info Aliasing. Used in `%bull` `++type` to typecheck aliased faces. ~zod/try=> (~(busk ut %cell %noun [%atom %ud]) %fal [%& 3]~) [ %bull p=[p=%fal q=~[[%.y p=3]] r=3 s=[%atom p=%ud]] q=[%cell p=%noun q=[%atom p=%ud]] ] ~zod/try=> &2:(~(busk ut %cell %noun [%atom %ud]) %fal [%& 3]~) p=[p=%fal q=~[[%.y p=3]] r=3 s=[%atom p=%ud]] ~zod/try=> (twin &2:(~(busk ut %cell %noun [%atom %ud]) %fal [%& 3]~)) [p=%fal q=~[[%.y p=3]] r=3 s=[%atom p=%ud]] ------------------------------------------------------------------------ ### ++type See Type section of Hoon reference ------------------------------------------------------------------------ ### ++typo ++ typo type :: old type Pointer for `++type`. `++typo` preserves the previous `++type` in your context when upating. See also: `++seem`, `++vise`, `++type` ------------------------------------------------------------------------ ### ++udal ++ udal :: atomic change (%b) $: p=@ud :: blockwidth q=(list ,[p=@ud q=(unit ,[p=@ q=@])]) :: indels == :: XX Unused ------------------------------------------------------------------------ ### ++udon ++ udon :: abstract delta $: p=umph :: preprocessor $= q :: patch $% [%a p=* q=*] :: trivial replace [%b p=udal] :: atomic indel [%c p=(urge)] :: list indel [%d p=upas q=upas] :: tree edit == :: == :: See `%clay` doc ------------------------------------------------------------------------ ### ++umph ++ umph :: change filter $| $? %a :: no filter %b :: jamfile %c :: LF text == :: $% [%d p=@ud] :: blocklist == :: See `%clay` doc ------------------------------------------------------------------------ ### ++unce ++ unce |* a=_,* :: change part $% [%& p=@ud] :: skip[copy] [%| p=(list a) q=(list a)] :: p -> q[chunk] == :: See `%clay` doc ------------------------------------------------------------------------ ### ++unit ++ unit |* a=_,* :: maybe $|(~ [~ u=a]) :: Tile generator. A `++unit` is either `~` or `[~ u=a]` where `a` is the type that was passed in. See also: `++bind`, Section 2bA ~zod/try=> :type; *(unit time) ~ u(@da) ~zod/try=> `(unit time)`[~ -<-] [~ ~2014.9.24..19.25.10..7dd5] ------------------------------------------------------------------------ ### ++upas ++ upas :: tree change (%d) $& [p=upas q=upas] :: cell $% [%0 p=axis] :: copy old [%1 p=*] :: insert new [%2 p=axis q=udon] :: mutate! == :: See `%clay` doc ------------------------------------------------------------------------ ### ++urge ++ urge |*(a=_,* (list (unce a))) :: list change See `%clay` doc ------------------------------------------------------------------------ ### ++vase ++ vase ,[p=type q=*] :: type-value pair Typed data. A `++vase` is used wherever typed data is explicitly worked with. See `%arvo` doc ~zod/try=> `vase`!>(~) [p=[%cube p=0 q=[%atom p=%n]] q=0] ------------------------------------------------------------------------ ### ++vise ++ vise ,[p=typo q=*] :: old vase Used to convert from previously-typed data during reboot. See `++typo`, `++seer` ------------------------------------------------------------------------ ### ++wall ++ wall (list tape) :: text lines (no \n) A list of lines. A `++wall` is used instead of a single `++tape` with `\n`. See also: `++wash` ~zod/try=> `wall`(wash [0 20] leaf/<(bex 256)>) << "\/115.792.089.237.\/" " 316.195.423.570." " 985.008.687.907." " 853.269.984.665." " 640.564.039.457." " 584.007.913.129." " 639.936" "\/ \/" >> ------------------------------------------------------------------------ ### ++wain ++ wain (list cord) :: text lines (no \n) A list of lines. A `++wain` is used instead of a single `++cord` with `\n`. See also: `++lore`, `++role` ~zod/try=> `wain`/som/del/rok <|som del rok|> ~zod/try=> `wain`(lore ^:@t/=main=/bin/tree/hoon) <| !: :: /===/bin/tree/hoon |= ^ |= [pax=path fla=$|(~ [%full ~])] =- ~[te/-]~ =+ len=(lent pax) =+ rend=?~(fla |=(a=path +:(spud (slag len a))) spud) |- ^- wain =+ ark=;;(arch .^(cy/pax)) =- ?~ q.ark - [(crip (rend pax)) -] %- zing %- turn :_ |=(a=@t ^$(pax (weld pax `path`/[a]))) %- sort :_ aor %- turn :_ |=([a=@t ~] a) (~(tap by r.ark)) |> ------------------------------------------------------------------------ ### ++wing ++ wing (list limb) :: Address in subject. A `++wing` is a path to a value in the subject. A term alone is the trivial case of a `++wing`. See also: `++twig` ~zod/try=> (ream 'a.+.c') [%cnzz p=~[%a [%.y p=3] %c]] ~zod/try=> (wing +:(ream 'a.+.c')) ~[%a [%.y p=3] %c] ------------------------------------------------------------------------ ### ++wine ++ wine $| ?(%noun %path %tank %void %wall %wool %yarn) $% [%atom p=term] :: [%core p=(list ,@ta) q=wine] :: [%face p=term q=wine] :: [%list p=term q=wine] :: [%pear p=term q=@] :: [%pick p=(list wine)] :: [%plot p=(list wine)] :: [%stop p=@ud] :: [%tree p=term q=wine] :: [%unit p=term q=wine] :: == :: Printable type. `++wine` is used for pretty printing. See also: `++calf` ~zod/try=> ~(dole ut p:!>(*@tas)) [p={} q=[%atom p=%tas]] ~zod/try=> `wine`q:~(dole ut p:!>(*@tas)) [%atom p=%tas] ~zod/try=> ~(dole ut p:!>(*path)) [ p { [ p=1 q [ %pick p ~[ [%pear p=%n q=0] [%plot p=~[[%face p=%i q=[%atom p=%ta]] [%face p=%t q=[%stop p=1]]]] ] ] ] } q=%path ] ~zod/try=> `wine`q:~(dole ut p:!>(*path)) %path ~zod/try=> ~(dole ut p:!>(*(map time cord))) [ p { [ p=1 q [ %pick p ~[ [%pear p=%n q=0] [ %plot p ~[ [ %face p=%n q [ %plot p=~[[%face p=%p q=[%atom p=%da]] [%face p=%q q=[%atom p=%t]]] ] ] [%face p=%l q=[%stop p=1]] [%face p=%r q=[%stop p=1]] ] ] ] ] ] } q [ %tree p=%nlr q=[%plot p=~[[%face p=%p q=[%atom p=%da]] [%face p=%q q=[%atom p=%t]]]] ] ] ~zod/try=> `wine`q:~(dole ut p:!>(*(map time cord))) [ %tree p=%nlr q=[%plot p=~[[%face p=%p q=[%atom p=%da]] [%face p=%q q=[%atom p=%t]]]] ] ------------------------------------------------------------------------ ### ++wonk ++ wonk |*(veq=edge ?~(q.veq !! p.u.q.veq)) :: :: :: :: :: XX Not a model? ++ wonk |*(veq=edge ?~(q.veq !! p.u.q.veq)) :: Pull result out of a `++edge`, or crash if there's no result. See also: `++edge`, Section 2eC ~zod/try=> (wide:vast [1 1] "(add 2 2)") [ p=[p=1 q=10] q [ ~ [ p=[%cnhp p=[%cnzz p=~[%add]] q=~[[%dtzy p=%ud q=2] [%dtzy p=%ud q=2]]] q=[p=[p=1 q=10] q=""] ] ] ] ~zod/try=> (wonk (wide:vast [1 1] "(add 2 2)")) [%cnhp p=[%cnzz p=~[%add]] q=~[[%dtzy p=%ud q=2] [%dtzy p=%ud q=2]]] ------------------------------------------------------------------------ ### ++map ++ map |* [a=_,* b=_,*] :: associative tree $|(~ [n=[p=a q=b] l=(map a b) r=(map a b)]) :: Tile generator. A `++map` is a [treap](http://en.wikipedia.org/wiki/Treap) of key, value pairs. See also: `++by` ~zod/try=> :type; *(map ,@t ,@u) {} nlr([p=@t q=@u]) ~zod/try=> `(map ,@ta ,@ud)`(mo (limo a/1 b/2 ~)) {[p=~.a q=1] [p=~.b q=2]} ------------------------------------------------------------------------ ### ++qeu ++ qeu |* a=_,* :: queue $|(~ [n=a l=(qeu a) r=(qeu a)]) :: Tile generator. A `++qeu` is an ordered [treap](http://en.wikipedia.org/wiki/Treap) of items. See also: `++to` ~zod/try=> (qeu time) <1.qyo [* <1.sxx [a=<1.ebd [* <101.jzo 1.ypj %164>]> <101.jzo 1.ypj %164>]>]> ~zod/try=> (~(gas to *(qeu time)) [~2014.1.1 ~2014.1.2 ~]) {~2014.1.2 ~2014.1.1} ------------------------------------------------------------------------ ### ++set ++ set |* a=_,* :: set $|(~ [n=a l=(set a) r=(set a)]) :: Tile generator. A `++set` is a [treap](http://en.wikipedia.org/wiki/Treap) with unique values. See also: `++in` ~zod/try=> (sa "abc") {~~a ~~c ~~b} ~zod/try=> (~(put in (sa "abc")) %d) {~~d ~~a ~~c ~~b} ~zod/try=> (~(put in (sa "abc")) %a) {~~a ~~c ~~b} ------------------------------------------------------------------------ ### ++jar ++ jar |*([a=_,* b=_,*] (map a (list b))) :: map of lists Tile generator. A `++jar` is a `++map` of `++list`. See also: `++ja`, `++by`, `++map`, `++list` ~zod/try=> =a (limo [1 2 ~]) ~zod/try=> a [i=1 t=[i=2 t=~]] ~zod/try=> =b (limo [3 4 ~]) ~zod/try=> b [i=3 t=[i=4 t=~]] ~zod/try=> =c (mo (limo [[%a a] [%b b] ~])) ~zod/try=> c {[p=%a q=[i=1 t=[i=2 t=~]]] [p=%b q=[i=3 t=[i=4 t=~]]]} ~zod/try=> (~(get ja c) %a) [i=1 t=[i=2 t=~]] ~zod/try=> (~(get ja c) %c) ~ ------------------------------------------------------------------------ ### ++jug ++ jug |*([a=_,* b=_,*] (map a (set b))) :: map of sets Tile generator. Similar to `++jar`, but with `++set`. A `++jug` is a `++map` of `++set`. See also: `++ju`, `++by`, `++map`, `++set` ~zod/try=> =a (sa (limo [1 2 ~])) ~zod/try=> a {1 2} ~zod/try=> =b (sa (limo [3 4 ~])) ~zod/try=> b {4 3} ~zod/try=> =c (mo (limo [[%a a] [%b b] ~])) ~zod/try=> c {[p=%a q={1 2}] [p=%b q={4 3}]} ~zod/try=> (~(get ju c) %b) {4 3} ~zod/try=> (~(put ju c) [%b 5]) {[p=%a q={1 2}] [p=%b q={5 4 3}]} ------------------------------------------------------------------------