2a: Unit Logic
+biff
+biff
A +unit
as argument.
Applies a $gate
.b
that produces a +unit
to the unwrapped value of +unit
.a
(.u.a
). If .a
is empty, ~
is produced.
Accepts
.a
is a +unit
.
.b
is a $gate
that accepts a $noun
and produces a +unit
.
Produces
A +unit
.
Source
++ biff
|* [a=(unit) b=$-(* (unit))]
?~ a ~
(b u.a)
Examples
> (biff (some 5) |=(a=@ (some (add a 2))))
[~ u=7]
> (biff ~ |=(a=@ (some (add a 2))))
~
+bind
+bind
Non-unit $gate
to +unit
, producing +unit
.
Applies a $gate
.b
to the value (.u.a
) of a +unit
.a
, producing a +unit
. Used when you want a $gate
that does not accept or produce a +unit
to both accept and produce a +unit
.
Accepts
.a
is a +unit
.
.b
is a gate.
Produces
A +unit
.
Source
++ bind
|* [a=(unit) b=gate]
?~ a ~
[~ u=(b u.a)]
Examples
> (bind ((unit @) [~ 97]) ,@t)
[~ u='a']
> =a |=(a=@ (add a 1))
> (bind ((unit @) [~ 2]) a)
[~ u=3]
+bond
+bond
Replace null.
Replaces an empty +unit
.b
with the product of a called +trap
.a
. If the +unit
is not empty, then the original +unit
is produced.
Accepts
.a
is a +trap
.
.b
is a +unit
.
Produces
Either the product of .a
or the value inside of +unit
.b
.
Source
++ bond
|* a=(trap)
|* b=(unit)
?~ b $:a
u.b
Examples
> (bex 10)
1.024
> ((bond |.((bex 10))) ~)
1.024
> ((bond |.((bex 10))) (slaw %ud '123'))
123
+both
+both
Group +unit
values into pair.
Produces ~
if either .a
or .b
are empty. Otherwise, produces a +unit
whose value is a cell of the values of two input +unit
s .a
and .b
.
Accepts
.a
is a +unit
.
.b
is a +unit
.
Produces
A +unit
of the two initial values.
Source
++ both
|* [a=(unit) b=(unit)]
?~ a ~
?~ b ~
[~ u=[u.a u.b]]
Examples
> (both (some 1) (some %b))
[~ u=[1 %b]]
> (both ~ (some %b))
~
+clap
+clap
Combine two +unit
s with a gate.
Applies a binary $gate
.c
(which does not usually accept or produce a +unit
) to the values of two +unit
s, .a
and .b
, producing a +unit
.
If .a
is null, produces .b
. If .b
is null, produces .a
. Otherwise, produces the product of .c
in a +unit
.
Accepts
.a
is a +unit
.
.b
is a +unit
.
.c
is a $gate
that performs a binary operation.
Produces
A +unit
.
Source
++ clap
|* [a=(unit) b=(unit) c=_=>(~ |=(^ +<-))]
?~ a b
?~ b a
[~ u=(c u.a u.b)]
Examples
> (clap ~ `'b' |=([a=@tD b=@tD] `tape`[a b ~]))
[~ u='b']
> (clap `'a' ~ |=([a=@tD b=@tD] `tape`[a b ~]))
[~ u='a']
> (clap `'a' `'b' |=([a=@tD b=@tD] `tape`[a b ~]))
[~ u="ab"]
+clef
+clef
Compose two +unit
s with a gate.
Applies a binary $gate
.c
(which does not usually accept +unit
s) to the values of two +unit
s, .a
and .b
, producing a +unit
.
If .a
or .b
are null, produces null. Otherwise, produces the produce of .c
.
Accepts
.a
is a +unit
.
.b
is a +unit
.
.c
is a $gate
that takes a +cell
and produces a +unit
.
Produces
A +unit
.
Source
++ clef
|* [a=(unit) b=(unit) c=_=>(~ |=(^ `+<-))]
?~ a ~
?~ b ~
(c u.a u.b)
Examples
> (clef ~ `'b' |=([a=@tD b=@tD] `(unit tape)`[~ [a b ~]]))
~
> (clef `'a' ~ |=([a=@tD b=@tD] `(unit tape)`[~ [a b ~]]))
~
> (clef `'a' `'b' |=([a=@tD b=@tD] `(unit tape)`[~ [a b ~]]))
[~ "ab"]
+drop
+drop
Convert a +unit
to a list.
Makes a +list
of the unwrapped value (.u.a
) of a +unit
.a
.
Accepts
.a
is a +unit
.
Produces
A list.
Source
++ drop
|* a=(unit)
?~ a ~
[i=u.a t=~]
Examples
> =a ((unit @) [~ 97])
> (drop a)
[i=97 t=~]
> =a ((unit @) [~])
> (drop a)
~
+fall
+fall
Give +unit
a default value.
Produces a default value .b
for a +unit
.a
in cases where .a
is null.
Accepts
.a
is a +unit
.
.b
is a $noun
that's used as the default value.
Produces
Either a $noun
.b
or the unwrapped value of +unit
.a
.
Source
++ fall
|* [a=(unit) b=*]
?~(a b u.a)
Examples
> (fall ~ 'a')
'a'
> (fall [~ u=0] 'a')
0
+flit
+flit
Make filter.
Accepts $gate
.a
which produces a $flag
. Applies .a
to .b
, producing .b
wrapped in a +unit
if true, otherwise produces null.
+flit
is a wet $gate
that takes .a
and produces a new wet $gate
that takes .b
.
Accepts
.a
is a $gate
which produces a $flag
, and is the sample of the outer wet gate.
.b
is any $noun
, and is the sample of the inner wet gate.
Produces
A (unit [type])
, where [type]
is the type of .b
.
Source
++ flit
|* a=$-(* ?)
|* b=*
?.((a b) ~ [~ u=b])
Examples
> =f (flit |=(=@ud ?:(=(ud 1) %.y %.n)))
> (f 1)
[~ 1]
> (f 2)
~
+hunt
+hunt
First of units.
Apply binary $gate
.ord
, which produces a $flag
, to units .a
and .b
. Produce .a
if true and .b
if false. If .a
is null, produce .b
. If .b
is null, produce .a
.
This allows selecting between two units by some rule.
Accepts
.ord
is a $-(^ ?)
- a binary $gate
that produces a $flag
.
.a
is a +unit
.
.b
is a +unit
.
Produces
A +unit
.
Source
++ hunt
|* [ord=$-(^ ?) a=(unit) b=(unit)]
^- %- unit
$? _?>(?=(^ a) u.a)
_?>(?=(^ b) u.b)
==
?~ a b
?~ b a
?:((ord u.a u.b) a b)
Examples
> (hunt gte ~ `20)
[~ 20]
> (hunt gte `10 ~)
[~ 10]
> (hunt gte `10 `20)
[~ 20]
+lift
+lift
Curried bind.
Accepts $gate
.a
and produces a $gate
that accepts +unit
.b
to which it applies .a
. Used when you want a $gate
that does not accept or produce a +unit
to both accept and produce a +unit
.
Accepts
.a
is a $mold
.
.b
is a +unit
.
Produces
A +unit
.
Source
++ lift
|* a=mold
|* b=(unit)
(bind b a)
Examples
> ((lift dec) `(unit @)`~)
~
> ((lift dec) `(unit @)`[~ 20])
[~ 19]
+mate
+mate
Choose.
Accepts two +unit
s .a
and .b
whose values are expected to be equivalent. If either is empty, then the value of the other is produced. If neither are empty, it asserts that both values are the same and produces that value. If the assertion fails, +mate
crashes with 'mate'
in the stack trace.
Accepts
.a
is a +unit
.
.b
is a +unit
.
Produces
A +unit
or crash.
Source
++ mate
|* [a=(unit) b=(unit)]
?~ b a
?~ a b
?.(=(u.a u.b) ~>(%mean.'mate' !!) a)
Examples
> =a ((unit @) [~ 97])
> =b ((unit @) [~ 97])
> (mate a b)
[~ 97]
> =a ((unit @) [~ 97])
> =b ((unit @) [~])
> (mate a b)
[~ 97]
> =a ((unit @) [~ 97])
> =b ((unit @) [~ 98])
> (mate a b)
! 'mate'
! exit
+need
+need
Unwrap +unit
.
Retrieve the value from a +unit
and crash if the +unit
is null.
Accepts
.a
is a +unit
.
Produces
Either the unwrapped value of .a
(.u.a
), or crash.
Source
++ need
~/ %need
|* a=(unit)
?~ a ~>(%mean.'need' !!)
u.a
Examples
> =a ((unit [@t @t]) [~ ['a' 'b']])
> (need a)
['a' 'b']
> =a ((unit @ud) [~ 17])
> (need a)
17
> =a ((unit @) [~])
> (need a)
! exit
+some
+some
Wrap value in a +unit
.
Takes any $noun
.a
and produces a +unit
with the value set to .a
.
Accepts
.a
is a $noun
.
Produces
A +unit
.
Source
++ some
|* a=*
[~ u=a]
Examples
> (some ['a' 'b'])
[~ u=['a' 'b']]
> (some &)
[~ u=%.y]
Last updated