ff5 Sheet
ff5 Sheet
( n1 n2 n3 -- n1*n2/n3 )
Uses 32-bit intermediate result.
for PIC and AVR Microcontrollers .
u.
Display a number. ( n -- )
Display u unsigned. ( u -- )
*/mod Scale with remainder. ( n1 n2 n3 -- n.rem n.quot )
Uses 32-bit intermediate result.
u.r Display u with field width n, 0 < n < 256. ( u n -- ) u*/mod Unsigned Scale u1*u2/u3 ( u1 u2 u3 -- u.rem u.quot )
d. Display double number. ( d -- ) Uses 32-bit intermediate result.
Interpreter ud. Display unsigned double number. ( ud -- ) abs Absolute value. ( n -- u )
The outer interpreter looks for words and numbers delimited by .s Display stack content (nondestructively). negate Negate n. ( n -- -n )
whitespace. Everything is interpreted as a word or a number. .st Emit status string for base, current data section, ?negate Negate n1 if n2 is negative. ( n1 n2 -- n3 )
Numbers are pushed onto the stack. Words are looked up and acted and display the stack contents. ( -- ) min Leave minimum. ( n1 n2 -- n )
upon. Names of words are limited to 15 characters. Some words are ? Display content at address. ( addr -- ) PIC24-30-33 max Leave maximum. ( n1 n2 -- n )
compile-time use only and cannot be used interpretively. These are dump Display memory from address, for u bytes. ( addr u -- ) umin Unsigned minimum. ( u1 u2 -- u )
coloured blue. umax Unsigned maximum. ( u1 u2 -- u )
Stack manipulation
dup Duplicate top item. ( x -- x x )
Data and the stack ?dup Duplicate top item if nonzero. ( x -- 0 | x x )
swap Swap top two items. ( x1 x2 -- x2 x1 ) Arithmetic with double-cell numbers
The data stack (S:) is directly accessible and has 32 16-bit cells for
over Copy second item to top. ( x1 x2 -- x1 x2 x1 )
holding numerical values. Functions get their arguments from the
drop Discard top item. ( x -- )
stack and leave their results there as well. There is also a return Some of these words require core.txt, math.txt and qmath.txt.
nip Remove x1 from the stack. ( x1 x2 -- x2 )
address stack (R:) that can be used for temporary storage. d+ Add double numbers. ( d1 d2 -- d1+d2 )
rot Rotate top three items. ( x1 x2 x3 -- x2 x3 x1 )
tuck Insert x2 below x1 in the stack. ( x1 x2 -- x2 x1 x2 ) d- Subtract double numbers. ( d1 d2 -- d1-d2 )
Notation pick Duplicate the u-th item on top. m+ Add single cell to double number. ( d1 n -- d2 )
( xu ... x0 u -- xu ... x0 xu ) m* Signed 16*16 to 32-bit multiply. ( n n -- d )
n, n1, n2, n3 Single-cell integers (16-bit). d2* Multiply by 2. ( d -- d )
2dup Duplicate top double-cell item. ( d -- d d )
u, u1, u2 Unsigned integers (16-bit). d2/ Divide by 2. ( d -- d )
2swap Swap top two double-cell items. ( d1 d2 -- d2 d1 )
x, x1, x2, x3 Single-cell item (16-bit). um* Unsigned 16x16 to 32 bit multiply. ( u1 u2 -- ud )
2over Copy second double item to top. ( d1 d2 -- d1 d2 d1 )
c Character value (8-bit). ud* Unsigned 32x16 to 32-bit multiply. ( ud u -- ud )
2drop Discard top double-cell item. ( d -- )
d ud Double-cell signed and unsigned (32-bit). um/mod Unsigned division. ( ud u1 -- u.rem u.quot )
t ut Triple-cell signed and unsigned (48-bit). >r Send to return stack. S:( n -- ) R:( -- n )
r> Take from return stack. S:( -- n ) R:( n -- ) 32-bit/16-bit to 16-bit
q uq Quad-cell signed and unsigned (64-bit). ud/mod Unsigned division. ( ud u1 -- u.rem ud.quot )
f Boolean flag: 0 is false, -1 is true. r@ Copy top item of return stack. S:( -- n ) R:( n -- n )
rdrop Discard top item of return stack. S:( -- ) R:( n -- ) 32-bit/16-bit to 32-bit
flt flt1 flt3 Floating-point value (32-bit). fm/mod Floored division. ( d n -- n.rem n.quot )
PIC24-30-33 only, with build option. sp@ Leave data stack pointer. ( -- addr )
sm/rem Symmetric division. ( d n -- n.rem n.quot )
addr, addr1, addr2 16-bit addresses. sp! Set the data stack pointer to address. ( addr -- )
32-bit/16-bit to 16-bit.
a-addr cell-aligned address. m*/ Scale with triple intermediate result. d2 = d1*n1/n2
c-addr character or byte address. Operators ( d1 n1 n2 -- d2 )
Arithmetic with single-cell numbers um*/ Scale with triple intermediate result. ud2 = ud1*u1/u2
Numbers and values ( ud1 u1 u2 -- ud2)
Some of these words require core.txt and math.txt. dabs Absolute value. ( d -- ud )
2 Leave integer two onto the stack. ( -- 2 ) + Add. ( n1 n2 -- n1+n2 ) sum dnegate Negate double number. ( d -- -d )
#255 Leave decimal 255 onto the stack. ( -- 255 ) - Subtract. ( n1 n2 -- n1-n2 ) difference ?dnegate Negate d if n is negative. ( d n -- -d )
%11 Leave integer three onto the stack. ( -- 3 ) * Multiply. ( n1 n2 -- n1*n2 ) product
$10 Leave integer sixteen onto the stack. ( -- 16 ) / Divide. ( n1 n2 -- n1/n2 ) quotient
23. Leave double number on the stack. ( -- 23 0 ) mod Divide. ( n1 n2 -- n.rem ) remainder Arithmetic with triple- and quad-numbers
decimal Set number format to base 10. ( -- ) /mod Divide. ( n1 n2 -- n.rem n.quot )
hex Set number format to hexadecimal. ( -- ) u/ Unsigned 16/16 to 16-bit division. ( u1 u2 -- u2/u1 )
bin Set number format to binary. ( -- ) u/mod Unsigned division. ( u1 u2 -- u.rem u.quot ) For PIC18, these words require core.txt, math.txt and qmath.txt.
s>d Sign extend single to double number. ( n -- d ) 16-bit/16-bit to 16-bit q+ Add a quad to a quad. ( q1 q2 -- q3 )
Since double numbers have the most significant bits 1 Leave one. ( -- 1 ) For PIC24-30-33.
in the cell above the least significant bits, you can 1+ Add one. ( n -- n1 ) qm+ Add double to a quad. ( q1 d -- q2 )
just drop the top cell to recover the single number, 1- Subtract one. ( n -- n1 ) For PIC18 and PIC24-30-33.
provided that the value is not too large to fit in a 2+ Add two. ( n -- n1 ) uq* Unsigned 32x32 to 64-bit multiply. ( ud ud -- uq )
single cell. 2- Subtract 2 from n. ( n -- n1 ) For PIC18 and PIC24-30-33.
d>q Extend double to quad-cell number. ( d -- q ) 2* Multiply by 2; Shift left by one bit. ( u -- u1 ) ut* Unsigned 32x16 to 48-bit multiply. ( ud u -- ut )
Requires qmath.h to be loaded. PIC18, PIC24-30-33. 2/ Divide by 2; Shift right by one bit. ( u -- u1 ) ut/ Divide triple by single. ( ut u -- ud )
uq/mod Divide quad by double. ( uq ud -- ud-rem ud-quot )
Relational AVR8 Memory map The following come from bit.txt
= Leave true if x1 x2 are equal. ( x1 x2 -- f ) bit1: name Define a word to set a bit. ( addr bit -- )
<> Leave true if x1 x2 are not equal. ( x1 x2 -- f ) All operations are restricted to 64kB byte address space that is bit0: name Define a word to clear a bit. ( addr bit -- )
< Leave true if n1 less than n2. ( n1 n2 -- f ) divided into: bit?: name Define a word to test a bit. ( addr bit -- )
$0000 – (RAMSIZE-1) SRAM
> Leave true if n1 greater than n2. ( n1 n2 -- f ) When executed, name leaves a flag. ( -- f )
RAMSIZE – (RAMSIZE+EEPROMSIZE-1) EEPROM
0= Leave true if n is zero. ( n -- f )
($ffff-FLASHSIZE+1) – $ffff Flash
Inverts logical value.
The SRAM space includes the IO-space and special function
0< Leave true if n is negative. ( n -- f )
registers. The high memory mark for the Flash context is set by the
within Leave true if xl <= x < xh. ( x xl xh -- f )
u< Leave true if u1 < u2. ( u1 u2 -- f )
combined size of the boot area and FF kernel. The Dictionary
u> Leave true if u1 > u2. ( u1 u2 -- f )
d= Leave true if d1 d2 are equal. ( d1 d2 -- f ) Dictionary management
Memory Context
d0= Leave true if d is zero. ( d -- f )
d0< Leave true if d is negative. ( d -- f ) ram Set address context to SRAM. ( -- ) marker -my-mark Mark the dictionary and memory
d< Leave true if d1 < d2. ( d1 d2 -- f ) eeprom Set address context to EEPROM. ( -- ) allocation state with -my-mark.
d> Leave true if d1 > d2. ( d1 d2 -- f ) flash Set address context to Flash. ( -- ) -my-mark Return to the dictionary and allotted-memory
fl- Disable writes to Flash, EEPROM. ( -- ) state that existed before -my-mark was created.
Bitwise find name Find name in dictionary. ( -- n )
invert Ones complement. ( x -- x ) fl+ Enable writes to Flash, EEPROM, default. ( -- )
iflush Flush the flash write buffer. ( -- ) Leave 1 immediate, -1 normal, 0 not found.
dinvert Invert double number. ( du -- du ) forget name Forget dictionary entries back to name.
and Bitwise and. ( x1 x2 -- x ) here Leave the current data section dictionary
empty Reset all dictionary and allotted-memory
or Bitwise or. ( x1 x2 -- x ) pointer. ( -- addr )
pointers. ( -- )
xor Bitwise exclusive-or. ( x -- x ) align Align the current data section dictionary
words List words in dictionary. ( -- )
lshift Left shift by u bits. ( x1 u -- x2 ) pointer to cell boundary. ( -- )
rshift Right shift by u bits. ( x1 u -- x2 ) hi Leave the high limit of the current
data space. ( -- u )
Defining constants and variables
Memory
Typically, the microcontroller has three distinct memory contexts: Accessing Memory constant name Define new constant. ( n -- )
Flash, EEPROM and SRAM. FlashForth unifies these memory 2constant name Define double constant. ( x x -- )
! Store x to address. ( x a-addr -- )
spaces into a single 64kB address space. name Leave value on stack. ( -- n )
@ Fetch from address. ( a-addr -- x )
@+ Fetch cell and increment address by cell size. variable varname Define a variable in the current data
PIC18 Memory map ( a-addr1 -- a-addr2 x ) section. ( -- )
The address ranges are: 2! Store 2 cells to address. ( x1 x2 a-addr -- ) Use ram, eeprom or flash to set data section.
$0000 – $ebff Flash 2@ Fetch 2 cells from address. ( a-addr -- x1 x2 ) 2variable name Define double variable. ( -- )
$ec00 – $efff EEPROM c! Store character to address. ( c addr -- ) varname Leave address on stack. ( -- addr )
$f000 – $ff5f SRAM, general use c@ Fetch character from address. ( addr -- c ) value valname Define value. ( n -- )
$ff60 – $ffff SRAM, special function registers c@+ Fetch char, increment address. to valname Assign new value to valname. ( n -- )
The high memory mark for each context will depend on the ( addr1 -- addr2 c ) valname Leave value on stack. ( -- n )
particular device used. Using a PIC18F26K22 and the default values +! Add n to cell at address. ( n addr -- ) user name Define a user variable at offset +n. ( +n -- )
in p18f-main.cfg for the UART version of FF, a total of 423 bytes -@ Fetch from addr and decrement addr by 2.
is dedicated to the FF system. The rest (3473 bytes) is free for ( addr1 -- addr2 x )
application use. Also, the full 64kB of Flash memory is truncated to cf! Store to Flash memory. ( dataL dataH addr -- )
fit within the range specified above. PIC24-30-33 only. Examples
cf@ Fetch from Flash memory. ( addr -- dataL dataH )
PIC24 Memory map PIC24-30-33 only. ram Set SRAM context for variables and
>a Write to the A register. ( x -- ) values. Be careful not to accidentally
A device with EEPROM will have its 64kB address space divided
a> Read from the A register. ( -- x ) define variables in EEPROM or Flash
into:
$0000 – $07ff SRAM, special function registers memory. That memory wears quickly
$0800 – ($0800+RAMSIZE-1) SRAM, general use with multiple writes.
($0800+RAMSIZE) – $fbff Flash Accessing bits in RAM $ff81 constant portb Define constant in Flash.
$fc00 – $ffff EEPROM 3 value xx Define value in SRAM.
The high memory mark for the Flash context will depend on the mset Set bits in file register with mask c. ( c addr -- ) variable yy Define variable in SRAM.
device. Also, the full Flash memory of the device may not be For PIC24-30-33, the mask is 16 bits. 6 yy ! Store 6 in variable yy.
accessible. mclr Clear bits in file register with mask c. ( c addr -- ) eeprom 5 value zz ram Define value in EEPROM.
mtst AND file register byte with mask c. ( c addr -- x ) xx yy zz portb yy @ Leaves 3 f172 5 ff81 6
warm Warm restart clears SRAM data. : mk-byte-array Defining word ( n -- ) Predefined variables
xx yy zz portb yy @ Leaves 0 f172 5 ff81 0 create allot ...to make byte array objects
base Variable containing number base. ( -- a-addr )
4 to xx Sets new value. does> + ; ...as shown in FF user’s guide.
irq Interrupt vector (SRAM variable). ( -- a-addr )
xx yy zz portb yy @ Leaves 4 f172 5 ff81 0 10 mk-byte-array my-bytes Creates an array object
Always disable user interrupts and clear
hi here - u. Prints the number of bytes free. my-bytes ( n -- addr ).
related interrupt enable bits before zeroing
$ff8a constant latb PortB latch for the PIC18. 18 0 my-bytes c! Sets an element
interrupt vector.
$ff93 constant trisb PortB direction-control register. 21 1 my-bytes c! ...and another.
di false to irq ei
%00000010 trisb mclr Sets RB1 as output. 255 2 my-bytes c!
turnkey Vector for user start-up word. ( -- a-addr )
latb 1 bit1: pb1-high Defines a word to set RB1 high. 2 my-bytes c@ Should leave 255.
EEPROM value mirrored in SRAM.
pb1-high Sets RB1 high. : mk-cell-array Defining word ( n -- )
prompt Deferred execution vector for the info displayed
create cells allot ...to make cell array objects.
by quit. Default value is .st ( -- a-addr )
does> swap cells + ;
’emit EMIT vector. Default is tx1 ( -- a-addr )
5 mk-cell-array my-cells Creates an array object
’key KEY vector. Default is rx1 ( -- a-addr )
my-cells ( n -- addr ).
’key? KEY? vector. Default is rx1? ( -- a-addr )
Defining compound data objects 3000 0 my-cells ! Sets an element
’source Current input source. ( -- a-addr )
45000 1 my-cells ! ...and another.
s0 Variable for start of data stack. ( -- a-addr )
63000 2 my-cells !
create name Create a word definition and store r0 Bottom of return stack. ( -- a-addr )
1 my-cells @ . Should print 45000
the current data section pointer. rcnt Number of saved return stack cells. ( -- a-addr )
does> Define the runtime action of a created word. tib Address of the terminal input buffer. ( -- a-addr )
allot Advance the current data section dictionary tiu Terminal input buffer pointer. ( -- a-addr )
pointer by u bytes. ( u -- ) >in Variable containing the offset, in characters,
, Append x to the current data section. ( x -- ) Memory operations from the start of tib to the current
c, Append c to the current data section. ( c -- ) parse area. ( -- a-addr )
," xxx" Append a string at HERE. ( -- ) pad Address of the temporary area for strings. ( -- addr )
i, Append x to the flash data section. ( x -- ) Some of these words come from core.txt. : pad tib ti# + ;
ic, Append c to the flash data section. ( c -- ) cmove Move u bytes from address-1 to address-2. Each task has its own pad but has zero default size.
( addr1 addr2 u -- ) If needed the user must allocate it separately
cf, Compile xt into the flash dictionary. ( addr -- )
Copy proceeds from low addr to high address. with allot for each task.
c>n Convert code field addr to name field addr.
wmove Move u cells from address-1 to address-2. dp Leave the address of the current data section
( addr1 -- addr2 )
( addr1 addr2 u -- ) PIC24-30-33 only dictionary pointer. ( -- addr )
n>c Convert name field addr to code field addr.
fill Fill u bytes with c starting at address. EEPROM variable mirrored in RAM.
( addr1 -- addr2 )
( addr u c -- ) dps End address of dictionary pointers. ( -- d )
n>l Convert nfa to lfa. ( nfa -- lfa )
erase Fill u bytes with 0 starting at address. Absolute address of start of free Flash.
Not implemented; use 2- instead.
( addr u -- ) Library and C code can be linked,
>body Leave the parameter field address of the created blanks Fill u bytes with spaces starting at address.
word. ( xt -- a-addr ) starting at this address. PIC24, dsPIC33
( addr u -- ) hp Hold pointer for formatted numeric output.
:noname Define headerless forth code. ( -- addr )
cells Convert cells to address units. ( u -- u ) ( -- a-addr )
>xa Convert a Flash virtual address to a real executable chars Convert chars to address units. ( u -- u )
address. PIC24-30-33, ATmega ( a-addr1 -- a-addr2 ) up Variable holding a user pointer. ( -- addr )
char+ Add one to address. ( addr1 -- addr2 ) latest Variable holding the address of the latest
xa> Convert a real executable address to a Flash virtual cell+ Add size of cell to address. ( addr1 -- addr2 )
address. PIC24-30-33, ATmega ( a-addr1 -- a-addr2 ) defined word. ( -- a-addr )
aligned Align address to a cell boundary. ( addr -- a-addr ) float? Interpreter defer for parsing floating-point values.
’ >float is float?
PIC24-30-33 only
Array examples
Data memory – program memory operations Assembler words for AVR8 Arithmetic and logic instructions
tblrd*, Table read. ( -- ) For the ATmega instructions, Rd denotes the destination (and
tblrd*+, Table read with post-increment. ( -- ) source) register, Rr denotes the source register, Rw denotes a
tblrd*-, Table read with post-decrement. ( -- ) register-pair code, K denotes constant data, k is a constant address, b add, Add without carry. ( Rd Rr -- )
tblrd+*, Table read with pre-increment. ( -- ) is a bit in the register, x,Y,Z are indirect address registers, A is an adc, Add with carry. ( Rd Rr -- )
tblwt*, Table write. ( -- ) I/O location address, and q is a displacement (6-bit) for direct adiw, Add immediate to word. ( Rw K -- )
tblwt*+, Table write with post-increment. ( -- ) addressing. Rw = {XH:XL,YH:YL,ZH:ZL}
tblwt*-, Table write with post-decrement. ( -- ) sub, Subtract without carry. ( Rd Rr -- )
tblwt+*, Table write with pre-increment. ( -- ) subi, Subtract immediate. ( Rd K -- )
Conditions for structured flow control
sbc, Subtract with carry. ( Rd Rr -- )
cs, carry set ( -- cc ) sbci, Subtract immediate with carry. ( Rd K -- )
Low-level flow control operations eq, zero ( -- cc ) sbiw, Subtract immediate from word. ( Rw K -- )
bra, Branch unconditionally. ( rel-addr -- ) hs, half carry set ( -- cc ) Rw = {XH:XL,YH:YL,ZH:ZL}
call, Call subroutine. ( addr -- ) ie, interrupt enabled ( -- cc )
and, Logical AND. ( Rd Rr -- )
goto, Go to address. ( addr -- ) lo, lower ( -- cc )
andi, Logical AND with immediate. ( Rd K -- )
pop, Pop (discard) top of return stack. ( -- ) lt, less than ( -- cc )
or, Logical OR. ( Rd Rr -- )
push, Push address of next instruction to mi, negative ( -- cc )
ori, Logical OR with immediate. ( Rd K -- )
top of return stack. ( -- ) ts, T flag set ( -- cc )
eor, Exclusive OR. ( Rd Rr -- )
rcall, Relative call. ( rel-addr -- ) vs, no overflow ( -- cc )
com, One’s complement. ( Rd -- )
retfie, Return from interrupt enable. ( -- ) not, invert condition ( cc -- not-cc )
neg, Two’s complement. ( Rd -- )
retlw, Return with literal in WREG. ( k -- ) sbr, Set bit(s) in register. ( Rd K -- )
return, Return from subroutine. ( -- ) Register constants cbr, Clear bit(s) in register. ( Rd K -- )
Z ( -- 0 ) inc, Increment. ( Rd -- )
Other MCU control operations Z+ ( -- 1 ) dec, Decrement. ( Rd -- )
clrwdt, Clear watchdog timer. ( -- ) -Z ( -- 2 ) tst, Test for zero or minus. ( Rd -- )
nop, No operation. ( -- ) Y ( -- 8 ) clr, Clear register. ( Rd -- )
reset, Software device reset. ( -- ) Y+ ( -- 9 ) ser, Set register. ( Rd -- )
sleep, Go into standby mode. ( -- ) -Y ( -- 10 ) mul, Multiply unsigned. ( Rd Rr -- )
X ( -- 12 ) muls, Multiply signed. ( Rd Rr -- )
X+ ( -- 13 ) mulsu Multiply signed with unsigned. ( Rd Rr -- )
Assembler words for PIC24-30-33 -X ( -- 14 ) fmul, Fractional multiply unsigned. ( Rd Rr -- )
As stated in the wordsAll.txt, there is only a partial set of words XH:XL ( -- 01 ) fmuls, Fractional multiply signed. ( Rd Rr -- )
for these families of microcontrollers. YH:YL ( -- 02 ) fmulsu, Fractional multiply signed with unsigned. ( Rd Rr -- )
ZH:ZL ( -- 03 )
Branch instructions sec, Set carry. ( -- ) Alternate set I2 C words for PIC18
clc, Clear carry. ( -- )
rjmp, Relative jump. ( k -- ) sen, Set negative flag. ( -- )
ijmp, Indirect jump to (Z). ( -- ) Load these words from i2c_base.txt for a PIC18 microcontroller.
cln, Clear negative flag. ( -- ) They make use of the structured assembler for the PIC18.
eijmp, Extended indirect jump to (Z). ( -- ) sez, Set zero flag. ( -- ) i2cinit Initializes I2 C master mode, 100 kHz clock. ( -- )
jmp, Jump. ( k16 k6 -- ) clz Clear zero flag. ( -- ) i2cws Wake slave. Bit 0 is R/W bit. ( slave-addr -- )
k6 is zero for a 16-bit address. sei, Global interrupt enable. ( -- ) The 7-bit I2 C address is in bits 7-1.
rcall, Relative call subroutine. ( k -- ) cli, Global interrupt disable. ( -- ) i2c! Write one byte to I2 C bus and wait for ACK. ( c -- )
icall, Indirect call to (Z). ( -- ) ses, Set signed test flag. ( -- ) i2c@ak Read one byte and continue. ( -- c )
eicall, Extended indirect call to (Z). ( -- ) cls, Clear signed test flag. ( -- ) i2c@nak Read one last byte from the I2 C bus. ( -- c )
call, Call subroutine. ( k16 k6 -- ) sev, Set two’s complement overflow. ( -- ) i2c-addr1 Write 8-bit address to slave. ( addr slave-addr -- )
k6 is zero for a 16-bit address. clv, Clear two-s complement overflow. ( -- ) i2c-addr2 Write 16-bit address to slave ( addr slave-addr -- )
ret, Subroutine return. ( -- ) set, Set T in SREG. ( -- ) Lower-level words.
reti, Interrupt return. ( -- ) clt, Clear T in SREG. ( -- ) ssen Assert start condition. ( -- )
cpse, Compare, skip if equal. ( Rd Rr -- ) seh, Set half carry flag in SREG. ( -- ) srsen Assert repeated start condition. ( -- )
cp, Compare. ( Rd Rr -- ) clh, Clear half carry flag in SREG. ( -- ) spen Generate a stop condition. ( -- )
cpc, Compare with carry. ( Rd Rr -- ) srcen Set receive enable. ( -- )
MCU control instructions
cpi, Compare with immediate. ( Rd K -- ) break, Break. ( -- ) snoack Send not-acknowledge. ( -- )
sbrc, Skip if bit in register cleared. ( Rr b -- ) nop, No operation. ( -- ) sack Send acknowledge bit. ( -- )
sbrs, Skip if bit in register set. ( Rr b -- ) sleep, Sleep. ( -- ) sspbuf! Write byte to SSPBUF and wait for
sbic, Skip if bit in I/O register cleared. ( A b -- ) wdr, Watchdog reset. ( -- ) transmission. ( c -- )
sbis, Skip if bit in I/O register set. ( A b -- )
lsl, Logical shift left. ( Rd -- ) i2c.c@.ack Fetch a byte and ack for another.
lsr, Logical shift right. ( Rd -- ) ( -- c ) This guide assembled by Peter Jacobs, School of Mechanical Engineering,
rol, Rotate left through carry. ( Rd -- ) i2c.c@.nack Fetch one last byte. ( -- c ) The University of Queensland, February-2016 as Report 2016/02.
( -- ) It is a remix of material from the following sources:
ror, Rotate right through carry. ( Rd -- ) FlashForth v5.0 source code and word list by Mikael Nordman
asr, Arithmetic shift right. ( Rd -- ) Low level words.
i2c.idle? Leave true if the I2 C bus is idle. ( -- f ) http://flashforth.sourceforge.net/
swap, Swap nibbles. ( Rd -- ) i2c.start Send start condition. ( -- ) EK Conklin and ED Rather Forth Programmer’s Handbook 3rd Ed.
bset, Flag set. ( s -- ) 2007 FORTH, Inc.
i2c.rsen Send restart condition. ( -- ) L Brodie Starting Forth 2nd Ed., 1987 Prentice-Hall Software Series.
bclr, Flag clear. ( s -- ) i2c.stop Send stop condition. ( -- ) Robert B. Reese Microprocessors from Assembly Language to C Using
sbi, Set bit in I/O register. ( A b -- ) i2c.wait Poll the I2 C hardware until the operation the PIC18Fxx2 Da Vinci Engineering Press, 2005.
cbi, Clear bit in I/O register. ( A b -- ) has finished. ( -- ) Microchip 16-bit MCU and DSC Programmers Reference Manual
bst, Bit store from register to T. ( Rr b -- ) i2c.bus.reset Clock through bits so that slave devices Document DS70157F, 2011.
bld, Bit load from T to register. ( Rd b -- ) Atmel 8-bit AVR Insturction Set Document 08561-AVR-07/10.
are sure to release the bus. ( -- )