DataMuseum.dk

Presents historical artifacts from the history of:

RC4000/8000/9000

This is an automatic "excavation" of a thematic subset of
artifacts from Datamuseum.dk's BitArchive.

See our Wiki for more about RC4000/8000/9000

Excavated with: AutoArchaeologist - Free & Open Source Software.


top - metrics - download

⟦4dce7b5f5⟧ TextFile

    Length: 96000 (0x17700)
    Types: TextFile
    Names: »cgdump«, »tcgorder010«

Derivation

└─⟦00964e8f7⟧ Bits:30007478 RC8000 Dump tape fra HCØ.
    └─⟦b2ec5d50f⟧ 
        └─⟦this⟧ »cgdump« 
        └─⟦this⟧ »tcgorder010« 

TextFile

*load:  m2901
        ; -----------------------------------------------
        ; generel abrivations:
        ;
        ;   msw = most significant word.
        ;   lsw = least significant word.
        ;   msh = most significant halfword.
        ;   lsh = least significant halfword.
        ;   mso = most significant octet.
        ;   ino = intermidiate octet.
        ;   lso = least significant octet.
        ;   msb = most significatnt bit.
        ;   lsb = least significatnt bit.
        ;  
        ;    C(<number>) = contents of memory location <number>,
        ;                  <number> can in this case also
        ;                  be a register.
        ;
        ; dot notation examples:
        ;   wrk0.msh.lsb  = bit 11 inwrk0 register.
        ;   wrk0.lso.msb  = bit 16 in wrk0 register.
        ;
        ;   octet = 8 bits.
        ;   halfword = 12 bits.
        ;   word = 24 bit.
        ; 
        ;   the words is numbered so bit 0 is the most
        ;   significant bit ( sign bit) and bit 23 is
        ;   the least significant bit ( one bit).
        ;   note: this is completely oposite from
        ;         the normal rc8000 notation, but is
        ;         due to some numbering facts in the bits
        ;         bitslices.
        ; ------------------------------------------------
        ; -----------------------------------------
        ; 19810505:
        ;     temporary the iccn bus is skipped
        ;       with the skip construction 'iccnx',
        ;       or 'iccn'.
        ;       procedures only used by the iccn bus logic
        ;       is also skipped.
        ;       channel bus logic inserted.
        ; 810722/1600:
        ;       status/interupt level fetch is changed,
        ;       in module 'ansin'.
        ;       only checked for rh2901.
        ;       instead for two call of hlfwrd move
        ;       subroutines the extraction of the interupt
        ;       level is performed on the spot.
        ;       constant 'hlfwdm1' declered for this 
        ;       purpose.
        ; 810722/1607:
        ;       all occurences of the word octet is
        ;       changed to octet.
        ; 810722/1645:
        ;       the set disable/enable module is changed
        ;       so halfword move subroutines is not called.
        ; 810722/1650:
        ;       sobroutines 'hwmrtl' and 'hwmltr' is skipped
        ;       with the controlwords 'hlfwds'.
        ; 810722/1650:
        ;       return form interupt module is changed so
        ;       half word move is not called, new entry
        ;       in set level module.
        ;       level is noe in intrupt level register
        ;       and not in wrk0.
        ; 810723/1230:
        ;       error corrected: interupt bit in intreg cleared
        ;       in set disable module.
        ;       error corrected: answer interupt calls set disable
        ;       for exit
        ;       module for control of interupt of lower level.
        ; 810730/1100: 
        ;       only relewant for hc2901.
        ;       generel wait with x modification after fetch of
        ;       instruction is deleted from the fetch routines.
        ;       the generel wait logic is skipped out with
        ;       the control word gewax.
        ; 810730/1130:
        ;       only in rh8000.
        ;       clock before and after evry channel output
        ;       opration.
        ; 810730/1200:
        ;       the subroutine entry for init orf wrk 
        ;       registers is changed so it continues
        ;       directly to generel wait.
        ;       init of wrk registers is introduced
        ;       as seperate code in the init 2901 
        ;       sequence.
        ; 810803/1500:
        ;       init from prom instead from local dma
        ;       insertet in hc8000 text.
        ; 810805/1200:
        ;       generel get instruction inserted
        ;       to recieve level from external
        ;       interupt devices. am9519.
        ;       introduced as register 100,
        ;       bu schould be changed to register 
        ;       94. therefor the generel get instruction
        ;       with effective address 94 schould only
        ;       be allowed in monitor mode.
        ; 810807/1406:
        ;       disarming of charakter interupt controler
        ;       after interupt and arm after generel get 94.
        ;
        ; 810810/1749:
        ;       no prefetch module changed so the subroutine
        ;       call of ge03w0 is removed. this can be done
        ;       in the rh2901 because the 2903 never sends
        ;       a uneven instruction address.
        ; 810810/1750:
        ;       all iccn bus logic and definition is now removed.
        ;       the definition and the version up to this date
        ;       can be found in the file 'ticcnbus'.
        ; 810814/1750:
        ;       channel input/output logic changed, so it now
        ;       accepts negative length buffers.
        ; 810824/0930:
        ;       entry for external interupt  fetch with a
        ;       generel get instruction (gg 94) is inserted.
        ; 810824/0930:
        ;       all generel get (gg) and generel put (gp)
        ;       instrcution is allowed in rh8000, but
        ;       their function is different.
        ; 810827/1500:
        ;       dump of ic after evry instruction fetch
        ;       introduced. gp 64 gives the address at which
        ;       the dump schould start. gp 64 with the contents
        ;       zero stops the dump.
        ;       only in rh8000.
        ; 810903/1130:
        ;       in rh8000 the start stop reset furnction send
        ;       from hc8000 is changed so start after stop
        ;       is a specific operation, and not mixed in with 
        ;       start interupt.
        ;NEXT         
        ;--------------------------------------------------------
        ; ------------------------------------------------------
        ; project to be made in the future.
        ; 
        ; 001:    thre entry jump table schould be removed,
        ;         and the hc2903 schould jump direcly to 
        ;         funtions mudoules wanted.
        ;         before doing this subroutines and things 
        ;         which differ in length schoul be moved to 
        ;         the back of the program, so the rh and the hc
        ;         version get the same entry addrress if possible.
        ;         if that is not possible it dosent matter.
        ; 
        ; 002:    if it is decided to keep the entry jump table
        ;         then some call of cl2903 schoud be moved up
        ;         to the table.
        ;
        ; 003:    it schould be tried to ballance the time
        ;         from call of a memory acces to the acces
        ;         is finished, so their is as little waste time
        ;         as possible.
        ;
        ; 004:    change of the interupt signal from the
        ;         timer so it comes in as a seperate
        ;         condition from the charakter device interupt.
        ; 005:    check for parity error schould be performed
        ;         after memory data out and memory data in
        ;         the time out function in the memory data out
        ;         and memory data in schould also be finishd.
        ;PROJECT:
        ;------------------------------------------------------
        ; -----------------------------------------

        ; helping logical table.
        ; after the operation
        ;   sub(op1,op2)  op1 - op2
        ;
        ; cjmp(neg,l)    . op1 < op2
        ; cjmp(neg,l) not. op1 >= op2
        ; cjmp(zero,l)   . op1=op2
        ; cjmp(zero,l) not. op1 <> op2
*const: metimo,200            ;  no. of micro instructions before
                              ; memory timeout.
*const: butimo,200            ; no of micro instructions before
*const: intimo,100            ; no. of micro instrcutions before
                              ; time out for wait for
                              ; pause signal in the amd9519
                              ; interupt controler.
*const: sendto,4095           ; no of mic. instr. before sender
                              ; reciever has send timeout.
*const: intsta,6              ; least significant bit in status reg that 
                              ; contains the interupt bits.
*const: rc80le,3              ; interupt from rc8000 level,
                              ; same as timer interupt level.
*const: timele,3              ; timer interupt level - (1+3).
*const: chifil,4              ; channel input finis 
                              ; interupt level. ( 8)
*const: chisil,5              ; channel input start 
                              ; interupt level (9).
*const: chofil,6              ; channel output finis 
                              ; interupt level (10).
*const: lodmle,7              ; local dma interupt level.
*const: chdele,8              ; charakter device interupt level -(1+3).
*const: intno,9               ; no of allowed interupt bits
                              ; in the interupt register.
*const: hlfwrd,11             ; halfword,
                              ; no of bits - 1 in a half word.
*const: hfwdm1,10             ; halfword - 1,
                              ; no of bits - 2 in halfword.
*const: octet,7               ; no of bits - 1 in a data octet.
*const: dyreno,7              ; number of allowed dynamic registers
                              ; to be transferred to hc2903  - 1.
        ; power on logic starts microprogram in address 0
e01ini/:jmp(init)             ; program should start with a jump
                              ; for hardware reasons
                              ; also entry address of init from hc2903.
*onlyin:rh8000
        jmp(choint)           ; address 1 
                              ; channel out interupt.
        jmp(chiint)           ; address 2
                              ; channel in interupt.
reset:  cont     set(14)      ; power reset
        jmp(rc80in)           ; address 4
                              ; interupt from rc8000.
*until: rh8000
*onlyin:hc8000                ; local dma only in hc8000
        jmp(dmain)            ; entry micro program address 1.
        jmp(choint)           ; address 2,
                              ; channel out interupt.
        cont                  ; not used address 3.
        jmp(chiint)           ; address 4,
                              ; channel in interupt.
*until: hc8000
        ; entry address in hc2901 from hc2903
e01dob/:                      ; data out function jump table base.
e01dom/:jmp(dowrme)           ; write data word direct to memory.
*onlyin:hc8000
e01do0/:jmp(dontus)           ; own dma start
*until: hc8000
*onlyin:rh8000
e01do0/:jmp(douni0)           ; data out on unibus control 0.
*until: rh8000
e01do1/:jmp(dochst)           ; channel output start
*onlyin:hc8000
e01do2/:jmp(dontus)           ; own dma reset.
*until: hc8000
*onlyin:rh8000
e01do2/:jmp(douni1)           ; unibus reset.
*until: rh8000
e01do3/:jmp(dochre)           ; channel output reset.
*onlyin:rh8000
e01do4/:jmp(dontus)           ; not used.
*until: rh8000
*onlyin:hc8000
e01do4/:jmp(dochde)           ; write external char device.
*until: hc8000
e01do5/:jmp(dontus)           ; data out not used.
e01do6/:jmp(dontus)           ; data out not used.
e01do7/:jmp(dontus)           ; data out not used.
e01dib/:                      ; data in functon jump table base.
e01dim/:jmp(direme)           ; read data word direct form memory.
e01di0/:jmp(dintus)           ; data in not used.
e01di1/:jmp(dichst)           ; channel input start.
e01di2/:jmp(dintus)           ; data in not used.
e01di3/:jmp(dichre)           ; channel input reset.
*onlyin:hc8000
e01di4/:jmp(dichde)           ; read external chararcter device.
*until: hc8000
*onlyin:rh8000
e01di4/:jmp(dintus)           ; data in not used.
*until: rh8000
e01di5/:jmp(dintus)           ; data in not used.                    
e01di6/:jmp(dintus)           ; data in not used.
e01di7/:jmp(dontus)           ; data out not used.
e01inp/:jmp(npref0)           ; get instr with no prefetch
e01ip/: jmp(prftc0)           ; get instr with prefetch
e01gmw/:jmp(rem0)             ; get data word from memory.          
e01pmw/:jmp(wrm0)             ; put data word to memory.                
e01gdw/:jmp(drem0)            ; get double data word from memory.      
e01pdw/:jmp(dwrm0)            ; put double data word to memory.         
e01rtc/:jmp(gng100)           ; gg(100) get real time clock.
e01rtr/:jmp(geng64)           ; gg test register with no wait.
e01wtr/:jmp(genp64)           ; gp test register.
e01rtw/:jmp(geng66)           ; gg test register with wait.
                              ; rh8000: wait start by rc8000, and send
                              ;         interupt register to hc2903.
e01drd/:jmp(sadyre)           ; entry save dynamic registers.
e01sel/:jmp(stenle)           ; entry set enable level.
e01sdl/:jmp(stdile)           ; entry set disable level.
e01drr/:jmp(redyre)           ; entry reestablish dynamic registers.
e01rin/:jmp(rtrnpr)           ; entry return to next process.      
e01aci/:jmp(ansin)            ; entry answer and clear interupt.
e01is1/:jmp(intser)           ; entry goto  interupt service 1.
e01skn/:jmp(sknin0)           ; entry skip next instruction and fetch.
e01cil/:jmp(geng94)           ; entry gg (94) get interupt level from
                              ; amd9511 interupt controler,
                              ; not on rh8000.


        ; init of wrk1, wrk2 and q reg before entr&ering
        ; generel wait loop.

        ; standard init of wrk registers is
        ; wrk0 = 0, but presently expected. 
        ; wrk1 = 1.
        ; wrk2 = 8.
        ; q    = 2.
        ; use of the working registers schold be
        ; done in the following order wrk0,wrk1,wrk2,q.
gewwri: 
iniwrk: mzero(wrk0)           ; wrk0 := 0.
        moinc(wrk1,wrk0)      ; wrk1 := 1.
        moinc(q,wrk1)         ; q := 2.
        move(wrk2,q) sl       ; wrk2 := 4.
        move(wrk2,wrk2) sl    ; wrk2 := 8.
gewait:                       ; generel wait loop.
        ;===================
*onlyin:hc8000
        cjmp(chioin,gewai1) not; if charakter interupt then goto
                              ; gewwai1, this is done because
                              ; the hc2903 cpu or the channel bus
                              ; otherwise could delay the timer
                              ; interupt. ( not used yet).
*until: hc8000
        cjvt(vect) and(wrk1,hc2903) noload noint opinde;
                              ; hc2903 schould be addressed as source
                              ; because this allowes the the clocking
                              ; of the hc2903 data buffer into the
                              ; vector prom, the hc2903 register no 
                              ; is equivalent with the register no
                              ; of the internal register intreg so
                              ; because intreg(0) tells if an
                              ; interupt schold be send to the hc2903
                              ; the alu operation will result in
                              ; zero if no interupt an not zero if 
                              ; interupt, this is used in fetch         
                              ; and in prefetch.
*onlyin:rh8000
        jmp(gewait)           ; goto generel wait.
*until: rh8000
*onlyin:hc8000
        cjmp(chioin,gewait)   ; if no interupt from char device then
                              ; goto generel wait .
                              ; if char device interupt then
gewai1: moinc(wrk1,q)         ; wrk1 := divice 1 + read bit.
        jsb(rechd0)           ; call subroutine read char device
                              ; special device 0 to 7.
                              ; if sign bit set in the data word read
        cjmp(neg,timein)      ; then goto timer interupt.
                              ; disArment of first interupt controler.
        mzero(wrk1)           ; wrk1 := 0.
        move(wrk0,q)          ; wrk0 := const(2).
        lcpu(3)               ; for 0 to 3 do
        move(wrk1,wrk1) sraq  ;   wrk1.msb := q.lsb.
        move(wrk1,wrk1) sraq  ;   wrk1.msb := q.lsb.
        rep move(q,wrk0)      ;   q := const(2).
                              ;   end.
        moinc(wrk0,wrk2) sl   ; wrk0 := const(9) shift 1,
                              ; control device no of first
                              ; interupt controler.
        or(wrk1,wrk0)         ; wrk1 := dataword + device address.
        jsb(wrchde)           ; call subtroutine write charakter
                              ; device.
        lcpu('chdele)         ; counter := cha device interupt level.
        modec(wrk1,q)         ; wrk1 := 1.
        jmp(clcint)           ; goto calculate interupt .



*skip:  gewaix                ; skip general wait x entry.
gewaix: move(wrk0,q) sl       ; wrk0 := 4.
        and(status,wrk0) noload; if bit 4 is set in 
        cjmp(zero,gewaxx)     ; then goto gewaxx.          
geww1:  jsb(waitst)           ; wait for test register.
        move(wrk2,tstreg)     ; if test register <> 0 then
        move(wrk2,wrk2)       ;
        cjmp(zero,gewwri) not ; goto generel wait.
        andn(status,wrk0)     ; clear bit 4 in status reg.
        jmp(gewwri)           ; goto generel wait with init.
gewaxx:                       ; program counter test.
        sub(ic,pctst) noload  ; if current ic <> program counter
        cjmp(zero,gewwri) not ; test reg. then goto generel wait.
        or(status,wrk0)       ; set bit 4 in status.
        jmp(geww1)            ; goto wait for test reg.
*until: hc8000
*until: gewaix                ; skip of genarel wait with x entry.



        ; initialize.             
        ; -----------
init:   
*onlyin:rh8000
        mzero(clrf80)         ; clear flag bit signal from
                              ; rc8000.
        cont  init03          ; reset hc2903
        cont  init03
        cont  init03
                              ; hc2903 now goes to init.
        ;. temp test.
        mzero(ictsad)         ; clear instrcution test address.
*until: rh8000
        mzero(intreg)         ; init of wrk registers.
                              ; interupt bit register := 0.
        moinc(wrk1,intreg)    ; wrk1 := intreg+1 ( 1).
        moinc(q,wrk1)         ; q := wrk1 + 1 ( 2).
        move(wrk2,q) sl       ; wrk2 := q*2 ( 4).
*onlyin:rh8000:
init6:                        ; wait for start by rc8000.
        ; only control word with address bit(21:22) = 00 
        ; accepted as start.
        cjmp(re8000,init6) not; wait for data word from rc8000.
        move(wrk0,rc80cn)     ; get control word form rc8000 into wrk0.
        mzero(clrf80)         ; clear flag indicating that
                              ; word was send from hc8000.
        and(wrk0,wrk2) noload ; if bit(21) <> 0 then
        cjmp(zero,init6)  not ; goto wait for data word start.
        and(q,wrk0) noload    ; if bit(22) <> 0 then
        cjmp(zero,init6) not  ; goto wait for data word start.
*until: rh8000

        move(wrk2,wrk2) sl    ; wrk2 := wrk2*2 ( 8).
*skip:  newint
*onlyin:hc8000                ; init of hc8000 from 512 k octet prom.
        ;*skip: intprm   . skip init of hc8000 from prom
        ;. init of hc8000 from prom.
        ;. not used wrk2 = r1.
        ;.          intreg = r7.
        ;.          q.
        ;. destroyed:
        ;. wrk1 = r6.
        ;. prom word counter = r11.
        ;. memory storage address = r12.
        ;. data mask ( 255) = r8.
        ;. prom address counter = r9.
        ;. prom address address incrementer = r10.
        ;. memory data word = r14.
        ;. memory octet counter = r15.
        mzero(r9)             ; reset prom address counter.
        mzero(q)              ; reset q register.
        moinc(r10,r9) sl      ; r10 := constant 2.
        moinc(wrk2,r9) sl     ; wrk2 := 1 shift left 1 ( 2).
        add(wrk2,wrk2) sl     ; wrk2 := wrk2 + wrk2 ) shift left 1,
                              ; C(2).
        move(r12,wrk2)        ; memory address := first memory address C(8).
        move(r11,wrk2) sl     ; prom octet counter := wrk2 shift 1 C(16).
        lcpu(4)               ; for 0 to 4 do
        rep move(r11,r11) sl  ;   proc octet counter := prom octet counter
                              ;     shift 1 C(512).
        sub(r11,r10)          ; decrease prom octet counter with 2,
                              ; C(510) used memory location.
nxtwrd: move(r15,r10)         ; octet in word counter := 2.
nxtoct: dec(r11)              ; decrement prom octet counter.
        cjmp(neg,intfin)      ; i negative then goto init finis.
        move(wrk1,r9)         ; wrk1 := prom octet address.
        move(extreg,wrk1) opdirz oprama readch trnbus  sltiml;
                              ; read prom  at adress in mso snd ino of
                              ; wrk1.
        lcpu(7)               ; for 0 to 7 do
        rep move(wrk1,wrk1) slaq; ( q.mso := q.ino, q.ino := q.lso,
                              ;  q.lso := wrk1.mso) C(shift
                              ; recived data octet into q reg.).
        add(r9,r10)           ; increment prom address counter,
                              ; by 2.

        dec(r15)              ; decrement octet in word counter.
        cjmp(neg,nxtoct) not  ; if not negative then
                              ; nextoctet.
        move(meaddr,r12)      ; send memory data address at memory
        add(r12,r10)          ; calculate next memory address.
                              ; C(C()+2).
intw1:  cjmp(rememo,intw1) not; wait for memory ready.
        move(medata,q)        ; send data word to memory.
intw2:  cjmp(rememo,intw2) not; wait for memory write cycle 
                              ; finis.
        jmp(nxtwrd)           ; goto next word.
intfin:                       ; finis of init.
        mzero(q)              ; reset q register.
        mzero(intreg)         ; clear interupt register.
*until: hc8000
*until: newint
        mzero(intlev)         ; clear current interupt level.
        mzero(intlim)         ; clear disable level and
                              ; enable level.
        mzero(dichwc)         ; clear data in channel word counter.
        mzero(dochwc)         ; clear data out channel word counter.
                              ; init of channel interupt.
        cont firech           ; clock finis read channel.
        cont fiwrch           ; ckock finis write channel.
        cont clchii           ; clear channel input interupt.
        cont clchoi           ; clear channel output interupt.
        ;*skip:  oldint
*onlyin:hc8000                ; program is loaded from dma.
        move(lmem,wrk2)       ; local dma memory address := 8.
        move(lwco,wrk2) sl    ; local dma word counter := 16 ( 8 words.)
        lcpu(5)               ;
        rep move(lwco,lwco) sl; lwco := 1 (segm ) * 256 (words)         
                              ;          * 2 halfwords (lwco = 512)
init7:  cjmp(reldma,init7) not; wait for signal from local dma.
init6:  jsb(ipldma)           ; call subroutne input local dma.
        cjmp(zero,init7)   not; if lat word in memeory counter 
                              ; then goto continue init.
*onlyin:hc8000                ; only in test version.
        jsb(waitst)           ; call subroutine wait for test register.
*until: oldint.
*onlyin:hc8000
                              ; reset of first interupt controler.
        moinc(wrk1,wrk2) sl   ; wrk1 := 9 shift 1.
        jsb(wrchde)           ; goto write charakter device.
init5:  move(meaddr,wrk2)     ; send address of word 8 to memory.
*until: hc8000
*onlyin:rh8000
init5:  move(wrk0,wrk2) opexde sl; send addrs or word 8 to memory.
                              ; and load 8 shift 1 (i.e.16 ) to wrk0.
        move(wrk0,wrk0) sl    ; wrk0 := 32.
        move(c66,wrk0) sl     ; generate contant 66 in local dma
                              ; addrs register. c66 := 64.
        move(wrk2,c66) sl     ; wrk2 := c66( 64) * 2, 
                              ; ( wrk2 is now 128 
                              ; i.e. device 16*8).
        add(wrk2,wrk0)        ; wrk2 := wrk2  + wrk0, ( i.e.
                              ; wrk2 := 128 + 32 ( device 20 * 8)),
                              ; now wrk2 points to the relative 
                              ; distance from device table 0 to 
                              ; device table 20.
        add(c66,q)            ; c66 := c66 (64) + q (2).

init3:  cjmp(rememo,init3) not; wait for memory ready
                              ; get word 8 from memory.
        add(wrk2,medata)      ; wrk1 := word8 or memory
                              ; ( device base) + wrk2
                              ; (device no 20 * 8))

        move(meaddr,wrk2)     ; move addrs of device table to memory.
*until: rh8000                ; no 66 setting in hc8000.
init2:  cjmp(re2903,init2) not; nb: for sync of memory,
                              ; wait for hc2903 ready.


init4:  cjmp(rememo,init4) not; wait for ready of memory.
        move(hc2903,medata)   ; send memory data to hc2903.
        jmp(gewwri) cl2903    ; goto generel wait
                              ; and clock hc2903.
        ;*page:  XX tcgorder01
        ; generel subroutine section
        ; --------------------------
        ; subroutine get a word from hc2903 to wrk0.
        ; ==========================================
ge03w0: cjmp(re2903,ge03w0) not; wait until ready.
        rtn move(wrk0,hc2903) ; move word from hc2903 to wrk0.
        ; subroutine get a word from hc2903
        ; ==================================
        ; to wrk0 and memory address register,
        ;  ===================================
        ; usualy called as : jmp(ge03a0) cl2903
ge03a0: cjmp(re2903,ge03a0)  not; wait loop until hc2903 is  ready.
*onlyin:hc8000
        rtn move(meaddr,hc2903) opramf; return from subroutine and 
                              ; move the word recieved from hc2903
                              ; to  the memory address register
                              ; and start
                              ; memory read cycle, and open for 
                              ; internal registers  so the address
                              ; also is moved to wrk0, ( does
                              ; only function because the value
                              ; the  value of reg.address  = the value
                              ; of reg.wrk0 mod 16).
*until: hc8000
*onlyin:rh8000

        move(wrk0,hc2903)     ; get word form hc2903.
        andinv(wrk0,wrk1)     ; clear possibly bit ( 23).
        rtn move(meaddr,wrk0) ; send addrs to memory.
                              ; the trick with word 66 is only
                              ; performed in rh8000.

        ; subroutine get a word from hc2903
        ; =================================
        ; to wrk0 and control that if the word is
        ; equal to 66 then send 132 to memory address
        ; else send thw word to  memory address register.
ge03a6: cjmp(re2903,ge03a6) not; wait loop until hc2903 ready.
        move(wrk0,hc2903)     ; get address to wrk0.
        andinv(wrk0,wrk1)     ; clear bit(23) in address.
ge03ad: sub(wrk0,c66) noload  ; entry for read double word:
                              ; if address of data word = 66 then
        crtn(zero) move(meaddr,wrk0) not; return and send address to
                              ; memory  , and clock memory read cycle.
ge03aw: cjmp(rememo,ge03aw) not; else wait for memory.
        rtn add(wrk0,c66) noload opexde; send 132 to memory addrs register
                              ;  and  start memory read cycle.
*until: rh8000                ;
*skip:  hlfwds


        ; subroutine halfword move left to rigth.
        ; =======================================
        ; left half word of wrk0 is moved to rigth half word,
        ; and left half word is set to 0.
        ; entry call:
        ; q(23) = 0.
hwmltr: lcpu('hlfwrd)         ; load counter with length of half word.
        rep move(wrk0,wrk0) sr; wrk0 := wrk0 shift (-1),
                              ; if counter = 0 then next mic. instr.
                              ; else counter := counter -1 and
                              ; repeat this micro instruction.
        rtn                   ; return from subroutine.


        ; subroutine halfword move rigth to left.
        ; =======================================
        ; rigth half word of wrk0 is moved to left half word,
        ; and rigth half wrod is set to 0.
        ; entry call
        ; q(0) := 0.
hwmrtl: lcpu('hlfwrd)         ; load counter with length of half word.
        rep move(wrk0,wrk0) sl; wrk0 := wrk0 shift 1.
                              ; if counter = 0 then next mic. instr.
                              ; else counter := counter -1 and
                              ; repeat this micro instr.
        rtn                   ; return from subroutine.
*until: hlfwds
*onlyin:hc8000

        ; subroutine divide wrk0 with 8 , 4 or 2.
        ;========================================
        ; entry call:
        ; q(23) = 0.
        ; their is no reasonto use divide by 2,
        ; as a subroutine call.

divw08: move(wrk0,wrk0) sr    ; wrk0 := wrk0 / 2.
divw04: move(wrk0,wrk0) sr    ; wrk0 := wrk0 / 2.
divw02: rtn move(wrk0,wrk0) sr; wrk0 := wrk0 / 2.
*until: hc8000

        ; end of generel subroutine section.
        ;  ----------------------------------
        ;*page:  XX
        ; read memory section.
        ; --------------------
        ; read data word from memory to hc2903.
        ; ------------------------------------
*onlyin:rh8000
rem0:   jsb(ge03a6) cl2903    ; clock the hc2903, and call subroutine 
                              ; with control of address 66.
*until: rh8000
*onlyin:hc8000
rem0:   jsb(ge03a0) cl2903    ; clock the hc2903, and call subroutine
                              ; to get address of  data word to 
                              ; to memory and wrk0 (not used  here).
        cont                  ; nb: sync of memory.                
*until: hc8000

rlt2:   cjmp(rememo,rlt2) not ; wait until memory ready
        move(hc2903,medata) cl2903; move data from memory to hc2903.
        jmp(gewait)           ; goto wait cyclus.                   
        ; read double word from memory to hc2903.          
        ; ---------------------------------------           
*onlyin:rh8000
drem0/: jsb(ge03a6) cl2903    ; clock hc2903, and call subroutine
*until: rh8000
                              ; to get address of data word with
                              ; control of address 66.
*onlyin:hc8000
drem0/: jsb(ge03a0) cl2903    ; clock hc2903, and call subroutine
                              ; to get address of data word to memory 
                              ; and start memory read cycle.
*until: hc8000
        negadd(wrk0,q)        ; wrk0 := address of second data word
                              ; ( wrk0 - 2).
drlt2:  cjmp(rememo,drlt2) not; wait for first address fecth is ready.
        move(hc2903,medata) cl2903; hc2903 := memory'first data word,
                              ; and clock hc2903.
*onlyin:rh8000
        jsb(ge03ad)           ; call subroutine for control of
                              ; address 66 and start memory read cycle.
*until: rh8000
*onlyin:hc8000
        move(meaddr,wrk0)     ; memory'address := second word address.
*until: hc8000
drlt4:  cjmp(re2903,drlt4) not; wait forhc2903.
drlt3:  cjmp(rememo,drlt3) not; wait for memory address cycle.
        move(hc2903,medata) cl2903; hc2903 := memory'second data word,
                              ; clock hc2903.
        jmp(gewait)           ; clock hc2903, goto wait cycle.
        ;  end of read memory section
        ;  --------------------------
        ;  write memory section
        ; ---------------------
        ; write to memory from hc2903.     
        ; ----------------------------    
*onlyin:rh8000
wrm0:   jsb(ge03w0) cl2903    ; clock hc2903, and call subroutine
                              ; to get address into wrk0.
*until: rh8000
*onlyin:hc8000
wrm0/:  jsb(ge03a0) cl2903    ; clock hc2903, and call  subroutine
                              ; to get address of data word to
                              ; memeory address register and 
                              ; to wrk0.

*until: hc8000
*onlyin:hc8000
        cont             cl2903; clock ready for data word.
*until: hc8000
*onlyin:rh8000
        andinv(wrk0,wrk1) cl2903; clear bit(23) of address and
                              ; clock hc2903 ready.
*until: rh8000
wlt3:   cjmp(re2903,wlt3) not ; wait for memory data word.
*onlyin:hc8000
wlt2:   cjmp(rememo,wlt2) not ; wait for memory ready
*until: hc8000
        move(medata,hc2903)  cl2903; memory := hc2903.data, clock ready
                              ; the hc2903.
*onlyin:rh8000
        move(meaddr,wrk0)     ; memory address reg. := address
                              ; of data word.
*until: rh8000
*onlyin:hc8000
        cont                  ; sync of memory
*until: hc8000
wlt4:   cjmp(rememo,wlt4) not ; wait for memory write cycle.
        jmp(gewait)           ; goto wait cyclus.                     
        ; write double word to memory from hc2903.        
        ; ----------------------------------------        
*onlyin:rh8000
dwrm0/: jsb(ge03w0) cl2903    ; clock hc2903, and call subroutine
                              ; to get address into wrk0.

        andinv(wrk0,wrk1)   cl2903; clock ready for recieve first data 
                              ; word.
*until: rh8000
*onlyin:hc8000                ; next instead of above
dwrm0/: jsb(ge03a0) cl2903    ; clock hc2903, and call subroutine to get 
                              ; to get address of data word to
                              ; memory address register and wrk0.
        negadd(wrk0,q)  cl2903; wrk0 := wrk0 - 2, (  calc. of
                              ; next memory addrs., clock hc2903 ready 
                              ; for recieve data word.
*until: hc8000
dwlt3:  cjmp(re2903,dwlt3) not; wait for ready hc2903.
*onlyin:hc8000
dwlt5:  cjmp(rememo,dwlt5) not; wait for memory ready.
*until: hc8000
        move(medata,hc2903) cl2903; memory := hc2903'data.
                              ; clock hc2903 ready.
*onlyin:rh8000
        move(meaddr,wrk0)     ; move address of data word to address re
                              ; register and clock memory.
        negadd(wrk0,q)        ; wrk0 := wrk0 -  q, (  next address).
*until: rh8000
*onlyin:hc8000
        cont                  ; nessecary fo sync of
                              ; memory.
*until: hc8000
dwlt4:  cjmp(rememo,dwlt4) not; wait for memory ready.
*onlyin:hc8000
        move(meaddr,wrk0)     ; memory'address := calculated 
                              ; next address.
*until: hc8000
        jmp(wlt3)             ; goto last of write single word
                              ; to memory for continuation.
        ; end of write memory section.
        ; ----------------------------
        ;*page:  XX
        ; fetch instruction section.
        ; --------------------------

        ; after one of the fetch entries
        ;  contains pir ( prefetched instruction)
        ;  the next instrcution and   ic the address of  the next
        ;  after pir.
        ; fetch instruction with no prefetch.                
        ; -----------------------------------                
        ; subroutine send interupt to hc2903.
        ; -----------------------------------
sndint: 
        rtn intr03            ; return and set interupt bit to 
                              ; hc2903.
npref0/:and(wrk1,intreg) noload; temporary test entry.
nprftc/:cjsb(zero,sndint) not cl2903; normal no prefetch entry:
                              ;  if intreg(23) = 1
                              ; (i.e. interupt bit set
                              ;    then call subroutine send interupt,
                              ; clock hc2903 ready to accept data.
npref1: cjmp(re2903,npref1) not; wait for ic from hc2903.
        move(meaddr,hc2903) opramf; move the address to memory and start
                              ; memory addres cycle, and open for  
                              ; internal registers so the address 
                              ; also is moved to
                              ; to work 0. (does only function because
                              ; the value off  reg.addrs = the value
                              ; of reg.wrk0 mod 16 ).
sknin1: move(ic,q)            ; entry from skip next,
                              ;  sync. of memory, ic := 2 .
                              ; ( prepered for calculation of
                              ; next next instr in prefetch logic.)
npref2: cjmp(rememo,npref2) not; wait for memory address cycle.
        move(hc2903,medata) cl2903; move memory data word to hc2903,
                              ; and clock hc2903.
*onlyin:rh8000
        ;   jsb(ictst)            . call subroutine for posible writing
                              ; of instrcution counter out in
                              ; in memory for test purposes.
*until: rh8000
        add(wrk0,q) opexde    ; wrk0 := wrk0 + 2, wrk0 is now
                              ; pointing to next instruction,
                              ; open also to extern registers
                              ; which will cause a move of
                              ; wrk0 to memory address register
                              ; and start memory read cycle.
        add(ic,wrk0)          ; calculate address of next instr.
npref3: cjmp(rememo,npref3) not; wait for memory ready.
        move(pir,medata)      ; move prefetched instruction to
                              ; prefetch register from memory.
        jmp(gewait)           ; goto wait cycle.


        ; skip next instrcution.
        ; entry for skip instructions.
        ; ============================
sknin0/:and(wrk1,intreg) noload; temporary test entry:
sknins/:cjsb(zero,sndint) not ; if bit(23) intreg = 1 then goto
                              ; send interupt to hc2903.
        move(wrk0,ic) opexde  ; move address of next instr to wrk0,
                              ; open also 
                              ; the external registers which will
                              ; cause a move of wrk0 to the memory
                              ; address register and start a read 
                              ; cycle.
        jmp(sknin1)           ; continue in  fetch next instruction
                              ; with no prefetch.


        ; get prefetched instruction.
        ; ----------------------------
prftc0/:and(wrk1,intreg) noload; temporary test entry:
prftch/:cjsb(zero,sndint) not ; normal entry for prefetch next 
                              ; instruction:
                              ; if intreg(23)<>0 (i.e.      
                              ; interupt set) then call subroutine
                              ; set interupt.
        move(hc2903,pir) cl2903; move prefetched instrcution to
                              ; hc2903 and clock ready.
*onlyin:rh8000
        move(wrk0,ic)         ; wrk0 := ic of instruction +2.
        sub(wrk0,q)           ; wrk0 := wrk0 - 2.
        ; jsb(ictst)            . call subroutine ic test.
*until: rh8000.
        move(meaddr,ic)       ; move address of next prefetched 
                              ; instruction 
                              ; to memory.              
        add(ic,q)             ; calculate address of next instruction
                              ; to be prefetched.
prftc1: cjmp(rememo,prftc1) not; wait for memory address cycle.
        move(pir,medata)      ; move prefetched instruction from memory
                              ; to prefetch register.
        jmp(gewait)           ; goto wait cycle.
        ; end fetch instruction section
        ; -----------------------------

*onlyin:rh8000
ictst:  move(ictsad,ictsad)   ; if ic test address = 0 then
        crtn(zero)            ; then return from subroutine.
        move(medata,wrk0)     ; send wrk0 to memory.
        move(meaddr,ictsad)   ; send instrcution test address to
                              ; memory address register and start write cycle.
        add(ictsad,q)         ; calc. next ic test address.
ictsw1: cjmp(rememo,ictsw1) not; wait for memory ready.
        rtn                   ; retrun from subroutine.
*until: rh8000





*onlyin:rh8000
        ; special functions in rh8000
        ; ----------------------------
        ; subroutine control address from rc8000
        ; --------------------------------------
        ; the 2 second last bit of the instrcution
        ; controls the function of the control address.
        ; inst(21:22) = 00 => start after init and
        ;                     give interupt.
        ; inst(21:22) = 01 => reset ( goto init).
        ; inst(21:22) = 10 => stop imidiatly ( micro tempi stop).
        ; inst(21:22) = 11 => start after stop ( micro tempi start).
cnrc80: move(wrk0,rc80cn)     ; get control bits into wrk0.
        mzero(clrf80)         ; clear flag bit indicating
                              ; word send from rc8000.
        move(wrk2,wrk2) sr    ; wrk2 := 4.
        and(wrk0,wrk2) noload ; if control bits '1x' then
        cjmp(zero,cnrc82) not ;  goto control ( '11' or '10').
        and(q,wrk0) noload    ; if control bits is '01' then
        cjmp(zero,reset) not  ; then goto reset
        rtn move(wrk2,wrk2) sl; else wrk2 := 8 , start.
cnrc82: and(q,wrk0) noload    ; if control bits '10' then
        cjmp(zero,gewwri) not ; goto generel wait with init else
cnrc83: cjmp(re8000,cnrc83) not; wait until signal from rc8000.
        move(wrk0,rc80cn)     ; get control bits into wrk0.
        mzero(clrf80)         ; clear flag indicating word
                              ; send from rc8000.
        and(wrk0,wrk2) noload ; if bit(21) <> 1 then
        cjmp(zero,cnrc83)     ; then goto wait for start ( stop).
        and(q,wrk0) noload    ; if bit(22) <> 1 then
        cjmp(zero,cnrc83)     ; then goto wait for start ( stop).
        jmp(gewwri)           ; else start met goto 
                              ; generel wait with init.
*until: rh8000
*notin: rh8000


        ; write data in testregister. Startaddress by hardware.
        ; -----------------------------------------------------
genp64: jsb(ge03w0) cl2903    ; call subroutine to get word to wrk0,
                              ; and clock hc2903.
        move(tstreg,wrk0) cl2903; testregister:= wrk0 (hc290.data)
        jmp(gewait)           ; goto generel wait.

        ; Wait manual test and read testreg.
geng66: 
        jsb(waitst)           ; call subroutine wait test register.
geng64:                       ; entry generel get with no wait.
lab5:   move(hc2903,tstreg) cl2903; move test register to hc2903,
                              ; clock hc2903 ready.
        jmp(gewait)           ;   goto generel wait.

        ; subroutine wait manuel signal from test register.
        ; -------------------------------------------------
waitst: cjmp(tstrdy,waitst) not; wait for test register in read mode.
waits1: cjmp(tstrdy,waits1)   ; wait for test register in write mode.
        rtn                   ; return from subroutine.
        ; get real time clock, genereal get 100.
        ;---------------------------------------
        ; real time clock is not fixed yet. 800505
        ; real time clock is there for used for different test 
        ; purposes.
gng100: move(hc2903,intreg)  cl2903; move contents of real time clock
        jmp(gewait)           ; to hc2901, goto generel wait.

        ; get interupt level from external interupt device.
        ; generel get 94.
        ; -------------------------------------------------
        ; when an internal interupt is detected the
        ; true level can be optaind with gg 94.
        ; see: advanced micro device 9519 for
        ;      detailed and complete description.
geng94: 
                              ; arm first interupt controler.
                              ; create data word for arming.
        move(wrk0,q)          ; wrk0 := const(2).
        move(q,wrk1)          ; q := const(1).
        lcpu(3)               ; for 0 to 3 do begin
        move(wrk1,wrk1) sraq  ;   wrk1.msb := q.lsb.
        move(wrk1,wrk1) sraq  ;   wrk1.msb := q.lsb.
        rep move(q,wrk0)      ;   q := cost(2).
                              ;   end.
        moinc(wrk0,wrk2) sl   ; wrk0 := const(9) shift 1,
                              ; device address of first
                              ; interupt controler.
        or(wrk1,wrk0)         ; wrk1 := data word + device address.
        jsb(wrchde)           ; write charakter device for disarment
                              ; of interupt controler.
        modec(wrk1,q)         ; wrk1 := const(1).
        move(extreg,wrk1) oprama opdirz trnbus readch;
                              ; start read device 0, without selecting of
                              ; timer device.
        push move(extreg,wrk1) oprama opdirz trnbus readch clexde;
                              ; push next micro instr and start read
                              ; device 0, send iack puls to interupt
                              ; controler.
        loop(wainle) move(extreg,wrk1) oprama opdirz trnbus readch clexde;
                              ; repeat read and sen iack pulse to 
                              ; interupt controler until pause signal
                              ; from the interupt controler is finished.
        move(extreg,wrk1) oprama opdirz clexde trnbus readch;
                              ; read response level from interupt controler.
                              ; amd9519 interupt controler
                              ; to answer.
                              ; read level from external device bus.
                              ; into mso of wrk1.
        mzero(q)              ; clear q register.
        lcpu(7)               ; for 0 to 7 do
        rep move(wrk1,wrk1) slaq; q.lsb := wrk1.msb.
        move(hc2903,q) cl2903 ; send data word to hc2903.
        jmp(gewwri)           ; goto generel wait.
*until: rh8000                ;
        ;*page:  XX
*onlyin:rh8000
        ; generel get 66
        ; --------------
        ; wait for start by rc8000, send intreg to  hc2903.
geng66: jmp(cnrc83) cl2903    ; goto wait signal from
                              ; rc8000 and check control bits.

geng64:                       ; generel get 64.
        ; ---------------
        ; get test register.
        move(hc2903,intreg) cl2903; send interupt register to
                              ; hc2903 and clock hc2903 ready.
        jmp(gewait)           ; goto generel wait.

geng94:                       ; generel get 94.
        ; ---------------
        ; get interupt controler interupt.
        move(hc2903,intlev) cl2903; send interupt level to hc2903
                              ; and clock hc2903 ready.
        jmp(gewait)           ; goto generel wait.

gng100:                       ; generel get 100
        ; ---------------
        ; get real time clock.
        move(hc2903,intlim) cl2903; send interupt limit register
                              ; to hc2903 and clokc hc2903 ready.
        jmp(gewait)           ; goto generel wait.

genp64:                       ; generel put 64
        ; ---------------
        ; generel put test register.
        jsb(ge03w0) cl2903    ; get word from hc2903 to wrk0.
        move(ictsad,wrk0)     ; move data word to 
                              ; ic test address register.
        jmp(gewait)           ; goto generel wait.
*until: rh8000
        ; set interupt bit in interupt register.
        ; ------------------------------------
        ; call :                                        
        ;      wrk1 = std init 1.
        ;      wrk2 = std init 2.
        ;      q    = std init 2.
*onlyin:hc8000
timein:                       ; timer interupt.
        add(wrk1,q,wrk1)      ; wrk1 := 2 shift 1 + 1.
        jsb(rechd0)           ; call subroutine read char device no 0
                              ; to 7.
        modec(wrk1,q)         ; wrk1 := 1.
        ldct(timele)          ; load counter with timer interupt 
                              ; level.
*until: hc8000
*onlyin:rh8000
rc80in:                       ; interupt from rc8000
        ; the interupt is clocked direct into address location 4.
        jsb(cnrc80)           ; call subroutine to check control
                              ; bit from rc8000.
        ldct(rc80le)          ; load counter with interupt level
                              ; from rc8000.
*until: rh8000
clcint: jsb(clcin1)           ; push address of next micro instr.
clcin1: move(wrk2,wrk2) sl    ; wrk2 := wrk2 * 2, ( interupt bit).
        rep inc(wrk1)         ; wrk1 := wrk1 + 1 ( interupt no ).
enin03:                       ; entry for interupt bit 0, interupt 3,
                              ; or entry with initialised interupt 
                              ; values in wrk1 (interupt no) and
                              ; wrk2 ( the interupt bit in the
                              ; interupt register).
        add(wrk1,q)           ; wrk1 := wrk1 + q ( the first inetrupt
                              ; no is infact level 3).
                              ; entry intrs1:
                              ; entry when wrk2 and wrk1 is defined.
intrs1: or(intreg,wrk2)       ; set interupt bit in interupt register.
        sub(wrk1,intlev) noload; if interupt no > current interupt 
        cjmp(neg,gewwri)  not ; level then  goto generel wait.
intsr2: move(intlev,wrk1)     ; interupt level := interupt no as
                              ; new level.                  
        modec(wrk0,q)         ; wrk0 := 1 ( bit 23).
        or(intreg,wrk0)       ; intreg(23) := 1 ( interupt schold
                              ; be send to hc2903).
        jmp(gewwri)           ; goto general wait.
*onlyin:rh8000
        ; interupt service
        ; ================
        ; entry from monitor call and exeptions.
intser/:
        jmp(intse4) cl2903    ; goto intse4, clock hc2903 ready
                              ; to recieve information register.
*until: rh8000



        ; answer interupt cause and clear interupt bit
        ;=============================================
        ; in interupt register, continue in interupt
        ; service.
        ; interupt cause is current level.
        ; call:                              
        ;       wrk0,wrk1,kwr2,q = std. reg. init.
ansin/: move(hc2903,intlev) cl2903; send level to hc2903, and clock
                              ; hc2903 ready to recieve data.
        negadd(intlev,q)      ; justifi intlev because the
        dec(intlev)           ; first interupt bit corrospond
                              ; with intlev 3.
ansin3: andinv(intreg,wrk2)   ; clear  interupt bit.
        move(wrk2,wrk2) sl    ; wrk2 := wrk2 * 2 (next interupt bit).
        dec(intlev)           ; intlev := intlev - 1.
        cjmp(neg,ansin3) not  ; if interupt level > 0 then got ansin3.
*onlyin:hc8000
        jsb(ge03a0)           ; call subroutine to get address
                              ; of status and interupt limit
                              ; initialisation and start memory
                              ; ready cycle.
        jmp(intse4)           ; continue in interupt service 4.



        ; interupt service.
        ;==================
intser/:jsb(ge03a0) cl2903    ; call subroutine to get address to wrk0
                              ; and memory address register and start
                              ; memory read cycle, ( wrk0 := inf )
intse4: move(wrk2,wrk0)       ; wrk2 := wrk0 ( inf ).
                              ; this mic. instr is nessecary for memory
                              ; syncronitation.
        andinv(intreg,wrk1)   ; clear possible interupt bit in
                              ; interupt register.
*until: hc8000
*onlyin:rh8000
intse4: andinv(intreg,wrk1)   ; clear possible interupt bit
                              ; in interupt register.
        cjmp(re2903,intse4) not; wait for hc2903 ready.
        move(wrk2,hc2903)     ; get address of status and interupt
                              ; limit initialisation.
        move(intlev,wrk2)     ; remove possible last bit 
        andinv(intlev,wrk1)   ; in address.
        move(meaddr,intlev)   ; send address to memory and
                              ; start read cycle.
*until: rh8000
        moinv(wrk0,wrk1)  sr  ; start make bit in last halfword.
                              ; wrk0 := -1 ( all bits)  shift -1.
        lcpu(hfwdm1)          ; load counter with no of bits in
                              ; a halfword minus 1 ( first shift 
                              ; made when negating wrk1 into wrk0).
        rep move(wrk0,wrk0) sr; repeat until counter = 0 do
                              ;  wrk0 := wrk0 shift -1.
                              ;  counter := counter -1.
                              ;  end.
intse1: cjmp(rememo,intse1) not; wait for memory ready cycle.
        move(hc2903,medata) cl2903; send status/intlim to
                              ; hc2903 data register
                              ; and clock hc2903.
        move(intlim,medata)   ; intlim := status/intlim.
*onlyin:hc8000
        add(meaddr,q,wrk2)    ; send wrk2 + 2 (inf + 2) 
                              ; to memory address
                              ; and start memory read cycle.
*until: hc8000
*onlyin:rh8000
        add(meaddr,q,intlev)  ; send inf+2 to memory address
                              ; register and start read cycle.
*until: rh8000
        and(intlim,wrk0)      ; intlev := intlev(12:23),
                              ; only last 12 bits contain 
                              ; interupt limit.
        move(intlev,intlim)   ; interupt level := interupt limit.
        negadd(wrk2,q)        ; nessecary for sunc of memory,
                              ; wrk2 (inf) := wrk2 - 2.
        dec(wrk2)             ; wrk2 := wrk2 -1.
                              ; ( totaly  inf := inf - 3).
*onlyin:rh8000
        andinv(wrk2,wrk1)     ; clear bit(23) in address.
*until: rh8000
intsw2: cjmp(re2903,intsw2) not; wait for hc2903.
intse2: cjmp(rememo,intse2) not; wait for memory  ready.
        move(hc2903,medata) cl2903; send reg. dump. addr to hc2903,
                              ;  and clock hc2903 ready
        move(wrk1,medata)     ; wrk1 := reg. dump. addrs.
        jsb(dmp8w)            ; call subroutine to dump 8 words from
                              ; hc2903 to memory, first word addresed by
                              ; by wrk1.
        move(meaddr,wrk2)     ; sedn addres of new ic to memory.
intsw3: cjmp(re2903,intsw3) not; wait for hc2903 ready.
                              ; ness. sync. of mem.
intse3: cjmp(rememo,intse3) not; wait for memory ready.
        move(hc2903,medata) cl2903; send new ic to hc2903,
                              ; and clock hc2903 ready.
        jmp(stdil3)           ; continue in set disable level
                              ; entry 3, for control of
                              ; possible interupts with
                              ; lover level.





        ; set current interupt level.          
        ; -----------------------------
        ; entry select interupt enable level.
        ; disable level and enable level is in intlim register.
        ; current level is intlev register.
        ; entry call:
        ; wrk1 := 1.
        ; q := 2.
stenle/:moinv(intlev,wrk1) sr cl2903; intlev := -1 (allbits) shift -1,  
                              ; clock hc2903 ready.
        lcpu('hfwdm1)         ; load counter with no of
                              ; bits in a halfword minus 1, and
                              ; push next micro instr address.
        rep move(intlev,intlev) sr; intlev := intlev(0:11), all bits
                              ; in rigth halfword.
        and(intlev,intlim)    ; interupt level := enable level.
        jmp(stdil1)           ; goto set disable level entry 1.
stdile/:move(intlev,intlim) sr cl2903; intlev := interupt limit,
                              ; clock hc2903 ready.
        lcpu('hfwdm1)         ; load counter with no of bits
                              ; in half word and push next address.
        rep move(intlev,intlev) sr; interupt limit := interupt limit(0:11).
                              ; ( disable level).
stdil1: 
stdil2:                       ; entry from return from interupt.
        andinv(intreg,wrk1)   ; clear possible interupt bit.
stdil3:                       ; entry from answer interupt.
        move(wrk1,q)          ; wrk1 := q (2).     
        move(wrk2,wrk1) sl    ; wrk2 := wrk1*2 (4).
        lcpu('intno)          ; load counter with max no of interupt
                              ; allowed.
        inc(wrk1)             ; wrk1 := next interupt no.
        move(wrk2,wrk2) sl    ; wrk2 := next interupt bit.
        and(intreg,wrk2) noload; if interupt bit is set then
        cjmpp(zero,intsr2) not; pop counter and goto intse2 ( entry
                              ; in interupt routine.
        sub(wrk1,intlev) noload; if interupt no > new level then
        twb(neg,gewwri)  not  ; pop counter and continue in next
                              ; micro instr, else invistigate
                              ; next interupt bit while not all interupt
                              ; is examinied.
        jmp(gewwri)           ; goto generel wait.

        ; entry function restore 8 dynamic registers to hc2903.
        ; -----------------------------------------------------
redyre/:jsb(ge03w0) cl2903    ; get address of first dynamic register.
                              ; into w0.
        jsb(lodyre)           ; call subroutine load dynamic registers.
        jmp(gewait)           ; goto generel wait.
        ; subroutine load 8 registers.
        ; ----------------------------
lodyre: ldct('dyreno)         ; load counter with no of dynamic register
                              ; entry load any number of registers,
                              ; from hc2901 to hc2903.
lonore: jsb(lonor1)           ; push address of next micro instr.
lonor1: move(meaddr,wrk0)     ; send wrk0 to memory address regsiter and
                              ; start memory read cycle.
        add(wrk0,q)           ; memory address pointer := memory
                              ; address pointer + 2.
redyr1: cjmp(re2903,redyr1) not; wait until hc2903 is ready.
redyr2: cjmp(rememo,redyr2) not; wait for memory ready.
        rep move(hc2903,medata) cl2903; move word from memory to hc2903,
                              ; clock hc2903 ready, repeat loop.
        rtn                   ; return from subroutine.
        ; entry function return from interupt select next process registers. 
        ; ------------------------------------------------------------------
rtrnpr/:jsb(ge03a0) cl2903    ; get address of system table 
                              ; register dump addressfrom hc2903
                              ; to memory and start read cycle.
*onlyin:hc8000
        cont                  ; sync of memory.                    
*until: hc8000
rtnnp2: cjmp(rememo,rtnnp2) not; wait for memory ready.
        move(hc2903,medata) cl2903; send reg dump address to hc2903.
        move(wrk0,medata)     ; get register dump address to wrk0.
*onlyin:rh8000
        andinv(wrk0,wrk1)     ; clear bit(23) in address.
*until: rh8000
        jsb(lodyre)           ; call subroutine load dynamic registers.
rtnnp3: cjmp(re2903,rtnnp3) not; wait for hc2903 to recieve address
                              ; of process definition registers.
        move(wrk0,hc2903)     ; move address of register definition
                              ; registers to wrk0.
*onlyin:rh8000
        andinv(wrk0,wrk1)     ; clear bit(23) of address.
*until: rh8000
        ldct(3)               ; load counter with number of process
                              ; definition registers.
        jsb(lonore)           ; call subroutine load nomber of
                              ; registers.
        move(meaddr,wrk0)     ; send wrk0 to memory address.
        moinv(intlev,wrk1) sr ; intlev := -1 ( all bits) shift -1.
        lcpu('hfwdm1)         ; load counter with no of bits in
                              ; a halfword minus 1, and push
                              ; next address.
        rep move(intlev,intlev) sr; intlev := intlev(0:11) 
                              ; all last 12 bit set.
rtnnp4: cjmp(rememo,rtnnp4) not; wait for memory ready.
        move(intlim,medata)   ; load interupt limit.
        ; set enable level.
        and(intlev,intlim)    ; intlev := intlim(12:23).
                              ; last halfword of interupt limit.
        jmp(stdil1)           ; goto set disable level entry 1.


        ; entry functionsave 8 dynamic registers.
        ; ---------------------------------------
sadyre/:jsb(ge03w0) cl2903    ; get address whereto the registers
                              ; is to be written.
        move(wrk1,wrk0) cl2903; wrk1 := wrk0, clock hc2903 to continue.
        jsb(dmp8w)            ; call subruotine to dump 8 words 
                              ; from hc2903 .                
        jmp(gewwri)           ; goto generel wait with init.

        ; subroutine dump 8 words from hc2903 to memory.
        ; entry wrk1 := address.
        ; entry q    := 2.
dmp8w:  lcpu('dyreno)         ; load counter with number of 
                              ; registers to be saved, and clock hc2903
                              ; ready to accept 1. data word.
                              ; repeat:
*onlyin:hc8000

        move(meaddr,wrk1)     ; send address of data word to be
                              ; dumped to memory address register
                              ; and start memory write cycle.
                              ; of dumped word to memory address
                              ; and start memory write cycle.
*until: hc8000
dmp8w1: cjmp(re2903,dmp8w1) not; wait until hc2903 ready to send data 
                              ; word.
*onlyin:hc8000
dmp8w2: cjmp(rememo,dmp8w2) not; wait for memory write cycle.
*until: hc8000
        move(medata,hc2903) cl2903; send data word from hc2903 to memory,
                              ; and clock hc2903 ready to accept
                              ; next data word.
*onlyin:rh8000
        move(meaddr,wrk1)     ; send address to memory
                              ; address register and
                              ; start memory write cycle.
*until: rh8000
*onlyin:hc8000
        cont                  ; sync. of memory.
*until: hc8000
dmp8w3: cjmp(rememo,dmp8w3) not; wait for memory ready.
        rep add(wrk1,q)       ; increase memory address pointer
                              ; by to and repeat loop.
        rtn                   ; return from subroutine.




        ; data in and data out section.
        ; -----------------------------




        ; time out and other exceptions to hc2903.
        ; =========================================
        ; time out from data in and data out.
        ; -----------------------------------
iotmo0: cont cl2903           ; clock hc2903 for dummy address.
iotmw0: cjmp(re2903,iotmw0) not; wait for hc2903 ready.
iotmo1: cont          cl2903  ; send dummy data word to hc2903.
iotmw1: cjmp(re2903,iotmw1) not; wait for hc2903 ready.
iotmo2: move(hc2903,q)  cl2903; send status bit 2 ( time out ) 
                              ; to hc2903
        jmp(gewwri)           ; goto general wait.
        ; entry for not used data in and dataout instructions.
dintus:                       ; data in functions not used.
dontus:                       ; data out functions not used.
        ; bus comunication error in data in and data out.
        ; -----------------------------------------------
bucoe0: cont cl2903           ; clock hc2903 and wait.
bucow0: cjmp(re2903,bucow0) not; wait for ready.
bucoe1: cont cl2903           ; clock hc2903 for dummy data word.
bucow1: cjmp(re2903,bucow1) not; wait for ready.
bucoe2: cont cl2903           ; clock hc2903 for  data word recieve.
bucow2: cjmp(re2903,bucow2) not; wait for hc2903 to accept status word.
bucoer: move(hc2903,wrk1)   cl2903; send a one  or what ever the
                              ; contents of wrk1 is as status word 
                              ; to hc2903 and clock  
                              ; the hc2903 ( the  bus communication 
                              ; error bit).
        jmp(gewwri)           ; goto general wait with init.

        ; normal answer from data in and data out.
        ; ----------------------------------------
noran0: cont          cl2903  ; clock hc2901 for dummy addrs.
noraw0: cjmp(re2903,noraw0) not; wait for hc2903 ready to send addrs.
noran1: cont          cl2903  ; clock hc2903 , for dummy
                              ;  address word.
noraw1: cjmp(re2903,noraw1) not; wait for hc2903to send data.
noran2: cont          cl2903  ; return data word to hc2901 and wait.
noraw2: cjmp(re2903,noraw2) not; wait for hc2901 to accept data word 
                              ; and be ready to accept status bits.
norans: mzero(hc2903) cl2903  ; send a zero  to hc2903 indicating   
                              ; that no exceptions bit are set.
        jmp(gewwri)           ; goto generel wait with init.

        ; subroutine wait for hc2903.
wa0300: cjmp(re2903,wa0300) not; wait for hc2903
        cont cl2903           ; clock hc2903
wa0301: cjmp(re2903,wa0301) not; wait for hc2903
        rtn                   ; return form subroutine.
        ; subroutine get device block address.
        ; ------------------------------------
        ; call w0 = divice no*8.
        ;      wrk2 = 8.
gedvbl: move(meaddr,wrk2)     ; start memeory read cycle in word 8.
gedvb1: cjmp(rememo,gedvb1) not; wait for memory ready.
        move(wrk1,medata)     ; get device base.
        add(wrk0,wrk1)        ; wrk0 := wrk0 ( device no * 8) +
                              ;         device address base.
        rtn modec(wrk1,q)     ; wrk1 := 1, return .
*onlyin:hc8000


        ; subroutine write character device, no 0 to 7.
        ; ==================================
        ; wrk1 = data octet shift 16 + device address shift 1 + 0.
        ;
wrchd0: cjmp(chiosy,wrchd0) not; wait for char io clock tom go
                              ; low.
wrchd7: cjmp(chiosy,wrchd7)   ; wait for char io clock to go 
                              ; high. (now it is syncroniced
                              ; with the data bus clock pulse).
        sync                  ; wait for syncr.
        move(extreg,wrk1) writch sltiml; sync
        move(extreg,wrk1)  writch sltiml; send data and address to 
        move(extreg,wrk1)  writch sltiml; char io bus register and 
        move(extreg,wrk1)  writch sltiml; set clok external device signal
        move(extreg,wrk1)  writch sltiml; (valid memory address in 
                              ; motorola
        move(extreg,wrk1)  writch sltiml;
                              ; terminology) 4 times,
                              ;  clear the
        rtn move(extreg,wrk1) writch sltiml; return after a addressing
                              ; sending the addres out 
                              ; on the bus with out clocking
                              ; the external device.
                              ; read bit and return
                              ; from subroutine.
        ; subroutine read character divice, for dev. no 0. to 7.
        ; =================================
        ; wrk1 = data octet shift 16 + divice address shift 1 + 1.
        ;
rechd0: cjmp(chiosy,rechd0) not; wait for char io clock to go low.
rechd7: cjmp(chiosy,rechd7)   ; wait for char io clock to go high.
        sync                  ; wait for syncronation.
        move(extreg,wrk1) opdirz oprama sltiml trnbus; sync. and start signal.
        move(extreg,wrk1)  opdirz oprama sltiml trnbus
                              ; send divice and read bit to
                              ; char io bus and clock the bus,
                              ; open for direct and zero input to
                              ; the alu, and open for wrk1 as des
                              ; destination, four times.
        move(extreg,wrk1)  opdirz oprama sltiml trnbus;
        move(extreg,wrk1)  opdirz oprama sltiml trnbus;
        move(extreg,wrk1)  opdirz oprama sltiml trnbus;
        rtn move(extreg,wrk1) noload sltiml trnbus;
                              ; return from subroutine.




        ; subroutine write character device.
        ; ==================================
        ; wrk1 = data octet shift 16 + device address shift 1 + 0.
        ;
wrchde: cjmp(chiosy,wrchde)  not; wait for char io clock tom go
                              ; low.
wrchd1: cjmp(chiosy,wrchd1)   ; wait for char io clock to go 
                              ; high. (now it is syncroniced
                              ; with the data bus clock pulse).
        sync                  ; wait for sync.
        move(extreg,wrk1) writch; sync. and start signal.
        move(extreg,wrk1) clexde writch; send data and address to
        move(extreg,wrk1) clexde writch; char io bus register and 
        move(extreg,wrk1) clexde writch; set clok external device signal
        move(extreg,wrk1) clexde writch; (valid memory address in motorola
        move(extreg,wrk1) clexde writch; terminology) 4 times , clear the
                              ; read bit .         
        rtn move(extreg,wrk1) writch; sync addressing of external
                              ; bus and return.

        ; subroutine read character divice.
        ; =================================
        ; wrk1 = data octet shift 16 + divice address shift 1 + 1.
        ;
rechde: cjmp(chiosy,rechde) not; wait for char io clock to go low.
rechd1: cjmp(chiosy,rechd1)   ; wait for char io clock to go high.
        sync                  ; wait for syncronation.
        move(extreg,wrk1) opdirz oprama readch trnbus; sync. and start
                              ; signal.
        move(extreg,wrk1) clexde opdirz oprama readch trnbus
                              ;send divice and read bit to
                              ; char io bus and clock the bus,
                              ; open for direct and zero input to
                              ; the alu, and open for wrk1 as des
                              ; destination, four times.
        move(extreg,wrk1) clexde opdirz oprama readch trnbus;
        move(extreg,wrk1) clexde opdirz oprama readch trnbus;
        move(extreg,wrk1) clexde opdirz oprama readch trnbus
        rtn move(extreg,wrk1) noload readch trnbus;
                              ; retrun from subroutine.
*until: hc8000

*onlyin:rh8000
        ; data out unibus reset and start.
        ; --------------------------------
douni1:                       ; data out on unibus reset command.
        jsb(ge03w0) cl2903    ; get address from hc2903.
        or(wrk0,q)            ; set reset control bit an address.
        jmp(dounix)           ; continus in data out unibus start.

douni0:                       ; data out on unibus start command.
        ; ---------------------------------
        jsb(ge03w0) cl2903    ; get address from hc2903 into wrk0.
dounix: move(wrk1,wrk1) sraq  ; set sign bit in wrk1 by shifting
        move(wrk1,wrk1) sraq  ; the contents of q register ( 2)
                              ; into bit 23.
        or(wrk0,wrk1)         ; set sign bit in address.
        move(wrk1,wrk1) slaq  ; reestablish wrk1 and q.
        move(wrk1,wrk1) slaq  ;
        jmp(dowmw3) cl2903    ; continue in data out
                              ; write memory word.
*until: rh8000



        ; data out, write data word in own memory.
        ; ----------------------------------------------
*onlyin:hc8000                ;
dowrme: jsb(ge03a0) cl2903    ; clock hc2903 and call subroutine to get
                              ; get address of memory word.


*until: hc8000                ;
*onlyin:rh8000                ;
dowrme: jsb(ge03w0) cl2903    ; get address of memory word to
                              ; wrk0.
*until: rh8000
        cont cl2903           ; clock hc2903 to accept data word.
dowmw3: cjmp(re2903,dowmw3) not; wait for hc2903 ready sen data word.
*onlyin:hc8000
dowmw2: cjmp(rememo,dowmw2) not; wait for memory ready.
*until: hc8000
        move(medata,hc2903)   ; move data word to memory data register.
*onlyin:rh8000
        move(meaddr,wrk0)     ; move addrs of memory data word to
                              ; memory address register and clock memory.
*until: rh8000
        lcpu('metimo)         ; load counter and pusch next micro instr.
                              ; into micro stack.
        twb(rememo,iotmo2)    ; repeat                       
                              ; if counter = 0 then goto iotmo1.
                              ; micro counter := micro counter.
                              ; until memory ready.
        jmp(noraw1)           ; goto normal answer, ( wait for data
                              ; ready).



        ; data in, read data word from memory.
        ; ----------------------------------------
direme: jsb(ge03a0) cl2903    ; clock hc2903, and  call subroutine 
                              ;  to get word from hc2903 to memory
                              ; address register and clock memory.
        lcpu('metimo)         ; load micro counter with
                              ; 200 and push next micro instr to
                              ; micro stack.
        twb(rememo,iotmo0)    ; wait for memory ready 200 cycles.
                              ; if not memory ready then goto iotmo0.
        jsb(wa0300)           ; call subroutine to accept dummy
                              ; data word and wait ready.
        move(hc2903,medata) cl2903; move data word to hc2903, and clock
                              ; hc2903.
        jmp(noraw2)           ; goto normal answer with 1 wait.
*notin: rh8000                ; no external  char device in rh8000.

        ; data out, write external character device.
        ; --------------------------------------------
        ; entry gendo4.
dochde: jsb(ge03w0) cl2903    ; clock hc2903, and call subroutine
                              ; to device no into wrk0.
                              ; if dev no < 8 ).
        jsb(divw08)           ; call subroutine to divide wrk0 by 8
                              ; to get rigth address.
        move(wrk1,wrk0) sl    ; wrk1 := wrk0 shift 1 ( bit 0 = 0 signifi
                              ; write function ).
        negadd(wrk2,wrk0)     ; wrk2 := dev no - 8. (result used to 

                              ; test which dev write routine to
                              ; be used).
        jsb(ge03w0) cl2903    ; call subroutine to get data word into 
                              ; wrk0.
        lcpu('octet)          ; load counter with length of data
                              ; octet.
        rep move(wrk0,wrk0) sraq; q(0..8) := wrk0(16.23) ( shift data
                              ; octet into q reg as the most significant
                              ; octet).
        or(wrk1,q,wrk1)       ; wrk1 := q ( data) or wrk1 ( device addrs

                              ; addrs +device funtion).
        move(wrk2,wrk2)       ; if wrk2 < 0 then goto
        cjmp(neg,dochd1)      ; dochd1.
        jsb(wrchde)           ; call subroutine write char. devices.
                              ; dev no from 8 , 9 , 10 ......
        jmp(noran2)           ; goto send normal answer, with 1 wait.
dochd1: jsb(wrchd0)           ; call subroutine write char devices,
                              ; dev. no from 0 to 7.
        jmp(noran2)           ; goto normal answer, with 1 wait.

        ; data in, read external character device.
        ; ----------------------------------------
        ; entry gendi4.
dichde: jsb(ge03w0) cl2903    ; clock the hc2903, and call subroutine
                              ; to get divice no into wrk0.
        jsb(divw08)           ; call subroutine to divide address
                              ; by 8 to get rigth device address.
        negadd(wrk2,wrk0)     ; wrk2 := dev no - 8 ( used to 
                              ; find out which read routine to be
                              ; used).
        move(wrk0,wrk0) sl    ; wrk0 := device address shift 1.
        or(wrk1,wrk0)         ; wrk1 := device address shift 1 + 1
                              ; (signifieng the read bit).
        move(wrk2,wrk2)       ; if wrk2 < 0 then goto 
        cjmp(neg,dichd1)      ; dichd1.
        jsb(rechde)           ; call subroutine read char device.
dichd2: mzero(q)              ; q reg := 0.
        lcpu('octet)          ; load counter with octet length.
        rep move(wrk1,wrk1) slaq; q(16.23) := data octet.
        jsb(wa0300)           ; call subroutine to accept dummy 
                              ; word.
        move(hc2903,q) cl2903 ; send data octet to hc2903, and
                              ; clock hc2903 ready.
        jsb(noraw2)           ; goto normal answer with 1 wait.
dichd1: jsb(rechd0)           ; call subroutine read char dev
                              ; dev no 0 to 7.
        jmp(dichd2)           ; goto send data word back to hc2903.
*until: rh8000
        ; section channel input output.
        ; =============================
        ; data out, channal reset.
dochre: mzero(dochwc)         ; reset data out word counter.
        jmp(noran0)           ; goto normal answer.
                              ; NOTE: after the resetting it
                              ; is possibly that
                              ; a data out finis interupt
                              ; will be given.

        ; data out, channel start.
        ; ------------------------
dochst/:
        move(dochwc,dochwc) cl2903; clock hc2903 ready to recieve 
                              ; address,
                              ; if word counter <> 0 then
        cjmp(zero,bucow0) not ; then goto bus cummunication error.
dochw1: cjmp(re2903,dochw1) not; wait for hc2903 ready to sned address.
        move(wrk0,hc2903) cl2903; wrk0 := address, clock hc2903 ready
                              ; to recieve data word.
dochw2: cjmp(re2903,dochw2) not; wait for hc2903 to revieve data word.
        move(dochwc,hc2903) cl2903; get data word form hc2903, clock
                              ; hc2903 ready to accept not used
                              ; data word.
        negadd(dochwc,q) noload; if word counter < 2 then
        cjmp(neg,dochs3)      ; then goto dochs3, ( send message).
        jsb(gedvbl)           ; call subroutine to get device block 
                              ; address.
        add(wrk0,q)           ; divice block address := device 
                              ; block address + 2.
        move(meaddr,wrk0)     ; send adrress of word counter to
                              ; memory and start read cycle.
dochs1: cjmp(rememo,dochs1) not; wait for memory ready.
        move(dochad,medata)   ; get channel block address.
        sub(dochad,wrk2) noload; if address of data block < 8
        cjmp(neg,bucow2)      ; then goto bus communication error.
*onlyin:rh8000
        cont stwrch           ; clock start write channel.
*until: rh8000
        move(chdata,dochwc)   ; send channel output word counter
                              ; to channal data buffer as first
                              ; word.
*onlyin:rh8000
        cont fiwrch           ; clock finis write channel.
*until: rh8000
        add(dochwc,q)         ; data out channel word counter :=
                              ; data out channel word counter +2,
                              ; (after a subtraction by 2 in start of
                              ;  channel input interupt fetch, docchwc
                              ; contain the number of bytes left to send,
                              ; i.e. dochwc gives the no of bytes which
                              ; their is not recieved a interupt answer
                              ; for, that includes the first control word.)
        jmp(noraw2)           ; goto normal answer 1.
dochs3:                       ; entry word counte < 2.
        ; only word counter is send.
        cont stwrch           ; clock start write channel.
        move(chdata,dochwc)   ; send word counter.
        cont fiwrch           ; clcok finis write channel.
        jmp(noraw2)           ; goto to normal answer.

        ; entry interupt from channel output buffer.
        ; ------------------------------------------
choint: cont   clchoi         ; clear channel output interupt.
        negadd(dochwc,q)      ; channel word counter := channel word       
                              ; counter -2.
        cjmp(neg,dochni)      ; if word counter < 0
                              ; then goto answer message▶16◀▶16◀▶16◀▶16◀
                              ; with no interrupt
        move(dochwc,dochwc)   ; if data out channel word counter = 0 then
        cjmp(zero,dochfi)     ;  send channel output finis interupt
                              ; to hc2903.
        move(meaddr,dochad)   ; send channel output block address
                              ; to memory and start read cycle.
        add(dochad,q,dochad)  ; block address counter := 
                              ; block address counter + 2.
docht1: cjmp(rememo,docht1) not; wait for memory ready.
*onlyin:rh8000
        cont stwrch           ; clock start write channel.
*until: rh8000

        move(chdata,medata)   ; send memory data word to channel
                              ; data word.
*onlyin:rh8000
        cont fiwrch           ; finis write channel.
*until: rh8000
        jmp(gewait)           ; goto generel wait.
dochni: mzero(dochwc)         ; reset data word couter, and goto
        jmp(gewait)           ; general wait without interrupt.
dochfi:                       ; data out channel finis interuot.
        ; --------------------------------
        mzero(dochwc)         ; reset data word counter.
        ldct('chofil)         ; load mic. counterwith channel output
                              ; finis interupt level.
        jmp(clcint)           ; goto calculate and set interupt.




        ; data in, channel reset.
        ; -----------------------
dichre/:mzero(dichwc)         ; reset data in word counter.
        jmp(noran0)           ; goto normal answer.
                              ; if given in the middle of in input 
                              ; input operation the output opration
                              ; from the other computer is migth
                              ; not finis.
        ; data in, channel start
        ; ----------------------
dichst/:
        jsb(ge03w0) cl2903    ; get device address from hc2903.
        cont strech  cl2903   ; clock start reading of channel,
                              ; clock hc2903 ready to get recieve
                              ; not used data word.
        move(dichwc,chdata)   ; get first data word.
        cont firech           ; click finis reading of channel.
        negadd(dichwc,q) noload; if data word < 2 then
        cjmp(neg,dichs3)      ; then goto dichs3, ( message arrived).
        jsb(gedvbl)           ; call subroutine to get divice block
                              ; address, and clock hc2903 ready to recieve dummy
                              ; data word.
        add(wrk0,q)           ; device block address + 2 to get
                              ; data block address, ( word counter is
                              ; not used).
        move(meaddr,wrk0)     ; send address of data block address to memory
                              ; memory and start read cycle.
dichs1: cjmp(re2903,dichs1) not; wait for accept not used data word.
        move(hc2903,dichwc) cl2903; send word counter to hc2903,
                              ; ( goes to the data in instruction
                              ;   w register), and clock hc2903 ready.
dichs2: cjmp(rememo,dichs2) not; wait for memory ready.
        move(dichad,medata)   ; get channel block address.
        negadd(dichwc,q) noload; if data in channel word counter < 2 
        cjmp(neg,dichei)      ;  goto data in channel error in start.
        jmp(noraw2)           ; else goto normal answer.
dichs3:                       ; message word revieved through channel.
        cjmp(re2903,dichs3) not; wait for acccepting not used
                              ; data word.
        move(hc2903,dichwc) cl2903; send message word to
                              ; hc2903 and clock data word ready
                              ; from input.
        mzero(dichwc)         ; reset data channel input word counter.
        jmp(noraw2)           ; goto normal answer 2.

dichei:                       ; error at start of data in instruction.
        mzero(dichwc)         ; clear data in word counter.
        jmp(bucow2)           ; goto bus communication error.


        ; entry: interupt from channel input buffer.
        ; ------------------------------------------
chiint: cont clchii           ; clear channel input interupt.
        move(dichwc,dichwc)   ; data in word counter = 0 then
        cjmp(zero,dichsi)     ; goto data in channel interupt start.
*onlyin:hc8000
        move(meaddr,dichad)   ; send data block address to memory
                              ; and start read cycle.
        cont     strech       ; clock start reading of channel.
        move(wrk0,chdata)     ; sync of memory, get channel data to
                              ; wrk0 ( schold all clock ready in rh8000).
        cont     firech       ; clock finis reading of channel.
chiin1: cjmp(rememo,chiin1) not; wait for memory ready.
        move(medata,wrk0)     ; send channel data to memory.
*until: hc8000
*onlyin:rh8000
        cont strech           ; clock start reading of channel
        move(medata,chdata)   ; send channel data to memory
        cont firech           ; clock finis reading of channel.
        move(meaddr,dichad)   ; send channel data in data block
                              ; address to memory and start 
                              ; write cycle.
*until: rh8000
chiin2: cjmp(rememo,chiin2) not; wait for memory ready.
        negadd(dichwc,q)      ; decrease word counter with 2.
        cjmp(zero,dichfi)     ; if word counter = 0 then
                              ; goto data in channel interupt finis.
        add(dichad,q)         ; increase data in channel block address 
                              ; with 2.

        jmp(gewait)           ; goto generel wait.
dichfi:                       ; data in channel input finis transport interupt.
        ; -----------------------------------------------
        ldct('chifil)         ; load counter with channel input finis 
                              ; level.
        jmp(clcint)           ; goto calcuæate and set interupt bit.
dichsi:                       ; data in channel input start transport interupt.
        ; -----------------------------------------------
        ldct('chisil)         ; load counter with channel input start
                              ; interupt level.
        jmp(clcint)           ; goto calculate interupt.

*onlyin:hc8000                ; local dma  not in rh8000.
        ; local dma interupt service.
        ;----------------------------
dmain:                        ; select from status if it is
                              ; input or output.


        jsb(ipldma)           ; goto input dma from local dma.
                              ; if local memory counter <> 0 then
        cjmp(zero,gewait)  not; then generel wait else
        ldct('lodmle)         ; load counter with local dma interupt
                              ; level.
        jmp(clcint)           ; goto clock interupt.
        ; subroutine input local dma.
        ; ----------------------------
ipldma: move(meaddr,lmem)     ; addrs:= local dma memory addres reg.
                              ; clock memory.
        move(wrk0,dmada) set(14); wrk0:= dma data, clock dma control
ipldm1: cjmp(rememo,ipldm1) not; loop while memory not rteady
        move(medata,wrk0)     ; memory := wrk0.
        add(lmem,q)           ; local dam mem addrs :=+2.
dmain2: cjmp(rememo,dmain2) not; wait memory ready
        rtn  negadd(lwco,q)   ; return from subroutine, decrease local
                              ; dma word counter with 2.
*until: hc8000                ; end version hc8000
        ;*page:  XX
        ;*page:  XX
*skip:  gengp


        ; entry generel put instr
        ; -----------------------

genp00: cont cl2903           ; ready set hc2903.
wait00: cjmp(re2903,wait00) not; loop until hc2903 is ready.
        move(r0,hc2903)       ; r0  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp01: cont cl2903           ; ready set hc2903.
wait01: cjmp(re2903,wait01) not; loop until hc2903 is ready.
        move(r1,hc2903)       ; r1  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp02: cont cl2903           ; ready set hc2903.
wait02: cjmp(re2903,wait02) not; loop until hc2903 is ready.
        move(r2,hc2903)       ; r2  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp03: cont cl2903           ; ready set hc2903.
wait03: cjmp(re2903,wait03) not; loop until hc2903 is ready.
        move(r3,hc2903)       ; r3  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp04: cont cl2903           ; ready set hc2903.
wait04: cjmp(re2903,wait04) not; loop until hc2903 is ready.
        move(r4,hc2903)       ; r4  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp05: cont cl2903           ; ready set hc2903.
wait05: cjmp(re2903,wait05) not; loop until hc2903 is ready.
        move(r5,hc2903)       ; r5  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp06: cont cl2903           ; ready set hc2903.
wait06: cjmp(re2903,wait06) not; loop until hc2903 is ready.
        move(r6,hc2903)       ; r6  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp07: cont cl2903           ; ready set hc2903.
wait07: cjmp(re2903,wait07) not; loop until hc2903 is ready.
        move(r7,hc2903)       ; r7  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp08: cont cl2903           ; ready set hc2903.
wait08: cjmp(re2903,wait08) not; loop until hc2903 is ready.
        move(r8,hc2903)       ; r8  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp09: cont cl2903           ; ready set hc2903.
wait09: cjmp(re2903,wait09) not; loop until hc2903 is ready.
        move(r9,hc2903)       ; r9  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp10: cont cl2903           ; ready set hc2903.
wait10: cjmp(re2903,wait10) not; loop until hc2903 is ready.
        move(r10,hc2903)      ; r10  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp11: cont cl2903           ; ready set hc2903.
wait11: cjmp(re2903,wait11) not; loop until hc2903 is ready.
        move(r11,hc2903)      ; ready set hc2903.
wait11: cjmp(re2903,wait11) not; loop until hc2903 is ready.
        move(r11,hc2903)      ; r11 := hc2903.
        jmp(gewait)  cl2903   ; ready set hc2903.
wait12: cjmp(re2903,wait12) not; loop until hc2903 is ready.
        move(r12,hc2903)      ; r12  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp13: cont cl2903           ; ready set hc2903.
wait13: cjmp(re2903,wait13) not; loop until hc2903 is ready.
        move(r13,hc2903)      ; r13  := hc2903.
        move(r14,hc2903)      ; r14  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp15: cont cl2903           ; ready set hc2903.
wait15: cjmp(re2903,wait15) not; loop until hc2903 is ready.
        move(r15,hc2903)      ; r15  := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.


genp16: cont cl2903           ; ready set hc2903.
wait16: cjmp(re2903,wait16) not; loop until hc2903 is ready.
        move(r16,hc2903)      ; r16 := hc2903.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.
        ;*page:  XX tcgorder01

        ; entry generel get instr.

        ; ------------------------

geng00: move(hc2903,r0)       ; entry get reg 0: hc2903 := r0.
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop

geng01: move(hc2903,r1)       ; entry get reg 00, hc2903 := r0
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng02: move(hc2903,r2)       ; entry get reg 02, hc2903 := r2
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng03: move(hc2903,r3)       ; entry get reg 03, hc2903 := r3
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng04: move(hc2903,r4)       ; entry get reg 04, hc2903 := r4
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng05: move(hc2903,r5)       ; entry get reg 05, hc2903 := r5
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng06: move(hc2903,r6)       ; entry get reg 06, hc2903 := r6
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng07: move(hc2903,r7)       ; entry get reg 07, hc2903 := r7
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng08: move(hc2903,r8)       ; entry get reg 08, hc2903 := r8
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng09: move(hc2903,r9)       ; entry get reg 09, hc2903 := r9
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng10: move(hc2903,r10)      ; entry get reg 10, hc2903 := r10
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng11: move(hc2903,r11)      ; entry get reg 11, hc2903 := r11,
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng12: move(hc2903,r12)      ; entry get reg 12, hc2903 := r12,
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng13: move(hc2903,r13)      ; entry get reg 13, hc2903 := r13,
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng14: move(hc2903,r14)      ; entry get reg 14, hc2903 := r14,  
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng15: move(hc2903,r15)      ; entry get reg 15, hc2903 := r15,
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.

geng16: move(hc2903,r16)      ; entry get reg 16, hc2903 := r16,
        jmp(gewait) cl2903    ; ready set hc2903, goto wait loop.
        ;*page:  XX
        ; end of micro program for the hc2901
*until: gengp
*end:   
▶EOF◀