home *** CD-ROM | disk | FTP | other *** search
/ Simtel MSDOS - Coast to Coast / simteldosarchivecoasttocoast2.iso / forth / bbl_a.zip / ASM.BLK next >
Text File  |  1986-10-25  |  69KB  |  1 lines

  1. \ BBL Post-Fix assembler                                                                                                        This assembler is almost a direct steal of the public domain    assembler written by Michael Perry.  You may NOT sell this      assembler.  If you pass it on, you must leave the credit        to Michael Perry intact!                                        Michael Perry                                                   1125 Bancroft Way                                               Berkeley California                                             94702  (415) 644-3421                                                                                                           This variant of it was written by                               Roedy Green                                                     Canadian Mind Products                                          #11 - 3856 Sunset Street                                        Burnaby BC Canada V5G 1T3                                       \ Load screen                                                   2 999 THRU                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                      \ General Notes                                                 ;S                                                              To create and assembler language definition, use the defining   word CODE.  It must be terminated with either END-CODE or ;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.                                                                                                                Here is the code for an equivalent to SWAP                      CODE MY-SWAP  ( a b -- b a )                                      DX POP   AX POP  BX PUSH  CX PUSH  CX DX MOV   BX AX MOV        NEXT  END-CODE                                                                                                                                                                                \ General Notes                                                 ;S                                                              Before you go writing your own code words, you had better       have a good look at BBLASM.DOC where the register               conventions are explained.                                                                                                      Briefly CX:BX is top element of the stack.                      DS:SI is the interpretive pointer.                                    DS: rarely points anywhere useful to you. Use CS: or ES:  SS:SP is stack pointer                                          SS:BP is return stack pointer                                   DI    is kept zero.  The system will crash if it isn't.         DX:AX are scratch regs                                          ES:   is a scratch reg                                          Direction bit in flags register for strings is kept 0.                                                                          \ sample code                                                   ;S                                                                      AX BX MOV  means move AX into BX                               5 # AX ADD  means add immediate data 5 to reg AX             0 [BX] AX SUB  means subtract value in memory location                         pointed to by BX from AX                      AX 9 [BX+SI] SUB  means subtract AX from the value in the                         memory location 9 past the sum of BX and SI  CS: XXX #) BX AND  means AND BX with the                                           contents of memory location CS:xxx                              leaving the result in BX                            # 1 AX SHL  means shift register AX left one bit                 CL AX SHL  means shift register AX left by count in CL        7 # AX TEST  means test AX with the immediate mask 7.      BYTE  7 # 0 [BX]  TEST means test contents of memory pointed                      to by BX with immediate data 7.              \ sample code                                                   ;S                                                                XXX [BX] AX LEA  get address of XXX+BX into AX                                   ( only offset portion LSW of XXX is )                           ( used. )                                     XXX MSW # DX MOV  if XXX is a VARIABLE get SEG part of its                        pfa into DX                                   XXX LSW # AX MOV  if XXX is a VARIABLE get OFFSET part of its                     pfa into AX                                  ES: XXX #) AX MOV  if XXX is a VARIABLE whose pfa SEG is in ES                     this will get the LSW of its contents into                      AX                                                   ' XXX JMP  start executing the code at XXX_cfa                   ' XXX JE  start executing the code at XXX_cfa          For more examples see the instructions themselves                                                                               \ WARNINGS                                                      ;S                                                              This assembler has almost NO error checking.  It just keeps     on lumbering along generating garbage.  Until you learn the     ropes I strongly suggest using a debugger such as Periscope to  disassemble all code you create.  There are lots of nasty       surprises and that is the only way I know to learn the          pitfalls.                                                                                                                       Ordinary assemblers keep track of # verses #) for you. You have to be explicit in this post-fix assembler.                                                                                      1 AX MOV is illegal!  You need 1 # AX MOV                                                                                       Between CODE and END-CODE you are EXECUTING not COMPILING.      Thus you use ' rather than [']                                  \ WARNINGS continued                                            ;S                                                              The assembler is postfix.  The source comes before the          destination opposite to MASM.  Numbers or addresses must        be followed by # for immediate data or #) to indicate a direct  address.                                                                                                                        Index registers must always be preceeded by a constant even     if the constant is 0.                                                                                                           There are special rules on shift instructions and TEST that     might catch you off guard. JMP and JE have tricky rules.                                                                        You also need to put in your own segment overrides.  MASM does  this for you.  Nearly every memory reference will need a CS:    or ES: override.                                                \ WARNINGS continued                                            ;S                                                              Make sure you fully understand the difference between           XXX JMP and XXX #) JMP.  Normally you want XXX JMP.                                                                             Words such as BL IF THEN BEGIN END are in both the ASSEMBLER    and FORTH vocabularies.  Be very careful about the search       order or you will get the wrong version.  The assembler         versions have totally different effects.                                                                                        Order is very important.  1 [BX] is correct, [BX] 1 is not.     1 # AX TEST is correct AX 1 # TEST is not.                                                                                                                                                                                                                                                                                      \ Notes to people who wish to modify the assembler              ;S                                                              Read the iAPX 88 book by Intel published by Reston Publishing   if you want to how op codes, registers, addressing modes etc    are encoded.  This book is a little more useful than The 8086   Book by Russell Rector and George Alexy Osborne/McGraw Hill     for this purpose because all the variants of an op code are     gathered together on one page.  It is not as useful for         understanding what instructions do however.  It also has        8088 instruction timings, -- something The 8086 Book lacks.                                                                     Another good book is the PD70108/70116 Low-Power CMOS           Microprocessors User's manual published by NEC electronics on   the V20/V30 chip.  The legal beavers at Intel and NEC forced    NEC to use non-standard mnemonics, but other than that the      book is concise and clear and sometimes free.                   \ ASSEMBLER CODE                                                                                                                FORTH DEFINITIONS                                               DECIMAL 3000 VOC-SIZE ! ( nfas only not bodies )                VOCABULARY ASSEMBLER ( not immediate )                          ONLY FORTH ALSO ASSEMBLER DEFINITIONS                                                                                           : CODE  ( -- starts assembler definition )                        CREATE UNCREATE ( build nfa and empty cfa )                     SMUDGE          ( make name temporarily invisible )             ASSEMBLER ;                                                                                                                   ' CODE FORTH DEFINITIONS ALIAS CODE                                                                                                                                                                                                                             \ ;CODE                                                                                                                         ASSEMBLER DEFINITIONS                                           : ;CODE  ( -- : used in defining words with actions  )                             ( written in assembler )                       ?CSP             ( colon stack depth same as when started? )    COMPILE (;CODE)  ( will pop Rstack into IP )                    HEREC TOKEN,     ( redirect high level to low level code )                       ( we are about to write )                      [COMPILE] [      ( stop compilation so things like AX POP )                      ( will be executed at compile time )           ( don't UNSMUDGE yet.  Wait for END-CODE )                      ASSEMBLER ; IMMEDIATE                                                                                                         ' ;CODE FORTH DEFINITIONS ALIAS ;CODE                                                                                           \ END-CODE                                                      ASSEMBLER DEFINITIONS                                                                                                           : END-CODE  ( -- : ends assembler definition )                    UNSMUDGE ( reveal definition )                                  FORTH ;                                                                                                                       ' END-CODE ALIAS ;C                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                             \ 8086 Assembler   Register Definitions                         ;S                                                              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 opcodes  This makes octal ( base 8 ) natural for describing the registers                                                                                                                                                                                                                                                                                                                                \ 8086 Assembler   Register Definitions                         OCTAL                                                           : REG   ( mode index -- ) 11 Q* SWAP 1000 Q* OR CONSTANT   ;    : REGS   ( Count mode -- )   SWAP 0 DO  DUP I REG  LOOP  DROP ;            ( 0   1   2   3   4   5   6   7  )                   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] ( synonyms )         4 3 REGS   ES  CS  SS  DS                                       2 4 REGS   #   #)                                                DECIMAL   ;S                                                  e.g SP is defined as constant 1044 octal                        mode:0:index:index 1 octal digit per field                      # is immediate data #) is direct address                                                                                        \ Addressing Modes                                              OCTAL                                                           : MD ( mode -- : builds a word to test mode )                           CREATE  1000 Q* W,  DOES> UW@ SWAP 7000 AND =  ;                                                                          1 MD R16? ( n -- flag : true if 16-bit reg AX BX etc )                                                                          2 MD [RX]? ( n -- flag : true if [BX+SI] [BX] etc )                                                                             3 MD SEG? ( n -- flag : true if seg reg CS ES etc )                                                                           DECIMAL                                                                                                                                                                                                                                                                                                                         \ words to interrogate addressing modes MEM? REG? ACC?          OCTAL                                                           : MEM?  ( n -- f : true if memory reference )                           DUP [RX]? SWAP #) = OR ;                                : REG? ( n -- f : true if any reg 8 or 16 bit )                           7000 AND 2000 < ;                                     : ACC?  ( n -- f : true if reg is AX or AL )                          DUP AL = SWAP AX = OR ;                                    HEX                                                            : BIG?   ( N -- F : True if won't fit in one byte )                     ( 7 bit signed numbers from -128 to +127 will fit )             ( numbers with all 0 or all 1s in bits 15..7 will fit )         ( can ignore seg MSW part )                                     0FF80 AND ?DUP IF 0FF80 <> ELSE FALSE THEN ;            DECIMAL                                                                                                                         \ masking words RLOW RMID                                       OCTAL                                                                                                                           : RLOW   ( n1 -- n2 : mask off all but low register field)            7 AND ;                                                                                                                   : RMID   ( n1 -- n2 : mask off all but middle register field )        70 AND ; DECIMAL                                          DECIMAL                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                         \ SIZE WORD BYTE                                                                                                                VARIABLE SIZE   SIZE ON                                         ( SIZE  true for 16 bit, false for 8 bit. )                                                                                     : BYTE ( -- : set size to 8 bit ) SIZE OFF ;                       \ e.g. BYTE LODS instead of LODSB                                                                                            : WORD ( -- : set size to 16 bit ) SIZE ON ;                       \ e.g. WORD LODS instead of LODSW                               \ nothing at all to do with usual FORTH WORD                                                                                                                                                                                                                                                                                                                                                 \ BYTE, WORD,                                                                                                                   ' C,C ALIAS BYTE,                                                  ( c -- )                                                        \ compile 8 bits following the code field                                                                                    ' W,C ALIAS WORD,                                                  ( n -- )                                                        \ compile 16 bits following the code field                                                                                                                                                                                                                                                                                                                                                                                                                                                                                   \ OP, OPW, OPSIZE,                                                                                                              : OP,   ( N OP -- )   OR BYTE, ;                                    ( for efficiency. OR two numbers and assemble )                                                                             : OPW,   ( OP MR -- )   R16? 1 AND OP,  ;                           (  assemble opcode with W field set for size of register. )                                                                 : OPSIZE,   ( N OP -- )   SIZE @ 1 AND OP,  ;                       ( assemble opcode with W field set for size of data. )                                                                      : W/B,  ( n f -- )   IF  WORD, ELSE  BYTE, THEN  ;                  ( if flag is true compiles 16 bit else 8 bit value )                                                                                                                                                                                                        \ OPR, LOGICAL B/L?                                             OCTAL                                                                                                                           : OPRR,   ( MR1 MR2 -- )   RMID SWAP RLOW OR 300 OP,  ;          ( assemble register to register instruction. )                                                                                 VARIABLE LOGICAL                                                  ( true while assembling logical instructions. )                                                                               : B/L?   ( n -- f )   BIG? LOGICAL @ OR  ;                        ( true if offset is BIG or assembling a logical instruction )                                                                 DECIMAL                                                                                                                                                                                                                                                         \ Addressing MEM,                                               OCTAL                                                           : MEM,   ( DISP MR RMID -- )                                      ( handles memory reference modes.  It takes a displacement,)    ( a mode/register, and a register, and encodes and assembles)   ( them. )                                                        OVER #) = ( direct address )                                        IF  RMID 6 OP, DROP WORD,                                   ELSE  RMID OVER RLOW OR -ROT [BP] = OVER 0= AND                     IF  SWAP 100 OP, BYTE, ( reg-reg )                          ELSE  SWAP OVER BIG?  ( 16 bit displacement )                       IF  200 OP, WORD,                                           ELSE  OVER 0=  ( no regs )                                          IF  BYTE, DROP                                              ELSE  100 OP, BYTE, ( 8 bit displacement )                      THEN THEN THEN THEN  ; DECIMAL                               \ Addressing WMEM, R/M,                                                                                                         : WMEM,   ( DISP MEM REG OP -- )   OVER OPW, MEM,  ;             ( uses MEM, after packing the register size into the opcode )                                                                  : R/M,   ( MR REG -- )                                             OVER REG? IF  OPRR,  ELSE  MEM,  THEN  ;                     (  assembles either a register to register or a register to       or from memory mode. )                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                        \ WR/SM, INTER FAR                                              OCTAL                                                           : WR/SM,   ( R/M R OP -- )   2 PICK DUP REG?                       IF  OPW, OPRR,  ELSE  DROP OPSIZE, MEM,  THEN  ;              (  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. )                                                                                                             VARIABLE INTER                                                  ( true if inter-segment far jump, call, or return. )                                                                            : FAR    ( -- )   INTER ON  ;                                    ( Usage:  FAR JMP   FAR CALL   FAR RET )                                                                                        DECIMAL                                                                                                                        \ Defining Words to Generate Op Codes                           OCTAL                                                           : 1MI   CREATE  C,  DOES>  C@ BYTE, WORD ;                         ( define one byte constant instructions. e.g. CLD CWD )                                                                      : 2MI   CREATE  C,  DOES>  C@ BYTE, 12 BYTE, WORD ;                ( define ascii adjust instructions. e.g. AAD )                  ( op code followed by HEX 0A )                                                                                               : 3MI   CREATE  C,  DOES>  C@ BYTE, HEREC - 1- BYTE, WORD ;       ( define branch instructions, with one byte offset. )           ( 074 3MI JE )                                                  ( op code for ' XXX JE -- no modifier after the address ! )     ( also handles LOOP LOOPE JCXZ )                              DECIMAL                                                                                                                         \ Defining Words to Generate Op Codes                                                                                           OCTAL                                                           : 4MI   CREATE  C,  DOES>  C@ BYTE, MEM,  WORD ;                  ( define LDS, LEA, LES instructions. )                        DECIMAL                                                         ;S                                                                8D  4MI LEA                                                     op code for LEA                                                   ' XXX #) BX LEA         LEA BX,XXX_cfa                        ' XXX [BX] AX LEA         LEA AX,XXX_cfa[BX]                        0 [BX] AX LEA         LEA AX,[BX]                            you cannot have immediate data or a register as the source                                                                                                                                                                                                   \ Defining Words to Generate Op Codes                           OCTAL                                                           : 5MI   CREATE  C,  DOES>  C@ OPSIZE,  WORD ;                   DECIMAL                                                         ;S                                                              define string instructions.                                     0AC  5MI LODS                                                   opcode for LODS                                                 used WORD LODS instead of LODSW                                 or BYTE LODS instead of LODSB                                                                                                   alternatively you can use                                       0AD  1MI LODSW     0AC 1MI LODSB                                opcode for LODSW                                                allows LODSB instead of BYTE LODS                               allows LODSW instead of WORD LODS                               \ 7MI defines MUL DIV Op Codes                                  OCTAL                                                                                                                           : 7MI   CREATE  C,  DOES>  C@ 366 WR/SM, WORD ;                     ( define multiply and divide instructions. )                                                                                DECIMAL                                                         ;S                                                               30  7MI DIV                                                                 BX DIV        DIV BX                                        2 [BX] DIV        DIV WORD PTR [BX+2]                     BYTE  2 [BX] DIV        DIV BYTE PTR [BX+2]                           XXX #) DIV        DIV XXX_pfa                                                                                          Note that immediate data is not allowed                         The AX or DX registers are implied and are not mentioned        \ 8MI defines IN OUT Op Codes                                   OCTAL                                                                                                                           : 8MI   CREATE  C,  DOES>  C@ SWAP R16? 1 AND OR  SWAP # =         IF  BYTE, BYTE, ELSE  10 OR  BYTE, THEN  WORD ;                 ( define input and output instructions. )                                                                                    DECIMAL                                                         ;S                                                               E4  8MI IN                                                                                                                     6 # AL IN      IN AL,6                                          6 # AX IN      IN AX,6                                           DX AL IN      IN AL,DX                                          DX AX IN      IN AX,DX                                                                                                         \ 9MI Generate Op Codes for INC DEC                             OCTAL                                                                                                                           : 9MI   CREATE  C,  DOES>  C@  OVER R16?                           IF  100 OR SWAP RLOW OP,  ELSE  376 WR/SM,  THEN  WORD ;       ( define increment/decrement instructions. )                  DECIMAL                                                         ;S                                                                 00  9MI INC                                                     08  9MI DEC                                                         Special short forms for INC/DEC 16 bit reg                            BX INC        INC BX                                        2 [BX] INC        INC WORD PTR [BX+2]                     BYTE  2 [BX] INC        INC BYTE PTR [BX+2]                           XXX #) INC        INC XXX_pfa                                                                                          \ 10MI to Generate shift Op Codes such as SHL                   OCTAL                                                                                                                           : 10MI  CREATE  C,  DOES>  C@ ( CL AX op ) OVER REG?               IF ROT CL =                                                        IF  ( CL AX case ) 322                                          ELSE ROT DROP ( rid of 1 ) 320 THEN                          ELSE ( CL/1# 0 [BX] case )                                         >R >R >R ( get rid of 0 [BX] op )                               CL =                                                              IF ( CL 0 [BX] case ) R> R> R> 322                              ELSE ( 1 # 0 [BX] case ) DROP R> R> R> 320 THEN               THEN                                                         WR/SM,  WORD ;                                                 (  define shift/rotate instructions. )                        DECIMAL                                                         \ Notes on 10MI to Generate shift Op Codes such as SHL          ;S                                                               20 10MI SHL                                                       1 # AX SHL      SHL AX,1                                         CL AX SHL      SHL AX,CL                                    CL 0 [BX] SHL      SHL [BX],CL                                     5 # AX SHL      SHL AX,5 <--- later will be added for NEC                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                    \ JMPF                                                           OCTAL                                                          : JMPF ( dest -- : FAR JMP )                                          DUP MSW                                                           IF ( XXX JMP - store absolute address )                            352 BYTE, ,C ( 4 bytes offset:seg )                          ELSE ( mem/reg JMP )                                               377 BYTE, 50 ( reg field ) R/M, THEN                        INTER OFF WORD ;                                                                                                         DECIMAL                                                                                                                                                                                                                                                                                                                                                                                         \ JMP                                                            OCTAL                                                          : JMP ( dest -- )                                                   INTER @                                                           IF JMPF                                                         ELSE DUP MSW                                                      IF ( XXX JMP - convert to disp16 )                                 HEREC - 3 - DUP BIG? OVER 1+ BIG? OR                               ( relative to byte after either jmp l h or jmp l )              IF ( long JMP ) 351 BYTE, WORD,                                 ELSE ( short XXX JMP ) 353 BYTE, 1+ BYTE, THEN            ELSE ( mem/reg JMP )                                               377 BYTE, 40 ( reg field ) R/M, THEN                       THEN WORD ;                                               DECIMAL                                                                                                                         \ CALLF                                                          OCTAL                                                          : CALLF ( dest -- : FAR CALL )                                        DUP MSW                                                           IF ( XXX CALL - store absolute address )                           232 BYTE, ,C ( 4 bytes offset:seg )                          ELSE ( mem/reg CALL )                                              377 BYTE, 30 ( reg field ) R/M, THEN                        INTER OFF WORD ;                                                                                                         DECIMAL                                                                                                                                                                                                                                                                                                                                                                                         \ CALL                                                           OCTAL                                                          : CALL ( dest -- )                                                  INTER @                                                           IF CALLF                                                        ELSE DUP MSW                                                       (  We can distinguish XXX from the code for anything )          ( else because its MSW seg portion will be non-zero )           ( and the seg part of all other codes is 0. )                  IF ( XXX CALL - convert to disp16 )                                350 BYTE, HEREC - 2- WORD,                                   ELSE ( mem/reg CALL )                                              377 BYTE, 20 ( reg field ) R/M, THEN                       THEN WORD ;                                               DECIMAL                                                                                                                         \ CALL and JMP                                                  ;S                                                               CALL JMP work the same way except CALL lacks a short disp.      FAR CALL or CALLF and FAR JMP or JMPF do intersegment transfers                                                                       XXX JMP        JMP XXX        code is at XXX                 XXX #) JMP        JMP [XXX]      address of code is at XXX          BX JMP        JMP BX         address of code is in BX       0 [BX] JMP        JMP [BX]       address of code is in Ram                                       pointed to by BX                ' XXX JMP        JMP XXX_cfa    code is at XXX_cfa           XXX [BX] JMP        JMP XXX_pfa [BX]                                                               address is in RAM.  Does                                        not mean start executing                                        BX bytes past XXX                                                                          \ 12MI Generate PUSH and POP Op codes                           OCTAL                                                           : 12MI                                                              ( define pushes and pops. )                                     ( e.g. 8F 07 58 12MI POP )                                      ( op codes for 2 [BX] POP  ES POP  AX POP )                     ( immediate data not allowed )                                   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@ BYTE, MEM,                                THEN THEN  WORD ;                                            DECIMAL                                                         ;S                                                              special op codes are needed to handle the SEG regs.             later # 88 PUSH will be added for the NEC                       \ RET +RET FAR RET RETF FAR +RET +RETF                          OCTAL                                                           : RETF ( -- ) 313 BYTE, INTER OFF ;                                                                                             : +RETF ( n -- ) 312 BYTE, WORD, INTER OFF ;                                                                                    : RET ( -- ) INTER @ IF RETF ELSE 303 BYTE, THEN ;                                                                              : +RET ( n -- ) INTER @ IF +RETF ELSE 302 BYTE, WORD, THEN ;                                                                    DECIMAL                                                           ;S                                                                 RET         RET                                              4 +RET         RET 4                                           FAR RET         RETF                                               RETF         RETF                                           \ 13MI arithmetic and logical Op Codes                           ( define arithmetic and logical instructions. ) OCTAL          : 13MI   CREATE  C, C,  DOES>  COUNT >R C@ LOGICAL !  DUP REG?     IF  OVER REG?                                                     IF  R> OVER OPW, SWAP OPRR, ELSE OVER MEM?                      IF  R> 2 OR WMEM,  ELSE  ( # ) NIP  DUP ACC?                    IF  R> 4 OR OVER OPW, R16? W/B,                                 ELSE  OVER B/L? OVER R16? 2DUP AND                                -ROT 1 AND SWAP NOT 2 AND OR 200 OP,                            SWAP RLOW 300 OR R> OP,  W/B,                                 THEN  THEN  THEN                                              ELSE  ( MEM )  ROT DUP REG?                                       IF  R> WMEM,                                                    ELSE  ( # ) DROP  2 PICK B/L? DUP NOT 2 AND 200 OR OPSIZE,        -ROT R> MEM,  SIZE @ AND W/B, THEN  THEN WORD  ;         DECIMAL                                                         \ Notes on 13MI arithmetic and logical ops e.g. AND SUB         ;S                                                              2 20 13MI AND 0 28 13MI SUB                                     2=Logical no 8bit sign extend of immediate ops 0=arithmetic             special short forms can be used when dest is AX or AL             AX BX AND        AND AX,BX                                      CX BX AND        AND BX,CX                                      CL BL AND        AND BL,CL                                     1 # AX AND        AND AX,1                                      1 # AL AND        AND AL,1                                      1 # BX AND        AND BX,1                                  1 # 7 [BX] AND        AND WORD PTR [BX+7],1                BYTE 1 # 0 [BX] AND        AND BYTE PTR [BX],1                        2 [BX] CX AND        AND CX,[BX+2]                              2 [BX] CL AND        AND CL,[BX+2]                              XXX #) CX AND        AND CX,XXX_pfa                       \ TEST                                                          OCTAL                                                           : TEST   ( source dest -- )   DUP REG?                             IF  OVER REG?                                                     IF ( reg reg ) 204 OVER OPW, SWAP OPRR,                         ELSE OVER MEM?                                                    IF  ( mem reg ) 204 WMEM,                                       ELSE  ( # reg ) NIP  DUP ACC?                                    IF ( # AX/AL ) 250 OVER OPW, R16? W/B,                          ELSE ( # RX ) 366 OVER OPW,  DUP RLOW 300 OP,  R16? W/B,     THEN  THEN  THEN                                              ELSE  ( ? mem )  ROT DUP REG?                                     IF ( was reg mem ) 204 WMEM,                                    ELSE  ( was # mem )                                               DROP  366 OPSIZE,  0 MEM,  SIZE @ W/B,                      THEN  THEN  WORD ; DECIMAL                                   \ Notes on TEST                                                 ;S                                                                      01 # AX TEST        TEST AX,01                                  01 # AL TEST        TEST AL,01                                  01 # BX TEST        TEST BX,01                                    BX CX TEST        TEST CX,BX                               1 # 7 [BX] TEST        TEST WORD PTR [BX+7],1              BYTE 1 # 0 [BX] TEST        TEST BYTE PTR [BX],1                      2 [BX] CX TEST        TEST CX,WORD PTR [BX+2]                   2 [BX] CL TEST        TEST CL,BYTE PTR [BX+2]                   CX 2 [BX] TEST        TEST CX, WORD PTR [BX+2]                  CL 2 [BX] TEST        TEST CL,BYTE PTR [BX+2]             special short forms exist for AX AL and with immediate data     Any immediate data must be shown as the source rather than      the destination.                                                                                                                \ Instructions  ESC INT                                         HEX                                                             : ESC   ( source ext-opcode -- )   RLOW 0D8 OP, R/M,  WORD ;                                                                    : INT   ( N -- )   DUP 3 =                                          IF DROP 0CC BYTE, ( can be done with 1 byte )                   ELSE 0CD BYTE, BYTE, THEN WORD ;                                                                                            DECIMAL                                                         ;S                                                                     0 [BX] ESC         ESC [BX]                                   ' XXX #) ESC         ESC XXX_cfa                                 ESC cannot be used with a plain register or immediate           data                                                                  3 INT         INT 3                                                                                                 \ Instructions  XCHG                                            HEX                                                                                                                             : XCHG   ( MR1source MR2dest  -- )   DUP REG?                      IF  DUP AX =                                                      IF  ( dest was AX )                                                 OVER REG? ( source a reg too? )                                   IF ( BX AX style ) DROP RLOW 90 OP,                             ELSE ( [BX] AX style ) 86 WR/SM, THEN                    ELSE ( dest reg but not AX ) OVER AX = ( source = AX )           IF  NIP  RLOW 90 OP,                                            ELSE  86 WR/SM,  THEN  THEN                                   ELSE  ROT 86 WR/SM,  THEN  WORD ;                                                                                            DECIMAL                                                                                                                         \ Notes on XCHG                                                 ;S                                                                     BX AX XCHG         XCHG BX                                      AX BX XCHG         XCHG BX                                      BX CX XCHG         XCHG CX,BX                               CX 0 [BX] XCHG         XCHG [BX],CX                             0 [BX] CX XCHG         XCHG [BX],CX                                                                                          XCHG has short form if dest register is AX and source is reg.   When one operand is Memory it must be the destination not the   source.  This assembler will swap the operands if necessary     to automatically care of these two cases.                                                                                                                                                                                                                                                                                       \ Instructions   CS: DS: ES: SS: SEG                            HEX                                                             : SEG   ( SEG -- )   RMID 26 OP,  ;                             : CS:   CS SEG ;                                                : DS:   DS SEG ;                                                : ES:   ES SEG ;                                                : SS:   SS SEG ;                                                DECIMAL                                                         ;S                                                              use of segment override                                                                                                         AX CS: 1 [BX] MOV         MOV AX,CS:[BX+1]                                                                                      The override can come anywhere before the op-code                                                                                                                                               \ Instructions                                                  HEX                                                             : MOV   ( Source Dest ) DUP SEG?                                   IF  8E BYTE, R/M,  ELSE  DUP REG?                                 IF  OVER #) = OVER ACC? AND                                       IF  A0 SWAP OPW,   DROP  WORD,  ELSE  OVER SEG?                 IF  SWAP 8C BYTE, OPRR,  ELSE  OVER # =                         IF  NIP DUP R16? SWAP RLOW OVER 8 AND OR B0 OP, W/B,            ELSE  8A OVER OPW, R/M,  THEN THEN THEN                       ELSE  ( MEM ) ROT DUP SEG?                                        IF  8C BYTE,  MEM,  ELSE  DUP # =                               IF  DROP C6 OPSIZE, 0 MEM,  SIZE @ W/B,                         ELSE  OVER #) = OVER ACC? AND                                   IF  A2 SWAP OPW,  DROP  WORD,   ELSE  88 OVER OPW, R/M,     THEN THEN THEN THEN THEN   WORD  ;                            DECIMAL                                                        \ Notes an MOV                                                  ;S                                                              Place the Source before the destination -- this is the          opposite of MASM Version 4 conventions!! Watch out                    AX BX MOV              MOV BX,AX                                2 # AL MOV             MOV AL,2                                 2 #) AX MOV            MOV AX,[2]                               AX 2 [BX] MOV          MOV [BX+2],AX                            AX ' XXX >BODY #) MOV  MOV XXX_PFA,AX                           AX 2 #) MOV            MOV [2],AX                               CS AX MOV              MOV AX,CS                                CS: 0 #) AX MOV        MOV AX,CS:[0]                                                                                      Note CS: means seg override, and CS is just the reg.                                                                                                                                            \ Instructions                                                  HEX                                                              37  1MI AAA     D5  2MI AAD     D4  2MI AAM     3F  1MI AAS    0 10 13MI ADC  0 00 13MI ADD   2 20 13MI AND       ( 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                                                                    DECIMAL                                                                                                                                                                                                                                                                                                                                                                                        \ Instructions                                                  HEX                                                             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            ( 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  5MI LODS    E2  3MI LOOP    E1  3MI LOOPE   E0  3MI LOOPNE                                                                  DECIMAL                                                                                                                                                                                                                                                                                                                                                                                        \ Instructions                                                  HEX                                                                    ( 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                         ( 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  5MI STOS  0 28 13MI SUB           ( TEST ) 9B  1MI WAIT           ( XCHG )  D7  1MI XLAT  2 30 13MI XOR          ( +RET )                                                  DECIMAL                                                                                                                        \ alias string Instructions                                     HEX                                                             0A4  1MI MOVSB                                                  0AE  1MI SCASB                                                  0AA  1MI STOSB                                                   A6  1MI CMPSB                                                  0AC  1MI LODSB                                                                                                                  0A5  1MI MOVSW                                                  0AF  1MI SCASW                                                  0AB  1MI STOSW                                                   A7  1MI CMPSW                                                  0AD  1MI LODSW                                                  DECIMAL                                                                                                                                                                                         \ NEC-V20 instructions                                          ;S                                                              To come: bit and nibble instructions and immediate SHL and PUSH     BL ROL4   XXX #) ROL4         BL ROR4            XXX #) ROR4 3 # BL INS                                                       BL CL EXT    3 # BL EXT                                          4 # PUSH         PUSHR                                       3 # BX SET1   3 # BL SET1  3 # XXX #) SET1  BYTE 3 # XXX #) SET1 CL BX SET1    CL BL SET1   CL XXX #) SET1   BYTE CL XXX #) SET13 # BX CLR1   3 # BL CLR1  3 # XXX #) CLR1  BYTE 3 # XXX #) CLR1 CL BX CLR1    CL BL CLR1   CL XXX #) CLR1   BYTE CL XXX #) CLR13 # BX NOT1   3 # BL NOT1  3 # XXX #) NOT1  BYTE 3 # XXX #) NOT1 CL BX NOT1    CL BL NOT1   CL XXX #) NOT1   BYTE CL XXX #) NOT13 # BX TEST1 3 # BL TEST1 3 # XXX #) TEST1 BYTE 3 # XXX #) TEST1 CL BX TEST1  CL BL TEST1  CL XXX #) TEST1  BYTE CL XXX #) TEST1                                                                \ ?CONDITION                                                                                                                    : ?CONDITION ( true -- )                                            TRUE <> ( must be exact -1 )                                    ABORT" Conditionals not paired properly" ;                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                  \ Structured Conditionals                                                                                                       : ?>MARK    ( -- f addr ) TRUE   HEREC   0 BYTE,   ;               ( assembler version of forward mark. )                                                                                       : ?>RESOLVE ( f addr -- ) HEREC OVER 1+ - SWAP C! ?CONDITION ;     ( assembler version of forward resolve. )                                                                                    : ?<MARK    ( -- f addr ) TRUE   HEREC   ;                         ( assembler version of backward mark. )                                                                                      : ?<RESOLVE ( f addr -- ) HEREC 1+ -  BYTE,  ?CONDITION ;          (  assembler version of backward resolve. )                                                                                                                                                                                                                  \ 0= OV ALWAYS etc conditionals                                 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   EB CONSTANT ALWAYS  ( op code for JMP )        E3 CONSTANT CX0<>  74 CONSTANT <>  75 CONSTANT =                DECIMAL                                                         ;S                                                              These conditional test words leave the opcodes of conditional   branches to be used by the structured conditional words.        0= is opcode for JE -- opposite of meaning i.e. jmp to bypass   IF clause.                                                        For example,                                                     5 # CX CMP   0< IF  AX BX ADD  ELSE  AX BX SUB  THEN         \ Subtle conditional Notes                                      ;S                                                              You may be wondering why there are both < and 0< conditionals.  < corresponds to JGE and 0< correponds to JNS.                                                                                  < is the one normally used after an arithmetic operation          because it is accurate even if the result overflowed.                                                                         0< is the one used if you wish to test the result after the       overflow information is lost.                                                                                                 If there has been no overflow then both give the same results.                                                                                                                                                                                                                                                                  \ Structured Conditionals                                       HEX                                                             : IF     BYTE,  ?>MARK  ;                                       : THEN   ?>RESOLVE   ;                                          : ELSE   ALWAYS IF ( not the FORTH IF ) 2SWAP   THEN   ;        : BEGIN   ?<MARK   ;                                            : UNTIL  BYTE,  ?<RESOLVE   ;                                   : AGAIN   ALWAYS UNTIL   ;                                      : WHILE   IF   ;                                                : REPEAT   2SWAP   AGAIN   THEN   ;                             : DO      HEREC   ;  ( LOOP is machine instr )                  DECIMAL                                                         \ BE VERY CAREFUL NOT TO CONFUSE WITH THE FORTH EQUIVALENTS     \ THIS CAN HAPPEN AFTER AN ERROR WHEN THE CONTEXT IS            \ AUTOMATICALLY RESTORED TO FORTH RATHER THAN ASSEMBLER.                                                                        \ Examples of use of structured conditionals.                   ;S                                                                 5 # CX CMP 0<                                                   IF  ( executes if CX < 5 )                                          AX BX ADD                                                   ELSE ( executes if CX >= 5 ) AX BX SUB  THEN                                                                                    BEGIN                                                             ( code executes until low bit of AX is 0 )                      ...                                                           1 # AX TEST 0= UNTIL                                                                                                            BEGIN                                                             ...  ( loops endlessly )                                      AGAIN                                                                                                                        \ Examples of use of structured conditionals.                   ;S                                                                 BEGIN                                                             ( code executes as long as low bit of AX is 0 )                 ...                                                           1 # AX TEST 0<> WHILE                                             ...                                                           REPEAT                                                                                                                          9 # CX MOV DO                                                   ... ( perform this code 9 times with CX=9,8,...1 )              LOOP                                                                                                                                                                                                                                                                                                                         \ Macros NEXT POPCB POPDX PUSHCB PUSHDX                                                                                         \ Because : rather than CODE used, these words                  \ will assemble the code rather than execute it.                                                                                : NEXT    ( inline inner interpreter ) LODSW AX JMP ;                                                                           : POPCB    CX POP BX POP ;                                                                                                      : POPDA    DX POP AX POP ;                                                                                                      : PUSHCB   BX PUSH CX PUSH ;                                                                                                    : PUSHDA   AX PUSH DX PUSH ;                                                                                                                                                                    \ Last Screen                                                   FORTH DEFINITIONS