2c: Bit Arithmetic
+bex
+bexBinary exponent.
Computes the result of 2^a, where .a is a block size (see $bloq), producing an $atom.
Accepts
.a is a +bloq.
Produces
An $atom.
Source
++ bex
~/ %bex
|= a=bloq
^- @
?: =(0 a) 1
(mul 2 $(a (dec a)))Examples
> (bex 4)
16> (bex (add 19 1))
1.048.576> (bex 0)
1+can
+canAssemble.
Produces an $atom from a +list .b of length-value pairs .p and .q, where .p is the length in blocks of size .a, and .q is an $atomic value.
Accepts
.a is a block size (see +bloq).
.b is a +list of length-value pairs, .p and .q:
.pis a+step..qis a@.
Produces
An $atom.
Source
++ can
~/ %can
|= [a=bloq b=(list [p=step q=@])]
^- @
?~ b 0
(add (end [a p.i.b] q.i.b) (lsh [a p.i.b] $(b t.b)))Examples
> `@ub`21
0b1.0101> `@ub`(can 3 ~[[1 21]])
0b1.0101> `@ub`(can 3 ~[[1 1]])
0b1> `@ub`(can 0 ~[[1 255]])
0b1> `@ux`(can 3 [3 0xc1] [1 0xa] ~)
0xa00.00c1> `@ux`(can 3 [3 0xc1] [1 0xa] [1 0x23] ~)
0x23.0a00.00c1> `@ux`(can 4 [3 0xc1] [1 0xa] [1 0x23] ~)
0x23.000a.0000.0000.00c1> `@ux`(can 3 ~[[1 'a'] [2 'bc']])
0x63.6261+cat
+catConcatenate.
Concatenates two $atoms, .b and .c, according to block size .a, producing an $atom.
Accepts
.a is a block size (see +bloq).
.b is an $atom.
.c is an $atom.
Produces
An $atom.
Source
++ cat
~/ %cat
|= [a=bloq b=@ c=@]
(add (lsh [a (met a b)] c) b)Examples
> `@ub`(cat 3 1 0)
0b1> `@ub`(cat 0 1 1)
0b11> `@ub`(cat 0 2 1)
0b110> `@ub`(cat 2 1 1)
0b1.0001> `@ub`256
0b1.0000.0000> `@ub`255
0b1111.1111> `@ub`(cat 3 256 255)
0b1111.1111.0000.0001.0000.0000> `@ub`(cat 2 256 255)
0b1111.1111.0001.0000.0000> (cat 3 256 255)
16.711.936> (cat 2 256 255)
1.044.736+cut
+cutSlice.
Slices .c blocks of size .a that are positioned .b blocks from the end of .d. That slice is produced as an $atom.
Accepts
.a is a block size (see +bloq).
[b c] where:
.d is an $atom.
Produces
An $atom.
Source
++ cut
~/ %cut
|= [a=bloq [b=step c=step] d=@]
(end [a c] (rsh [a b] d))Examples
> (cut 0 [1 1] 2)
1> (cut 0 [2 1] 4)
1> `@t`(cut 3 [0 3] 'abcdefgh')
'abc'> `@t`(cut 3 [1 3] 'abcdefgh')
'bcd'> `@ub`(cut 0 [0 3] 0b1111.0000.1101)
0b101> `@ub`(cut 0 [0 6] 0b1111.0000.1101)
0b1101> `@ub`(cut 0 [4 6] 0b1111.0000.1101)
0b11.0000> `@ub`(cut 0 [3 6] 0b1111.0000.1101)
0b10.0001+end
+endTail.
Produces an $atom by taking the last +step blocks of size +bloq from .b.
Accepts
.a is an $atom slice specifier (see $bite), which is a block size (see +bloq) with optional block count.
.b is an $atom.
Produces
An $atom.
Source
++ end
~/ %end
|= [a=bite b=@]
=/ [=bloq =step] ?^(a a [a *step])
(mod b (bex (mul (bex bloq) step)))Examples
> (end [2 2] 255)
255> (end [3 1] 255)
255> (end 3 255)
255> (end 3 256)
0> `@ub`12
0b1100> `@ub`(end [0 3] 12)
0b100> (end [0 3] 12)
4> `@ub`(end [1 3] 12)
0b1100> (end [1 3] 12)
12> `@ux`'abc'
0x63.6261> `@ux`(end [3 2] 'abc')
0x6261> `@t`(end [3 2] 'abc')
'ab'+fil
+filFill bloqstream.
Produces an $atom by repeating .c for .b blocks of size .a.
Accepts
.a is a block size (see +bloq).
.b is a +step.
.c is an $atom.
Produces
An $atom.
Source
++ fil
~/ %fil
|= [a=bloq b=step c=@]
=| n=@ud
=. c (end a c)
=/ d c
|- ^- @
?: =(n b)
(rsh a d)
$(d (add c (lsh a d)), n +(n))Examples
> `@t`(fil 3 5 %a)
'aaaaa'> `@t`(fil 5 10 %ceeb)
'ceebceebceebceebceebceebceebceebceebceeb'> `@t`(fil 4 10 'eced')
'ecececececececececec'> `@tas`(fil 4 10 %bf)
%bfbfbfbfbfbfbfbfbfbf> `@ub`(fil 2 6 1)
0b1.0001.0001.0001.0001.0001+lsh
+lshLeft-shift.
Produces an $atom by left-shifting .b by +step blocks of size +bloq.
Accepts
.a is an $atom slice specifier (see $bite), which is a block size (see +bloq) with optional block count.
.b is an $atom.
Produces
An $atom.
Source
++ lsh
~/ %lsh
|= [a=bite b=@]
=/ [=bloq =step] ?^(a a [a *step])
(mul b (bex (mul (bex bloq) step)))Examples
> `@ub`1
0b1> `@ub`(lsh [0 1] 1)
0b10> (lsh [0 1] 1)
2> (lsh 0 1)
2> `@ub`255
0b1111.1111> `@ub`(lsh [3 1] 255)
0b1111.1111.0000.0000> (lsh [3 1] 255)
65.280+met
+metMeasure.
Computes the number of blocks of size .a in .b, producing an $atom.
Accepts
.a is a block size (see +bloq).
.b is an $atom.
Source
++ met
~/ %met
|= [a=bloq b=@]
^- @
=+ c=0
|-
?: =(0 b) c
$(b (rsh a b), c +(c))Examples
> (met 0 1)
1> (met 0 2)
2> (met 3 255)
1> (met 3 256)
2> (met 3 'abcde')
5+rap
+rapAssemble non-zero.
Concatenates a +list of $atoms .b using block size .a, producing an $atom.
Accepts
.a is a block size (see +bloq).
.b is a +list of $atoms.
Produces
An $atom.
Source
++ rap
~/ %rap
|= [a=bloq b=(list @)]
^- @
?~ b 0
(cat a i.b $(b t.b))Examples
> `@ub`(rap 2 [1 2 3 4 ~])
0b100.0011.0010.0001> `@ub`(rap 1 [1 2 3 4 ~])
0b1.0011.1001> (rap 0 [0 0 0 ~])
0> (rap 0 [1 0 1 ~])
3> `@ub`3
0b11> (rap 0 [0 1 0 0 1 2 ~])
11> (rap 0 [1 1 2 ~])
11> `@ub`11
0b1011Discussion
Any element of the value 0 is not included in concatenation.
+rep
+repAssemble single.
Produces an $atom by assembling a +list of $atoms .b using block size .a.
Accepts
.a is an $atom slice specifier (see $bite), which is a block size (see +bloq) with optional block count.
.b is a +list of $atoms.
Produces
An $atom.
Source
++ rep
~/ %rep
|= [a=bite b=(list @)]
=/ [=bloq =step] ?^(a a [a *step])
=| i=@ud
|- ^- @
?~ b 0
%+ add $(i +(i), b t.b)
(lsh [bloq (mul step i)] (end [bloq step] i.b))Examples
> `@ub`(rep 2 [1 2 3 4 ~])
0b100.0011.0010.0001> (rep 0 [0 0 1 ~])
4> (rep 0 [0 0 0 1 ~])
8> `@ub`(rep 0 [0 0 0 1 ~])
0b1000> `@ub`8
0b1000> `@ub`(rep 0 [1 0 1 0 ~])
0b101> `@ub`(rep 0 [1 2 3 4 ~])
0b101> (rep 0 [0 1 0 1 ~])
10> (rep 0 [1 0 1 0 1 ~])
21> `@ub`21
0b10.1010> `@ub`(rep 3 [12 166 8 34 ~])
0b10.0010.0000.1000.1010.0110.0000.1100> `*`"abcd"
[97 98 99 100 0]> `@t`(rep 3 "abcd")
'abcd'+rev
+revReverses block order, accounting for leading zeroes.
Produces an $atom from the bits of .dat in reverse order according to a block size .boz and a size .len.
If the total size is less than the length of .dat, then only the first bits of .dat up to the total size will be taken and reversed. If the total size is longer, trailing zeroes will be added.
Accepts
.boz is a block size with optional block count (see +bloq).
.len is a @ud of the number of blocks of size .boz to be reversed.
.dat is an $atom.
Produces
An $atom.
Source
++ rev
~/ %rev
|= [boz=bloq len=@ud dat=@]
^- @
=. dat (end [boz len] dat)
%+ lsh
[boz (sub len (met boz dat))]
(swp boz dat)Examples
> =a 0b1111.0000.1111.1010.0011
> `@ub`(rev 0 20 a)
0b1100.0101.1111.0000.1111
> `@ub`(rev 0 12 a)
0b1100.0101.1111
> `@ub`(rev 2 5 a)
0b11.1010.1111.0000.1111
> `@ub`(rev 2 4 a)
0b11.1010.1111.0000
> `@ub`(rev 2 6 a)
0b11.1010.1111.0000.1111.0000> (rev 1 10 1.000)
179.200> (rev 2 5 1.000)
582.400> (rev 1 5 1.000)
175+rip
+ripDisassemble.
Produces a +list of $atoms from the bits of .b using block size .a.
Accepts
.a is an $atom slice specifier (see $bite), which is a block size (see +bloq) with optional block count.
.b is an $atom.
Produces
A +list of $atoms.
Source
++ rip
~/ %rip
|= [a=bite b=@]
^- (list @)
?: =(0 b) ~
[(end a b) $(b (rsh a b))]Examples
> `@ub`155
0b1001.1011> (rip 0 155)
~[1 1 0 1 1 0 0 1]> (rip 2 155)
~[11 9]> (rip 0 11)
~[1 1 0 1]
> (rip 1 155)
~[3 2 1 2]> `@ub`256
0b1.0000.0000> (rip 0 256)
~[0 0 0 0 0 0 0 0 1]> (rip 2 256)
~[0 0 1]> (rip 3 256)
~[0 1]> `tape`(rip 3 'abcd')
"abcd"+rsh
+rshRight-shift.
Right-shifts .b by +step blocks of size +bloq, producing an $atom.
Accepts
.a is an $atom slice specifier (see $bite), which is a block size (see +bloq) with optional block count.
.b is an $atom.
Produces
An $atom.
Source
++ rsh
~/ %rsh
|= [a=bite b=@]
=/ [=bloq =step] ?^(a a [a *step])
(div b (bex (mul (bex bloq) step)))Examples
> `@ub`145
0b1001.0001> `@ub`(rsh [1 1] 145)
0b10.0100> (rsh [1 1] 145)
36> (rsh 1 145)
36> `@ub`(rsh [2 1] 145)
0b1001> (rsh [2 1] 145)
9> `@ub`10
0b1010> `@ub`(rsh [0 1] 10)
0b101> (rsh [0 1] 10)
5> `@ux`'abc'
0x63.6261> `@t`(rsh [3 1] 'abc')
'bc'> `@ux`(rsh [3 1] 'abc')
0x6362+run
+run+turn into $atom.
Disassembles $atom .b into slices specified by .a, applies .c to each slice, and reassembles the results back into an $atom.
Accepts
.a is an $atom slice specifier (see $bite), which is a block size (see +bloq) with optional block count.
.b is an $atom.
.c is a gate that accepts an $atom and produces an $atom.
Produces
An $atom.
Source
++ run
~/ %run
|= [a=bite b=@ c=$-(@ @)]
(rep a (turn (rip a b) c))Examples
> `@ux`65.535
0xffff> `@ux`(run 2 65.535 dec)
0xeeee+rut
+rut+turn into +list.
Disassembles $atom .b into slices specified by .a, applies .c to each slice, and assembles the results back into a.
Accepts
.a is an $atom slice specifier (see $bite), which is a block size (see +bloq) with optional block count.
.b is an $atom.
.c is a gate that accepts an $atom.
Produces
A +list.
Source
++ rut
~/ %rut
|* [a=bite b=@ c=$-(@ *)]
(turn (rip a b) c)Examples
> `@ux`65.535
0xffff> `(list @ux)`(rut 2 65.535 dec)
~[0xe 0xe 0xe 0xe]+sew
+sewStitch one $atom into another.
Replace .c blocks of size .a at offset .b of $atom .e with .c blocks of size .a from $atom .d.
That is, take (end [a c] d) from .d and overwrite the (cut a [b c] e) part of .e.
Or in simpler terms, take from the start of .d and replace some part of .e with it.
Accepts
.a is a $bloq (block size).
[b c d] where:
.bis a step specifying the number of+bloqs to offset..bis a step specifying the number of+bloqs to replace..dis the donor$atom.
.e is the recipient $atom.
Produces
An $atom.
Source
++ sew
~/ %sew
|= [a=bloq [b=step c=step d=@] e=@]
^- @
%+ add
(can a b^e c^d ~)
=/ f [a (add b c)]
(lsh f (rsh f e))Examples
> `@t`(sew 3 [0 0 'XXXX'] 'OOOO')
'OOOO'> `@t`(sew 3 [0 1 'XXXX'] 'OOOO')
'XOOO'> `@t`(sew 3 [2 1 'XXXX'] 'OOOO')
'OOXO'> `@t`(sew 3 [2 2 'XXXX'] 'OOOO')
'OOXX'> `@t`(sew 3 [0 4 'XXXX'] 'OOOO')
'XXXX'+swp
+swpReverse block order.
Switches little-endian to big-endian and vice versa: produces an $atom by reversing the block order of .b using block size .a.
Accepts
.a is a block size (see +bloq).
.b is an $atom.
Produces
An $atom.
Source
++ swp
~/ %swp
|= [a=bloq b=@]
(rep a (flop (rip a b)))Examples
> `@ub`24
0b1.1000> (swp 0 24)
3> `@ub`3
0b11> (swp 0 0)
0> (swp 0 128)
1+xeb
+xebBinary logarithm.
Computes the base-2 logarithm of .a, producing an $atom.
Accepts
.a is an $atom.
Produces
An $atom.
Source
++ xeb
~/ %xeb
|= a=@
^- @
(met 0 a)Examples
> (xeb 31)
5> (xeb 32)
6> (xeb 49)
6> (xeb 0)
0> (xeb 1)
1> (xeb 2)
2+fe
+feModulo bloq.
Core that contains arms for +bloq and modular integer operations.
Accepts
.a is a +bloq.
Source
|_ a=bloq
:: ...+dif:fe
+dif:feProduces the difference between two $atoms in the modular basis representation.
Accepts
.a is a +bloq (and is the sample of the parent core).
.b is an $atom.
.c is an $atom.
Produces
A @s.
Source
++ dif
|=([b=@ c=@] (sit (sub (add out (sit b)) (sit c))))Examples
> (~(dif fe 3) 63 64)
255> (~(dif fe 3) 5 10)
251> (~(dif fe 3) 0 1)
255> (~(dif fe 0) 9 10)
1> (~(dif fe 0) 9 11)
0> (~(dif fe 0) 9 12)
1> (~(dif fe 2) 9 12)
13> (~(dif fe 2) 63 64)
15+inv:fe
+inv:feInverse.
Inverts the order of the modular field.
Accepts
.a is a +bloq (and is the sample of the parent core).
.b is a +bloq. (see +bloq)
Produces
An $atom.
Source
++ inv |=(b=@ (sub (dec out) (sit b)))Examples
> (~(inv fe 3) 255)
0> (~(inv fe 3) 256)
255> (~(inv fe 3) 0)
255> (~(inv fe 3) 1)
254> (~(inv fe 3) 2)
253> (~(inv fe 3) 55)
200+net:fe
+net:feFlip endianness.
Reverses bytes within a block.
Accepts
.a is a +bloq (and the sample of the parent core).
.b is a +bloq (see +bloq).
Produces
An $atom.
Source
++ net |= b=@ ^- @
=> .(b (sit b))
?: (lte a 3)
b
=+ c=(dec a)
%+ con
(lsh c $(a c, b (cut c [0 1] b)))
$(a c, b (cut c [1 1] b))Examples
> (~(net fe 3) 64)
64> (~(net fe 3) 128)
128> (~(net fe 3) 255)
255> (~(net fe 3) 256)
0> (~(net fe 3) 257)
1> (~(net fe 3) 500)
244> (~(net fe 3) 511)
255> (~(net fe 3) 512)
0> (~(net fe 3) 513)
1> (~(net fe 3) 0)
0> (~(net fe 3) 1)
1> (~(net fe 0) 1)
1> (~(net fe 0) 2)
0> (~(net fe 0) 3)
1> (~(net fe 6) 1)
72.057.594.037.927.936> (~(net fe 6) 2)
144.115.188.075.855.872> (~(net fe 6) 3)
216.172.782.113.783.808> (~(net fe 6) 4)
288.230.376.151.711.744> (~(net fe 6) 5)
360.287.970.189.639.680+out:fe
+out:feMax integer value.
Produces the maximum integer value that the current block can store; 2^a^a.
Accepts
.a is a +bloq (and is the sample of the parent core).
Produces
An $atom.
Source
++ out (bex (bex a))Examples
> ~(out fe 0)
2> ~(out fe 1)
4> ~(out fe 2)
16> ~(out fe 3)
256> ~(out fe 4)
65.536> ~(out fe 10)
179.769.313.486.231.590.772.930.519.078.902.473.361.797.697.894.230.657.273.430.081.157.732.675.805.500.963.132.708.477.322.407.536.021.120.113.879.871.393.357.658.789.768.814.416.622.492.847.430.639.474.124.377.767.893.424.865.485.276.302.219.601.246.094.119.453.082.952.085.005.768.838.150.682.342.462.881.473.913.110.540.827.237.163.350.510.684.586.298.239.947.245.938.479.716.304.835.356.329.624.224.137.216+rol:fe
+rol:feRoll left.
Rolls .d to the left by .c .b-sized blocks.
Accepts
.a is a +bloq (and is the sample of the parent core).
.b is a +bloq.
.c is an $atom.
.d is an $atom.
Produces
An $atom.
Source
++ rol |= [b=bloq c=@ d=@] ^- @
=+ e=(sit d)
=+ f=(bex (sub a b))
=+ g=(mod c f)
(sit (con (lsh [b g] e) (rsh [b (sub f g)] e)))Examples
> `@ux`(~(rol fe 6) 4 3 0xabac.dedf.1213)
0x1213.0000.abac.dedf> `@ux`(~(rol fe 6) 4 2 0xabac.dedf.1213)
0xdedf.1213.0000.abac> `@t`(~(rol fe 5) 3 1 'dfgh')
'hdfg'> `@t`(~(rol fe 5) 3 2 'dfgh')
'ghdf'> `@t`(~(rol fe 5) 3 0 'dfgh')
'dfgh'+ror:fe
+ror:feRoll right.
Rolls .d to the right by .c .b-sized blocks.
Accepts
.a is a +bloq (and is the sample of the parent core).
.b is a +bloq.
.c is an $atom.
.d is an $atom.
Produces
An $atom.
Source
++ ror |= [b=bloq c=@ d=@] ^- @
=+ e=(sit d)
=+ f=(bex (sub a b))
=+ g=(mod c f)
(sit (con (rsh [b g] e) (lsh [b (sub f g)] e)))Examples
> `@ux`(~(ror fe 6) 4 1 0xabac.dedf.1213)
0x1213.0000.abac.dedf> `@ux`(~(ror fe 6) 3 5 0xabac.dedf.1213)
0xacde.df12.1300.00ab> `@ux`(~(ror fe 6) 3 3 0xabac.dedf.1213)
0xdf12.1300.00ab.acde> `@t`(~(rol fe 5) 3 0 'hijk')
'hijk'> `@t`(~(rol fe 5) 3 1 'hijk')
'khij'> `@t`(~(rol fe 5) 3 2 'hijk')
'jkhi'+sum:fe
+sum:feSum.
Sums two numbers in this modular field.
Accepts
.a is a +bloq (and is the sample of the parent core).
.b is an $atom.
.c is an $atom.
Produces
An $atom.
Source
++ sum |=([b=@ c=@] (sit (add b c)))Examples
> (~(sum fe 3) 10 250)
4> (~(sum fe 0) 0 1)
1> (~(sum fe 0) 0 2)
0> (~(sum fe 2) 14 2)
0> (~(sum fe 2) 14 3)
1> (~(sum fe 4) 10.000 256)
10.256> (~(sum fe 4) 10.000 100.000)
44.464+sit:fe
+sit:feEnforce modulo.
Produces an $atom in the current modular block representation.
Accepts
.a is a +bloq (and is the sample of the parent core).
.b is an $atom.
Produces
An $atom.
Source
++ sit |=(b=@ (end a b))Examples
> (~(sit fe 3) 255)
255> (~(sit fe 3) 256)
0> (~(sit fe 3) 257)
1> (~(sit fe 2) 257)
1> (~(sit fe 2) 10.000)
0> (~(sit fe 2) 100)
4> (~(sit fe 2) 19)
3> (~(sit fe 2) 17)
1> (~(sit fe 0) 17)
1> (~(sit fe 0) 0)
0> (~(sit fe 0) 1)
1Last updated