++ut
Hoon compiler backend
Source
This core is too large to include here, refer to hoon.hoon
for the source.
++us
Pretty-printer backend
Source
This core is too large to include here, refer to hoon.hoon
for the source.
++cain
Tank pretty-print
Pretty-print a vase
as a tank
using ++deal
. This is the same as ++sell
.
Accepts
A vase
.
Produces
A tank
.
Source
++ cain sell
Examples
> (cain !>(['foo' 'bar']))[%rose p=[p=" " q="[" r="]"] q=~[[%leaf p="'foo'"] [%leaf p="'bar'"]]]
++noah
Tape pretty-print
Pretty-print a vase
as a tape
. This is the same as ++text
.
Accepts
A vase
.
Produces
A tape
.
Source
++ noah text
Examples
> (noah !>(['foo' 'bar']))"['foo' 'bar']"
++onan
Vise to vase
Convert a vise
(old vase
) to the new vase
. This is the same as ++seer
.
Accepts
A vise
.
Produces
A vase
.
Source
++ onan seer
Examples
> (onan `vise`!>(['foo' 'bar']))[#t/[@t @t] q=[7.303.014 7.496.034]]
++levi
Type nests or crash
Check if type b
nests under type a
. Produces %.y
if it nests and crashes if it does not.
Accepts
a
is a type
.
b
is a type
.
Produces
A ?
.
Source
++ levi|= [a=type b=type](~(nest ut a) & b)
Examples
> (levi -:!>('foo') -:!>(%foo))%.y> (levi -:!>(%foo) -:!>('foo'))-need.%foo-have.@tnest-fail
++text
Tape pretty-print
Pretty print vase vax
as a tape
.
Accepts
vax
is a vase
.
Produces
A tape
.
Source
++ text|= vax=vase ^- tape~(ram re (sell vax))
Examples
> (text !>(['foo' 'bar']))"['foo' 'bar']"
++seem
Promote typo
Convert typo
(old type) to the new type
.
Accepts
toy
is a typo
.
Produces
A type
.
Source
++ seem |=(toy=typo `type`toy)
Examples
> (seem -:!>('foo'))#t/@t
++seer
Promote vise
Convert a vise
(old vase
) to the new vase
.
Accepts
vix
is a vise
.
Produces
A vase
.
Source
++ seer |=(vix=vise `vase`vix)
Examples
> (seer !>('foo'))[#t/@t q=7.303.014]
++sell
Pretty-print vase to a tank
Pretty-print vase vax
to a tank
using ++deal:us
.
Accepts
vax
is a vase
.
Produces
A tank
.
Source
++ sell~/ %sell|= vax=vase^- tank~| %sell(~(deal us p.vax) q.vax)
Examples
> (sell !>(['foo' 'bar']))[%rose p=[p=" " q="[" r="]"] q=~[[%leaf p="'foo'"] [%leaf p="'bar'"]]]
++skol
Pretty-print type to tank
Pretty-print type typ
to a tank
using ++duck:ut
.
Accepts
typ
is a type
.
Produces
A tank
.
Source
++ skol|= typ=type^- tank~(duck ut typ)
Examples
> (skol -:!>(['foo' 'bar']))[%rose p=[p=" " q="[" r="]"] q=~[[%leaf p="@t"] [%leaf p="@t"]]]
++slam
Slam a gate
Slam gat
, a gate in a vase
, with sam
, a sample in a vase
. Produces a vase
containing the result.
Accepts
gat
is a gate in a vase
.
sam
is a noun in a vase
.
Produces
A vase
.
Source
++ slam|= [gat=vase sam=vase] ^- vase=+ :- ^= typ ^- type[%cell p.gat p.sam]^= gen ^- hoon[%cnsg [%$ ~] [%$ 2] [%$ 3] ~]=+ gun=(~(mint ut typ) %noun gen)[p.gun (slum q.gat q.sam)]
Examples
> (slam !>(|=([a=@ud b=@ud] [b a])) !>([1 2]))[#t/[@ud @ud] q=[2 1]]
++slab
Test if contains
States whether you can access named wing cog
in type typ
using access method way
.
Accepts
way
is a ?(%read %rite %both)
(A $vial
without %free
). This represents the access method (read, write, or both read and write).
cog
is a @tas
, the name of a wing.
typ
is a type
.
Produces
A ?
.
Source
++ slab|= [way=?(%read %rite %both) cog=@tas typ=type]?= [%& *](~(fond ut typ) way ~[cog])
> =au |=(a=@ +(a))> (slab %read %a -:!>(au))%.y> (slab %rite %a -:!>(au))%.y> (slab %both %a -:!>(au))%.y> (slab %both %blah -:!>(au))%.n> =fe ^|(|=(a=@ +(a)))> (slab %read %a -:!>(fe))%.n> (slab %rite %a -:!>(fe))%.y> (slab %both %a -:!>(fe))%.n
++slap
Untyped vase .*
Compile hoon gen
with subject vax
using .*
, producing a vase
of the result.
Accepts
vax
is a noun in a vase
, and is the subject.
gen
is some hoon
.
Produces
A vase
.
Source
++ slap|= [vax=vase gen=hoon] ^- vase=+ gun=(~(mint ut p.vax) %noun gen)[p.gun .*(q.vax q.gun)]
Examples
> (slap !>(b='foo') (ream '|=(a=@t [a b])'))[#t/<1.qgm [a=@t b=@t]> q=[[[0 6] 0 7] 0 7.303.014]]> !<($-(@t [@t @t]) (slap !>(b='foo') (ream '|=(a=@t [a b])')))<1|xpg [@t @t @t @t]>> (!<($-(@t [@t @t]) (slap !>(b='foo') (ream '|=(a=@t [a b])'))) 'bar')['bar' 'foo']
++slog
Deify printf
Prints stack trace a
if the stack trace isn't null, then produces the other input. +slog
first takes a
, producing a gate. The gate then takes some hoon.
Accepts
a
is a tang
, and is the sample of +slog
.
(slog a)
takes some hoon
.
Produces
The result of the hoon given to (slog a)
, with a
printed to the terminal.
Source
++ slog=| pri=@|= a=tang ^+ same?~(a same ~>(%slog.[pri i.a] $(a t.a)))
Examples
foo> ((slog leaf+"foo" ~) (add 1 1))2
Discussion
slog
is intended to be put in the middle of a bunch of chained function calls that string a piece of data through them, so that an error message will be printed if there's one to print.
++mean
Crash and printf
Ends the program and prints a
, a tracing error message.
Accepts
a
is a tang
.
Produces
A crash, with a
printed to the terminal.
Source
++ mean|= a=tang^+ !!?~ a !!~_(i.a $(a t.a))
Examples
> (mean leaf+"foo" ~)foodojo: hoon expression failed
++road
Evaluate trap
Evaluate a trap
, producing the result if successful or else crashing with a trace.
Accepts
A trap
.
Produces
A noun.
Source
++ road|* =(trap *)^+ $:trap=/ res (mule trap)?- -.res%& p.res%| (mean p.res)==
Examples
> (road |.("foo"))"foo"> (road |.(~|('crash!' !!)))'crash!'dojo: hoon expression failed
++slew
Get axis in vase
Get axis axe
in vase vax
, producing the resulting vase
in a unit
which is null if the axis cannot be retrieved.
Accepts
axe
is an atom.
vax
is a vase
.
Produces
A (unit vase)
.
Source
++ slew|= [axe=@ vax=vase] ^- (unit vase)?. |- ^- ??: =(1 axe) &?. ?=(^ q.vax) |$(axe (mas axe), q.vax .*(q.vax [0 (cap axe)]))~`[(~(peek ut p.vax) %free axe) .*(q.vax [0 axe])]
Examples
> (slew 3 !>(['foo' 'bar']))[~ [#t/@t q=7.496.034]]> !<(@t (need (slew 3 !>(['foo' 'bar']))))'bar'> (slew 7 !>(['foo' 'bar']))~
++slim
Identical to ++seer
Convert a vise
(old vase
) to a vase
. Identical to ++seer
.
Accepts
old
is a vise
.
Produces
A vase
.
Source
++ slim|= old=vise ^- vaseold
Examples
> (slim !>('foo'))[#t/@t q=7.303.014]
++slit
Type of slam
The type
produced if a gate of type gat
were slammed with a sample of type sam
.
Accepts
gat
is a type
.
sam
is a type
.
Produces
A type
.
Source
++ slit|= [gat=type sam=type]?> (~(nest ut (~(peek ut gat) %free 6)) & sam)(~(play ut [%cell gat sam]) [%cnsg [%$ ~] [%$ 2] [%$ 3] ~])
Examples
> (slit -:!>(|*(a=@ [a a])) -:!>(42))#t/[@ud @ud]> (slit -:!>(|*(a=@ [a a])) -:!>('foo'))#t/[@t @t]
++slob
Superficial arm
Source
++ slob|= [cog=@tas typ=type]^- ??+ typ |[%hold *] $(typ ~(repo ut typ))[%hint *] $(typ ~(repo ut typ))[%core *]|- ^- ??~ q.r.q.typ |?| (~(has by q.q.n.q.r.q.typ) cog)$(q.r.q.typ l.q.r.q.typ)$(q.r.q.typ r.q.r.q.typ)====
++sloe
Get arms in core
Produces a list of the arms in a core of type typ
.
Accepts
typ
is a type.
Produces
A (list term)
.
Source
++ sloe|= typ=type^- (list term)?+ typ ~[%hold *] $(typ ~(repo ut typ))[%hint *] $(typ ~(repo ut typ))[%core *]%- zing%+ turn ~(tap by q.r.q.typ)|= [* b=tome]%+ turn ~(tap by q.b)|= [a=term *]a==
Examples
> (sloe -:!>(|=(@ 1)))~[%$]> =cr |%++ foo 1++ bar 2++ baz 3--> (sloe -:!>(cr))~[%foo %baz %bar]> (sloe -:!>(42))~
++slop
Cons two vases
Produce the vase of a cell of vases hed
and tal
.
Accepts
hed
is a vase
.
tal
is a vase
.
Produces
A vase
.
Source
++ slop|= [hed=vase tal=vase]^- vase[[%cell p.hed p.tal] [q.hed q.tal]]
Examples
> (slop !>('foo') !>(42))[#t/[@t @ud] q=[7.303.014 42]]> !<([@t @ud] (slop !>('foo') !>(42)))['foo' 42]
++slot
Got axis in vase
Get axis axe
in vase vax
, returning it in a vase
. Crashes if the axis cannot be retrieved.
Accepts
axe
is an atom.
vax
is a vase
.
Produces
A vase
.
Source
++ slot|= [axe=@ vax=vase] ^- vase[(~(peek ut p.vax) %free axe) .*(q.vax [0 axe])]
Examples
> (slot 3 !>(['foo' 'bar']))[#t/@t q=7.496.034]> !<(@t (slot 3 !>(['foo' 'bar'])))'bar'> (slot 7 !>(['foo' 'bar']))dojo: hoon expression failed
++slym
Slam without sample-type
Slam gat
, a gate in a vase
, with sam
, a noun
. The type of sam
is ignored and the type of the resulting vase is determined by the gate alone.
Accepts
gat
is a vase
.
sam
is a noun.
Produces
A vase
.
Source
++ slym|= [gat=vase sam=*] ^- vase(slap gat(+<.q sam) [%limb %$])
Examples
> (slym !>(|*(a=@ux [a a])) 'foo')[#t/[@ux @ux] q=[7.303.014 7.303.014]]> (slym !>(|*(a=@ux [a a])) "foobar")[#t/[@ux @ux] q=[[102 111 111 98 97 114 0] 102 111 111 98 97 114 0]]
++sped
Reconstruct type
Source
++ sped|= vax=vase^- vase:_ q.vax?@ q.vax (~(fuse ut p.vax) [%atom %$ ~])?@ -.q.vax^= typ%- ~(play ut p.vax)[%wtgr [%wtts [%leaf %tas -.q.vax] [%& 2]~] [%$ 1]](~(fuse ut p.vax) [%cell %noun %noun])
++swat
Deferred ++slap
This is the same as ++slap
except tap
is the subject vase
encapsulated in a trap
, and a (trap vase)
is produced.
Accepts
tap
is a (trap vase)
.
gen
is hoon
.
Produces
A (trap vase)
.
Source
++ swat|= [tap=(trap vase) gen=hoon]^- (trap vase)=/ gun (~(mint ut p:$:tap) %noun gen)|. ~+[p.gun .*(q:$:tap q.gun)]
Examples
> %. 10!< $-(@ @)%- road%+ swat|.(!>(add-42=(cury add 42)))(ream '|=(a=@ (add-42 a))')52