=======BLOCK 2: by alphabetical order ==========================

A D 2 SYNTAX: A2D varint,mux[,RUN | READ | OFF | INTERRUPT | IR | IDLE]  

This command is available only on the XX33 processors. When no option is specified, this instruction initates and reads
the result of a single A/D conversion. Varint must be an integer variable and will receive the result of the conversion. Mux may
be a constant in the range of 0-8 or a byte variable which will be masked to the range of 0-7. The value of mux selects the pin
of port C to use as an input. If mux is an 8, The internal bandgap voltage of 1.22 volts will be the input. In any case, the pin
selected for input should have been previously set to input (see MAKEIN) and the output bit for that pin should have been set to
zero (see CLRBIT).
 

When IDLE is specified, this instruction initiates a single conversion after placing the processor in a SLEEP IDLE mode. This
is the preferred method of making a single conversion because it removes processor noise.

When RUN is specified, this instruction initiates a freerunning mode. No read is performed at this time so varint is unaffected.

When READ is specified, varint receives the lastest conversion value. This does NOT initiate a conversion: RUN must be previously
executed.

OFF simply terminates a freerunning mode.

INTERRUPT initiates a conversion and enables an interrupt. No read is performed. You must write an interrrupt handler to read the

result. See INTERRUPT.

IR initiates a freerunning mode and enables an interrupt on each completion. See INTERRUPT.


ADD16 SYNTAX: ADD16 dh,dl,sh,sl

Adds two pair of register-bytes together as unsigned integers. The equivalent is dh:dl = dh:dl + sh:sl
 

ANALOG SYNTAX: ANALOG ON | OFF | var

Controls the analog comparator. If "ON" or " OFF " is used it turns the power to the comparator on or off. Any other term
is treated as a variable and the current state of the comparator is read into that variable. In this case the result appears in bit 5.
All other bits will be 0. Example:

ANALOG ON

ANALOG x

 

ASM or SYNTAX: ASM | ! statement

       This allows an assembler statement to be embedded directly in the RB source code. ASM or ! must be in the first position on
the line and must be followed by a space or tab. Example:

ASM ADD r2,r1
! SUB r29,r30

     Assembler statements  may freely use byte variable names which are used somewhere else in a Basic statement. Note that the variable
  name in the ASM file will be related to the variable name in the RVK BASIC source file as follows.

 

       Byte variables will be suffixed with an underscore in the ASM file. Integer variables will be suffixed with an "_L" for the
  lower byte and with "_H" for the higher byte.

E.g.

x = y - 27
! CPSE x_,y_

                   Integer  variables are not so easily accessed, as they are stored in SRAM. Integer variables are named by following the root of the
  variable name with "_L" (lower byte) and "_H" (upper byte). Integer variables may be loaded into registers with an "LDS" operation and
  written to using the "STS" operation. To see how this is done, write a very small program in RB using an integer variable, compile
  it, and look at the asm file. Variables within a SUB procedure are assigned names beginning with "L_", so, to avoid conflict, do not
  name any variables beginning with "L_". For example, in a procedure you may have a variable called X% and find it renamed as two
byte locations in static ram, L_2_L and L_2_H.  

 

BEGINCASE SYNTAX: BEGINCASE variable
           optional syntax: BEGIN CASE variable

This begins a CASE structure. See also CASE , ENDCASE.
 

       NOTE WELL: A CASE structure may not be used within an interrupt handler if there is any other CASE structure in the program.

BYTES SYNTAX: BYTES intvar

  Swaps the bytes in an integer variable.  Intvar must be an integer variable. This instruction is not available in the 90S1200.

CALL SYNTAX: CALL subname(to-variable list)(from-variable-list)

  This calls a procedure  whose name is subname and passes it the values of the variables in the to-variable list. The variable list
   is a list of 0 or more variable names separated by commas. Each variable in the list must be either a byte or integer variable.
   The types of variables in this list must match the types of variables in the SUB list (see   SUB) by size. That is, an integer
   must match an integer and a byte variable must match a byte variable.

Variables in both lists are passed by value only. Those in the to-variable list cannot be modified in any way by the procedure.
   Information can be passed from the procedure only via the from-variable list. Example: 

CALL ADDINTEGERS(i1%, i2%)(result%)

.
.

SUB ADDINTEGERS(p%,q%)(r%)
r% = p% + q%
END SUB

  In this example result% receives the  value of the addition of i1% and  i2%.
 

CASE SYNTAX: CASE variable

  This variable may also be a number. This statement tests for equality between the variable and the variable declared in the BEGINCASE statement.  If equal, statements following this CASE are executed,  otherwise program execution resumes at the next CASE or  ENDCASE statement.  

 

CASEELSE SYNTAX: CASE ELSE

Optional SYNTAX: CASEELSE

  This is  a case without any test, so execution simply falls through to the next line of code. CASE ELSE must be the very last CASE
because it falls through. For example:

BEGIN CASE p
CASE 1
x=2
CASE y
GOTO somewhere
CASE ELSE
x=0
END CASE

  

CLRSYNTAX: CLR bytevar, bitnum

OR: CLEAR bytevar,bitnum

Clears bit number bitnum in byte variable bytevar. See SET, TEST .
                                                                 

CLRBIT SYNTAX: CLRBIT p,b

Where p is the letter of the port ("B" or "D") and b is the  number of the bit to clear (0-7). This resets a single bit in an output port. See SETBIT .
 

 

COMPARE16  SYNTAX: COMPARE16 dh,dl,sh,sl,flag  

  This compares two unsigned sixteen-bit numbers formed by dh:dl and sh:sl and places the result in flag. All five variables  must be register_bytes. If dh:dl is greater the result is 2.If dh:dl is equal to sh:sl the result is 1. Otherwise the result is 0. In short:
    

condition < = > 

result    0 1 2

CONTINUE  SYNTAX: CONTINUE 

  Transfers execution to the bottom statement of the current loop. E.g. in a FOR loop the next statement executed will be the NEXT statement of that loop.

 

 

DEBOUNCE SYNTAX: DEBOUNCE port,bitnum,numreps 

  This statement waits until numreps + 1 successive states of bit bitnum (0-7)on the specified port (B or D) are the same.

 

DECR SYNTAX: DECR variable

  Decrement a variable.
 

 

DEVICE SYNTAX: DEVICE processor

  Specifies the processor to compile for. This must be the first non-blank line of the file. Processor may be either 1200 or 2313
or 2323 or 2343, etc.

 

 

DIM SYNTAX: DIM var@,size

   This dimensions a data space in static ram of size bytes which is called var@. The variable name must have @ for the final character. Size must be a constant, not a variable. This instruction must precede the use of the variable name for another operation. See READ and STORE. Example:

DIM myvar@[10]

   

DIRPORT SYNTAX: DIRPORT p,d

   Where p is the letter of the port ("B" or "D") and d is a byte variable or constant. This controls the direction of bits in a port. 1 forces output, 0 forces input. Each bit in the byte value controls the direction of the corresponding bit in the port. E.G.

DIRPORT B,5

   sets bits 0 and 2 to output, all others to input states. When d is IN or OUT the entire port will also be appropriately directed. If d is an integer, only the lower byte will be used.

   

DO SYNTAX: DO

Begins a DO loop. See also EXITDO and LOOP.

  

DOGCLR SYNTAX: DOGCLR

Resets the Watchdog timer .

   

DOGOFF SYNTAX: DOGOFF

Turns off the watchdog timer.

   

DOGON SYNTAX: DOGON ctl

   Turns on the watchdog timer using ctl to specify the time before the watchdog resets the CPU in milliseconds. Eg.,

DOGON 128

   specifies a watchdog reset after 128 milliseconds. Ctl may only be specific values: 16, 32, 64, 128 , 256, 512 , 1024 and 2048 are the only allowable values. These values are only approximate as they depend on the frequency of the RC timer.
 

 

EDGE SYNTAX: EDGE UP|DOWN|ANY port,bitnum

   This causes the program to wait until the edge occurs as specified (UP waits for a 0 to 1 transition, DOWN waits for a 1 to 0 transition, ANY waits for any transition) on the specific bit of the port ("B" or "D"). Bitnum must be constant in the range of 0 through 7.

Example:

EDGE UP B,0

   No interrupts, timers, or stack are used for this type of instruction.

 

 

EEDATA SYNTAX: EEDATA [label:],data[,data[,data...]]

   This sets the data bytes into EEPROM. The optional label: is a reference ending in a colon which can be used to read data (see READ) or to write data (see STORE ) in this space. Examples:

EEDATA ALPHA:,65,66,67,68

EEDATA ,69,70


ELSE SYNTAX: ELSE

   Statements following ELSE are executed only if the test failed in the corresponding IF. See IF.

   

END SYNTAX: END

   Effectively stops execution by placing the microcontroller in a tight loop with no exit.
 

 

END INTERRUPT    SYNTAX: END INTERRUPT

Ends an interrupt routine. See INTERRUPT .

   

ENDCASE SYNTAX: ENDCASE

optional syntax: END CASE

Ends a BEGINCASE structure .

   

ENDIF SYNTAX: ENDIF

optional syntax: END IF

Terminates an IF ... ELSE ... ENDIF construct. See IF .

   

ENDSUB SYNTAX: END SUB | ENDSUB

   This marks the end of a sub procedure. See SUB. This statement causes the values of the variables in the variable list of the SUB statement to be passed back to the variables listed in the CALL statement and then execution resumes with the next statement after the CALL.

 

 

EQU SYNTAX: EQU "term1","alias"

   Informs the compiler that alias is equivalent to term1. For example, if a PRESENT signal is on port D,5 you may find it useful to

EQU "D,5","PRESENT"

Thereafter, instead of writing

INBIT temp,D,5

to read in the status, you could write

INBIT temp,"PRESENT"

   

   Note well that term1 in the EQU statement must be the physical port,pin description, not the alias. Also note that the term and alias must both be surrounded by quotes.

   

   The EQU statement can affect the INBIT, SETBIT, A2D, CLRBIT statements to replace port & pin or mux channel designators. It may also be used to set the time in a PAUSE statement.

   

EXITDO SYNTAX: EXITDO

optional syntax: EXIT DO

Transfers execution to the next instruction after the LOOP. See DO.

   

EXITFOR SYNTAX: EXITFOR

optional syntax: EXIT FOR

   Transfers execution to the next statement after the corresponding NEXT. See FOR

   

EXITSUB SYNTAX: EXIT SUB | EXITSUB

Causes program execution to transfer to the next END SUB.

   

EXITWHILE    SYNTAX: EXITWHILE

optional syntax: EXIT WHILE

   Exits the current WHILE loop, transferring execution to the next statement after WEND. See WHILE.
 

 

EXTINT SYNTAX: EXTINT UP|DOWN|LOW|OFF

   EXTINT enables an external interrupt to awaken the processor from a SLEEP mode. The arguments UP and DOWN specify and edge-triggered event while LOW specifies a wakeup whenever the INT0 pin goes low. See SLEEP.  An example of enabling an external interrupt on a rising edge is

EXTINT UP

Obviously the OFF option disables external interrupts.

   

FILTER SYNTAX: FILTER oldvar, newvar, num[, X]

   This performs an exponential filter funtion. Newvar and oldvar must both be integer variables and num must be a constant from 1 through 8. This filters newvar by 2^num sample periods into oldvar. E.G., if num is 3, after one application oldvar will move 1/8 of the distance toward newvar. Example of use:

A2D new%,0,IDLE

FILTER old%,new%,3
   The user must be aware that num shifts are preformed in this operation. Thus if num = 5 the value being filtered may not be greater than 11 bits or else information will be lost, unless the X option is used. For values obtained as a 10 bit number from the A/D num may not exceed 6 without the X option.
   The X option allows the filter to perform the computation as a 24 bit number using the dummy variable DUM_VAR (which is also used by the PAUSE routine). When using the X option, a 16 bit number may be filtered by num as high as 8 without loss of data. The only penalty for using the X option is that the filter takes slightly longer to execute and requires more program memory space.

   

FLIP SYNTAX: FLIP variable

   Makes a mirror image of the bits of a variable (MSB swaps with LSB, etc.). Must be a byte variable. This instruction uses one word (2 bytes) of stack.
 

 

FOR SYNTAX: FOR var1 = val1 TO val2

   Begins a FOR - NEXT loop. Val1 must be a constant. Val2 may be a constant or a variable. The type of variable of val2 should be less than or equal to that of var1. I.e., if var1 is a byte, val2 may be a byte but should not be an integer. Using an integer variable in this case may cause the loop to never terminate because the byte counter can never reach the value in vale2. Var1 may be any numeric variable. This loop is tested at the bottom of the loop and thus will always execute at least one time. See NEXT and EXITFOR    

   At the current time, the FOR ... NEXT loop may not span more than 4048 words of program memory. IF a larger loop is needed use DO ... LOOP or WHILE ... WEND.

   

GOSUB SYNTAX: GOSUB label

   Transfers execution to a subroutine. All variables are global. Subroutines may be nested no more than three deep on the AT90S1200. See RETURN .

   

GOTO SYNTAX: GOTO label

   Transfers execution to the statemnet bearing the same label. Labels are specified by placing the label followed by a colon at the start of a line. E.G.

LABEL1: END

   

IFBegins an IF...ELSE...ENDIF execution control. The IF, ELSE, and ENDIF statements must be placed on separate lines. The IF must be followed by one of four tests:
   

   IF v1 = v2 is true only if the two values are equal.  IF v1 > v2 is true only if v1 is greater than v2.  IF v1 < v2 is true only if v1 is less than v2.

IF  v1 | v2 is true only if v1 is not equal to v2.

   

   Note that the optional word THEN may follow the test expression provided it is preceded by one or more spaces. E.g., the following two statements are equivalent.

IF x > y THEN

IF x > y

   If the test is true the statements following IF are executed up  to the first ELSE or ENDIF. If false, execution resumes following the corresponding ELSE (if present) or ENDIF. See ELSE, ENDIF.

  In all cases v1 & v2 may be either a variable or a constant.

   NOTE WELL: This test supports variables and constants of the  same type ONLY!!! You may NOT compare an integer with a byte at this time.
   

INBIT SYNTAX: INBIT var,p,bitnum

Reads a single bit from port p into a byte variable. E.g.:

INBIT temp,B,3

results in temp having a value of 4 or 0 depending on port B,3.

    

INCR SYNTAX: INCR variable

Increments a variable.

    

INPORT SYNTAX: INPORT var,p

    where p is the letter of the port ("B" or "D"). Reads a byte from the port into the variable var.
 

 

INTERRUPT SYNTAX: INTERRUPT 0-7 [, OFF | UP | DOWN | LOW]

or: INTERRUPT T0 | T1 | T2 [, ON | OFF]

or: INTERRUPT A2D

or: INTERRUPT RECV

    Begins an interrupt handler or enables or disables an interrupt. Not all options are available on all processors. See END INTERRUPT.


    OFF disables the interrupt. UP, DOWN, or LOW specify the condition on the pin necessary to generate the interrupt for external interrupts. ON and OFF specify the condition of timer interrupts. A timer interrupt occurs when the timer in question overflows.

    The following example shows how to use this statement for external interrupts.
    

some code goes here

REM next line enables interrupt 1 on a falling edge

INTERRUPT 1,DOWN

more code goes here

REM next line disables interrupt 1

INTERRUPT 1,OFF

more code goes here

END

INTERRUPT 1 '..begins your interrupt handler

PUSHREG

your interrupt handler code goes here

POPREG

END INTERRUPT '..ends your interrupt handler
    

The following shows how to use timer interrrupts.

 

some code goes here

' next line enables a TIMER 0 interrupt

INTERRUPT T0,ON

TIMER0 ON,1

some more code goes here

END

INTERRUPT T0 '..begins your interrupt handler

PUSHREG

your interrupt handler code goes here

POPREG

END INTERRUPT '..ends your interrupt handler


    Note well that the TIMER0 interrupt is NOT available for programming in any program that uses the PAUSE routine. The TIMER0 interrupt is used by the PAUSE routine. So any program which uses PAUSE or SEROUT or SERIN may not also contain any
INTERRUPT T0 statement.

    The A2D option specifies an interrupt handler for the completion of an A/D conversion. If a repetitive series of conversions is required you must include the A2D command in the interrupt routine.

 

      The RECV option specifies an interrupt handler for the reception of a character from the UART. NOTE WELL, RECV IN must be executed within this interrupt handler in order to clear this interrupt.

WHERE TO PLACE YOUR INTERRUPT HANDLERS:

  

In some of the larger machines (8515 and larger) it is possible to place your interrupt handler outside of the RJMP range of  the processor if you have a large program and you put the interrupt handler at the end of your program. In such cases  you must locate the handler nearer to the beginning of your source code. One way to do this is show in the followiing example.

DEVICE 8535

MHZ 8

REVISION DEMO

INTERRUPT 0,UP

GOTO MAIN

'...interrupt handler begins here...

INTERRUPT 0

flag = 1

END INTERRUPT

'...end of interrupt handler......

MAIN: '...this is where your program continues..

 
    It should be clear that multiple interrupt handlers may be placed before the MAIN label.
                                                                                                                                                

LOOP SYNTAX: LOOP

Transfers execution to the next instruction after the DO. See DO.

    

MAKEOUT SYNTAX: MAKEOUT port,bitnum

MAKEIN SYNTAX: MAKEIN port,bitnum


  Where port is either B or D and bitnum is a number in the range of  0 through 7, these commands make that bit of that port either an output or an input. See also REVERSE, DIRPORT. The following example makes Port B bit 6 an output:

    MAKEOUT B,6

NEXT SYNTAX: NEXT

Increments the loop variable and tests for exit condition. See FOR.

    

MAKEINT SYNTAX: MAKEINT intvar, bytelow, bytehigh


     Makes two byte variables into an integer variable. Bytelow becomes the low byte of the integer, etc.
 

NIBBLES SYNTAX: NIBBLES bytevar

Swaps the nibbles of a byte variable. E.g. running the following  program will result in X having a value of $HEF.

              X=&HFE
               NIBBLES X


                      

OUTPORT SYNTAX: OUTPORT p,d

       where p is the port letter and d is the data to write out to that port.

                                   

PAUSE SYNTAX: PAUSE m

       delays further execution for m milliseconds based on the frequency previously set by MHZ. m may be a decimal value. (m may also be an alias, see EQU.) The maximum value of m for a 4 MHz clock is approximately 16600 (16.6 seconds). Example:

         PAUSE 5.1,16

       PAUSE uses up two stack locations of the stack. Therefore PAUSE may not be used any deeper than one subroutine deep on the AT90S1200 which has a 3-deep stack. The PAUSE instruction may use  the dummy variable DUM_VAR.

       Because the PAUSE uses the TIMER0 counter, no other use of this timer should be allowed in any program which uses PAUSE .

       Note also that PAUSE should never be used in an interrupt handler unless it is the only PAUSE statement in the entire program.


 

POPREG SYNTAX: POPREG {XXX3,8515}

       Pops the flag register ( SREG) off of the stack. See INTERRUPT, PUSHREG, PUSHFLAGS.

 

PUSHFLAGS SYNTAX: PUSHFLAGS

Pushes the flag register (SREG) onto the stack. See INTERRUPT, POPFLAGS.

PUSHREG SYNTAX: PUSHREG {XXX3,8515}

Pushes working registers onto the stack. This is mandatory in programs which use multiple interrupt routines (remember that PAUSE, PULSE, SEROUT, and SERIN are interrupt-driven). PUSHREG should be the first statement in the interrupt handler and POPREG should be placed just before the END INTERRUPT. This statement uses 4 stack locations.

PULSE SYNTAX: PULSE port,bitspec[,msec]

PULSE produces a pulse on bits specified in bitspec of port (B or D) for msec milliseconds using a processor clock of mhz (MHz). If the bitspec is a constant the number msut be in the range of 0-7 and that specifies the bit to be pulsed. If bitspec is a variable each 1 in that variable will pulse its corresponding bit in the port. Port must be the letter of the desired port. See TOGGLE. If the msec and mhz are omitted the pulse duration will be approximately 4 processor clock periods. When the time is specified this routine calls the PAUSE routine and thus uses up two of the  three available stack locations on the 1200, restricting its usage to no more than one subroutine deep. The pulse direction, high or low, is controlled by the state of the bit in the output port at the time that PULSE is called. If the bit was a 1, the pulse will be low-going. If the bit was a 0, the pulse will be high-going. Use SETBIT or CLRBIT before calling PULSE to control the pulse direction.

                          

PWM INIT  SYNTAX: PWM INIT fout,numbits

Initiates PulseWidth Modulation on the OC1 pin (you must separately direct this pin as an output, see MAKEOUT). The constant fout is the desired output frequency in Herz. The constant numbits is the number of bits to be used in the counter and in the counter comparison, 8, 9 or 10. See PWM THRESHOLD .

PWM OFF SYNTAX: PWM OFF

Turns the PWM output off

PWM THRESHOLD   SYNTAX: PWM THRESHOLD v1

The constant or integer variable v1 sets the duty cycle for the PWM output. Its range is 0 through MAX where MAX is given in the following table.

numbits         MAX
-------         ---
8                255
9                511
10               1023

See PWM INIT.

 

 

PWM2 INIT      SYNTAX: PWM2 INIT fout

Initiates PulseWidth Modulation on the OC2 pin (you must separately direct this pin as an output, see MAKEOUT). The constant fout is the desired output frequency in Herz. See PWM2 THRESHOLD.

PWM2 OFF SYNTAX: PWM2 OFF

Turns the PWM2 timer off.

PWM2 THRESHOLD      SYNTAX: PWM2 THRESHOLD v1

The constant or variable v1 sets the duty cycle for the PWM2 output. Its range is 0 through 255. If an v1 is an integer, only the lower byte is used. See PWM2 INIT .


READ
SYNTAX: READ destin,src,offset

Reads a single byte from src (a string or array variable or an EEDATA label) into variable destin. The offset is the number of bytes into the string or array referenced by src. For example

               p$="ABCDE"
               EEDATA BETA:,61,62
               READ x,p$,2
               READ y,BETA:,1

will place a value of 67 ($42, or "C) into x and 62 into y. Note well that the string or array definition must occur in the program before the read statement. Thus it is good programming practice to define strings and arrays at the beginning of a RB program. Also take care to remember that the offset counts the first character of the string or array as position 0. In the example just given, "A" is offset 0, "B" is offset 1, etc. See also STORE and DIM. An example of reading the second byte from the array p1@ is:

               READ x,p1@,1

Note that this is equivalent to

               x = p1@[1]
but it may be useful to note that the READ statement executes more quickly than the equation.
Note well that arrays are not allowed in the 90S1200. Note also that arrays which extend past byte 256 of SRAM can be addressed by the READ and STORE statements but not by an equation.


RECV INIT      SYNTAX: RECV INIT baudrate

This initialilzes the baudrate for the UART . This must be done before using RECV OUT . Port D pin 0 is the receive pin. Baudrate is a constant representing the desired baudrate (in bits per second, see also MHZ ). If both the UART receiver and transmitter are in use simultaneously the baudrate must be the same for both. (See XMIT.)


RECV OFF
     SYNTAX: RECV OFF

This turns the UART receiver off.


RECV IN      SYNTAX: RECV IN var,errorflag

This receives any data that has been received by the UART and puts it in the byte variable var. Bit(s) are set in the errorflag if there are any errors. The LSB is set if there is no data ready in the UART data register.

RECV INTERRUPT      SYNTAX: RECV INTERRUPT ON | OFF

Enables (ON) or disables ( OFF) interrupts when a reception is complete.


RECV2 INIT      SYNTAX: RECV2 INIT baudrate

This initialilzes the baudrate for the UART #2 . This must be done before using RECV2 OUT . Baudrate is a constant representing the desired baudrate (in bits per second, see also MHZ). If both the UART receiver and transmitter are in use simultaneously the baudrate   must be the same for both. (See XMIT2 .)

RECV2 OFF      SYNTAX: RECV2 OFF

This turns the UART #2 receiver off.

 

RECV2 IN      SYNTAX: RECV2 IN var,errorflag

This receives any data that has been received by UART #2 and puts it in the byte variable var. Bit(s) are set in the errorflag if there are any errors. The LSB is set if there is no data ready in the UART data register.


RECV2 INTERRUPT      SYNTAX: RECV2 INTERRUPT ON | OFF

Enables (ON) or disables ( OFF) interrupts when a reception is complete.


REGPOP      SYNTAX: REGPOP num

Pops num bytes off of the stack into registers up to r27. See REGPUSH.


REGPUSH     SYNTAX: REGPUSH num

Pushes num bytes onto the stack from registers r27 down. For example, if num is 3, r27, r26, and r25 will be pushed. R27 and below are the registers used for byte variables in registers. Use this    statement to save them on the stack before using VARPUS H. See REGPOP .

 

REM     A comment line. Note that REM must be followed by a space or tab. An apostrophe                     followed by a space or tab may also be used as the first character of a comment line.


RESETSP     SYNTAX: RESETSP

Resets the Stack Pointer to its original position at program  start. This effectively clears all stack information and should only be performed in the main program, never in a subroutine,  procedure, or interrupt handler.


RETURN SYNTAX: RETURN

Returns excution from a subroutine to the next instruction after where it was called. See GOSUB.


REVERSE
SYNTAX: REVERSE port,bitnum

reverses the in/out state of bit number bitnum in the specified port. Port must be the letter  of a port. Bitnum must be in range of 0 through 7. See also MAKEOUT, MAKEIN, and DIRPORT.


REVISION      SYNTAX: REVISION rev

Puts a comment in the asm souorce file with the rev revision and places a similar comment on the screen during compilation.


RUN SYNTAX: RUN

Turns off the timer and the watchdog, resets both ports to input mode, and restarts the program from the top.

SERIN SYNTAX: SERIN var,errflag,waitcnt,baudrate,p,bit#

This reads a serial input from PORT p, bit number bit# at a rate baudrate using the processor clock (see MHZ) into variable var. The routine will wait for waitcnt periods (1 to 255) where each period is 1/10 of a bit period at baudrate. If no start bit is detected in that time or no stopbit is detected the errflag will be non-zero. var and errflag must be byte variables in registers. The protocol must be N81 (no parity, 8 bits, 1 stop bit). The following example shows how to read a serial byte into X , using ERR as an errorflag variable, at 9600 baud from port D bit #5. The wait period is 25.5 bit periods (waitcnt = 255).

            SERIN X,ERR,255,9600,16,D,5

SERIN uses the PAUSE funtion so it may not be used more than one subroutine deep on a 1200. See PAUSE. NOTICE that SERIN uses a dummy variable, dum_var. You may use or ignore this variable in other parts of your program, recognizing that dum_var will be affected everytime SERIN is executed. The user is required to set the port bit to input mode before invoking SERIN .

SEROUT  SYNTAX: SEROUT port,bitnum,baudrate,var

This outputs a byte located in var to the bit number (bitnum) of the port (B or D) specified at the baudrate specified (see MHZ). The protocol is "N81", i.e. no parity, 8 bits, 1 start bit. The      baudrate must be in the range of 100 through 1,000,000. SEROUT  uses the PAUSE function so it may not be used more than one subroutine deep in a 1200. See PAUSE. The user is required to set up the direction of the port bit before invoking SEROUT. NOTE WELL: the contents of the variable var are destroyed by the SEROUT statement. Var must be a byte variable in a register.


SET
SYNTAX: SET bytevar,bitnum

Sets bit number bitnum in byte variable bytevar. See C LR, TEST.


SETBIT
SYNTAX: SETBIT p,b

where p is letter of the port and b is the number of the bit to be set (0-7). This sets a single bit in an output port. See CLRBIT .


 

 

SHIFT SYNTAX: SHIFT destin,reps,mode

ROTATE SYNTAX: ROTATE destin,reps,mode

This performs a logical shift (with a 0 fill) or a rotate through the carry bit on the variable destin. The shift or rotate will occur reps times where reps is a number from 1 through 8 for shifts and 1 through 9 for rotates. The direction of the shift or rotate will be set by mode where mode is either LEFT or RIGHT. Destin may be either a byte variable or an iinteger variable if performing a SHIFT. Destin must be a byte variable when performing a ROTATE.

 

SHIFT16R       SYNTAX: SHIFT16R v1%,vr,reps

or SHIFT16R vh,vl,vr,reps

Shifts an integer, v1%, or a pair of bytes in registers, vh (high) and vl (low), reps times to the right into a remainder. The remainder is then added to vr (a byte in register). If vr overflows the result (v1% or vh,vl) is incremented. This instruction allows a division by a power of two to be performed with a running remainder. Because this works with bytes in registers it can even be used on a 1200 processor.

SHIFT32 SYNTAX: SHIFT32 v2%,v1%,reps,mode

Performs a 32-bit shift using 2 integers (v2%, v1%, where v2% is the upper 16 bits). Mode may be RIGHT or LEFT. Reps must be a number from 1 through 8.


SLEEP SYNTAX: SLEEP [IDLE]

This places the processor in a sleep mode. Nothing further is executed until an enabled interrupt occurs which then executes the corresponding interrupt routine, after which execution resumes at the next statement following SLEEP. If the interrupt is from the Watchdog timer (see DOGON) execution will resume from the top of the program, exactly as if power were just turned on to the chip. If an external interrupt wakes up the processor, execution simply resumes following the SLEEP instruction. The argument to this instruction specifies whether the processor goes into an IDLE mode or whether it turns itself OFF. In the latter case allow 16 msec  for the oscillator to restart when it awakens. If no argument is specified IDLE mode will be entered.


SHARED
SYNTAX: SHARED varlist

Used only within a SUB procedure, this defines the variables in varlist to be shared by name with those in the main program. The variable list is a list of variable names separated by commas, e.g.,
               SHARED time%,distance,work~
Each variable in the list MUST be used somewhere within the main program (not just in another procedure). A failure to reference a shared variable in the main program will generate one or more errors at assembly time.


 

 

SPI SYNTAX: SPI varin, varout, port, inbit, outbit, outclk,                     numbits,mode [,usec]

The SPI function simultaneously sends out up to 8 clocked bits and reads in up to 8 clocked bits. This function generates its own clock output ( defaults to about 250 KHz on a 16 MHz processor). Three pins are used in a single port, an input for incoming data, an output for outgoing data, and a clock (also an output). Varin and varout are variable names. The port must be either B or D. Inbit, output, and outclk must be pin numbers for that port in the range of 0 through 7. Numbits (1-8) is the number of bits to transmit. Mode must be either PRE, MID , or POST, specifying whether to read the incoming bits before the first clock edge, after the first clock edge,or after the second clock edge. Output data is sent LSB first and input data is read LSB  first. The user is required to set up the direction of each bit before invoking SPI. See MAKEOUT, MAKEIN, and DIRPORT.

The optional usec may be added to specify the delay in microseconds before and after each clock edge. You may specify 0 here for maximum speed. If usec is omitted a default value of 3 will be assumed. The actual minimum delay depends on your processor clock: 2 uSec per clock edge is the minimum with an 8 MHz clock.

For example, to send 8 bits out from X and read into Y using PORTB with bit 1 the clock, bit 2 the output data, and bit 3 the input data, and pause 5 microseconds between clock edges (100 KBaud shift rate),

         SPI Y,X,B,3,2,1,8,PRE,5

NOTE WELL, input data is written into bit 7 and shifted to the  right. So if you input 4 bits into a variable, the data will  wind up in bits 4 through 7, with 4 being the LSB.


STACK SYNTAX: STACK num

Sets the number (num) of bytes to allocate in ram for the system stack. The user should allocate at least 2 bytes for each level of subroutine. This command may be used repetitively. E.G., in each  subroutine issue a STACK 2 command, thereby allocating 2 bytes of stack for each subroutine.

All processes controlled by the compiler directly, except for subroutines, compute their own stack usage without the need for programmer intervention. These include, but are not restricted to,
              CALL
               FLIP
               INTERRUPTS
               PAUSE
               PUSHREG
               PUSHFLAGS
               EQUATIONS

The programmer is responsible only for allocating stack for his subroutines.

STACK is not usable on the AT90S1200 which has a 3-deep hardware stack.


STORE SYNTAX: STORE destin,offset,src

STORE writes a byte to EEPROM (non-volatile memory) if the destin is a string or to static ram if the destin is an array. The destination must be defined earlier in the program. The offset may be a number or a byte variable. An offset of 0 points to the first byte in the string or array. SRC, the source may be a constant or a byte variable. This is a slow, slightly desctructive process requiring about 2.5 msec at 5 volts when used with EEPROM. The chip is expected to last 100,000 write cycles to EEPROM. See also READ and DIM . Note well that array variables are not allowed with the AT90S1200. Two examples follow showing how to write the second byte into a string and into an array.
               STORE p$,1,x
           
  STORE q@,1,x

A variable may also be stored to a data space in EEPROM . E.g.,
               EEDATA TEST:,1,2,3,4,5
               y = 8
               STORE TEST:,0,y


Note also that a STORE to an array may be executed by an equation also:
               q@[1] = x
however the STORE statement executes more quickly. Remember that arrays are not allowed in the AT90S1200.

Note also that arrays which extend past byte 256 of SRAM can be addressed by the READ and STORE statements but not by an equation.


SUB16
SYNTAX: SUB16 dh,dl,sh,sl

Subtracts two pair of register-bytes together as unsigned integers. The equivalent is
dh:dl = dh:dl - sh:sl


 

SUB SYNTAX: SUB subname(in-variable list)(out-variable list)

Begins a procedure. The variable lists are lists of variable names separated by commas. Each variable in the list must be either an integer or a byte variable in static ram (e.g. X~). Within the procedure (which ends with an END SUB statement) other variables may be referenced. All such byte or integer variables will be kept local to the procedure. Arrays, byte variables in registers, and strings may be used within the procedure but they will be treated as global variables. Local variables in a procedure are static variables: their value does not change between exiting and entering the procedure. The procedure is NOT re-entrant - you may NOT call the procedure from within itself.

In the following example, temp% is a local variable while x1~, x2~, and result% correspond to the variables in the corresponding CALL statement.

               SUB average(x1~, x2~)(result%)
                 temp% = x1~ + x2~
                 SHIFT temp%, 1, RIGHT
                 result% = temp%
               END SUB


The above procedure could be called by

        CALL average(x, y~)(avg%)

Note well that the variables in the in-variable list must correspond in size to the variables in the to-variable list of the CALL statement. Likewise the out-variable list must correspond to the from-variable list of the CALL statement.

 

SWAP SYNTAX: SWAP var1,var2

Exchanges the contents of variable var1 with variable var2.

TEST SYNTAX: TEST destbytevar, srcbytevar, bitnum

Tests bit number bitnum in srcbytevar by AND and places result  in destbytevar. See CLR, SET. For example, the following code  places the value &H08 in the variable temp.

               SET flags,3
               TEST temp,flags,3

                                          

TIMER0 OFF   SYNTAX: TIMER0 OFF var

       This stops the count of the timer and reads the timer count into variable var.

TIMER0 ON       SYNTAX: TIMER0 ON prescale[, var]

This turns off timer interrupts, zeros the 8-bit timer counter, and  starts the timer prescaling its clock with prescale. Prescale must be one of the following numbers: 1, 8, 64, 256, 1024. The prescale value is the number of processor clock cycles necessary to produce one count in the timer counter. Note that no PAUSE instructions ( SEROUT, SERIN, PAUSE, and PULSE if time is specified) may be used while you are using timer0.
If the optional variable var is included in the statement, the statement will record the value of the timer counter in var just before zeroing the timer and starting it.

TIMER0 READ    SYNTAX: TIMER0 READ var

Reads the count in the TIMER0 into the variable var. Leaves the TIMER0 still running.


TIMER1 OFF
   SYNTAX: TIMER1 OFF var

This stops the count of the timer and reads the timer count into integer variable var. This instruction will cause PWM to stop.


TIMER1 ON   SYNTAX: TIMER1 ON prescale[, var]

This turns off timer interrupts, zeros the 16-bit timer counter, and  starts the timer prescaling its clock with prescale. Prescale must one of the following numbers: 1, 8, 64, 256, 1024. The prescale value is the number of processor clock cycles necessary to produce one count in the timer counter.
If the optional integer variable var is included in the statement, the statement will record the value of the timer counter in var just before zeroing the timer and starting it. This instruction may not be used simultaneously with the PWM instruction.


TIMER1 READ    SYNTAX: TIMER1 READ var

Reads the count in the TIMER1 into the integer variable var. Leaves the TIMER1 still running.

TIMER2 OFF  SYNTAX: TIMER2 OFF var

This stops the count of the timer and reads the timer count into variable var.


TIMER2 ON        SYNTAX: TIMER2 ON prescale[, var] 

This turns off timer interrupts, zeros the 8-bit timer counter, and starts the timer prescaling its clock with prescale. Prescale must be one of the following numbers: 1, 8, 64, 256, 1024. The prescale value is the number of processor clock cycles necessary to produce one count in the timer counter.
If the optional variable var is included in the statement, the statement will record the value of the timer counter in var just before zeroing the timer and starting it.


TIMER2 READ          SYNTAX: TIMER2 READ var

Reads the count in the TIMER2 into the variable var. Leaves the TIMER2 still running.

TOGGLE  SYNTAX: TOGGLE p,bitnum


where p is letter of the port. Toggles state (1 or 0) of the bitnumber in the port. bitnum may be a number. E.g.
         TOGGLE D,7
toggles the MSB, bit 7, in port D.  Bitnum may also be a variable, in which case each 1 in the variable will toggle a corresponding output bit in the port. E.g.
         x=5
         TOGGLE D,x

       will toggle bits 0 and 2 of port D. See DIRPORT.


VARPUSH SYNTAX: VARPUSH variable list

This pushes a list of variables onto the stack. The list is a simple list of variable names, each separated by a comma. See VARPOP .


VARPOP  SYNTAX: VARPOP variable list

This pops a list of variables off of the stack. The list is a simple list of variable names, each separated by a comma. NOTE WELL that operations are performed from left to right, IN THAT ORDER. So if you push x,y,z onto the stack, you should pop z,y,x off of the stack. See VARPUSH .

WEND    SYNTAX: WEND

Ends a WHILE loop. See WHILE


WHILE
  SYNTAX: WHILE condition

Begins a WHILE loop. The loop continues to repeat so long as the condition is true. See FOR for a defition of conditions. Also see WEND, EXITWHILE

XMEM    SYNTAX: XMEM ENABLE | DISABLE

This statement enables or disables external memory for those chips that have external memory capability. When enabled, the affected registers, such as A and C in a 4414/8515, become dedicated to external memory and are unusable as output pins. IF YOU ARE PLANNING TO USE SUCH REGISTERS AS OUTPUTS YOU MUST INCLUDE AN "XMEM DISABLE" STATEMENT BEFORE SETTING THEIR DIRECTION REGISTERS.
Note also that an XMEM statement is required by the compiler for all source files for devices which allow external memory.


XMIT INIT
   SYNTAX: XMIT INIT baudrate

This initialilzes the baudrate for the UART. This must be done before using XMIT OUT. Port D pin 1, the XMIT output pin, must be directed for output before use. Baudrate is a constant representing the desired baudrate (in bits per second, see also MHZ ). If both the UART receiver and transmitter are in use simultaneously the baudrate must be the same for both.


XMIT OFF       SYNTAX: XMIT OFF

This turns the UART off, but not until any pending character has finished transmitting.


XMIT OUT
      SYNTAX: XMIT OUT data

This transmits the data in the variable var. If data is a byte, or a constant in the range of 0-255, one byte is transmitted. If data is an integer, two bytes are transmitted, the least significant first.
WARNING: DO NOT USE XMIT OUT WHILE ANY EXTERNAL INTERRUPT IS ENABLED. THE ATMEL UART CAN AND WILL GENERATE FALSE TRANSMISSIONS OF &HFF UNDER SUCH CASES.


XMIT2 INIT
     SYNTAX: XMIT2 INIT baudrate

This initialilzes the baudrate for UART #2. This must be done before using XMIT2 OUT. Port D pin 1, the XMIT2 output pin, must  be directed for output before use. Baudrate is a constant representing the desired baudrate (in bits per second, see also MHZ). If both the UART receiver and transmitter are in use simultaneously the baudrate must be the same for both.


XMIT2 OFF      SYNTAX: XMIT2 OFF

This turns UART #2 off, but not until any pending character has finished transmitting.


XMIT2 OUT      SYNTAX: XMIT2 OUT data

This transmits the data in the variable var. If data is a byte, or a constant in the range of 0-255, one byte is transmitted. If data is an integer, two bytes are transmitted, the least significant first.


EQUATIONS are allowed. Operations supported in equations are:
           +     addition
           -     subtraction
           *     multiply (integer = byte * byte)
           /     divide (byte = byte / byte)

The divide operation is an unsigned byte divide with no remainder. This operation use the dummy variable DUM_VAR (see PAUSE).
The following operators must be delineated by spaces or tabs on both ends of the operator.

           AND   logical and
           OR    logical or
           XOR   logical exclusive or.
           MOD   a MOD b returns the remainder of a/b. Both a and b
                 must be bytes.

Constants may be freely used in place of variables on the righthand side. All of the following are legal examples. The equations are strictly processed from left to right.
         y7=x+5 and &H0F
         y7=5+x+y~
         p123 = a and b
         p123 = &H17 and charlie
         Y=-X
         a@[7] = a@[1] XOR a@[i] AND 7


Note also that arrays which extend past byte 256 of SRAM can be addressed by the READ and STORE statements but not by an equation.
The following are not legal.
         17=x-1        (left side must be a variable.)
         p= x7xor y1   (must precede xor with a space or tab.)


SPECIAL ATTENTION is called to the special case of equating a byte variable to an integer variable. This is allowed but the user is responsible for recognizing that the byte variable will contain only the lower byte of the integer variable. Consider the following example:
               Y% = &H1234
               X = Y%
This results in X having a value of &H34. The placing of the lower byte of an integer into a byte variable will occur whenever the first operand to the right of the equal sign is an integer and the destination (on the left of the equal sign) is a byte variable.


NOTE WELL that integer variables are not allowed in the 90S1200.
Comments may be placed at the end of an equation following a " '". Note that the apostrophe must be preceeded by either a space or a tab character.


IN THE INTEREST OF SPEED, you will do better to not begin an equation with a negative sign (-). The equation processor will interpret Y=-X+1 as Y=0-X+1. Performance will be enhanced if you will write this as Y=1-X .
Two bytes of stack are used by an equation if an array computation is involved or if there is a multiply or a divide.
CONSTANTS may be described in several forms.
       23      is a decimal number.
       &H16    is a hexadecimal number.
       &B0010  is a binary number whose value is 2 decimal.
       "A      is a 1-byte constant whose value is 65, the ASCII value of  the character immediately following the double-quote.


STRINGS are implemented as constants stored in EEPROM. A string is defined in a list where literal characters may be included in quotes and numeric values of bytes are separated by commas. For example:
               P$ = "ABC",&H44,"E",70
is equivalent to P$="ABCDEF". Strings are stored in EEPROM followed by a byte with a value of 0. So the P$ just defined will use up 7 bytes of EEPROM. The label assigned to the string in the EEPROM segment will be the name of the string variable (less the $). Note that the literal string must be surrounded by quotes. You may not use variables of the same name and differing types in the  same program. E.g. if you use X you may not also use X%, X$ , or X@.


=================================================================

       A SAMPLE PROGRAM

       device 1200
       MHZ     4

rem This program sends out the message "OK." at 4800 baud on PORT B5
rem each time that it receives a pulse on D0 that is between .008 and
rem .012 seconds long.

       outstr$="OK."
       curtime = 0

' For a 4 MHz clock, prescaling by 256 makes our 8-bit counter time up
' to .016384 seconds. So .008 seconds equates to a count of 125 and
'.012 seconds is a count of 187.

       TIMER0 ON 256

       DO
                               '  wait for any edge
         EDGE ANY D,0
                               ' read and then zero the time
         TIMER0 ON 256,curtime
                               ' test for invalid curtime
         IF curtime>187
           CONTINUE
         END IF
         IF curtime<125
           CONTINUE
         ENDIF
                               ' time was valid so send the string
         offset=0
         DO
           READ byte,outstr$,offset
           INCR offset
                               ' all done when the byte is 0
           IF byte=0
             EXITDO
           ELSE
             SEROUT B,5,4800,byte
           ENDIF
         LOOP
       LOOP

       END