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

⟦9f724aeda⟧ TextFile

    Length: 132864 (0x20700)
    Types: TextFile
    Names: »ticcnbus«

Derivation

└─⟦667bb35d6⟧ Bits:30007480 RC8000 Dump tape fra HCØ.
    └─⟦4334b4c0b⟧ 
        └─⟦this⟧ »ticcnbus« 

TextFile

          ;  hc2901
*test:  off
          ; --------------------------------------------------
          ; 810730/1130:
          ;      stwrch and fiwrch defined  as clocking registers.
          ;      substitutes recvst and recvcl from iccn bus
          ;      logic.
          ; NEXT.
          ; ----------------------------------------------------
          ; mask
*mask:  regsrc,21,(36:39)          ; full register source mask.
*mask:  cndslc,(6:10)              ; condition select mask.
*mask:  aludst,23,24,25            ; alu destination select mir (23:25).
*mask:  alufnc,26,27,28            ; alu function select    mir (26:28).
*mask:  alusrc,29,30,31            ; alu source select      mir (29:31).
                                   ; clear ready bit hc2903 mir(15).


          ; jump addrs codes
          ; use full sekvens mask.
          ; type = 12.
          ; bit(1:4) in instr. format is the sekvens kontrol,
          ; bit(5) in instr. format is  condition enable.
*name:  cjsb,12,1,0                ; conditional jump to subroutine
*name:  jsb,12,1,1                 ; jump to subroutine
*name:  cjmp,12,3,0                ; conditional jump addrs.
*name:  jmp,12,3,1                 ; jump addrs unconditional.

*name:  cjsrp,12,4,0               ; conditional jump to subroutine conditional addrs.
                                   ; from sekvenser reg. or direct.

*name:  cjmrd,12,7,0               ; jump to addrs. conditional
                                   ; from secvenser register or direct.
*name:  rpct,12,9,0                ; repeat direct and derease counter until
                                   ; counter = 0.
*name:  cjmpp,12,11,0              ; conditional: if pass then
                                   ;    pop stack and jump to direct addrs. 
                                   ;      else continue.
*name:  twb,12,15,0                ; tree way branch

          ; jump sekvens codes.
*name:  jmpz,14,0,0                ; jump to addrs. zero,
                                   ;   clear stack.
*name:  jmap,14,2,0                ; jump to addrs. given by map prom
*name:  push,14,4,1                ; push addrs of next mic. instr to 
                                   ; micro secvens stack and continue.
*name:  cjvt,14,6,0                ; jump to addrs. given by vektor prom
*name:  rep,14,8,0                 ;  if counter <> 0 then goto first in stack
                                   ; else pop stack and continue.
*name:  crtn,14,10,0               ; conditional: if pass then
                                   ;      jump to first in stack and pop stack
                                   ;      else continue.
*name:  rtn,14,10,3                ; return: jump to first in stack
                                   ;   and pop stack.

*name:  loop,14,13,0               ; conditional loop:
                                   ;   if pass then pop sctak and continue
                                   ;      else jump to first in stack.
*name:  pop,14,13,3                ; pop stack and continue.
*name:  sync,14,14,0               ; dummy syncronotation instruction.
*name:  cont,14,14,0               ; continue to next micro instr.




          ; type 15 load counter types.

*name:  ldct,15,12,0               ; load counter whit addrs. field and continue.
*name:  clcpu,15,4,0               ; pusch mic. program counter to stack and
                                   ;  if pass then load counter whit addrs. field
                                   ;     else hold counter.
*name:  lcpu,15,4,1                ; load counter with address field and
                                   ; push address of next mic. instr. to stack.





          ; alu function codes.

*name:  add,11,0,1                 ; add: a+b  , internal reg. carry = 0.
*name:  add1,11,0,2                ; add1: a+b+1  , internal reg. carry = 1.
*name:  sub,11,1,2                 ; sub:  b-a   , int. reg. carry = 1.
*name:  sub1,11,1,1                ; sub1: b-1a-1 , int. reg. carry = 0
*name:  negadd,11,2,2              ; nadd: -b+a    , int. reg. carry = 1
*name:  negad1,11,2,1              ; nadd1: -b+a-1 , int. reg. carry = 0
*name:  and,11,4,1                 ; and: a and b , int. reg. carry = don't care.

*name:  or,11,3,1                  ; or: a or b, int. reg. crrry = don't care.
*name:  xor,11,6,1                 ; xor: a xor b, int. reg. carry = don't care
*name:  nxor,11,7,1                ; nxor: not(a xor b), int. reg. carry = don't care.
*name:  andinv,11,5,1              ; andinv: not(a) and b, int. reg. carry = 
                                   ; don't care.
*name:  andn,11,5,1                ; andn: not(a) and b, int. reg. carry = don't care.
          ; inc and dec instr whit one internal op.
*name:  inc,11,0,7                 ; increase a register.
*name:  dec,11,1,6                 ; decease.
          ; move and move zero instr.
*name:  move,11,3,3
*name:  mzero,11,4,5               ; 
*name:  moinc,11,0,4               ; move and increment.
*name:  modec,11,1,3               ; move adn decrement.
*name:  moinv,11,7,3               ; move invert
          ; the nonaddressable q-register.
*name:  q,30,-1                    ; the negative value to
                                   ; destingues from the others .
          ; internal register definitions.
          ; ------------------------------
*name:  status,30,7                ; rc2901 status bit register
                                   ; same as int reg, mus corrospon with
                                   ; hc2903 buffer register.
*name:  wrk0,30,2                  ; working register 0.
*name:  intreg,30,7                ; interupt register, part of status register.
                                   ; must correspond whit hc2903 buffer
                                   ; register.
*name:  intlev,30,0                ; current interupt level number.
*name:  pctst,30,3                 ; temp. pc test register.
                                   ; used to stop hc2901 when
                                   ; when pctst ( from manual test 
                                   ; register) is equal ic.
*name:  iccnch,30,3                ; interupt enablet level.
*name:  intlim,30,4                ; interupt limit register.
*name:  ic,30,5                    ; instruction counter (absolute address)
*name:  pir,30,8                   ; prefetched instruction register.
*name:  wrk1,30,6                  ; working register 1.
*name:  wrk2,30,1                  ; working register 2.
          ; iccn bus not used until futher
*name:  icmas,30,9                 ; iccn dma master memory address.
*name:  icwoco,30,10               ; iccn word counter.
*name:  icsla,30,11                ; iccn dma slave memory address.
*name:  icdev,30,12                ; iccn dma reciever 
                                   ; dev. no<12 + send dev. no.
          ; channel register same as iccn bus registers.
*name:  dichwc,30,9                ; data in channel word counter.
*name:  dichad,30,10               ; data in channel block address.
*name:  dochwc,30,11               ; data out channel word counter.
*name:  dochad,30,12               ; data out channel block address.
*name:  c66,30,13                  ; in rh8000 this reg. 
                                   ; contain the constant 66.
*name:  lmem,30,13                 ; local dma memory address.
*name:  lwco,30,14                 ; local dma word counter.
*name:  icbiba,30,15               ; iccn bus informaiton block address.
                                   ; --   -   -           -     -
          ; internal names or internal registers.
*name:  r0,30,0                    ; internal register.
*name:  r1,30,1                    ; internal register.
*name:  r2,30,2                    ; internal register.
*name:  r3,30,3                    ; internal register.
*name:  r4,30,4                    ; internal register.
*name:  r5,30,5                    ; internal register.
*name:  r6,30,6                    ; internal register.
*name:  r7,30,7                    ; internal register.
*name:  r8,30,8                    ; internal register.
*name:  r9,30,9                    ; internal register.
*name:  r10,30,10                  ; internal register.
*name:  r11,30,11                  ; internal register.
*name:  r12,30,12                  ; internal register.
*name:  r13,30,13                  ; internal register.
*name:  r14,30,14                  ; internal register.
*name:  r15,30,15                  ; internal register.
          ; external registers.
*name:  tstreg,30,16               ; dest: write hc2903
                                   ; source: read hc2903
*name:  r16,30,16                  ; external reg 16.
*name:  medata,30,17               ; dest:   write hc memory data
                                   ; source: read hc memory data.
*name:  r17,30,17                  ; external reg 17.
*name:  meaddr,30,18               ; dest: write hc memory addrs. 
                                   ; => start read cyc.
                                   ; source: in hc8000 not meaningfull
*name:  rc80cn,30,18               ; source: in rh8000 last 4 bit from
                                   
                                   ;          address in data out instruction    
                                   ;          from rc8000.
*name:  r18,30,18                  ; external reg18.
*name:  dmada,30,19                ; dest:   write dma data.
                                   ; source: read dma data
*name:  r19,30,19                  ; external reg 19.
*name:  dmaadr,30,20               ; dest in hc2901:   write dma addrs.
*name:  clrf80,30,20               ; dest in rh2901: clear flag from rc8000.
*name:  iccnid,30,20               ; source: device number of this system
                                   ;         as functioning in 
                                   ;         the iccn bus system,
                                   ;          does  not function on rh8000,
                                   ;          only on hc8000.
          ; iccn bus not used until futher.
*name:  iccn,30,21                 ; dest:   write iccn register.
                                   ; source: read iccn register.
          ; channel bus data register.
*name:  chdata,30,21               ; dest: write channel bus
                                   ;       read channel bus .
*name:  hc2903,30,23               ; dest:   write  hc2903 buffer register.
                                   ; source: read  hc2903 buffer register.
*name:  extreg,30,22               ; external reg. no. 6.
                                   ; must correspond with register no
                                   ; wrk1.
                                   ; realy not a register but only
                                   ; used for clocking of external
                                   ; devices in connection with
                                   ; opening of external devices.
                                   ; dest: read and write external char device.
                                   ; source: not meaning full.
*name: intprm,30,22                ; address the init prom in hc8000.
                                   ; works as extreg but without opening
                                   ; of external devices.
          ; the iccn bus is not used until futher.
          ; iccn bus control
          ; implemented as specials but is acutally
          ; unused source in alufunction.
*name:  burqst,16,24,1,regsrc      ; ask for iccn bus request.
*name:  burels,16,25,1,regsrc      ; release iccn bus ( i.e not master on bus any
                                   ; more).
*name:  slctst,16,26,1,regsrc      ; set iccn bus device select logic.
*name:  slctcl,16,27,1,regsrc      ; clear iccn bus device select logic.
*name:  sendst,16,28,1,regsrc      ; set iccn bus send control logic.
*name:  sendcl,16,29,1,regsrc      ; clear iccn bus send control logic.
*name:  recvst,16,30,1,regsrc      ; set iccn bus recieve control.
*name:  recvcl,16,31,1,regsrc      ; clear iccn bus recieve control.



          ; channel control registers.
          ; implemented as specials but is actually
          ; unused source in alufunction.
*name:  clchii,16,25,1,regsrc      ; clear channel input  interupt.
                                   ; same as clear master request.
*name:  clchoi,16,29,1,regsrc      ; clear channel output interupt.
                                   ; same as clear sender control.
*name:  strech,16,26,1,regsrc      ; start read channel.
*name:  firech,16,27,1,regsrc      ; finis read channel.
*name:  stwrch,16,30,1,regsrc      ; start write channel.
*name:  fiwrch,16,31,1,regsrc      ; finis write channel.





          ; hc2901 status register ( condition code bits)
          ; type is condition type = 40
          ; format is: <name>/40/<value>/<not used>,<mask name>
          ;
*name:  ovrun,40,16,0,cndslc       ; overrun on alu function.
*name:  neg,40,17,0,cndslc         ; negative alu output.
*name:  zero,40,18,0,cndslc        ; zero alu output.
*name:  carry,40,19,0,cndslc       ; carry on alu function.
*name:  vect,40,20,0,cndslc        ; vector interupt
*name:  rememo,40,21,0,cndslc      ; memory ready
*name:  npmem,40,22,0,cndslc       ; parity error (memory)
*name:  re2903,40,23,0,cndslc      ; hc2903 ready
*name:  re8000,40,11,0,cndslc      ; wait for ready from bit 11 only in rh8000
*name:  reldma,40,11,0,cndslc      ; wait for ready from bit 11, local dma
                                   ; only in initial version.
*name:  icsic,40,8,0,cndslc        ; iccn sender input control
*name:  icric,40,9,0,cndslc        ; iccn receive input control
*name:  nabrqi,40,10,0,cndslc      ; -, iccn bus request init
*name:  chioin,40,13,0,cndslc      ; timerdivice interupt.
*name:  chiosy,40,14,0,cndslc      ; character divice clock syncronation signal.
*name:  tstrdy,40,15,0,cndslc      ; wait manual test
*name:  wainle,40,12,0,cndslc      ; wait interupt level 
                                   ; form external interupr device to
                                   ; be ready on charakter data bus.
*name:  icmabu,40,12,0,cndslc      ; wait until master on bus.
          ;
          ;
          ;
          ;
          ; specials
          ;
          ;
          ;
          ;
          ;
          ; type 4 gives the actuel no of the bit.
*name:  noint,16,0,4,13            ; clear interupt enable bit
                                   ; mir(13) := 0 ( normaly 1).
*name:  not,16,1,2,5               ; change polarity of condition
*name:  setcar,16,1,2,13           ; set carry bit in micro instr.
*name:  clcar,16,0,2,13            ; clear carry bit in micro instr.
          ; specials in alu. destinaliton field
*name:  onlyq,16,0,1,aludst        ; store output from alu. only in q_reg.
*name:  noload,16,1,1,aludst       ; do not store result from alu. in
                                   ; intern reg.
*name:  soout,16,2,1,aludst        ; send reg. contents pointed by a_addrs
                                   ; to extern bus, store result from
                                   ; alu. in intern reg. pointed by b_addrs.
*name:  stddes,16,3,1,aludst       ; std. destinaltion control.
                                   ; store result from alu in
                                   ; intern registe pointed out by
                                   ; b_addrs field.
*name:  sraq,16,4,1,aludst         ; shift alu_result rigth 1 bit and
                                   ; shift contents of q_reg rigth 1 bit.
                                   ; store alu_result after shift in 
                                   ; register stack pointed out by b_addrs
                                   ; field.
*name:  sr,16,5,1,aludst           ; shift alu_reult rigth 1 bit.
                                   ; store alu_result after shift in reg.
                                   ; register stack pointed out by b_addrs
                                   ; field.
*name:  slaq,16,6,1,aludst         ; shift alu_result left 1 bit and 
                                   ; and store shifted result in reg.
                                   ; in internal register stack pointed
                                   ; out by b_addrs field, shift also
                                   ; contents of q_reg left 1 bit.
*name:  sl,16,7,1,aludst           ; shift alu_result left 1 bit,
                                   ; and store shifted result in reg.
*name:  cl2903,16,1,4,15           ; clear bit indicating that
                                   ; the reg to the hc 2903 is ready
                                   ; mir(15) := 1.
*name:  clexde,16,1,4,18           ; clock external dev. clock bit,
                                   ; also callsed valid memory address in
                                   ; the motorola pia system, mir(18) = 1.
*name:  trnbus,16,1,4,19           ; turn bus direction for 1 third of
                                   ; the  bus so bus(0.7) is input
                                   ; and bus(8.23) is output of control and 
                                   ; device number, used by reading of charakter
                                   ; type devices, ( set mir(19)).
*name:  opdira,16,5,1,alusrc       ; open for direct and a ram source.
*name:  opdirz,16,7,1,alusrc       ; open for direct and zero source.
*name:  opinde,16,3,1,alusrc       ; open for zero and internal source.
                                   ; the internal source is the same as destination.
*name:  opramf,16,3,1,aludst       ; open for internal registers.
*name:  oprama,16,2,1,aludst       ; open for internal reg. and 
                                   ; move a bus to out port.
*name:  clkint,16,1,4,14           ; clock interupt  logic  
                                   ; for reading of
                                   ; external interupt level.
*name:  readch,16,1,4,16           ; select read from external char device ,
                                   ; mir(16) = 1, schould be set together with
                                   ; bit(1) in the bus word.
*name:  writch,16,0,4,16           ; select write from external char device,
                                   ; mir(16) = 1, normaly allways cleared.
*name:  sltiml,16,1,4,17           ; select timer divice or other divice no less
                                   ; from deivce no 0 to device no 7,
                                   ; mir(17) = 1.
*name:  init03,16,1,4,17           ; set mir(17) , cause hc2903 to 
                                   ; start initialize, schould be send
                                   ; at least 3 times following
                                   ; each other. only functioning
                                   ; in rh8000.
*name:  intr03,16,1,4,0            ; set mir(0), which interupt the
                                   ; hc2903
                                   ; open for interupt group 0,
                                   ; dev on 2901 board.
*name:  opexde,16,1,2,11           ; open fore xtern destination registers.
          ; set or clear selected bit or bits 
          ; selected from the argument.
*name:  set,16,-1,3,1              ; set one bit
*name:  clear,16,0,3,1             ; clear one bit
*name:  setall,16,-1,3,2           ; set all bit from arg1 to arg2
*name:  clall,16,0,3,2             ; clear all bit from arg1 to arg2
                                   ; in internal register stack pointed
                                   ; out by b_addrs field.
*save:  m2901
*end:   
*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.
        ;
        ; 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 byte 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 diable 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'.
        ;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.
        ;PROJECT:
        ;------------------------------------------------------
        ; -----------------------------------------
        ; the status regsister in hc2901 and rh2901
        ; declared as status(0:23).
        ; status(23) = interupt set.
        ; status(22) = 1 indicating that the simulated message
        ;                'fifo' is full, can be refferenced by the standard
        ; initialisation of the q register ( value 2).
        ; status(21) = 1  test after fetch and prefetch ( not in final
        ;                 version ).
        ; status(20:6)   interupt register.
        ;                status(20) the first interupt bit can be
        ;                refferenceded by the standard value initialisation
        ;                of the wrk2 register ( value 8 ),
        ;                the first bit is in fact interupt 3,
        ;                and correspond to interupt level 3.

        ; status(0)
        ; status(1)
        ; status(2)

        ; 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
                              ; iccn bus time out.
*const: sendto,4095           ; no of mic. instr. before sender
                              ; on iccn bus has detected that
                              ; 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)
*skip:  iccnx
*const: icfile,4              ; iccn message fifo full - (1+3).
*until: iccnx
*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.
        cont                  ; address 3
                              ; not used.
        jmp(rc80in)           ; address 4
                              ; interupt from rc8000.
*until: rh8000
*onlyin:hc8000                ; local dma only in hc8000
        jmp(dmain)            ; entry micro program address 1.
*until: hc8000
*skip:  iccnx
        jmp(iccnma)           ; entry micro program address 2.
*origo: 4
        jmp(iccnin)           ; goto iccn bus interupt.
                              ; entry jump table from hc2903.
                              ; only in use until final version.
                              ; if vect=true
*until: iccnx
*onlyin:hc8000
        jmp(choint)           ; address 2,
                              ; channel out interupt.
        cont                  ; not used address 3.
*origo: 4
        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
*skip:  iccnx
e01do1/:jmp(doicst)           ; iccn bus dma start.
*until: iccnx
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
*skip:  iccnx
e01do3/:jmp(doreic)           ; iccn bus reset.
*until: iccnx
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
*skip:  iccnx
e01do5/:jmp(doiswc)           ; iccn bus send message
                              ; use iccn singele word communication.
*until: iccnx
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.
*skip:  iccnx
e01di1/:jmp(dintus)           ; iccn bus fifo read.
*until: iccnx
e01di1/:jmp(dichst)           ; channel input start.
e01di2/:jmp(dintus)           ; data in not used.
*skip:  iccnx
e01di3/:jmp(direfi)           ; iccn bus fifo reset.
*until: iccnx
e01di3/:jmp(dichre)           ; channel input reset.
*onlyin:hc8000
e01di4/:jmp(dichde)           ; read external chararcter device.
*until: hc8000
*onlyin:rh8000
*skip:  iccnx
e01di4/:jmp(doiswc)           ; data in readuword from iccn bus,
                              ; use single word communication.
*until: iccnx
e01di4/:jmp(dintus)           ; data in not used.
*until: rh8000
*until: iccnx
e01di5/:jmp(dintus)           ; data in not used.                    
e01di6/:jmp(dintus)           ; data in not used.
*skip:  iccnx
e01di7/:jmp(diicoi)           ; read own iccn bus identification.
                              ; limit control
*until: iccnx
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.         
*onlyin:hc8000
        ; real time clock is substituted with external interupt
        ; level.
        ;e01rtc/:jmp(gng100)           . gg(100) get real time clock.
e01rtc/:jmp(geng94)           ; gg external interupt level.
e01rtr/:jmp(geng64)           ; gg test register with no wait.
e01wtr/:jmp(genp64)           ; gp test register.
e01rtw/:jmp(geng66)           ; gg test register with wait.
*until: hc8000
*onlyin:rh8000
        cont                  ; dummy entries for test register and
        cont                  ; real time clock.
        cont
e01rtw/:jmp(geng66)           ; wait start by rc8000, send
                              ; interupt register to hc2903.
*until: rh8000
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.


        ; 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 iccn 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.
*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).
        move(wrk2,wrk2) sl    ; wrk2 := wrk2*2 ( 8).
*onlyin:rh8000
        jsb(cnrc81)           ; call subroutine to wait for 
                              ; signal from rc8000 and check of
                              ; control bits.


*until: rh8000
*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.
*skip:  iccnx
        mzero(iccnch)         ; clear iccn chain.           
*until: iccnx
        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:  iccn


        ; subroutine get word from memory
        ;-===============================
        ; pointed out by wrk0, if not memory ready
        ; then goto timeout0.
gemewo: move(meaddr,wrk0)     ; send send  address of memory word
                              ;  to memory,  and clock memory 
                              ;  read cycle.
        lcpu('metimo)         ; load counter with timeout
        twb(rememo,iotmo0)    ; while not memory ready do
                              ;   if memory ready then next mic. instr.
                              ;   else if counter = 0 then goto iotmot.
                              ;   decrease(counter)
                              ;   od.
        rtn add(wrk0,q)       ; increase wrk0 to point to next mic. instr
                              ; and return from subroutine.
        ;*until: iccn
        ; in rh 8000 in address 132.


        ; subroutine put data from wrk1 to memory addressed by wrk0.
        ; ==========================================================
*onlyin:hc8000
puw1w0: move(meaddr,wrk0)     ; send address to memory.
        cont                  ; sync of memory.
puwww0: cjmp(rememo,puwww0) not; wait for memory.
*until: hc8000
*onlyin:rh8000
puw1w0:                       ;
*until: rh8000
        move(medata,wrk1)     ; send data word to memory.
*onlyin:rh8000
        move(meaddr,wrk0)     ; send address to memory.
*until: rh8000
*onlyin:hc8000
        cont                  ; sync of memory.
*until: hc8000
puwww1: cjmp(rememo,puwww1) not; wait for memory ready.
        rtn add(wrk0,q,wrk0)  ; wrk0 := next memory address,
                              ; return from subroutine.
*until: iccn                  ; puw1w0 only used in iccn bus service.
*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

        ; 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.

        ; 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.
        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
                              ; send interupt.
        move(hc2903,pir) cl2903; move prefetched instruction 
                              ; to hc2903, and clock hc2903. 
        move(lwco,pir)
        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
        ; -----------------------------
        ;test subroutine
        ;pud132:   move(c66,c66) sl
        ;         move(meaddr,c66)
        ;         move(c66,c66) sr
        ;pud133: cjmp(rememo,pud133) not
        ;       rtn





*onlyin:rh8000
        ; special functions in rh8000
        ; ----------------------------
        ; subroutine control address from rc8000
        ; --------------------------------------
cnrc81: cjmp(re8000,cnrc81) not; wait for addressing from rc8000.
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,init) not   ; then goto init
        rtn move(wrk2,wrk2) sl; else wrk2 := 8 , start.
cnrc82: move(wrk2,wrk2) sl    ; wrk2 := 8.
        and(q,wrk0) noload    ; if control bits '10' then
        cjmp(zero,cnrc81)     ; goto stop else
        rtn                   ; not used ( work as start).
*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.
        ; -------------------------------------------------
        ; 810805: temp. instead of gg 100.
        ; 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 fisrt interupt controler.
                              ; cretae 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)
        modec(wrk1,q)         ; wrk1 := const(1).
        jsb(gng941)           ; push next mic. address into
                              ; stack.
gng941: move(extreg,wrk1) clkint  ; send writebit (lsb=0) to
                              ; external device bus and send clock 
                              ; interupt acknowlege.
        loop(wainle) move(extreg,wrk1) clkint; wait for level to apear on
                              ; external device bus. ( amd9519.pause
                              ; to go high).
        move(extreg,wrk1) oprama opdirz clkint trnbus readch;
                              ; 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: jsb(cnrc81)           ; call subroutine wait signal from
                              ; rc8000 and check control bits.
                              ; bits from rc8000.
        move(hc2903,medata) cl2903; send word from data bus to
                              ; hc2903 and clock ready.
        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.
        ;   wrk2 values   init. no    interupt indication.
        ;       1             3       system table interupt,
        ;                             and signal auto load.
        ;       2             4
        ;       4             5                                            
        ;       8             6                                       
        ;      16              7    timer interupt.
        ;      32              8    iccn bus interupt.
        ;      64              9    local dma interupt, or in rh8000 interupt
        ;                           from rc8000.
        ;     128             10    iccn message interupt.
        ;     256             11    
        ;     512             12      char device bus interupt.
*skip:  iccnx
inicme:                       ; message from iccn bus.
inldma:                       ; interupt from local dma, only in
                              ; hc8000.
inicff:                       ; interupt iccn fifo full.
*until: iccnx
*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 ).
inauto:                       ; interupt entry auto load.
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 diable 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 diable 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 .
*skip:  iccnx
        ; subroutine get own iccn identification into wrk1.
        ;--------------------------------------------------
geicid: 
*onlyin:hc8000
        move(wrk1,iccnid)     ; the iccn id is in the 12 most significant
                              ; bit in the iccn register, the least 
                              ; significant bit is undefined.
        lcpu('hlfwrd)         ; load counter with half word.
        rep move(wrk1,wrk1) sr; wrk1 := wrk1 shift (-12).
        rtn                   ; return from subroutine.
*until: hc8000
*onlyin:rh8000
        rtn mzero(wrk1)       ; own iccn id is zero in rh8000
*until: rh8000
*until: iccnx
*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) clexde writch sltiml; send data and address to 
        move(extreg,wrk1) clexde writch sltiml; char io bus register and 
        move(extreg,wrk1) clexde writch sltiml; set clok external device signal
        move(extreg,wrk1) clexde writch sltiml; (valid memory address in 
                              ; motorola
        move(extreg,wrk1) clexde 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) clexde 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) clexde opdirz oprama sltiml trnbus;
        move(extreg,wrk1) clexde opdirz oprama sltiml trnbus;
        move(extreg,wrk1) clexde 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
*skip:  iccnx






        ; subroutine dump iccn block transport.
        ; =====================================
dmictn: add(wrk0,q,iccnch)    ; wrk0 := address of current iccn block
                              ; word counter.
        move(wrk1,icwoco)     ; wrk1 :=  iccn word counter.
        jsb(puw1w0)           ; write iccn word counter  to     
                              ; tranport block.
        move(wrk1,icsla)      ; dump iccn slave address.
        jsb(puw1w0)           ;
        move(wrk1,icmas)      ; dump iccn master address.
        jsb(puw1w0)           ;
        rtn move(wrk0,iccnch) ; wrk0 := address of iccn transport
                              ; block.

        ; subroutine load iccn block transport.
        ; =====================================
loictn: negadd(wrk0,q,wrk0)   ; wrk0 := iccn block chain address.
        move(wrk1,iccnch)     ; wrk1 := old chain.
        jsb(puw1w0)           ; save chain address.
        move(iccnch,wrk0)     ; chain := wrk0 ( new iccn block address).
        jsb(geicid)           ; get own iccnid to wrk1.
        move(icdev,wrk1)      ; icdev := own iccn id.
        jsb(gemewo)           ; get memory word ( reciever iccn dev no.).
        move(wrk0,medata)     ; wrk0 := iccn reciever dev no.
        jsb(hwmltr)           ; call subroutine half word move.
        jsb(hwmrtl)           ; call subroutine halword move.
        or(icdev,wrk0)        ; ic dev := sender dev + reciever dev.
        add(wrk0,q,iccnch)    ; reestablish wrk0.
        jsb(gemewo)           ; get next memory word.
        move(icwoco,medata)   ; get iccn word counter.
        jsb(gemewo)           ; get next memory word.
        move(icsla,medata)    ; get iccn slave address.
        jsb(gemewo)           ; get next memory word.
        rtn move(icmas,medata); get iccn master address,
                              ; return from subroutine.
*until: iccnx

*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).
*skip:  iccnx



        ; data out, start iccn block transport.
        ;--------------------------------------
        ; from hc2903 entry e01do1.
doicst/:
        move(iccnch,iccnch)   ; if iccn chain address    <> 0 then
        cjsb(zero,dmictn) not ; call dump current iccn transport.   
                              ; ( i.e. iccn bus  allready in use for
                              ; a block transport).
        jsb(ge03w0) cl2903    ; call subroutine to get iccn block
                              ; transport, information block into wrk0.
        jsb(divw08)           ; call subroutine to divide wrk0 
                              ; by 8 to get rigth address.
        jsb(loictn)           ; load iccn transport.              
                              ; (wrk0 = new addres block ).
        cont burqst           ; send bus reguest signal to iccn logic.
        jmp(noraw0)           ; go to normal answer with 1 dummy clear
                              ; of hc2903. ( the unused data word.)
*until: iccnx



        ; 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
                              ; bute.
        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
*skip:  iccnx
        ; data out, reset iccn blok transport.
        ; ------------------------------------
        ; entry e01do3 from hc2903.
doreic: mzero(icwoco)         ; clear icword counter.
        jmp(noran0)           ; go to normal answer entry 0 to 
                              ; hc2903 ( neither address or data word
                              ; is used).
        ; data in, get fifo message
        ; the effektive address form hc2903 is used to
        ; address a double word wrere the message is stored.
digefi/:move(wrk0,icbiba)     ; get address of current fifo word.
        jsb(gemewo)           ; 
        move(wrk1,medata)     ;
        negadd(wrk1,q,wrk1)   ; update current fifo address.
        negadd(wrk1,q,wrk1)   ;
        move(wrk0,icbiba)     ; dump updated fifo address.
        jsb(puw1w0)           ;
        move(wrk0,wrk1)       ; wrk0 := address of current fifo message.
        jsb(gemewo)           ; get fifo message divice part.
        move(wrk1,medata)     ; 
        jsb(gemewo)           ; get fifo message  message part.
        move(wrk1,medata)     ;
        jsb(ge03w0) cl2903    ; get address of messsge dump from hc2903.
        jsb(puw1w0)           ; put memory word.
        jsb(wa0300)           ; call subroutine to wait dummy data word.
        move(hc2903,wrk1)  cl2903; send iccn device no to hc2903 and clock
                              ; data ready.
        move(wrk1,wrk2)       ; wrk1 := fifo message divice address part.
        negadd(wrk0,q,wrk0)   ; wrk0 := q - 4.
        negadd(wrk0,q,wrk0)   ;
        jsb(puw1w0)           ; dump fifo message dev address field.
        jmp(noraw2)           ; goto normal answer with 1 wait.

        ; data  in, reset fifo.
        ; ---------------------
        ; entry e01di3 from hc2903.
direfi: jsb(ge03w0) cl2903    ; get address of simulated fifo from
                              ; hc2903.
        move(icbiba,wrk0)     ;
        moinc(wrk0,wrk1)      ; wrk0 := 2.
        andn(status,wrk0)     ; clear status(22) , indicating fifo full.
        jmp(noraw0)           ; goto normal answer.
*skip:  rh8000
        ; interupt level set.
        ; ===================
intlev: cont cl2903           ; clock hc2903.

intle1: cjmp(re2903,intle1) not; wait for hc2903.
        move(wrk1,hc2903)     ;
        jsb(wrin0)
        jsb(dochw1)           ;
        jmp(gewait)           ;
        *until rh8000         ;





        ; answer address of iccn bus interupt.
        ; -------------------------------------
iccnin: move(wrk0,iccn)       ; wrk0 := sender reciever address word.
                              ; (reciever shift 12 + sender)
        recvst                ; set iccn bus logic in reciever control
                              ; status.
iccni1: lcpu('butimo)         ; mic. sekvence conter := iccn bus timeout
                              ; push address af next micro instr.
        twb(icsic,iccni1)     ; no timeout in test version.
        ; next deleted in test version
        ;       twb(icsic,iccnit)       . wait iccn sender in control
                              ; or if not recevied in butimo
                              ; micro instr. then goto iccnit ( time out)
        move(wrk2,iccn)       ; if data word from iccn bus < 0 then
        cjmp(neg,iccnrm)      ;  goto iccnrm (  recieve message)
                              ; (data word is a message) else
        move(meaddr,iccn)     ; send data word to memory address register
                              ; and start memory read cycle.
        lcpu('metimo)         ; load counter with no of micro
                              ; instruction before timeout.
        twb(rememo,iccnit)    ; if memory not ready in 'metimo
                              ; micro instr. then goto timeout
                              ; after iccn bus interupt.
        move(iccn,medata)     ; send word read from memory
                              ; out on the iccn bus.
        recvcl                ; clear iccn bus reciever contol logic.
        jmp(gewwri)           ; goto generel wait with init.
iccnit: lcpu('sendto)         ; load counter with number of
                              ; instructions before it is sure
                              ; taht the iccn bus sender has 
                              ; found out that there is timeout.
        twb(icsic,iccntt)     ; wait for sender to clear sender control
                              ; to signal that time out is detected
                              ; if not recieved in 'sendto instr,
                              ; then continue uncunditionaly.
iccntt: cont recvcl           ; clear reciever control to indicate
                              ; end of timeout on iccn bus.
        jmp(gewwri)           ; goto generel wait with init.

        ; recive message from iccn bus.
        ; ------------------------------
        ; wrk0 = sender + reciever identificatin.
        ; wrk1(0) = 1  ( the sign bit) indicates that that the word 
        ;           recievved through
        ;            iccn bus is a message.
        ;            if wrk1(23) is set then it is a interupt message.



iccnrm:                       ; message recieved from iccn bus
                              ; to simulated fifo, or interupt message.
                              ; interupt message is treated on a special
                              ; way in the rh8000.
*onlyin:hc8000
        and(wrk2,wrk1) noload ; if last bit is set in message then
                              ; the message is interpreted as a
                              ; interupt signal, so goto iccn interupt,

        cjmp(zero,iccnim)     ; goto iccn interupt message.
*until: hc8000
        and(q,status)  noload ; if status (22) = 1 then
                              ; (i.e. fifo is full)  
        cjmp(zero,iccnit) not ; goto answer timeout.
        cont            recvcl; if not fifo full send signal ok to sender.
                              ; by clearing recive control logic.
        move(wrk1,wrk0)       ; wrk1 := sender dev. + reciever dev.
        move(wrk0,icbiba)     ; wr0 := iccn bus information block.
        jsb(gemewo)           ; get memory word.
        move(wrk0,medata)     ; get address of next free in fifo.
        jsb(puw1w0)           ; put sender dev and reciever dev into fif
                              ; fifo.
        move(wrk1,wrk2)       ; wrk1 := message word.
        jsb(puw1w0)           ; put message word into fiffo.
        move(wrk1,wrk0)       ; wrk0 := next address in fifo.
        move(wrk0,icbiba)     ; wrk0 := address of next infifo.
        jsb(puw1w0)           ; write new next in fifo to memory.
        jsb(gemewo)           ; get max fifo adddress.
        move(wrk0,medata)     ;
        sub(wrk1,wrk0) noload ; if last in fifo is greate in fifo level
        cjmp(neg,inicme) not  ; if posetive then goto set interupt    
                              ; iccn message.
                              ; interupt no 10.
        and(status,q,status)  ; status(22) := 1. (i.e. fifo full)
        ldct('icfile)         ; load counter with iccn fifo full
                              ; interupt level.
        jmp(clcint)           ; goto calculate interupt no.



        ; innc interupt message is recieved.
iccnim: cont   recvcl         ; clear recieve iccn logic.
*onlyin:rh8000                ; autoload message to hc8000 is not allowed
                              ; autoload is given from rc8000.
        jmp(iccnit)           ; goto iccn time out.
*until: rh8000                ;
*onlyin:hc8000                ; only auto load through iccn bus        
                              ; in hc8000 not in rh8000.
        jmp(inauto)           ; goto set interupt autoload ( answer 2)
*until: hc8000                ;
                              ; (last befor close interupt)


        ; subroutine read from iccn bus or
        ;            send message word through iccn bus.

        ; call wrk1 = reciver dev. shift 12 + sender device.
        ;      wrk0 = address to be read from reciever.
        ; return wrk0 = data word readif not iccn bus time out
        ;               else unchanged.

        ;        wrk1 = 0  => transport ok.
        ;        wrk1 = 1  => iccn bus communication error,
        ;                     ( i e time out and no answer or
        ;                       just no answer )
        ;        wrk1 = 2  => transport time out,
        ;                     ( i.e. reciever message buffer full,
        ;                        or reciever illegal address).

iccnre: cont slctst           ; set device select logic.
        move(iccn,wrk1)       ; send reciever dev and sender dev.
        mzero(wrk1)   slctcl  ; clear device select logic,
                              ; and set wrk2 to normal answer.

iccnr1: lcpu('butimo)         ; load conter with iccn bus read 
                              ; time out length.
        ; next is cleared in testversion
        twb(icric,iccnr1)     ; no time out in test wersion
        ;    twb(icric,icrece)          . wait iccn bus reciever in control
                              ; otherwise goto iccn read 
                              ; communication error.
        move(iccn,wrk0)       ; send address of data word to 
                              ; iccn bus.
        cont           sendst ; set iccn bus send logic.
iccnr2: lcpu('butimo)         ; load counter with iccn bus read
                              ; time out length.
        twb(icric,iccnr2) not ; no time out in testversion
        ; next cleared in test version
        ;    twb(icric,icreto) not      . wait iccn bus reciever out of control
                              ; otherwise goto iccn read timeout.
        cont             sendcl; clear iccn bus send logic,
                              ; which also turns direction on the bus.
        move(wrk0,iccn)       ; get data word from iccn bus.
        rtn             burels; return and release bus master request.
                              ; and clear wrk1 indicating that
                              ; bus transport ended
                              ; without timeout.
        ; iccn bus read or send message timeout.
icreto: cont           sendcl ; clear send iccn logic, which also
                              ; signal to sender that timeout is
                              ; detected.
        lcpu('butimo)         ; load bus timeout.
        twb(icric,icrece) not ; if reciever is not clered in
                              ; 'butimo instructions then goto
                              ; set iccn bus read comunication errror.
        rtn move(wrk1,q) burels; else send timeout and return.
icrece: rtn mzero(wrk1) burels; set wrk1 to transport ok.          
                              ; and release from master on iccn bus
                              ; and return from subroutine.
        ; entry ask for bus request.
        ; --------------------------
asbur0: cont    burqst        ; ask for a bus request
        jmp(gewwri)           ; and goto general  wait.


        ; data in and data out iccn bus single word communnication
        ;---------------------------------------------------------
        ; on the iccn bus.
doiswc: cjmp(nabrqi,doiswc) not; if asked for bus request then

        cont  burqst          ; ask for bus request.
doisw1: jsb(ge03w0) cl2903    ; get iccn bus identicication
                              ; ( reciever address).
        jsb(divw08)           ; call divide w0 with 8.
        jsb(hwmrtl)           ; call move rigth halfword of wrk0 to
                              ; left halfword of wrk0.
        jsb(geicid)           ; get own iccn id into rigth half word
                              ; of wrk1.
        or(wrk1,wrk0)         ; wrk1 := reciever shift 12 + sender.          
        jsb(ge03w0) cl2903    ; get either message word or
                              ; address in other computers memory.
        move(wrk2,wrk0)       ; save message.
doisw2: cjmp(icmabu,doisw2) not; wait until master on iccn bus.
        jsb(iccnre)           ; call read a word from iccn bus
                              ; or write a message.
        move(wrk2,wrk2)       ; if it was a message then
        cjmp(neg,doisw3)      ;  goto reestablish data word send
        move(hc2903,wrk0) cl2903; send data word from iccn bus to 
                              ; hc2903.
        jmp(doisw4)           ; goto control for iccn block transport.
doisw3: move(hc2903,wrk2) cl2903; reestablis message to hc2903.
doisw4: move(icwoco,icwoco)   ; if icwoco <> 0 then
        cjmp(zero,bucow2)     ;  ask for bus request before
        jmp(bucow2)           ; entering bus cumunication errro,
                              ; the status of the operation is in the
                              ; wrk1 register.

        ; entry when master on bus.
        ; =========================
iccnma: 



iccnrb:                       ; iccn bus read block.
        move(wrk1,icdev)      ; wrk2 := iccn bus block read device
                              ; reciever shift  12 +  sender device.
        move(wrk0,icsla)      ; addess of data in iccn bus slave computer.
        jsb(iccnre)           ; call iccn read bus.
        cjmp(zero,stburq) not ; if not ok then goto do it again.
                              ; (i.e. start bus request.)
*onlyin:rh8000
        move(medata,wrk0)     ; move read data word to memory.
*until: rh8000
        move(meaddr,icmas)    ; send address of data in own memory
                              ; to memory  address register and clock 
                              ; memory write.
icblr1: cjmp(rememo,icblr1) not; wait for memory ready.
*onlyin:hc8000

        move(medata,icmas)    ; send address of data in own memory.
*until: hc8000
        sub(icwoco,q)         ; iccn bus block word counter :=
                              ; iccn bus block word counter -2.
        cjmp(zero,icblr2)     ; if last word read then goto
                              ; finis block transport.
        add(icmas,q)          ; iccn master memory addres + 2.
        add(icsla,q)          ; iccn slave memory address + 2.
stburq: cont burqst           ; start bus request.
        jmp(gewwri)           ; goto general wait 0.
                              ; last of a block transport,
                              ; interupt hc2903.
icblr2: jsb(dmictn)           ; call subroutine dump current 
                              ; iccn transport blovk.
        negadd(wrk0,q,iccnch) ; get addres of iccn transport chain.
        jsb(gemewo)           ; get memory word.
        move(wrk0,medata)     ; get memory data word.
        move(wrk0,wrk0)       ; for control
        cjmp(zero,icblr3)     ; if chain empty then goto send 
                              ; interupt to hc2903 from iccn transport.
        jsb(loictn)           ; else call subroutine load iccn
                              ; transport.

        cont  burqst          ; ask for bus request.
icblr3: move(wrk0,wrk2)       ; wrk0 := interupt level  address.
        jsb(gemewo)           ; call subroutine get memory word.
        move(wrk0,medata)     ; wrk0 := medata.
        move(wrk2,q) sl
icblr4: move(wrk2,wrk2) sl    ; wrk2 := 8.
        dec(wrk0)             ; interupt level := interupt level - 1.
        cjmp(neg,icblr4) not  ; if not negative then contiue.
        jmp(intrs1)           ; else goto intrs1.


        ; get own iccn bus id.
        ;=====================
diicoi: jsb(geicid) cl2903    ; call own iccn bus id into wrk1. 
                              ; to hc2903,( get address, not used).
        jsb(wa0300)           ; call subroutine dor dummy data wait.
        move(hc2903,wrk1) cl2903; send own iccn bus id to hc2903 and
                              ; clock ready the hc2903.
        jmp(noraw1)           ; goto normal answer.
*until: iccnx
        ; 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/:
        jsb(ge03w0) cl2903    ; get device address from hc2903.
        move(dochwc,dochwc)   ; if word counter <> 0 then
        cjmp(zero,bucoe1) not ; then goto bus cummunication error.
        jsb(gedvbl)           ; call subroutine to get device block 
                              ; address.
        move(meaddr,wrk0)     ; send adrress of word counter to
                              ; memory and start read cycle.
        add(wrk0,q)           ; wrk0 := wrk0 + 2 .
dochs1: cjmp(rememo,dochs1) not; wait for memory ready.
        move(dochwc,medata)   ; get channel output wordcounter.
        move(meaddr,wrk0)     ; send address of data block address to
                              ; memory and start read cycle.
        negadd(dochwc,q) noload; if channel out put word counter < 2
        cjmp(neg,bucoe1)      ; then goto bus communication error.
dochs2: cjmp(rememo,dochs2) not; wait for memory ready.
        move(dochad,medata)   ; get channel block address.
        sub(dochad,wrk2) noload; if address of data block < 8
        cjmp(neg,bucoe1)      ; 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
        jmp(noran1)           ; goto normal answer 1.

        ; 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,dochfi)      ; if word counter < 0
                              ; then goto channel output finis
                              ; interupt.
        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.
dochs3: cjmp(rememo,dochs3) 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.



dochfi:                       ; channel output finis interupt.
        ; ------------------------------
        mzero(dochwc)         ; reset word counter.
        ldct('chofil)         ; load counter with 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.
        jsb(gedvbl) cl2903    ; 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.
        cont strech           ; clock start reading of channel.
        move(dichwc,chdata)   ; get first data word to
                              ; data in channel word counter.
        cont     firech       ; clock finis read channel.
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.

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◀