Thursday, December 17, 2009

SCIDRV.ASM

******************************************************************************
*                       S C I   D R I V E R   M O D U L E                     *
*                                                                             *
*******************************************************************************

isrrtn    equ    $360        ; Address of Common Interrupt Exit routine

SCIINTLV  equ    5           ; SCI Interrupt Level
SCIINTV   equ    $3A         ; SCI Interrupt Vector

QMCR      equ    $FC00
QILR      equ    $FC04       ; QSM Interrupt Levels Register
QIVR      equ    $FC05       ; QSM Interrupt Vector Register

SCCR0     equ    $FC08       ; SCI Control Register 0
SCCR1     equ    $FC0A       ; SCI Control Register 1
SCSR      equ    $FC0C       ; SCI Status Register
SCDR      equ    $FC0E       ; SCI Data Register

*******************************************************************************
*  SCCR1 REGISTER FIELDS                                                      *
*******************************************************************************

SRK       equ    $01         ; Send Break
RWU       equ    $02         ; Receiver Wakeup
RE        equ    $04         ; Receiver Enable
TE        equ    $08         ; Transmitter Enable
RIE       equ    $20         ; Receiver Interrupt Enable
TIE       equ    $80         ; Transmitter Interrupt Enable

*******************************************************************************
*  SCI STATUS REGISTER FIELDS                                                 *
*******************************************************************************

RDRF      equ    $40         ; Receive Data Register Full
TDRE      equ    $01         ; Transmit Data Register Empty (high byte of $0100)

*******************************************************************************
*  SCI DRIVER EQUATES                                                         *
*******************************************************************************

INTS_OFF  equ    $00E0       ; Disable interrupts
SCIINTON  equ    (SCIINTLV<<5+$FF1F) ; Enable interrupts at SCIINTLV (2)
BR9600    equ    $37         ; SCCR0(0-12) setting for 9600 Baud

          PAGE
*******************************************************************************
*                                                                             *
*                       S C I   I N P U T   D R I V E R                       *
*                                                                             *
*******************************************************************************

sciidrv:  orp    #INTS_OFF   ; Turn off interrupts while enabling SCI
          ldab   #$F
          tbek               ; EK = F (K=$Fxxx)

          ldd    #$008A
          std    QMCR        ; Set IARB=10 for intermodule bus arbitration

          ldd    QILR        ; Get content of QSM Interrupt Levels Register
          anda   #$E8        ; Clear out ILSCI field
          oraa   #SCIINTLV   ; Set SCI interrupt level in ILSCI field
          ldab   #SCIINTV     ; Load SCI Interrupt Vector #
          std    QILR        ; Update QILR

          ldd    #RIE+RE+TE  ; Receiver enabled with interrupts active,
                             ; Transmitter enabled without interrupts,
                             ; 1 Start Bit, 1 Stop Bit, 8 Data Bits
          std    SCCR1       ; Set up SCI operating conditions
          ldd    #BR9600     ; Set up 9600 baud rate
          std    SCCR0

rdclr:    ldd    SCSR        ; Get current status of SCI
          bitb   #RDRF       ; See if receive data ready
          beq    scirdy      ; if not SCI is a
          ldab   SCDR        ; Read input data
          bra    rdclr       ; Loop until clear
scirdy:   andp   #$FF1F      ; Turn interrupts on again

inloop:   ldab   #1          ; bank 1
          tbek               ; EK = 1
          tbxk               ; XK = 1 (K=$11xx)
          ldab   #SCIISEMA
          ldaa   #MCX_WAIT   ; Wait for input character
          swi

          ldaa   inchar      ; Get input character captured by isr
          ldx    #EQ3src     ; Move it to safe place
          staa   0,x
          ldab   #SCIIQ      ; Then move the character into SCIIQ
          ldaa   #MCX_ENQUEUE_W
          swi

          bra    inloop      ; Loop forever

          PAGE
*******************************************************************************
*                                                                             *
*                     S C I   O U T P U T   D R I V E R                       *
*                                                                             *
*******************************************************************************

sciodrv:  ldab   #$F
          tbek               ; EK=F  (K=$Fxxx)
          ldab   #1
          tbxk               ; XK=1  (K=$F1xx)

scioloop: ldx    #DQ4dest
          ldab   #SCIOQ      ; Get next character from SCIOQ and put it into
          ldaa   #MCX_DEQUEUE_W  ; DQ4dest as temporary location
          swi

          ldab   0,x         ; Get the character
          cmpb   #$0A        ; New Line?
          bne    notnl       ; Branch if not "\n"
          ldd    SCSR        ; Get SCI status
          ldaa   #$0D
          staa   SCDR+1      ; Output a "\r"
          ldd    #RIE+RE+TE+TIE
          std    SCCR1       ; Enable transmitter interrupts
;         ldab   #RIE+RE+TE+TIE
;         stab   SCCR1+1     ; Enable transmitter interrupts

          ldab   #SCIOSEMA   ; Wait for it to be output completely
          ldaa   #MCX_WAIT
          swi

notnl:    ldd    SCSR        ; Read status
          ldaa   0,x         ; Get character to output
          staa   SCDR+1      ; Output it
          ldd    #RIE+RE+TE+TIE
          std    SCCR1       ; Enable transmitter interrupts
;         ldab   #RIE+RE+TE+TIE
;         stab   SCCR1+1     ; Enable transmitter interrupts

          ldab   #SCIOSEMA   ; Wait for it to be output completely
          ldaa   #MCX_WAIT
          swi

          bra    scioloop    ; Loop forever

          PAGE
*******************************************************************************
*                                                                             *
*           S C I   I N T E R R U P T   S E R V I C E   R O U T I N E         *
*                                                                             *
*******************************************************************************

pshsema   macro
          ldab   #\1
          orp    #INTS_OFF
          lde    $06,x
          stab   e,z
          incw   $06,x
          andp   #SCIINTON
          endm

sciisr:   orp    #INTS_OFF   ; Save the interrupt context
          pshm   d,e,x,y,z,k
          ldab   #1
          tbek               ; EK=1  (K=$1xxx)
          tbyk               ; YK=1  (K=$1x1x)
          tbzk               ; ZK=1  (K=$1x11)
          clrb
          tbxk               ; XK=0  (K=$1011)
          ldx    $0000       ; x = [$10000]
          tst    $000A
          bne    notlvl0
          ldy    $0004       ; y = [$10004]
          sts    8,y         ; [y+8] = SP
          lds    $14,x       ; SP = [X+20]
notlvl0:  inc    $000A       ; [$1000A] = [$1000A]+1
          andp   #SCIINTON   ; Interrupts back on
          ldz    $12,x

          ldab   #$F         ; EK = F  (K=$Fx11)
          tbek
          ldab   #1
          tbxk               ; XK = 1  (K=$F111)
          ldx    #$0000      ;
          ldy    #inchar     ; y = &inchar

          ldd    SCCR1       ; If TDRE is set, see if SCCR1 has TIE set
          bitb   #TIE
          beq    notout      ; If not, this is not an output interrupt
          ldd    SCSR        ; Check SCI status register for TDRE
          bita   #TDRE
          beq    chkrd       ; TDRE not set
          ldd    #RIE+RE+TE  ; If so, this is a transmitter interrupt, turn
                             ;  TIE off now that the character is out
          std    SCCR1       ; Update SCCR1. That takes care of the output side

          ldd    SCSR        ; Now treat a possible input interrupt that is
                             ;  simultaneous with the output. Reread the status
          bitb   #RDRF       ; Check for RDRF set
          beq    noin        ; Branch if no input occurred
          ldd    SCDR        ; Yes it did. Read the input character
          andb   #$7F        ; Strip it to 7 bits
          stab   0,y         ; Store in temporary location (inchar)
          pshsema SCIISEMA   ; Put SCIISEMA into Signal List
noin:     ldaa   #SCIOSEMA   ; Now signal the SCI output semaphore
          jmp    isrrtn

notout:   ldd    SCSR        ; Read status again
chkrd:    bitb   #RDRF       ; See if this is an input interrupt. Check RDRF
          beq    notin       ; It is not an input interrupt. So what was it?
          ldd    SCDR        ; If it was an input interrupt, get the character
          andb   #$7F        ; Strip it to 7 bits
          stab   0,y         ; Store in temporary location (inchar)
                             ; That takes care of the input. Now see if there
                             ;  was a simultaneous output interrupt
          ldd    SCSR        ; Check SCI status register for TDRE
          bita   #TDRE
          beq    noout       ; TDRE not set
          ldd    SCCR1       ; If TDRE is set, see if SCCR1 has TIE set
          bitb   #TIE
          beq    noout       ; If not, this cannot be an output interrupt
          ldd    #RIE+RE+TE  ; If so, this is a transmitter interrupt, turn
                             ;  TIE off now that the character is out
          std    SCCR1       ; Update SCCR1
          pshsema SCIOSEMA   ; Signal SCI Output Semaphore

noout:    ldaa   #SCIISEMA   ; Now signal the input semaphore
          jmp    isrrtn

notin:    clra               ; This wasn't a recognizable SCI interrupt
          jmp    isrrtn

          PAGE
*******************************************************************************
*  SCI VECTOR                                                                 *
*******************************************************************************

          ORG    SCIINTV*2

          dc.w   sciisr

*******************************************************************************
*  SCI DRIVER DATA VARIABLES                                                  *
*******************************************************************************

          ORG    $003FD

inchar:   ds     1
DQ4dest:  ds     1
EQ3src:   ds     1

*******************************************************************************
*                                                                             *
*                       S C I   D R I V E R   M O D U L E                     *
*

STARTUP.S

;����������������������������������������������������������������������������ͻ
;�                                                                            �
;�                SYSTEM STARTUP FOR 68HC16-BASED DATA-LOGGER                 �
;�                                                                            �
;�                    Copyright (c) 1995 by M. Lutfi                          �
;�                                                                            �
;����������������������������������������������������������������������������ͼ

    .PROCESSOR  M68HC16

    .external _main, __memory,__pdata
    .external ._main, .__pdata
    .external .__text__, .__data__, .__bss__
    .public    _exit, __stext

    .include "hc16regs.mac"
    .include "mcx16.mac"
    .include "lgrset.mac"

    .psect  _text
__stext:
;*********** MCU INIT ******************
; These procedures handled by MCX-16
; Rewritten for clarity only
;**********************************
;    ldab    #0Fh
;    tbek                    ; point EK to bank F for register access
;    ldab    #00H
;    tbxk                    ; point XK to bank 0
;    tbyk                    ; point YK to bank 0
;    tbzk                    ; point ZK to bank 0
;
;    ldaa    #007Fh          ; w=0, x=1, y=111111
;    staa    SYNCR           ; set system clock to 16.78 mhz
;
;    clr     SYPCR           ; turn cop (software watchdog) off,
;                            ; since cop is on after reset
;    ldab    #7FH
;    stab    SYNCR
;    clr     SYPCR
;
;****** init SRAM ******
;    ldab    #1
;    std     RAMBAH
;    clrd
;    std     RAMBAL
;    clr     RAMMCR          ;SRAM addr start from 0x10000 to 0x103FF

;****** init external RAM *******
    ldd     #00003          ; at reset, the csboot block size is 512k.
    std     CSBARBT         ; this line sets the block size to 64k since
                            ;  that is what physically comes with the evb16
    ldd     #00303h
    std     CSBAR0          ;set U1 ram base addr to 0x30000: bank 3, 64k
    std     CSBAR1          ;set U3 ram base addr to 0x30000: bank 3, 64k
    ldd     #05030h         ;no wait states
    std     CSOR0           ;set chip select 0, upper byte, write only
    ldd     #03030h
    std     CSOR1           ;set chip select 1, lower byte, write only
    ldd     #00303h
    std     CSBAR2          ;set chip select 2 to fire at base addr 0x30000
    ldd     #07830h
    std     CSOR2           ;set chip select 2, both bytes, read and write
    ldd     #03FFFh
    std     CSPAR0          ;set chip selects 0,1,2 to 16-bit ports

;�����������������������������������������������������������������������������͸
;�                          ADC INITIALIZATION                                 �
;�   Summary:                                                                  �
;�   The ADC module is mapped into 32 words of address space. Five words are   �
;�   control/status registers, one word is digital port data, and 24 words     �
;�   provide access to the results of ADC conversion (eight addresses for each �
;�   type of converted data). Two words are reserved for expansion.            �
;�   The ADC module base address is determined by the value of the MODMAP bit  �
;�   int the system integration module configuration register (SIMMCR).        �
;�   The base address is normaly $FFF700 in the MC68HC16Z1.                    �
;�       Internally, the ADC has both a differential data bus and a buffered   �
;�   IMB data bus. Registers not directly associated with AD conversion        �
;�   functions, such as the MCR, the MTR, and the PDR, reside on the bufferd   �
;�   bus, while conversion registers and result registers reside on the        �
;�   differential bus.                                                         �
;�                                                                             �
;�   Registers that must be set prior operation:                               �
;�     ADMCR:                                                                  �
;�       STOP = 0 (normal operation)                                           �
;�       FRZ  = 0                                                              �
;�       SUPV = 1 (supervisory mode)                                           �
;�     ADCTL0:                                                                 �
;�       PRS   = 1 (ADC clock = system clock/4 = 16.667 MHz/4)                 �
;�       STS   = 0 (4 A/D clock periods in the sample time)                    �
;�       RES10 = 1 (10-bit conversion)                                         �
;�     ADCTL1:                                                                 �
;�       SCAN  = 1 (continuous conversion)                                     �
;�       MULT  = 1 (sequential conversion of four or eight channels            �
;�                  selected by [CD:CA])                                       �
;�       S8CM  = 1 (eight-conversion sequence)                                 �
;�       CD    = 0 (measured data at each channel stored into his register)    �
;�                                                                             �
;�����������������������������������������������������������������������������;
    ldd     #0000h
    std     ADCMCR         ;turn on ADC
    ldd     #0001h
    std     ADCTL0         ;10-bit, set sample period


;�����������������������������������������������������������������������������͸
;�                                                                             �
;�                     SCI DRIVER INITIALIZATION                               �
;�                                                                             �
;� 1. Sets up the SCI and starts an infinite loop of receive transmit          �
;� 2. QSM configuration summary:                                               �
;�  * After reset, the QSM remains in an idle state, requiring initialization  �
;�    of several registers before any serial operations may begin execution.   �
;�  * The type of serial frame (8 or 9 bit) and the use of partiy must be      �
;�    determined by M. PE and PT.                                              �
;�  * For receive operation, WAKE, RWU, ILT, ILIE must be considered.          �
;�    The receiver must be enabled (RE) and, usually, RIE should be set.       �
;�  * For transmit operation, the transmitter must be enabled (TE) and,        �
;�    usually, TIE should be set. The use of wired-OR mode (WOMS) must also    �
;�    be decided. Once the transmitter is configured, data is not sent         �
;�    until TDRE and TC are cleared. To clear TDRE and TC, the SCSR read       �
;�    must be followed by a write to SCDR (either the lower byte or the        �
;�    entire word).                                                            �
;�  * QIVR should be programmed to one of the user-defined vectors ($40-$FF)   �
;�    during initialization of the QSM.                                        �
;�    After reset, QIVR determines which two vectors in the exception vector   �
;�    table are to be used for QSM interrupts. The QSPI and SCI submodules     �
;�    have separate interrupt vectors adjacent to each other.                  �
;�    Both submodules use the same interrupt vector which LSB:                 �
;�       1: interrupt generated by QSPI                                        �
;�       0: interrupt generated by QSCI                                        �
;�> Detail Configurations in QSM:                                              �
;�  * QMCR:                                                                    �
;�       STOP = 0 (Normal QSM clock operation)                                 �
;�       FRZ1 = 0 (Ignore the FREEZE signal on the IMB)                        �
;�       SUPV = 1 (supervisor access)                                          �
;�       IARB = $A (priority = 10; $F = highest priority, used by timer)       �
;�  * QILR:                                                                    �
;�       ILQSPI = 1 (lowest priority)                                          �
;�       ILSCI  = 7 (highest priority)                                         �
;�       QIVR   = set to SCI interrupt handler's address                       �
;�                                                                             �
;�����������������������������������������������������������������������������;
    orp    #INTS_OFF   ; Turn off interrupts while enabling SCI
    ldab   #0Fh
    tbek               ; EK = F (K=$Fxxx)

    ldd    #008Ah
    std    QMCR        ; Set IARB=10 for intermodule bus arbitration

    ldd    QILR        ; Get content of QSM Interrupt Levels Register
    anda   #0E8h       ; Clear out ILSCI field
    oraa   #SCIINTLV   ; Set SCI interrupt level in ILSCI field
    ldab   #SCIINTV    ; Load SCI Interrupt Vector #
    std    QILR        ; Update QILR

    ldd    #RIE+RE+TE  ; Receiver enabled with interrupts active,
                       ; Transmitter enabled without interrupts,
                       ; 1 Start Bit, 1 Stop Bit, 8 Data Bits
    std    SCCR1       ; Set up SCI operating conditions
    ldd    #BR9600     ; Set up 9600 baud rate
    std    SCCR0

;����������������������������������������������������������������������������͸
;�                           STACK ALLOCATION                                 �
;�                                                                            �
;�   I M P O R T A N T   S Y S T E M   C O N F I G U R A T I O N   N O T E:   �
;�                                                                            �
;�  MCX-16 Requires locations $10000 through $1002F for internal operations.  �
;�  Begin the allocation of MCX-16 System Tables at an address equal to or    �
;�  greater than $10030.                                                      �
;����������������������������������������������������������������������������;
    ldk     #.__pdata       ; select memory bank of _data
    tbxk
    tbyk
    ldk     #.__data__
    tbzk
    ldx     #__pdata        ; start of data descriptor
    ldy     0,x             ; start of data images
    aix     #2              ; next word
ibcl:
    ldab    0,x             ; flag
    beq     zbss            ; nul, next step
    bpl     idad            ; if segment
    aix     #2              ; move to it
    ldab    0,x             ; load it
    tbzk                    ; in data pointer extension
idad:
    ldz     1,x             ; data address
ircl:
    ldd     0,y             ; transfert by word
    std     0,z             ; size must be even
    aiy     #2              ; next word
    aiz     #2
    cpy     3,x             ; end of block ?
    blo     ircl            ; no, loop
    aix     #5              ; descriptor size
    bra     ibcl            ; next block
zbss:
    ldk     #.__bss__
    tbxk
    tbek
    tbyk
    tbzk
    tbsk
    ldx     #sbss       ; start of bss
    clrd                ; to be zeroed
    bra     mtest       ; start loop
bcl:
    std     0,x         ; clear memory
    aix     #2          ; next word
mtest:
    cpx     #__memory   ; end of memory ?
    blo     bcl         ; no, continue
;   aix     #4000H      ; you can set-up a 4K stack
;   txs                 ; above the BSS
    lds     #3FEh       ; or directly initialize ptr
    jsr     _main,#._main
                        ; call main routine of application
_exit:
    bra     _exit       ; loop here if return
;
    .end

MCXEVB.S

;   C STARTUP FOR 68HC16 UNDER MCX-16 REAL-TIME KERNEL
;   ==================================================
;   Copyright (c) 1995
;   Designed and programmed by Muhammad Lutfi
;   for Final Project (TA)
;   Thesis Advisors:
;     Dr. Ir. Farida Idealistina Muchtadi
;        and Ir. Sutanto Hadisupadmo, M.T.
;
;   Instrumentation and Controls Lab.
;   Engineering Physics Dept.
;   Institut Teknologi Bandung
;   Jl. Ganesha 10
;   Bandung 40132
;   Phone: (022) 2504424 ext 759
;   FACS:  (022)2504424
;
;
;
;   Platform : Microcontroller 68HC16Z1 on Evaluation Board (EVB)
;
;   Summary:
;   > Other initialization, except for QSM and ADC module, not necessarily
;     done
;   > Take care with heap an pre-initialized RAM initialization
;
    .include "lgrset.mac"

    .external _main, __memory,__pdata
    .external ._main, .__pdata
    .external .__text__, .__data__, .__bss__
    .public    _exit, __stext

.DEFINE STACK_SIZE = 1000H

    .psect _bss         ; stack section
sbss:

    .psect _text        ; program section

__stext:

;*********** MCU INIT ******************
; These procedures handled by MCX-16
; Rewritten for clarity only
; Still used in HARRAT version.
;***************************************
;
; ROM Start address: 0x00000 (program starts from 0x400 instead)
;
;                           BITS
; +--------------+--------------------------------+
; !              ! 2222 1111 1111 11              !
; ! ADDR PINS    ! 3210 9876 5432 1098 7654 3210  !
; +--------------+--------------------------------+----------+
; ! ADDR[23..0]  ! 0000 0000 0000 01?? ???? ????B != 0x00400 !
; ! ADDR[23..11] ! 0000 0000 0000 0xxx xxxx xxxxB != 0x00000 !
; +--------------+--------------------------------+----------+
;
; BLKSZ = 64 KB => address lines compared: ADDR[23..16]
;
; Frequency:
;      FQ_SYSTEM = FQ_REF*(4^(y+1)*(2^((2*W) + x)))
;      FQ_VCO    = F_SYSTEM^(2-X)
;
.DEFINE BLKSZ = 011B
.DEFINE ADDR  = 0000h
.SET CSBARBT_CFG = ((BLKSZ) | (ADDR << 3))
.DEFINE FQ_REF = 16780000   ; MHz
.DEFINE SW = 00B
.DEFINE SX = 01B
.DEFINE SY = 0111111B
.DEFINE
    SEDIV = (0<<7),
    SLIMP = (1<<4),
    SLOCK = (1<<3),
    RSTEN = (1<<2),
    STSIM = (1<<1),
    STEXT = 1

.SET SYNCR_CFG = ((SW<<7)|(SX<<6)|SY)

    ldab    #0Fh
    tbek                    ; point EK to bank F for register access
    ldab    #00H
    tbxk                    ; point XK to bank 0
    tbyk                    ; point YK to bank 0
    tbzk                    ; point ZK to bank 0
    ldd     #CSBARBT_CFG    ; at reset, the csboot block size is 512k, so
    std     CSBARBT         ; this line sets the block size to 64k since
                            ; that is what physically comes with the EVB16
                            ; Boot ROM starts from 0x400 to 0xFFFF
    ldab    #SYNCR_CFG
    stab    SYNCR           ; set system clock to 16.78 mhz

NOT_L:
    brclr   SYNCR+1,#SLOCK,NOT_L   ;wait until synthesizer lock bit is set

;
; SYPCR:
; �����������������������������������������������������������Ŀ
; � SWE = 0� SWP = 0� SWT = 11 � HME = 1 � BME = 0 � BMT = 00 �
; �������������������������������������������������������������
; SWE=0  : Watchdog disabled
; SWP=0  : Software watchdog clock not prescaled
; SWT[1:0]=11 : software watchdog timing
; HME=1  : enable halt monitor function
; BME=0  : disable bus monitor function for an internal to external bus cycle
; BMT=00 : 64 system clocks for bus monitor timing
;
.DEFINE
    SWE = 0,
    SWP = 0,
    SWT = 011B,
    HME=1,
    BME=0,
    BMT=0
.DEFINE SET_SYPCR = (BMT|(BME<<2)|(HME<<3)|(SWT<<4)|(SWP<<6)|(SWE<<7))

    ldab    #SET_SYPCR      ;#38H
    stab    SYPCR           ; turn cop (software watchdog) off,
                            ; since cop is on after reset

.IF TOROM
    ldd     CSORBT
    andd    #0E7FFh         ; R/W* = 00B, means that
    ord     #(01B<<11)      ; ROM is read only
    std     CSORBT
.ENDIF


;************* Stack Allocation *************
.IF USE_EXT_RAM
    ldk     #2
    tbsk                ; set SK to bank 2 for system stack
    lds     #3FEh        ; put SP at top of 1k internal SRAM (0x203FE)
.ELSE
    ldk     #1
    tbsk                ; set SK to bank 1 for system stack
    lds     #3FEh       ; directly initialize ptr to use 0x103FE (SRAM)
.ENDIF                  ; and below as system stack


;�����������������������������������������������������������������������������Ŀ
;�                          ADC INITIALIZATION                                 �
;�   Summary:                                                                  �
;�   The ADC module is mapped into 32 words of address space. Five words are   �
;�   control/status registers, one word is digital port data, and 24 words     �
;�   provide access to the results of ADC conversion (eight addresses for each �
;�   type of converted data). Two words are reserved for expansion.            �
;�   The ADC module base address is determined by the value of the MODMAP bit  �
;�   int the system integration module configuration register (SIMMCR).        �
;�   The base address is normaly $FFF700 in the MC68HC16Z1.                    �
;�       Internally, the ADC has both a differential data bus and a buffered   �
;�   IMB data bus. Registers not directly associated with AD conversion        �
;�   functions, such as the MCR, the MTR, and the PDR, reside on the bufferd   �
;�   bus, while conversion registers and result registers reside on the        �
;�   differential bus.                                                         �
;�                                                                             �
;�   Registers that must be set prior operation:                               �
;�     ADMCR:                                                                  �
;�       STOP = 0 (normal operation)                                           �
;�       FRZ  = 0                                                              �
;�       SUPV = 1 (supervisory mode)                                           �
;�     ADCTL0:                                                                 �
;�       PRS   = 00011B (ADC clock = system clock/8 = 2.1 MHz (Max ADC freq)   �
;�       STS   = 00 (4 A/D clock periods in the sample time)                   �
;�       RES10 = 01 (10-bit conversion)                                        �
;�     ADCTL1:                                                                 �
;�       SCAN  = 1 (continuous conversion)                                     �
;�       MULT  = 1 (sequential conversion of four or eight channels            �
;�                  selected by [CD:CA])                                       �
;�       S8CM  = 1 (eight-conversion sequence)                                 �
;�       CDCA  = 0xxx (measured data at each channel stored into his register) �
;�                                                                             �
;�������������������������������������������������������������������������������
.DEFINE MY_PRS   = 11B,
        MY_STS   = 00B,
        MY_RES10 = 1
.DEFINE MY_CDCA  = 1000B,
        MY_S8CM  = 1,
        MY_MULT  = 1,
        MY_SCAN  = 1

    ldab    #0Fh
    tbek                ; EK = F (K=$Fxxx)
    ADCMCR_SET 0, 0, 0
    ADCTL0_SET MY_PRS, MY_STS, MY_RES10
    ADCTL1_SET MY_CDCA, MY_S8CM, MY_MULT, MY_SCAN


;�����������������������������������������������������������������������������Ŀ
;�                                                                             �
;�                     SCI DRIVER INITIALIZATION                               �
;�                                                                             �
;� 1. Sets up the SCI and starts an infinite loop of receive transmit          �
;� 2. QSM configuration summary:                                               �
;�  * After reset, the QSM remains in an idle state, requiring initialization  �
;�    of several registers before any serial operations may begin execution.   �
;�  * The type of serial frame (8 or 9 bit) and the use of partiy must be      �
;�    determined by M. PE and PT.                                              �
;�  * For receive operation, WAKE, RWU, ILT, ILIE must be considered.          �
;�    The receiver must be enabled (RE) and, usually, RIE should be set.       �
;�  * For transmit operation, the transmitter must be enabled (TE) and,        �
;�    usually, TIE should be set. The use of wired-OR mode (WOMS) must also    �
;�    be decided. Once the transmitter is configured, data is not sent         �
;�    until TDRE and TC are cleared. To clear TDRE and TC, the SCSR read       �
;�    must be followed by a write to SCDR (either the lower byte or the        �
;�    entire word).                                                            �
;�  * QIVR should be programmed to one of the user-defined vectors ($40-$FF)   �
;�    during initialization of the QSM.                                        �
;�    After reset, QIVR determines which two vectors in the exception vector   �
;�    table are to be used for QSM interrupts. The QSPI and SCI submodules     �
;�    have separate interrupt vectors adjacent to each other.                  �
;�    Both submodules use the same interrupt vector which LSB:                 �
;�       1: interrupt generated by QSPI                                        �
;�       0: interrupt generated by QSCI                                        �
;�> Detail Configurations in QSM:                                              �
;�  * QMCR:                                                                    �
;�       STOP = 0 (Normal QSM clock operation)                                 �
;�       FRZ1 = 1 (Halt the QSM on a transfer boundary)                        �
;�       FRZ0 = 0                                                              �
;�       SUPV = 1 (supervisor access)                                          �
;�       IARB = $A (priority = A; $F = highest priority, used by timer)        �
;�  * QILR:                                                                    �
;�       ILQSPI = 0 (disabled)                                                 �
;�       ILSCI  = 7 (highest priority)                                         �
;�       QIVR   = set to SCI interrupt handler's address                       �
;�                                                                             �
;�������������������������������������������������������������������������������
    disable             ; Turn off interrupts while enabling SCI

    ldd    #(0080h+QSMIARB)
    std    QMCR         ; Set IARB=10 for intermodule bus arbitration

    ldd    #MY_QILR     ; our QILR configuration
    std    QILR         ;

    ldd    #BR9600      ; Set up 9600 baud rate
    std    SCCR0
    ldd    #RIE+RE+TE   ; Receiver enabled with interrupts active,
                        ; Transmitter enabled without interrupts,
                        ; 1 Start Bit, 1 Stop Bit, 8 Data Bits
    std    SCCR1        ; Set up SCI operating conditions

rdclr:
    ldd    SCSR         ; Get current status of SCI
    bitb   #RDRF        ; Read  receive data ready (RDR) until RDR reset
    beq    scirdy       ; ZF=1 (RDRF=0), so no RDR is empty
    ldab   SCDR         ; Read input data (a mechanism to reset RDRF)
    bra    rdclr        ; Loop until clear

scirdy:
    enable              ; Turn interrupts back on



;*************** BEGIN **************
    ldk     #.__bss__   ; load extended address of stack
    tbek
    tbxk
    tbyk
    tbzk
    ldx     #sbss       ; start of bss
    clrd                ; to be zeroed
    bra     mtest       ; start loop
bcl:
    std     0,x         ; clear memory
    aix     #2          ; next word
mtest:
    cpx     #__memory   ; end of memory ?
    blo     bcl         ; no, continue
    jsr     _main       ; call application
_exit:
    bgnd                ; loop here if return
1$:
    bra    1$
;
.end

MCXCALLS.S

;*****************************************************************************
;                      INTERFACE WhiteSmith to MCX-16
;                      ------------------------------
;    Platform : Motorola 68HC16 running MCX16 Multitasking Executive
;                        Compiler : Whitesmith C
;
;                    (c) M. Lutfi Shahab (13389011)
;                   Instrumentation and Control Labs.
;                   Department of Engineering Physics
;                   Institut Teknologi Bandung (ITB)
;
;                         Created : 13 Apr 1995
;                          Updated : 5 May 1995
;
;Interface Spec.
;---------------
;  In WSC:
;    - The default memory model is the COMPACT model, in which all of
;      the code and data must share the same 64K area.
;    - Type SHORT INT are stored as two bytes, MSB first
;    - Type LONG INTEGER are stored as four bytes, in descending order of
;      significance.
;    - Type FLOAT are represented in specific format adapted to the M68HC16
;      processor, is a 4 bytes of data; the first two bytes contain a signed
;      mantissa coding real values in the interval [-1.0,1.0]. The other 2
;      bytes contain signed exponent. If the first word is zero, the entire
;      number will be understood 0.0. The value of the number is the fraction
;      multiplied by 2 raised to the exponent. The mantissa is then compatible
;      with the internal DSP processor format.
;    - Type DOUBLE are represented as for the proposed IEEE-754 floating point
;      standard; 8 bytes stored in descending order of byte significance:
;        * MSB bit is one of four negative numbers, and zero otherwise.
;        * next 8 bits are the characteristic, biased such that the binary
;          exponent of the number is the characteristic minus 1002.
;        * the remaining bits are the fraction, starting with the weighted bit.
;    - Arguments are moved onto the stack from right to left. The first
;      argument is stored in the D register if its size is less than or equal
;      to the size of an int, or in the register pair E, D if it is a long
;      or float, and in the function doesn't return a struct or a double.
;    - By default, character data is sign extended to short, and floats are
;      extended to doubles.
;    - The function is called via jsr _func or jbsr _func.
;    - The arguments to the function are popped off the stack.
;    - A data space address is move onto stack if a struct or double return
;      area is required.
;    - The return value is in D register (if length less than 2 bytes), or
;      is in the registers E,D (the D register holds the low order bits).
;      The addresses of double and struct data are added on stack at call time.
;    - Each C function maintains its own stack frame, using IX as frame pointer.
;    - You must save an restore the K register if want to call an assembly
;      language routine that modifies the EK, XK, YK, or ZK registers.
;    - BSR does these microcode sequences:
;         1. put PC to stack
;         2. SP = SP-2
;         3. put CCR to stack
;         4. SP = SP-2
;       so SP (now) = SP (before bsr) + 4
;
;    - XK, YK, ZK and SK can be modified by using the transfer index register
;      to stack pointer and transfer stack pointer to index register instructions.
;      When SP is transfered to (TSX, TSY, and TSZ) or from (TXS, TSY, TSZ) an
;      index register, the corresponding address extension fields is also
;      transfered. Before the extension field is transfered, it is incremented
;      or decremented if bank overflow occured as a result of the instruction.
;
;   NOTE
;    > Be aware of invoking these routines. Make sure you have
;      set extension register (K) to a proper value, otherwise the system
;      will crash.
;*****************************************************************************/
.PROCESSOR M68HC16
.TITLE "Thesis Project : WSC -> MCX calling translation"
.INCLUDE "mcx16.mac"

    .psect    _text
    .even

.LIST + .MACRO

;* below are calling codes to MCX-16 *
;-----------------------------------
; __mcx_nop
;
;   cycles=14
;   code = 4 bytes
;----------------------------------
.PUBLIC __mcx_nop
__mcx_nop:
    MCX_CALL    MCX_NOP_
    rts

;------------------------------------------------------
;* Force a semaphore to PENDing state*
; Narrative:
;   WSC:
;   void _mcx_pend(int sema)
;     sema passed to D (ACCB = lo(sema), ACCA = hi(sema))
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_pend = 3
;     ACCB = semaphore number
;   return:
;     none
;
;   cycles = 14
;   code = 6 bytes
;------------------------------------------------------
.even
.PUBLIC __mcx_pend
__mcx_pend:
    MCX_CALL MCX_PEND_
    rts


;--------------------------------------------------
; * Signal the occurence of an event.
; Narrative:
;   WSC:
;   void _mcx_signal(int sema)
;   ACCD = sema
;
;   MCX:
;   parameters:
;     ACCA = code for mcx_signal = 1
;     ACCB = semaphore number
;   return:
;     none
;
;   cycles = 14
;   code = 6 bytes
;--------------------------------------------------
.even
.PUBLIC __mcx_signal
__mcx_signal:
    MCX_CALL MCX_SIGNAL_            ;* Signal semaphore  *
    rts


;------------------------------------------------------
; * Make a task wait for the occurence of a specified
;   event
; Narrative:
;   WSC:
;   int _mcx_wait(int sema)
;   on call, sema in D register
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_wait = 2
;     ACCB = semaphore number
;   return:
;     ACCA, 0 = success, 1 = fail
;
;   cycles = 16
;   code = 8 bytes
;------------------------------------------------------
.even
.PUBLIC __mcx_wait
__mcx_wait:
    MCX_CALL MCX_WAIT_           ;* Wait on event *
    clrb
    rts


;------------------------------------------------------
;* Signal completion of message processing*
; Narrative:
;   WSC:
;   void _mcx_msg_done(void *msg)
;     msg passed to D
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_msg_done = 18
;     IX = message address
;   return:
;     none
;
;   cycles = 28
;   code = 12 bytes
;------------------------------------------------------
.even
.PUBLIC __mcx_msg_done
__mcx_msg_done:
    pshm    x               ; save stack frame
    xgdx                    ; IX = msg
    MCX_CALL MCX_MSG_DONE_
    pulm    x               ; restore old IX (stack frame)
    rts


;------------------------------------------------------
;* Fetch message from a mailbox
; Narrative:
;   WSC:
;   void *_mcx_receive(int mbx)
;     mbx passed to D
;   return:
;     D = address of the received message
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_receive = 16
;     ACCB = mailbox number
;   return:
;     IX = address of received message
;
;   cycles = 28
;   code = 12 bytes
;------------------------------------------------------
.even
.PUBLIC __mcx_receive
__mcx_receive:
    pshm    x           ; save stack frame
    MCX_CALL MCX_RECEIVE_
    xgdx                ; D contain address of msg
    pulm    x           ; restore stack frame
    rts

;------------------------------------------------------
;* Fetch message from a mailbox with wait directive
;
; Narrative:
;   WSC:
;   void *_mcx_receive_w(int mbx)
;     mbx passed to D
;   return:
;     ACCD = address of the received message
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_receive_w = 17
;     ACCB = mailbox number
;   return:
;     IX = address of the received message
;
;   cycles = 28
;   code = 12 bytes
;------------------------------------------------------
.even
.PUBLIC __mcx_receive_w
__mcx_receive_w:
    pshm    x           ; save stack frame
    MCX_CALL MCX_RECEIVE_W_
    xgdx                ; D = address of received msg
    pulm    x           ; restore stack frame
    rts

;-------------------------------------------------------
;* send message MSG into target MAILBOX
;   with SEMA semaphore
; Narrative:
;   WSC:
;   void _mcx_send_mbx(int mbx, void *msg, int sema)
;     mbx in D
;     msg in [SP+6]
;     sema in [SP+8]
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_send_mbx = 14
;     ACCB = message semaphore number (sema)
;     ACCE = mailbox number to receive message (mbx)
;     IX   = message address
;   return:
;     none
;
;   cycles = 14
;   code = 18 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_send_mbx
__mcx_send_mbx:
    pshm    x            ; save old stack frame because IX used by MCX
    tsz                  ; Z = SP + 2
    xgde                 ; E = mbx
    ldd     8,z          ; D = sema
    ldx     6,z          ; IX = msg
    mcx_call MCX_SENDMBX_
                         ; accb = sema, acca = 14
    pulm    x
    rts

;-------------------------------------------------------
;* send message MSG into target MAILBOX
;   with SEMA semaphore and wait directive
; Narrative:
;   WSC:
;   void _mcx_send_mbx_w(int mbx, void *msg, int sema)
;     mbx in D
;     msg in [SP+6]
;     sema in [SP+8]
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_send_mbx_w = 15
;     ACCB = message semaphore number
;     ACCE = mailbox number to receive message
;     IX   = message address
;   return:
;     none
;
;   cycles =
;   code = 18 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_send_mbx_w
__mcx_send_mbx_w:
    pshm    x           ; save old stack frame because IX used by MCX
    tsz                 ; Z = SP + 2
    xgde                ; E = mbx
    ldd    8,z          ; D = sema
    ldx    6,z          ; IX = msg
    MCX_CALL MCX_SENDMBX_W_
                        ; accb = sema, acca = 15
    pulm    x
    rts

;-------------------------------------------------------
;* Get the oldest entry from a FIFO queue
; Narrative:
;   int _mcx_dequeue(int queue, void *ptr)
;     queue in D
;     ptr in [SP+6]
;   return: ACCD
;
;   parameters to mcx:
;     ACCA = code for mcx_dequeue = 12
;     ACCB = queue number
;     IX   = destination address of entry
;   return:
;     ACCA = 0, if queue was empty
;            1, if entry dequeued successfully other
;
;   cycles =
;   code = 16 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_dequeue
__mcx_dequeue:
    pshm    x
    tsz             ;
    ldx     6,z     ; IX = ptr
                    ; ACCD hold queue number, so we just set ACCA
    MCX_CALL MCX_DEQUEUE_
    pulm    x
    clrb
    rts

;-------------------------------------------------------
;* Get the oldest entry from a FIFO queue. If queue
;  empty, wait until queue not empty
; Narrative:
;   int _mcx_dequeue_w(int queue, void *ptr)
;     queue in ACCD
;     ptr in [SP+6]
;
;   parameters to mcx:
;     ACCA = code for mcx_dequeue_w = 13
;     ACCB = queue number
;     IX   = destination address of entry
;   return:
;     ACCA = 0, if queue was empty
;          = 1, if dequeue was successful
;
;   cyles =
;   code = 16 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_dequeue_w
__mcx_dequeue_w:
    pshm    x
    tsz
    ldx     6,z     ; IX = ptr
                    ; ACCD hold queue number, so we just set ACCA
    MCX_CALL MCX_DEQUEUE_W_
    pulm    x
    clrb            ; ACCD = return value of mcx_dequeue_w
    rts

;-------------------------------------------------------
;* Put an entry to a FIFO queue.
;
; Narrative:
;   int _mcx_enqueue(int queue, void *ptr)
;     queue in D
;     ptr in [SP+6]
;     return: ACCD
;
;   parameters to mcx:
;     ACCA = code for mcx_dequeue_w = 10
;     ACCB = queue number
;     IX   = destination address of entry
;   return:
;     ACCA = 0, if queue was empty
;          = 1, if dequeue was successful
;
;   cycles =
;   code = 16 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_enqueue
__mcx_enqueue:
    pshm    x
    tsz             ; Z = SP + 2
    ldx     6,z     ; IX = ptr
                    ; ACCD hold queue number, so we just set ACCA
    MCX_CALL MCX_ENQUEUE_
    pulm    x
    clrb
    rts

;-------------------------------------------------------
;* Put an entry to a FIFO queue and wait if empty.
; Narrative:
;   int _mcx_enqueue_w(int queue, void *ptr)
;     queue in ACCD
;     ptr in [SP+6]
;   return: ACCD
;
;   parameters to mcx:
;     ACCA = code for mcx_dequeue_w = 11
;     ACCB = queue number
;     IX   = source address of entry
;   return:
;     ACCA = 0, if queue successful
;          = 1, if empty
;
;   cycles =
;   code = 16 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_enqueue_w
__mcx_enqueue_w:
    pshm    x
    tsz             ; Z = SP + 2
    ldx     6,z     ; IX = ptr
                    ; ACCD hold queue number, so we just set ACCA
    MCX_CALL MCX_ENQUEUE_W_
    pulm    x
    clrb
    rts

;-------------------------------------------------------
;* Change the priority of a task *
; Narrative:
;   void _mcx_change_pri(int task, priority)
;    ACCD = task number
;    [SP+6] = priority
;
;   parameters:
;     ACCA = code for _mcx_execute = 9
;     ACCB = task number
;     ACCE = task priority
;
;   return:
;     none
;
;   cycles =
;   code = 12 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_change_pri
__mcx_change_pri:
    tsz             ; Z = SP + 2
    lde     6,z     ; E = priority
                    ; ACCD hold task address, so we just set ACCA
    MCX_CALL MCX_CHANGE_PRI_
    rts


;-------------------------------------------------------
;* Excecute a task *
; Narrative:
;   void _mcx_execute(int tsk_num, priority, (void *)(task)(),
;         void *stack_ptr, void *reg_init_ptr)
;   tsk_num = ACCD
;   reg_init_ptr = [SP +12]
;   stack_ptr    = [SP +10]
;   task address = [SP + 8]
;   priority     = [SP + 6]
;
;   parameters:
;     ACCA = code for _mcx_execute = 4
;     ACCB = task number
;     ACCE = task priority
;     IX   = starting address of task
;     IY   = base address of task's stack
;     IZ   = address of register initialization packet
;             (IZ=0 means no packet)
;   return:
;     none
;
;   cycles =
;   code = 22 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_execute
__mcx_execute:
    pshm    x
    tsz                 ; Z = SP + 2
                        ; ACCD = task number
    lde     6,z         ; ACCE = task priority
    ldx     8,z         ; IX = task
    ldy    10,z         ; IY = stack
    ldz    12,z         ; IZ = reg_init_pkt
    MCX_CALL MCX_EXECUTE_
                        ;* Execute a task *
    pulm    x
    rts


;-------------------------------------------------------
;* Clears the suspend state of task
;
; Narrative:
;   WSC:
;   void _mcx_resume(int task_num)
;   ACCD = task_num
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_resume = 7
;     ACCB = task number
;
;   return:
;     none
;
;   cycles =
;   code = 6 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_resume
__mcx_resume:
                        ; ACCB = task number
    MCX_CALL    MCX_RESUME_
    rts



;-------------------------------------------------------
;* Blocks the specified task with a SUSPEND condition
; Narrative:
;   WSC:
;   void _mcx_suspend(int task_num)
;   ACCD = task_num
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_suspend = 6
;     ACCB = task number (0= SELF)
;   return:
;     none
;
;   cycles =
;   code = 6 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_suspend
__mcx_suspend:
                        ; ACCB = task number
    MCX_CALL    MCX_SUSPEND_
    rts



;-------------------------------------------------------
;* Terminate a task's operation
;
; Narrative:
;   WSC:
;   void _mcx_terminate(int task_num)
;   ACCD = task_num
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_resume = 5
;     ACCB = task number
;
;   return:
;     none
;
;   cycles =
;   code = 6 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_terminate
__mcx_terminate:
                        ; ACCB = task number
    MCX_CALL    MCX_TERMINATE_
    rts


;-------------------------------------------------------
;* Blocks specified task with a DELAYED state for the
;  period
; Narrative:
;   WSC:
;   void _mcx_delay(int task_num, int tick)
;   ACCD = task_num
;   [SP+6] = tick
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_delay = 8
;     ACCB = task number (0= SELF)
;     ACCE = number of clock ticks to delay
;   return:
;     none
;
;   cycles =
;   code = 16 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_delay
__mcx_delay:
                        ; ACCB = task number
    tsz
    lde     6,z         ; ACCE = tick
    MCX_CALL MCX_DELAY_
    rts


;-------------------------------------------------------
;* Stop a timer whose handle is specified by ptr
; Narrative:
;   WSC:
;   void _mcx_kill_timer(void *tick_handler)
;   ACCD = tick_handler
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_kill_timer = 20
;     ACCE = Handle of timer to be killed
;   return:
;     none
;
;   cycles =
;   code = 10 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_kill_timer
__mcx_kill_timer:
    tsz
    xgde                ; ACCE = tick handler
    MCX_CALL MCX_KILL_TIMER_
    rts


;-------------------------------------------------------
;* Stop a active timer and reset its duration to a new
;   value
; Narrative:
;   WSC:
;   void _mcx_reset_t(void *hndr, int tick)
;   ACCD = hndlr
;   [SP+6] = tick
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_delay = 21
;     ACCE = Handle of timer to be reset
;     IX   = duration of timer's initial period
;   return:
;     none
;
;   cycles =
;   code = 16 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_reset_t
__mcx_reset_t:
                        ; ACCB = task number
    pshm    x
    tsz
    xgde                ; ACCE = tick handler
    ldx     6,z         ; tick
    MCX_CALL MCX_RESET_T_
    pulm    x
    rts


;-------------------------------------------------------
;* Stop a active timer and reset its duration to a new
;   value
; Narrative:
;   WSC:
;   void *_mcx_timer(int init_t, int recyle_t, int sema)
;       ACCD = init_t
;       [SP+6] = recyle_t
;       [SP+8] = sema
;   return: ACCD
;
;   MCX:
;   parameters:
;     ACCA = code for _mcx_timer = 19
;     ACCB = semaphore number
;     ACCE = Duration of initial period
;     IX   = duration of recycle time
;   return:
;     ADDE = handle of timer if it was established
;          = 0, if there were no timer blocks available
;            in the pool of free timers.
;
;   cycles =
;   code = 20 bytes
;-------------------------------------------------------
.even
.PUBLIC __mcx_timer
__mcx_timer:
    pshm    x
    tsz             ; z = SP
    xgde            ; ACCE = init_t
    ldd     8,z     ; ACCD = sema = [SP+8]
    ldx     6,z     ; IX = recycle_t = [SP+6]
    MCX_CALL MCX_TIMER_
    pulm    x
    ted             ; ACCD = handle of timer
    rts

.END