home *** CD-ROM | disk | FTP | other *** search
/ Frostbyte's 1980s DOS Shareware Collection / floppyshareware.zip / floppyshareware / DOOG / LPFORTH.ZIP / CPU8086.BLK < prev    next >
Text File  |  1980-09-12  |  53KB  |  1 lines

  1. \               The Rest is Silence                   11OCT83HHL*************************************************************   *************************************************************   ***                                                       ***   ***    Please direct all questions, comments, and         ***   ***    miscellaneous personal abuse to:                   ***   ***                                                       ***   ***    Henry Laxen          or    Michael Perry           ***   ***    1259 Cornell Avenue        1125 Bancroft Way       ***   ***    Berkeley, California       Berkeley, California    ***   ***    94706                      94702                   ***   ***                                                       ***   ***    (415) 525-8582             (415) 644-3421          ***   ***                                                       ***   *************************************************************   *************************************************************   \ Load Screen for 8086 Dependent Code                 07Apr84map                                                                ONLY FORTH ALSO DEFINITIONS   DECIMAL                                                                                              3 LOAD   ( The Assembler )                                     18 LOAD   ( The Low Level for the Debugger )                    21 LOAD   ( The Low Level for the MultiTasker )                 24 LOAD   ( The Machine Dependent IO words )                  CR .( 8086 Machine Dependent Code Loaded )                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                      \ 8086 Assembler                                      11OCT83HHLONLY FORTH ALSO DEFINITIONS                                        1 14 +THRU   CR .( 8086 Assembler Loaded )                   ONLY FORTH ALSO DEFINITIONS  EXIT                               The 8086 Assembler was written by Mike Perry.                   To create and assembler language definition, use the defining   word CODE.  It must be terminated with either END-CODE or       its synonym C;.  How the assembler operates is a very           interesting example of the power of CREATE DOES>   Basically    the instructions are categorized and a defining word is         created for each category.  When the nmemonic for the           instruction is interpreted, it compiles itself.                                                                                                                                                                                                                                                                                 \ 8086 Assembler                                      06Apr84map: LABEL   CREATE ASSEMBLER   ;                                  232 CONSTANT DOES-OP                                            3 CONSTANT DOES-SIZE                                            : DOES?   (S IP -- IP' F )                                         DUP DOES-SIZE + SWAP C@ DOES-OP =  ;                         ASSEMBLER ALSO DEFINITIONS                                      : C;   (S -- )   END-CODE   ;                                   OCTAL                                                           DEFER C,         FORTH ' C,       ASSEMBLER IS C,               DEFER ,          FORTH ' ,        ASSEMBLER IS ,                DEFER HERE       FORTH ' HERE     ASSEMBLER IS HERE             DEFER ?>MARK                                                    DEFER ?>RESOLVE                                                 DEFER ?<MARK                                                    DEFER ?<RESOLVE                                                 \ 8086 Assembler   Register Definitions               11OCT83HHL                                                                : REG    11 * SWAP 1000 * OR CONSTANT   ;                       : REGS   (S MODE N -- )   SWAP 0 DO  DUP I REG  LOOP  DROP ;                                                                    10 0 REGS   AL  CL  DL  BL  AH  CH  DH  BH                      10 1 REGS   AX  CX  DX  BX  SP  BP  SI  DI                      10 2 REGS   [BX+SI] [BX+DI] [BP+SI] [BP+DI] [SI] [DI] [BP] [BX]  4 2 REGS   [SI+BX] [DI+BX] [SI+BP] [DI+BP]                      4 3 REGS   ES  CS  SS  DS                                       3 4 REGS   #   #)  S#)                                                                                                         BP CONSTANT RP   [BP] CONSTANT [RP]   ( RETURN STACK POINTER )  SI CONSTANT IP   [SI] CONSTANT [IP]   ( INTERPRETER POINTER )   BX CONSTANT W    [BX] CONSTANT [W]    ( WORKING REGISTER )                                                                      \ Addressing Modes                                    16Oct83map: MD   CREATE  1000 * ,  DOES>  @ SWAP 7000 AND = 0<>  ;        0 MD R8?   1 MD R16?   2 MD MEM?   3 MD SEG?   4 MD #?          : REG?   (S n -- f )   7000 AND 2000 < 0<> ;                    : BIG?   (S N -- F )   ABS -200 AND 0<>  ;                      : RLOW   (S n1 -- n2 )    7 AND ;                               : RMID   (S n1 -- n2 )   70 AND ;                               VARIABLE SIZE   SIZE ON                                         : BYTE   (S -- )   SIZE OFF ;                                   : OP,   (S N OP -- )   OR C,  ;                                 : W,   ( OP MR -- )   R16? 1 AND OP,  ;                         : SIZE,   ( OP -- OP' )   SIZE @ 1 AND OP,  ;                   : ,/C,  (S n f -- )   IF  ,  ELSE  C,  THEN  ;                  : RR,   (S MR1 MR2 -- )   RMID SWAP RLOW OR 300 OP,  ;          VARIABLE LOGICAL                                                : B/L?   (S n -- f )   BIG? LOGICAL @ OR  ;                     \ Addressing                                          16Oct83map: MEM,   (S DISP MR RMID -- )   OVER #) =                          IF  RMID 6 OP, DROP ,                                           ELSE  RMID OVER RLOW OR -ROT [BP] = OVER 0= AND                 IF  SWAP 100 OP, C,  ELSE  SWAP OVER BIG?                       IF  200 OP, ,  ELSE  OVER 0=                                    IF  C, DROP  ELSE  100 OP, C,                                   THEN THEN THEN THEN  ;                                       : WMEM,   (S DISP MEM REG OP -- )   OVER W, MEM,  ;             : R/M,   (S MR REG -- )                                            OVER REG? IF  RR,  ELSE  MEM,  THEN  ;                       : WR/SM,   (S R/M R OP -- )   2 PICK DUP REG?                      IF  W, RR,  ELSE  DROP SIZE, MEM,  THEN  SIZE ON  ;          VARIABLE INTER                                                  : FAR    (S -- )   INTER ON  ;                                  : ?FAR   (S n1 -- n2 )   INTER @ IF  10 OR  THEN  INTER OFF ;   \ Defining Words to Generate Op Codes                 11APR83HHL: 1MI   CREATE  C,  DOES>  C@ C,  ;                             : 2MI   CREATE  C,  DOES>  C@ C,  12 C,  ;                      : 3MI   CREATE  C,  DOES>  C@ C,  HERE - 1- C, ;                : 4MI   CREATE  C,  DOES>  C@ C,  MEM,  ;                       : 5MI   CREATE  C,  DOES>  C@ SIZE,  SIZE ON ;                  : 6MI   CREATE  C,  DOES>  C@ SWAP W,  ;                        : 7MI   CREATE  C,  DOES>  C@ 366 WR/SM, ;                      : 8MI   CREATE  C,  DOES>  C@ SWAP R16? 1 AND OR  SWAP # =         IF  C, C,  ELSE  10 OR  C,  THEN  ;                          : 9MI   CREATE  C,  DOES>  C@  OVER R16?                           IF  100 OR SWAP RLOW OP,  ELSE  376 WR/SM,  THEN  ;          : 10MI  CREATE  C,  DOES>  C@ OVER CL =                            IF  NIP 322  ELSE  320  THEN  WR/SM,  ;                                                                                                                                                      \ Defining Words to Generate Op Codes                 09Apr84map: 11MI   CREATE  C, C,  DOES>  OVER #) =                           IF  NIP C@ INTER @                                                IF   1 AND IF  352  ELSE  232  THEN  C,  SWAP , ,               ELSE  SWAP HERE - 2- SWAP  2DUP 1 AND SWAP BIG? NOT AND           IF  2 OP, C,  ELSE  C,  1- ,  THEN  THEN                    ELSE  DUP S#) = IF  DROP #)  THEN                                 377 C,  1+ C@ ?FAR  R/M,  THEN  ;                          : 12MI   CREATE  C, C, C,  DOES>  OVER REG?                        IF  C@ SWAP RLOW OP,  ELSE  1+ OVER SEG?                          IF  C@ RLOW SWAP RMID OP,                                       ELSE  COUNT SWAP C@ C,  MEM,                                  THEN THEN  ;                                                 : 14MI   CREATE  C,  DOES> C@                                      DUP ?FAR C,  1 AND 0= IF  ,  THEN ;                                                                                          \ Defining Words to Generate Op Codes                 09Apr84map: 13MI   CREATE  C, C,  DOES>  COUNT >R C@ LOGICAL !  DUP REG?     IF  OVER REG?                                                     IF  R> OVER W, SWAP RR,  ELSE  OVER DUP MEM? SWAP #) = OR       IF  R> 2 OR WMEM,  ELSE  ( # ) NIP  DUP RLOW 0= ( ACC? )        IF  R> 4 OR OVER W, R16? ,/C,                                   ELSE  OVER B/L? OVER R16? 2DUP AND                                -ROT 1 AND SWAP NOT 2 AND OR 200 OP,                            SWAP RLOW 300 OR R> OP,  ,/C,                                 THEN  THEN  THEN                                              ELSE  ( MEM )  ROT DUP REG?                                       IF  R> WMEM,                                                    ELSE  ( # ) DROP  2 PICK B/L? DUP NOT 2 AND 200 OR SIZE,          -ROT R> MEM,  SIZE @ AND ,/C,  SIZE ON                      THEN  THEN  ;                                                                                                                \ Instructions                                        09Apr84map: TEST   (S source dest -- )   DUP REG?                            IF  OVER REG?                                                     IF  20 OVER W, SWAP RR,  ELSE  OVER DUP MEM? SWAP #) = OR       IF  22 WMEM,  ELSE  ( # ) NIP  DUP RLOW 0= ( ACC? )             IF  250 SWAP W, C,                                              ELSE  366 OVER W,  DUP RLOW 300 OP,  R16? ,/C,                  THEN  THEN  THEN                                              ELSE  ( MEM )  ROT DUP REG?                                       IF  20 WMEM,                                                    ELSE  ( # ) DROP  366 SIZE,  0 MEM,  SIZE @ ,/C,  SIZE ON     THEN  THEN  ;                                                                                                                                                                                                                                                                                                                \ Instructions                                        16Oct83mapHEX                                                             : ESC   (S source ext-opcode -- )   RLOW 0D8 OP, R/M,  ;        : INT   (S N -- )   0CD C,  C,  ;                               : SEG   (S SEG -- )   RMID 26 OP,  ;                            : XCHG   (S MR1 MR2 -- )   DUP REG?                                IF  DUP AX =                                                      IF  DROP RLOW 90 OP,  ELSE  OVER AX =                           IF  NIP  RLOW 90 OP,  ELSE  86 WR/SM,  THEN  THEN             ELSE  ROT 86 WR/SM,  THEN  ;                                                                                                 : CS:   CS SEG ;                                                : DS:   DS SEG ;                                                : ES:   ES SEG ;                                                : SS:   SS SEG ;                                                                                                                \ Instructions                                        18APR83HHL: MOV   (S S D -- )   DUP SEG?                                     IF  8E C, R/M,  ELSE  DUP REG?                                    IF  OVER #) = OVER RLOW 0= AND                                    IF  A0 SWAP W,   DROP   ,  ELSE  OVER SEG?                      IF  SWAP 8C C, RR,  ELSE  OVER # =                              IF  NIP DUP R16? SWAP RLOW OVER 8 AND OR B0 OP, ,/C,            ELSE  8A OVER W, R/M,  THEN THEN THEN                         ELSE  ( MEM ) ROT DUP SEG?                                        IF  8C C, MEM,  ELSE  DUP # =                                   IF  DROP C6 SIZE, 0 MEM,  SIZE @ ,/C,                           ELSE  OVER #) = OVER RLOW 0= AND                                IF  A2 SWAP W,  DROP   ,   ELSE  88 OVER W, R/M,            THEN THEN THEN THEN THEN   SIZE ON  ;                                                                                                                                                        \ Instructions                                        12Oct83map 37  1MI AAA     D5  2MI AAD     D4  2MI AAM     3F  1MI AAS    0 10 13MI ADC  0 00 13MI ADD   2 20 13MI AND  10 E8 11MI CALL    98  1MI CBW     F8  1MI CLC     FC  1MI CLD     FA  1MI CLI     F5  1MI CMC   0 38 13MI CMP     A6  5MI CMPS    99  1MI CWD     27  1MI DAA     2F  1MI DAS     08  9MI DEC     30  7MI DIV           ( ESC )   F4  1MI HLT     38  7MI IDIV    28  7MI IMUL    E4  8MI IN      00  9MI INC           ( INT )  0CE  1MI INTO   0CF  1MI IRET    77  3MI JA      73  3MI JAE     72  3MI JB      76  3MI JBE     E3  3MI JCXZ    74  3MI JE      7F  3MI JG      7D  3MI JGE     7C  3MI JL      7E  3MI JLE  20 E9 11MI JMP     75  3MI JNE     71  3MI JNO     79  3MI JNS     70  3MI JO      7A  3MI JPE     7B  3MI JPO     78  3MI JS      9F  1MI LAHF    C5  4MI LDS     8D  4MI LEA     C4  4MI LES     F0  1MI LOCK   0AC  6MI LODS    E2  3MI LOOP    E1  3MI LOOPE   E0  3MI LOOPNE                                                                 \ Instructions                                        12Apr84map       ( MOV )   0A4  5MI MOVS    20  7MI MUL     18  7MI NEG    90  1MI NOP      10  7MI NOT   2 08 13MI OR      E6  8MI OUT               8F 07 58 12MI POP     9D  1MI POPF                             0FF 36 50 12MI PUSH    9C  1MI PUSHF                  10 10MI RCL      18 10MI RCR                                    F2  1MI REP      F2  1MI REPNZ   F3  1MI REPZ                   C3 14MI RET      00 10MI ROL      8 10MI ROR     9E  1MI SAHF   38 10MI SAR    0 18 13MI SBB    0AE  5MI SCAS          ( SEG )  20 10MI SHL      28 10MI SHR     F9  1MI STC     FD  1MI STD    FB  1MI STI     0AA  6MI STOS  0 28 13MI SUB           ( TEST ) 9B  1MI WAIT           ( XCHG )  D7  1MI XLAT  2 30 13MI XOR    C2 14MI +RET                                                                                                                                                                                                                                                   \ Structured Conditionals                             09Apr84map: A?>MARK    (S -- f addr ) TRUE   HERE   0 C,   ;              : A?>RESOLVE (S f addr -- ) HERE OVER 1+ - SWAP C! ?CONDITION ; : A?<MARK    (S -- f addr ) TRUE   HERE   ;                     : A?<RESOLVE (S f addr -- ) HERE 1+ -  C,   ?CONDITION   ;      ' A?>MARK    ASSEMBLER IS ?>MARK                                ' A?>RESOLVE ASSEMBLER IS ?>RESOLVE                             ' A?<MARK    ASSEMBLER IS ?<MARK                                ' A?<RESOLVE ASSEMBLER IS ?<RESOLVE                             HEX                                                             75 CONSTANT 0=   74 CONSTANT 0<>   79 CONSTANT 0<               78 CONSTANT 0>=  7D CONSTANT <     7C CONSTANT >=               7F CONSTANT <=   7E CONSTANT >     73 CONSTANT U<               72 CONSTANT U>=  77 CONSTANT U<=   76 CONSTANT U>               71 CONSTANT OV                                                  DECIMAL                                                         \ Structured Conditionals                             06Apr84mapHEX                                                             : IF      C,   ?>MARK  ;                                        : THEN    ?>RESOLVE   ;                                         : ELSE    0EB IF   2SWAP   THEN   ;                             : BEGIN   ?<MARK   ;                                            : UNTIL   C,   ?<RESOLVE   ;                                    : AGAIN   0EB UNTIL   ;                                         : WHILE   IF   ;                                                : REPEAT   2SWAP   AGAIN   THEN   ;                             : DO      # CX MOV   HERE   ;                                   : NEXT    >NEXT #) JMP   ;                                      : 1PUSH   >NEXT 1- #) JMP   ;                                   : 2PUSH   >NEXT 2- #) JMP   ;                                   DECIMAL                                                                                                                         \ Load Screen for High Level Trace                    17Oct83mapONLY FORTH ALSO DEFINITIONS                                       1 2 +THRU   CR .( Low level Debugger Code Loaded )            ONLY FORTH ALSO DEFINITIONS     EXIT                            The debugger is designed to let the user single step the        execution of a high level definition.  To invoke the            debugger, type DEBUG XXX where XXX is the name of the           word you wish to trace.  When XXX executes, you will get        a single step trace showing you the word within XXX that        is about to execute, and the contents of the parameter          stack.  If you wish to poke around, type F and you can          interpret Forth commands until you type RESUME, and execution   of XXX will continue where it left off.  This debugger works    by patching the NEXT routine, so it is highly machine and       implementation dependent.  The same idea should work            however on any Forth system with a centralized NEXT routine.    \ High Level Trace                                    18APR83HHLVOCABULARY BUG   BUG ALSO DEFINITIONS                           VARIABLE 'DEBUG   ( Code field for high level trace )           VARIABLE <IP      ( Lower limit of IP )                         VARIABLE IP>      ( Upper limit of IP )                         VARIABLE CNT      ( How many times thru debug next )            ASSEMBLER HEX                                                   LABEL FNEXT   ( Fix the >NEXT code back to normal )                0AD # AL MOV   AL >NEXT    #) MOV                              D88B # AX MOV   AX >NEXT 1+ #) MOV                              RET                                                           LABEL DNEXT   ( The Debugger version of a normal >NEXT )           AX LODS   AX W MOV   0 [W] JMP                               DECIMAL                                                                                                                                                                                         \ High Level Trace                                    12Apr84mapHEX ASSEMBLER LABEL DEBNEXT                                        <IP #) IP CMP   U> IF                                              IP> #) IP CMP   U<= IF                                             CNT #) AL MOV   AL INC   AL CNT #) MOV                          2 # AL CMP   0= IF                                                 AL AL SUB   AL CNT #) MOV  FNEXT #) CALL                        IP PUSH   'DEBUG #) W MOV   0 [W] JMP                  THEN THEN THEN      DNEXT #) JMP                             CODE PNEXT   (S -- )                                               0E9 # AL MOV   AL >NEXT #) MOV                                  DEBNEXT  >NEXT 3 + - # AX MOV   AX >NEXT 1+ #) MOV              NEXT   C;                                                    FORTH DEFINITIONS                                               CODE UNBUG    (S -- )                                              FNEXT #) CALL   NEXT   C;   DECIMAL                          \ Load Screen for the MultiTasker                     18APR83HHLONLY FORTH ALSO DEFINITIONS                                        1 2 +THRU    CR .( MultiTasker Low Level Loaded )            ONLY FORTH ALSO DEFINITIONS    EXIT                             The MultiTasker is loaded as an application on top of the       regular Forth System.  There is support for it in the nucleus   in the form of USER variables and PAUSEs inserted inside of     KEY EMIT and BLOCK.  The Forth multitasking scheme is           co-operative instead of interruptive.  All IO operations cause  a PAUSE to occur, and the multitasking loop looks around at     all of the current task for something to do.                                                                                                                                                                                                                                                                                                                                                    \ Multitasking low level                              11OCT83HHLCODE (PAUSE)   (S -- )                                             IP PUSH   RP PUSH   UP #) BX MOV   SP 0 [BX] MOV                BX INC   BX INC   BX INC   BX INC                               0 [BX] BX ADD   BX INC   BX INC   BX JMP   C;                                                                                CODE RESTART   (S -- )                                             -4 # AX MOV   BX POP   AX BX ADD   BX UP #) MOV                 AX POP   AX POP                                                 0 [BX] SP MOV   RP POP   IP POP   NEXT   C;                                                                                                                                                                                                                                                                                                                                                                                                                  \ Manipulate Tasks                                    11OCT83HHLHEX   80 CONSTANT INT#                                          : LOCAL   (S base addr -- addr' )   UP @ -   +   ;              : @LINK   (S -- addr )   LINK DUP @ +   2+   ;                  : !LINK   (S addr -- )   LINK 2+ -   LINK !   ;                 : SLEEP   (S addr -- )   E990 SWAP ENTRY LOCAL !   ;            : WAKE    (S addr -- )   80CD SWAP ENTRY LOCAL !   ;            : STOP    (S -- )        UP @ SLEEP   PAUSE   ;                 : SINGLE  (S -- )        ['] PAUSE >BODY ['] PAUSE !   ;        CODE MULTI   (S -- )                                               ' (PAUSE) @ # BX MOV   BX ' PAUSE #) MOV                        ' RESTART @ # BX MOV                                            DS AX MOV   AX PUSH   AX AX SUB  AX DS MOV                      CS AX MOV   AX INT# 4 * 2+ #) MOV   BX INT# 4 * #) MOV          AX POP  AX DS MOV  NEXT   C;                                 UP @ WAKE   ENTRY !LINK      DECIMAL                            \ Load Screen for Machine Dependent IO Words          11OCT83HHLONLY FORTH ALSO DEFINITIONS                                        1 1 +THRU    CR .( Machine Dependent IO Words Loaded )       ONLY FORTH ALSO DEFINITIONS    EXIT                             Since the 8086 has a seperate IO path, we define a Forth        interface to it.  Use P@ and P! to read or write directly to    the 8086 IO ports.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                              \ Machine Dependent IO Words                          11OCT83HHLCODE PC@   (S port# -- n )                                         DX POP  0 AL IN  AH AH SUB  AX PUSH   NEXT   C;              CODE P@    (S port# -- n )                                         DX POP  0 AX IN  AX PUSH   NEXT   C;                         CODE PC!   (S n port# -- )                                         DX POP  AX POP  0 AL OUT   NEXT   C;                         CODE P!    (S n port# -- )                                         DX POP  AX POP  0 AX OUT   NEXT   C;                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                         \ Load Screen for 8086 Dependent Code                 11OCT83HHL                                                                All of the Machine Dependent Code for a Particular Forth        Implementation is factored out and placed into this file.  For  The 8086 there are 3 different components.  The 8086 assembler, The run time debugger, which must have knowledge of how NEXT    is implemented, and the MultiTasker, which uses code words to   WAKE tasks and put them to SLEEP.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                               \ 8086 Assembler                                      08OCT83HHLLABEL marks the start of a subroutine whose name returns its      address.                                                      DOES-OP Is the op code of the call instruction used for DOES> U C;  A synonym for END-CODE                                                                                                      Deferring the definitions of the commas, marks, and resolves      allows the same assembler to serve for both the system and the  Meta-Compiler.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                \ 8086 Assembler   Register Definitions               12Oct83map                                                                On the 8086, register names are cleverly defined constants.                                                                     The value returned by registers and by modes such as #) containsboth mode and register information. The instructions use the    mode information to decide how many arguments exist, and what toassemble.                                                         Like many CPUs, the 8086 uses many 3 bit fields in its opcodesThis makes octal ( base 8 ) natural for describing the registers                                                                                                                                We redefine the Registers that FORTH uses to implement its      virtual machine.                                                                                                                                                                                \ Addressing Modes                                    16Oct83mapMD  defines words which test for various modes.                 R8? R16? MEM? SEG? #?  test for mode equal to 0 thru 4.         REG?  tests for any register mode ( 8 or 16 bit).               BIG?  tests offsets size. True if won't fit in one byte.        RLOW  mask off all but low register field.                      RMID  mask off all but middle register field.                   SIZE  true for 16 bit, false for 8 bit.                         BYTE  set size to 8 bit.                                        OP,  for efficiency. OR two numbers and assemble.               W,  assemble opcode with W field set for size of register.      SIZE,  assemble opcode with W field set for size of data.       ,/C,  assemble either 8 or 16 bits.                             RR,  assemble register to register instruction.                 LOGICAL  true while assembling logical instructions.            B/L?  see 13MI                                                  \ Addressing                                          16Oct83mapThese words perform most of the addressing mode encoding.       MEM,  handles memory reference modes.  It takes a displacement,   a mode/register, and a register, and encodes and assembles      them.                                                                                                                                                                                         WMEM,  uses MEM, after packing the register size into the opcodeR/M,  assembles either a register to register or a register to    or from memory mode.                                          WR/SM,  assembles either a register mode with size field, or a    memory mode with size from SIZE. Default is 16 bit. Use BYTE    for 8 bit size.                                               INTER  true if inter-segment jump, call, or return.             FAR  sets INTER true.  Usage:  FAR JMP,   FAR CALL,   FAR RET.  ?FAR  sets far bit, clears flag.                                \ Defining Words to Generate Op Codes                 12Oct83map1MI  define one byte constant instructions.                     2MI  define ascii adjust instructions.                          3MI  define branch instructions, with one byte offset.          4MI  define LDS, LEA, LES instructions.                         5MI  define string instructions.                                6MI  define more string instructions.                           7MI  define multiply and divide instructions.                   8MI  define input and output instructions.                                                                                      9MI  define increment/decrement instructions.                                                                                   10MI  define shift/rotate instructions.                         *NOTE*  To allow both 'ax shl' and 'ax cl shl', if the register on top of the stack is cl, shift second register by cl. If not, shift top ( only) register by one.                              \ Defining Words to Generate Op Codes                 09Apr84map11MI  define calls and jumps.                                    notice that the first byte stored is E9 for jmp and E8 for call so C@ 1 AND  is zero for call, 1 for jmp.                       syntax for direct intersegment:   address segment #) FAR JMP                                                                                                                                                                                                   12MI  define pushes and pops.                                                                                                                                                                                                                                                                                                   14MI  defines returns.                                            RET    FAR RET    n +RET   n FAR +RET                                                                                         \ Defining Words to Generate Op Codes                 16Oct83map13MI  define arithmetic and logical instructions.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                               \ Instructions                                        16Oct83mapTEST  bits in dest                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                              \ Instructions                                        16Oct83map                                                                ESC                                                             INT  assemble interrupt instruction.                            SEG  assemble segment instruction.                              XCHG  assemble register swap instruction.                                                                                                                                                                                                                                                                                                                                                       CS: DS: ES: SS: assemble segment over-ride instructions.                                                                                                                                                                                                                                                                        \ Instructions                                        12Oct83mapMOV  as usual, the move instruction is the most complicated.     It allows more addressing modes than any other, each of which   assembles something more or less unique.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                       \ Instructions                                        12Oct83mapMost instructions are defined on these two screens. Mnemonics inparentheses are defined earlier or not at all.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                  \ Instructions                                        12Oct83mapMost instructions are defined on these two screens. Mnemonics inparentheses are defined earlier or not at all.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                  \ Structured Conditionals                             16Oct83mapA?>MARK     assembler version of forward mark.                  A?>RESOLVE  assembler version of forward resolve.               A?<MARK     assembler version of backward mark.                 A?<RESOLVE  assembler version of backward resolve.                                                                                                                                                                                                                                                                                                                                              These conditional test words leave the opcodes of conditional   branches to be used by the structured conditional words.          For example,                                                     5 # CX CMP   0< IF  AX BX ADD  ELSE  AX BX SUB  THEN                                                                                                                                         \ Structured Conditionals                             12Oct83map                                                                One of the very best features of FORTH assemblers is the abilityto use structured conditionals instead of branching to nonsense labels.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                         \ High Level Trace                                    11OCT83HHL                                                                                                                                                                                                                                                                BUG   The vocabulary that holds the high level trace words.                                                                     FNEXT                                                              A machine language subroutine that Fixes NEXT back to the       way it used to be.                                                                                                           DNEXT                                                              A copy of next that gets exeucted instead of the normal one.                                                                                                                                                                                                 \ High Level Trace                                    11OCT83HHLDEBNEXT  is the debugger's version of next                      If the IP is between <IP and IP> then the contents of the       execution variable 'DEBUG are executed.  First the IP is pushed onto the parameter stack.  The word pointed to by 'DEBUG can be any high or low level word so long as it discards the IP that   was pushed before it is called, and it must terminate by callingPNEXT to patch next once again for more tracing.                                                                                PNEXT patches Forth's Next to jump to DEBNEXT.                  This puts us into DEBUG mode and allows for tracing.                                                                                                                                                                                                            FIX restores Forth's Next to its original condition.            Effectively disabling tracing.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                  \ Multitasking low level                              11OCT83HHL(PAUSE)   (S -- )                                                  Puts a task to sleep by storing the IP and the RP on the        parameter stack.  It then saves the pointer to the              parameter stack in the user area and jumps to the code          pointed at by LINK, switching tasks.                         RESTART     (S -- )                                                Sets the user pointer to point to a new user area and           restores the parameter stack that was previously saved          in the USER area.  Then pops the RP and IP off of the           stack and resumes execution.   The inverse of PAUSE.                                                                                                                                                                                                                                                                                                                                         \ Manipulate Tasks                                    11OCT83HHLINT#   The software interrupt number to use on the 8086         LOCAL  Map a User variable from the current task to another task@LINK  Return a pointer the the next tasks entry point          !LINK  Set the link field of the current task (perhaps relative)SLEEP  makes a task pause indefinitely.                         WAKE  lets a task start again.                                  STOP  makes a task pause indefinitely.                          SINGLE  removes the multi-tasker's scheduler/dispatcher loop.   MULTI                                                             installs the multi-tasker's scheduler/dispatcher loop.          By patching the appropriate INT vector and enabling PAUSE.                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                    \ Machine Dependent IO Words                          07Apr84mapCODE PC@   (S port# -- n )                                         Fetch an 8 bit byte from an io port                          CODE P@    (S port# -- n )                                         Fetch a 16 bit word from an io port                          CODE PC!   (S n port# -- )                                         Store an 8 bit byte into an io port                          CODE P!    (S n port# -- )                                         Store a 16 bit word into an io port