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

⟦b20a5b064⟧ TextFile

    Length: 17664 (0x4500)
    Types: TextFile
    Names: »t2901dir«

Derivation

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

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:  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.
        ; channel register.                           
*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:  ictsad,30,15          ; ic test 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.
        ; 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.



        ; 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:  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:  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:   
▶EOF◀