home *** CD-ROM | disk | FTP | other *** search
- * * Clockdj *
-
- nolist
-
- mvc macro
- lea \1,a0 source
- lea \2,a1 destination
- moveq #\3-1,d0 count
- move\@ move.b (a0)+,(a1)+ move byte
- dbra d0,move\@
- endm
-
- clc macro
- lea \1,a0 source
- lea \2,a1 destination
- moveq #\3-1,d0 count
- comp\@ cmpm.b (a0)+,(a1)+ move byte
- dbne d0,comp\@
- endm
-
-
-
-
- ********* assembler offset files needed for this to work
- include "exec/types.i"
- include "exec/nodes.i"
- include "exec/lists.i"
- INCLUDE "exec/interrupts.i"
- INCLUDE "devices/input.i"
- INCLUDE "hardware/intbits.i"
- INCLUDE "devices/inputevent.i"
- include "offsets/rom.ofs"
- include "exec/io.i"
- include "graphics/view.i"
- include "graphics/sprite.i"
- include "graphics/copper.i"
- include "graphics/gfxbase.i"
-
- include "intuition/preferences.i"
- include "intuition/screens.i"
- include "exec/memory.i"
- include "intuition/intuition.i"
- include "libraries/dos.i"
- list
- * llen 80
-
-
- bra clockdjstart
-
- dc.b 'Clockdj V3.01'
- dc.b '29 Nov 88'
- cnop 0,2
- clockdjstart
-
- cmpi.b #10,(a0) any data
- beq noparm no
- move.b (a0),revswitch set reverse button switch
- moveq #80,d0 maximum initial length
- lea itext0,a1 Text for menu
- lea newcli,a2 command area
- lea 2(a0),a0 next field
- moveq #0,d2
- moveq #0,d3
- newinit cmpi.b #10,(a0) end
- beq noparm
- newinit2
- cmpi.b #10,(a0) end
- beq clrend
- tst.l d2
- bne.s 3$
- cmpi.b #8,d3 end?
- beq.s 2$
- cmpi.b #' ',(a0) end of initial command?
- bne.s 1$
- 2$ not.l d2 set switch
- bra 3$
- 1$ move.b (a0),(a1)+
- 3$ move.b (a0)+,(a2)+
- addq.b #1,d3
- dbra d0,newinit2
- clrend
- clr.b (a2) end of newcli
-
- noparm
- lea layersname,a1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- TST.L D0 ok?
- bne layok yes
- rts
- layok MOVE.L D0,layers save
-
-
- lea dosname,A1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- TST.L D0 ok?
- bne 4$ yes
- bra layerbye
-
- 4$ MOVE.L D0,a6 save
- move.l d0,doslib
- *
- * Read in key definitions
- *
- bsr readkeys
- lea savefile,a0 name of save string
- move.l a0,d1 move into right reg
- move.l #MODE_OLDFILE,d2 old file
- jsr Open(a6) Open
- tst.l d0 file there?
- beq.s closedos no use defaults
-
- move.l d0,d1 file handle
- move.l #diskbufferl,d4 length expected
- lea diskbuffer,a4
- readin
- move.l a4,d2 data
- move.l #1,d3 data length
- move.l d1,-(a7) save handle
- jsr Read(a6) read it in
- move.l (a7)+,d1 restore file handle
- tst.l d0 test result
- beq closein eof
- bmi closein error
- adda #1,a4 next
- dbra d4,readin
- closein
- jsr Close(a6) close file
- closedos
- MOVE.L a6,a1 dos Library
- movea.l 4,a6 Exec base
- jsr CloseLibrary(A6) call CloseLibrary
- nofile
- lea window,a0 new window structure
- move.w windowleft,nw_LeftEdge(a0) restore
- move.w windowtop,nw_TopEdge(a0) window
-
- cmpi.b #memtot,memory total memory display?
- beq.s 2$ yes
-
- ******* set up window for chip/fast memory display *********
-
- lea itext1b,a1 new text
- move.w #312,nw_Width(a0) set new width
- lea sepmsg,a2 new message text
- bra.s 3$
-
- ******** set up window for total memory display
-
- 2$ lea itext1,a1 new text
- lea totmsg,a2 new message text
- 3$ move.l a1,memtext set up text
- lea Date_Text,a0 message structure
- move.l a2,it_IText(a0) set up message address
- move.w colours,Date_Text restore colours
-
- ****** set up priority check mark ********
-
- lea priindex,a0 index of fields
- moveq #0,d0
- move.b priority,d0 get priority
- ext.w d0 extend sign
- addq #3,d0 create
- lsl.l #2,d0 index
- movea.l 0(a0,d0),a1
- ori.w #CHECKED,0(a1) set check mark
-
-
- ****** set up refresh check mark ********
-
- cmpi.l #100000,refrate
- bne.s not10
- ori.w #CHECKED,ref1
- bra blankcheck
- not10 cmpi.l #200000,refrate
- bne.s not20
- ori.w #CHECKED,ref2
- bra blankcheck
- not20 cmpi.l #500000,refrate
- bne.s not50
- ori.w #CHECKED,ref3
- bra blankcheck
- not50 cmpi.l #999999,refrate
- bne.s not10
- ori.w #CHECKED,ref4
-
- ********* Set up blank check mark ********
-
- blankcheck
- cmpi.w #0,blanktime
- bne.s notb0
- ori.w #CHECKED,blach1
- bra pointcheck
- notb0 cmpi.w #5*60,blanktime
- bne.s notb5
- ori.w #CHECKED,blach2
- bra pointcheck
- notb5 cmpi.w #10*60,blanktime
- bne.s notb10
- ori.w #CHECKED,blach3
- bra pointcheck
- notb10 cmpi.w #20*60,blanktime
- bne.s notb20
- ori.w #CHECKED,blach4
- bra pointcheck
- notb20 cmpi.w #30*60,blanktime
- bne.s notb30
- ori.w #CHECKED,blach5
- bra pointcheck
- notb30 ori.w #CHECKED,blach6
-
- ********* Set up blank check mark ********
-
- pointcheck
-
- cmpi.w #0,pointtime
- bne.s notp0
- ori.w #CHECKED,poich1
- bra speedset
- notp0 cmpi.w #5,pointtime
- bne.s notp5
- ori.w #CHECKED,poich2
- bra speedset
- notp5 cmpi.w #10,pointtime
- bne.s notp10
- ori.w #CHECKED,poich3
- bra speedset
- notp10 cmpi.w #20,pointtime
- bne.s notp20
- ori.w #CHECKED,poich4
- bra speedset
- notp20 cmpi.w #30,pointtime
- bne.s notp30
- ori.w #CHECKED,poich5
- bra speedset
- notp30 ori.w #CHECKED,poich6
-
- **** set mouse speed check mark
-
- speedset
- moveq #0,d0
- move.b mousespeed,d0 get speed
- lsl.l #2,d0 *4
- lea mousecheck,a0 addreses
- movea.l 0(a0,d0),a1 get address
- ori.w #CHECKED,(a1) set check mark
-
- ****** set sun mouse check mark
-
- tst.b sunswitch sun mouse on?
- beq ftest no
- ori.w #CHECKED,suncheck set tick
-
- ****** set window to front check mark
-
- ftest tst.b wtfcount neg?
- bmi fset0x yes
- fcheckdo
- moveq #0,d0
- move.b wtfcount,d0 get speed
- lsl.l #2,d0 *4
- lea frontcheckr,a0 addreses
- movea.l 0(a0,d0),a1 get address
- ori.w #CHECKED,(a1) set check mark
- bra btest
- fset0x clr.b wtfcount
- bra fcheckdo
- ****** set window to back check mark
-
- btest tst.b backswitch sun mouse on?
- bmi bset0x no
- bcheckdo
- moveq #0,d0
- move.b wtbcount,d0 get speed
- lsl.l #2,d0 *4
- lea backcheckr,a0 addreses
- movea.l 0(a0,d0),a1 get address
- ori.w #CHECKED,(a1) set check mark
- bra ctest
- bset0x clr.b wtbcount
- bra bcheckdo
-
- ****** set screen cycle check mark
-
- ctest tst.b cycleswitch screen cycle on?
- beq ktest no
- ori.w #CHECKED,cyclecheck set tick
-
-
- ****** set key to front check mark
-
- ktest tst.b keyswitch key to front on?
- beq ptest no
- ori.w #CHECKED,keycheck set tick
-
- ****** set pop to front check mark
-
- ptest tst.b popswitch key to front on?
- beq matest no
- ori.w #CHECKED,wtfcheck set tick
-
- ****** set key map check mark
-
- matest tst.b mapswitch key to front on?
- beq setwh no
- ori.w #CHECKED,mapcheck set tick
-
- setwh
- ****** set window height
- move.b windowheight,newwindowheight+1
- ***** open intuition library and store its pointer *****
-
- iopen LEA IntuitionName(PC),A1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- TST.L D0
- BNE.S *+4
- RTS ; FAIL: couldn't open intuition library
- MOVE.L D0,intuit ; store intuition library pointer
-
-
- ********* open window
-
- lea window,a0
- movea.l intuit,A6
- JSR OpenWindow(A6) ; call OpenWindow
-
- TST.L D0
- BEQ.L FailOpenWindow
- movea.l d0,a0
- move.l wd_WLayer(a0),layer window layer
- movea.l wd_WScreen(a0),a1 screen pointer
- lea sc_LayerInfo(a1),a0 get Layer_info address
- move.l a0,layerinfo save
-
-
- ****** set up menu strip
-
- movea.l d0,a3 save window pointer
- move.l d0,windowpoint
- movea.l d0,a0
- lea menu0,a1 menu structure
- jsr SetMenuStrip(a6) set up menu
-
-
- WindowOpened:
-
- ****
- * Initialise the intput handler structure.
- ***
-
- move.b #NT_INTERRUPT,inthandler+LN_TYPE set the node type
- move.b #127,inthandler+LN_PRI I want to be first
- move.l #datarea,inthandler+IS_DATA handler can see data
- move.l #intcode,inthandler+IS_CODE point to code
-
- *****
- * get a signal bit for input handler
- ****
- movea.l 4,a6 using exec.library again
- moveq.l #-1,d0 any signal will do
- jsr AllocSignal(a6)
- moveq.l #0,d1 convert signum to a mask
- bset.l d0,d1
- move.l d1,insig save
- move.l d1,d7 stash sig bit
-
-
- ; get ClockWindow->UserPort->mp_SigBit into D0
- MOVEA.L wd_UserPort(A3),A0 A0 = ClockWindow->UserPort
- MOVEQ #0,D0
- MOVE.B MP_SIGBIT(A0),D0 D0 = the ClockWindow's mp_SigBit
- MOVEQ #1,D4
- LSL.L D0,D4 ; D4 = windowSigs
- or.l D4,D7 ; D7 = waitFlags
-
- ***** create timer port *****
-
- movea.l 4,A6 load exec library address
- ; get a signal bit
- MOVEQ #-1,D0
- JSR AllocSignal(A6) ; call AllocSignal
- MOVE.L D0,D3 ; D3 = sigBit
- BMI FailCreateTimer1
-
-
- * alloc sprite data
-
- moveq #11*4,D0 size of structure
- MOVE.L #MEMF_CLEAR+MEMF_CHIP,D1 memory type = CLEAR and CHIP
- JSR AllocMem(A6) ; call AllocMem
- MOVE.L D0,spriteblank
-
-
- ; alloc port structure
- moveq #MP_SIZE,D0 size of structure
- MOVE.L #MEMF_CLEAR+MEMF_PUBLIC,D1 memory type = CLEAR and PUBLIC
- JSR AllocMem(A6) ; call AllocMem
- MOVE.L D0,D5 ; D5 = timer Port
- BNE.S SkipFailCode
- ; AllocMem failed
- MOVE.L D3,D0
- JSR FreeSignal(A6) ; call FreeSignal
- BRA FailCreateTimer2
- SkipFailCode:
- ; fill port fields
- MOVEA.L D5,A2
- ADDQ.L #LN_TYPE,A2 ; A2 now points to the LN_TYPE field
- MOVE.W #NT_MSGPORT+LN_PRI,(A2)+ LN_TYPE = NT_MSGPORT, LN_PRI = 0
- LEA TimerPortName(PC),A0
- MOVE.L A0,(A2)+ ; LN_NAME = address of timer port name
- MOVE.W D3,(A2)+ ; MP_FLAGS = (#PA_SIGNAL=0), MP_SIGBIT = sigBit
- MOVEQ #0,D0
- MOVEA.L D0,A1
- JSR FindTask(A6) ; call FindTask ( 0 arg means this task)
- MOVE.L D0,(A2) ; MP_SIGTASK = pointer to found task
- move.l d0,task save task pointer
- move.l d0,a1 my task
- moveq #0,d0
- move.b #50,d0 Priority 2
- jsr SetTaskPri(a6) call SetTaskPri
-
-
- ** get input device port space
-
- movea.l 4,a6 exec base
- moveq #MP_SIZE,d0 size of structure
- move.l #MEMF_CLEAR+MEMF_PUBLIC,d1 memory type = CLEAR and PUBLIC
- jsr AllocMem(a6) call AllocMem
-
- move.l d0,inputport save input Port
- bne gotsp
- moveq #8,d0
- rts Big trouble. give up
-
-
- ** fill in port fields
-
- gotsp movea.l inputport,a1
- move.b #NT_MESSAGE,LN_TYPE(a1) LN_TYPE = NT_MESSAGE(5)
- move.l #inputportname,LN_NAME(a1) name
-
- * stick task in the msg port.
-
- move.l task,MP_SIGTASK(a1) task pointer
-
-
- BRA SkipFailSection
-
- ********** FAILURE SECTION ************
- ClosedWindow:
- * abort any standing timer request
- movea.l 4,a6 exec base
- MOVEA.L timer,A1 timer IORequest
- ABORTIO
- ; close timer device
- movea.l timer,A1 timer IORequest
- JSR CloseDevice(A6) ; call CloseDevice
-
- * Free timer request storage
-
- movea.l timer,A1 timer IORequest
- moveq #MP_SIZE,D0 size of structure
- jsr FreeMem(A6) call FreeMem
-
- FailOpenDevice:
- FailTimeRequestAlloc:
- ; close timer port
- MOVEA.L D5,A1
- JSR RemPort(A6) ; call RemPort
- MOVEA.L D5,A2
- MOVEQ #-1,D6
- MOVE.B D6,$A(A2)
- MOVE.L D6,(A2)
- MOVE.L (SP)+,D0 ; get the sigBit
- JSR FreeSignal(A6) ; call FreeSignal
- move.l insig,d0 input handler signal
- JSR FreeSignal(A6) ; call FreeSignal
- MOVEA.L D5,A1
- MOVEQ #$22,D0
- JSR FreeMem(A6) ; call FreeMem
-
- FailCreateTimer2:
- FailCreateTimer1:
- MOVEA.L A3,A0
- movea.l intuit,A6
- jsr ClearMenuStrip(a6) remove menu
- MOVEA.L A3,A0
- JSR CloseWindow(A6) ; call CloseWindow
-
- FailOpenWindow:
- movea.l intuit,A1 Intuition Library
- movea.l 4,a6 exec base
- JSR CloseLibrary(A6) call CloseLibrary
-
-
- ;============================================================================
- ; remove intput handler
- ;============================================================================
-
- movea.l 4,a6 using exec.library
- lea inputreq,a1
- move.l #inthandler,IO_DATA(a1)
- move.l #IS_SIZE,IO_LENGTH(a1) set length
- move.w #IND_REMHANDLER,IO_COMMAND(a1) remove handler
-
- move.l 4,a6
- jsr DoIO(a6)
-
- lea inputreq,A1 input IORequest
- JSR CloseDevice(A6) ; call CloseDevice
-
- movea.l inputport,a1 Remove the input Port
- jsr RemPort(a6)
-
- movea.l inputport,a1 input port
- moveq #MP_SIZE,D0 size of structure
- jsr FreeMem(A6) call FreeMem
-
- movea.l spriteblank,a1 input port
- moveq #11*4,D0 size of structure
- jsr FreeMem(A6) call FreeMem
-
- bsr freekeymem
-
- layerbye MOVE.L layers,a1 layers
- MOVEA.L 4,A6 ; load exec library address
- JSR CloseLibrary(A6) call CloseLibrary
- moveq #0,d0
- rts
-
- ********* FAILURE END **********
-
- SkipFailSection:
- ; add the ports
- MOVEA.L D5,A1
- movea.l 4,a6 Exec base
- JSR AddPort(A6) ; call AddPort
-
- move.l inputport,a1 Message Port
- jsr AddPort(a6) Add another Port to list
-
-
- ** Set up input IOReq structures
-
-
- lea inputreq,a1 IORequest
- move.b #NT_MESSAGE,LN_TYPE(a1) LN_TYPE = NT_MESSAGE(5)
- move.b #0,LN_PRI(a1) LN_PRI = 0
- move.l inputport,MN_REPLYPORT(a1) move in message port pointer
-
- ** open input device
-
-
-
- lea inputname,a0 device name
- moveq #0,d0 unit number
- lea inputreq,a1 IOReq
- moveq #0,d1 flags
- jsr OpenDevice(a6)
- lea inputreq,a1 IOReq
- cmpi.b #0,IO_ERROR(a1) ok?
- beq.s openok yes
- moveq #0,d0
- move.b IO_ERROR(a1),d0
- rts
-
- openok
- move.l #inthandler,IO_DATA(a1)
- move.l #IS_SIZE,IO_LENGTH(a1) set length
- move.w #IND_ADDHANDLER,IO_COMMAND(a1)
- ******
- * now that everything is initialised, add the input handler
- ******
- lea inputreq,a1
- move.l 4,a6
- jsr DoIO(a6)
-
-
- ***** use the timer port sigBit(D3) to set the timeOutSig(D6) *****
-
- MOVE.L D3,D0
- MOVE.L D3,-(SP) ; save the sigBit
- MOVEQ #1,D6
- LSL.L D0,D6
- OR.L D6,D7 ; update the waitFlags
-
- ***** initialize timeRequest structure *****
-
- MOVEQ #IOTV_SIZE,D0 D0 = IOTV_SIZE
- MOVE.L #MEMF_CLEAR+MEMF_PUBLIC,D1 memory type = clear it, and public
- JSR AllocMem(A6) ; call AllocMem
- TST.L D0
- BEQ FailTimeRequestAlloc
- MOVEA.L D0,A5 ; A5 = timeRequest
- move.l d0,timer save timer IORequest
- move.b #NT_MESSAGE,LN_TYPE(A5) LN_TYPE = NT_MESSAGE(5)
- move.b #0,LN_PRI(A5) LN_PRI = 0
- MOVE.L D5,MN_REPLYPORT(A5) MN_REPLYPORT = timerPort
- ; AllocMem set to zero the IO_FLAGS, IO_ERROR fields
-
- ***** open vblank timer device *****
-
- LEA TimerName(PC),A0 ; A0 = timer name
- MOVEA.L A5,A1 ; A1 = timeRequest
- MOVEQ #1,D0 ; D0 = UNIT_VBLANK(1)
- MOVEQ #0,D1
- JSR OpenDevice(A6) ; call OpenDevice
- TST.L D0
- BNE FailOpenDevice
- MOVE.W #TR_ADDREQUEST,IO_COMMAND(A5) IO_COMMAND = TR_ADDREQUEST(9)
-
- ***** initialize main loop *****
-
- LEA buffer(PC),A2 ; A2 = bufferPTR
- LEA InitMainLoop(PC),A4
- BRA InitializeTime
- InitMainLoop:
- LEA WhileMoreMessages(PC),A4
- MainLoop:
- MOVE.L D7,D0 ; D0 = waitFlags
- movea.l 4,a6 Exec base
- JSR Wait(A6) ; call Wait
- move.l d0,d3 save
- move.l insig,d1 sigbit for input device
- and.l d0,d1 input signal
- beq notinput not input device
-
- ** process input events
-
- processinput
- *** test for window re-size
-
- cmp.b #'>',action do increase?
- bne.s testless no
-
- move.l intuit,a6
- movea.l a3,a0
- moveq #0,d0
- move.w wd_TopEdge(a0),d0
- add.w wd_Height(a0),d0
- cmpi.w #199,d0 at maximum?
- bcc notinput d0>=199
- moveq #0,d0 Dx
- moveq #1,d1 Dy
- JSR SizeWindow(A6) alter size
- addq.b #1,windowheight
- bra notinput
-
- testless
- cmp.b #'<',action do increase?
- bne.s keymaptest no
-
- move.l intuit,a6
- movea.l a3,a0
- moveq #0,d0 Dx
- moveq #-1,d1 Dy
- JSR SizeWindow(A6) alter size
- cmpi.b #1,windowheight
- beq notinput
- subq.b #1,windowheight
- bra notinput
-
- *** test for keymap translate
- keymaptest
- cmp.b #'m',action do key map?
- bne exwindow no
- move.l mapbuffer,a0 key map buffer
- adda.l #9,a0
- 1$ cmpi.b #$fe,(a0)+ look for end of string
- bne 1$
- cmpi.b #'s',1(a0) is it a string?
- bne docommand no
- movem.l a2-a4/d7,-(sp)
- moveq #0,d7
- cmpi.b #$ff,2(a0) is there a delay?
- beq nodelay no
- move.b 2(a0),d7 get delay
- and.b #$0f,d7
- mulu.w #10000,d7 convert to microsecs
- nodelay
- move.l mapbuffer,a0 key map buffer
- adda.l #9,a0
- move.l a0,a2 keep
- move.l 4,a6
- nexteventgen
- cmpi.b #$fe,(a2) end of string?
- beq resstack yes - out
-
- * test for qualifiers and special keys
- move.w #$8000,d1 no qualifier
- cmpi.b #'%',(a2) is it qualifier?
- bne.s nosqual no
-
- nextqual1
- adda.l #1,a2 next one
- lea qualifiers,a3 get all qualifiers
- qualloop1
- cmpi.b #$fe,(a3) end yet?
- beq nosqual ****** error *********
- clc (a2),(a3),3 are these the same
- beq.s gotqual1 yes
- adda.l #6,a3 next qualifier
- bra.s qualloop1
- gotqual1
- or.w 4(a3),d1 get qualifier
- nextqual3
- adda.l #3,a2 next key qualifier
- cmpi.b #',',(a2) end of qualifiers?
- bne.s nosqual yes
- adda.l #1,a2 next one
- cmpi.b #'%',(a2) end of qualifiers?
- bne.s nosqual yes
- beq.s nextqual1
- nosqual
- lea event,a0
- move.w d1,ie_Qualifier(a0)
-
- cmpi.b #'&',(a2) special key?
- bne notspec
- lea tim,a0
- clc (a0),1(a2),3 is it time request?
- bne trydate
- cmpi.b #memtot,memory total memory?
- beq.s 1$ yes
- lea buffer2+1,a0 time
- bra.s 2$
- 1$ lea buffer+1,a0 time
- 2$ move.l #11,d0 set length
- bsr subchars
- add.l #4,a2 next field
- bra nexteventgen
-
- trydate
- lea dat,a0
- clc (a0),1(a2),3 is it date request?
- bne notdate
- bsr getdate get date
- lea datefield,a0 date field
- move.l #11,d0 set length
- bsr subchars
- add.l #4,a2 next field
- bra nexteventgen
-
- notdate
- lea funnykeys,a4 get special keys
- nextspec2
- cmpi.b #$fe,(a4) end?
- beq notspec yes *********** error *********
- clc 1(a2),(a4),3 equal?
- beq gotfunny2 yes
- adda.l #4,a4 next entry
- bra nextspec2
- gotfunny2
- move.b 3(a4),d0 move in funny key code
- adda.l #3,a2 point to last byte
- bra.s setbyte
- notspec
-
- move.b (a2),d0
-
- bsr rawtrans translate to raw keys
- setbyte
- lea event,a0
- lea inputreq,a1 IOReq
- move.b d0,ie_Code+1(a0)
- and.b #$80,d0 shifted?
- beq.s norcode no
- and.b #$7f,ie_Code+1(a0) turn off shift bit
- or.w #IEQUALIFIER_LSHIFT,ie_Qualifier(a0) set to shifted
- norcode move.b #IECLASS_RAWKEY,ie_Class(a0)
- move.l a0,IO_DATA(a1)
- move.l #ie_SIZEOF,IO_LENGTH(a1) set length
- move.w #IND_WRITEEVENT,IO_COMMAND(a1)
- jsr DoIO(a6)
- adda.l #1,a2 next byte
- tst.l d7 delay?
- beq nexteventgen no
-
- *******
- *** Delay submission of characters
-
- movem.l a0/a5/a1,-(sp)
- lea pause,a1 new ioreq
- move.l a5,a0 old ioreq
- moveq #IOTV_SIZE/4-1,d0
- 1$
- move.l (a0)+,(a1)+
- dbra d0,1$
- lea pause,a1
- MOVE.W #TR_ADDREQUEST,IO_COMMAND(A1) IO_COMMAND = TR_ADDREQUEST(9)
- MOVE.l #0,IO_SIZE+TV_SECS(A1) TV_SECS = $01(01 seconds) ||dj
- MOVE.L d7,IO_SIZE+TV_MICRO(A1) TV_MICRO= specified time
- movea.l 4,a6 set Exec base
- JSR DoIO(A6) wait
-
- movem.l (sp)+,a0/a5/a1
- bra nexteventgen
- resstack
- movem.l (sp)+,a2-a4/d7
- bra notinput
- docommand
- lea keybuffer,a2 command buffer
- move.l mapbuffer,a0 key map buffer
- adda.l #9,a0
- 1$ cmpi.b #$fe,(a0) look for end of string
- beq comex
- move.b (a0)+,(a2)+ move in byte
- bra 1$
- comex clr.b (a2)
-
- LEA dosname,a1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- TST.L D0 ok?
- beq.s resstack no
- MOVE.L D0,a6 save
-
- move.l d3,-(a7) save d3
- lea keybuffer,a0 newcli command string
- moveq #0,d2 accept default
- moveq #0,d3 accept default
- move.l a0,d1
- jsr Execute(a6) Execute
- move.l (a7)+,d3 restore d3
- * close dos library
- MOVE.L a6,a1 dos Library
- movea.l 4,a6 Exec base
- jsr CloseLibrary(A6) call CloseLibrary
- bra notinput
-
- *** test for window expand
- exwindow
- cmp.b #'e',action do get window back?
- bne delwintest no
-
-
- move.l #windowtabl/16-1,d0 entries
- lea windowtab,a1 start of table
- add.l #windowtabl-16,a1 end of table
- wtab2 tst.l (a1) free?
- bne gotlast yes
- suba.l #16,a1 down 1
- dbra d0,wtab2
- bra notinput no more - ignore
-
- gotlast
- movem.l a2-a5/d2-d7,-(sp)
- move.l intuit,a6 intuition base
- move.l (a1),a0 window
-
- move.l ib_ActiveScreen(a6),d1 get active screen
-
- move.l #windowtab,d2 start of table
- move.l #windowtabl/16-1,d0 entries
- slook cmp.l 4(a1),d1 same screen?
- beq gotwscreen yes
- suba.l #16,a1 next entry
- cmp a1,d2 at start?
- bne slook
- movem.l (sp)+,a2-a5/d2-d7
- bra notinput
-
- gotwscreen
-
- *** look for window
- move.l d1,a0
- move.l sc_FirstWindow(a0),a2 get first window
- move.l a2,d2
- nextlwin2
- move.l d2,a2
- cmp.l 0(a1),d2 right one?
- beq gotewind yes
- move.l wd_NextWindow(a2),d2 get next window
- beq weend no more
- bra nextlwin2
-
- gotewind
- moveq #0,d0
- moveq #0,d1
- move.l (a1),a0
- move.w 12(a1),d0 x position
- move.w 14(a1),d1 y position
- move.l a1,-(sp)
- jsr MoveWindow(a6)
- move.l (sp)+,a1
- move.l (a1),a0 window
- moveq #0,d0
- moveq #0,d1
- move.w 8(a1),d0 x amount
- move.w 10(a1),d1 y amount
- subq #1,d0
- subq #1,d1
- move.l a1,-(sp) delete entry
- jsr SizeWindow(a6) like a rabbit out of a hat
- move.l (sp)+,a1
- weend move.l a1,d0
- sub.l #windowtab,d0
- move.l #windowtabl,d1
- sub.l d0,d1 get move length
- sub.l #16,d1
- divu #4,d1 in long words
- ext.l d1
- subq #1,d1
- lea (a1),a2 to address
- lea 16(a1),a3 from address
- clearentry
- move.l (a3)+,(a2)+
- dbra d1,clearentry
- movem.l (sp)+,a2-a5/d2-d7
- bra notinput
-
- *** test for window shrink
-
- delwintest
- cmp.b #'d',action do delete window?
- bne newclitst no
-
- * get next available slot
- lea windowtab,a1 start of table
- move.l #windowtabl/16-1,d0 entries
- wtab tst.l (a1) free?
- beq gotwspace yes
- adda.l #16,a1 next entry
- dbra d0,wtab
- bra notinput no space - ignore
- gotwspace
- move.l a1,-(sp)
- bsr windowpointer find where pointer is
- move.l (sp)+,a1
- tst.l d0 got window?
- beq notinput no
- move.l d0,a0
- tst.l wd_UserPort(a0)
- bne.s 1$
- tst.l wd_WindowPort(a0)
- beq notinput
- 1$
- move.l d0,(a1) save window pointer
- moveq #0,d0
- moveq #0,d1
- move.l wd_WScreen(a0),4(a1) save screen
- move.w wd_Width(a0),d0 width
- move.w wd_Height(a0),d1 height
- move.w wd_Width(a0),8(a1) width
- move.w wd_Height(a0),10(a1) height
- move.w wd_LeftEdge(a0),12(a1) x position
- move.w wd_TopEdge(a0),14(a1) y position
- subq #1,d0
- subq #1,d1
- neg.l d0
- neg.l d1
-
- move.l intuit,a6
- move.l a0,-(sp)
- jsr SizeWindow(a6) vapourize
- move.l (sp)+,a0
- moveq #0,d0
- moveq #0,d1
- move.w wd_LeftEdge(a0),d0 x position
- move.w wd_TopEdge(a0),d1 y position
- neg.l d0
- neg.l d1
- move.l a0,-(sp)
- jsr MoveWindow(a6)
- move.l (sp)+,a0
- *
- * Make next window active
- *
- move.l wd_NextWindow(a0),d0 get next window
- beq.s get1stwin
- actnextwin
- move.l d0,a0 activate this window
- jsr ActivateWindow(a6) activate the window
- bra notinput
- get1stwin
- move.l wd_WScreen(a0),d0 get screen
- beq notinput none
- move.l d0,a0
- move.l sc_FirstWindow(a0),d0 get 1st window
- beq notinput none
- bra.s actnextwin
-
- *** test for newcli
-
- newclitst
-
- sunact cmp.b #'f',action flip windows?
- bne winflip
-
- bsr windowpointer find where pointer is
- tst.l d0 got window?
- beq notinput no
- move.l intuit,a6
- cmp.l ib_ActiveWindow(a6),d0 active window?
- beq notinput yes
-
-
- move.l a0,-(sp)
- move.l d0,a0 activate this window
- jsr ActivateWindow(a6) activate the window
- movea.l (sp)+,a0
- bra notinput
- winflip
- move.l intuit,a6 get intuition base
- cmp.b #'w',action window to back?
- bne flipscreen no
-
- wtoback
- lea pause,a1 new ioreq
- move.l a5,a0 old ioreq
- moveq #IOTV_SIZE/4-1,d0
- copyreqw
- move.l (a0)+,(a1)+
- dbra d0,copyreqw
- lea pause,a1
- MOVE.W #TR_ADDREQUEST,IO_COMMAND(A1) IO_COMMAND = TR_ADDREQUEST(9)
- MOVE.l #0,IO_SIZE+TV_SECS(A1) TV_SECS = $01(01 seconds) ||dj
- MOVE.L #10000,IO_SIZE+TV_MICRO(A1) TV_MICRO= 10 ms
- movea.l 4,a6 set Exec base
- JSR DoIO(A6) wait
-
- bsr windowpointer find where pointer is
- tst.l d0 got window?
- beq SetAndPrintTime no
- move.l d0,a0 get window
- cmp.l backwin,d0 same window?
- bne clrswb no
-
-
- move.l wtbsecsnew,d0 get seconds
- sub.l wtbsecs,d0 minus old secs
- beq addoneb increase count
- cmpi.l #1,d0 one second difference?
- bhi clrswb more
-
- move.l wtbsecsnew+4,d0 get micros
- sub.l wtbsecs+4,d0 minus old micros
- bmi addoneb
- beq addoneb
- clrswb clr.b backswitch set count to 0
- move.l a0,backwin save window
- move.l wtbsecsnew,wtbsecs save
- move.l wtbsecsnew+4,wtbsecs+4 save micros
- addoneb add.b #1,backswitch
- moveq #0,d0 clear
- move.b wtbcount,d0 get count
- cmp.b backswitch,d0
- bne SetAndPrintTime no
- clr.b backswitch
- clr.l wtbsecs
- clr.l wtbsecs+4
- clr.b frontswitch
-
- move.l wd_Flags(a0),d0 get window flags
- andi.l #BACKDROP,d0 backdrop window?
- bne SetAndPrintTime yes - no window to back
-
- movea.l intuit,a6 layers base
- jsr WindowToBack(a6)
-
- bra SetAndPrintTime
-
- *** Subroutine to find which window the pointer is in
- *** Return window in d0
-
- windowpointer
- movea.l intuit,a6 get intuition base
- movea.l ib_FirstScreen(a6),a1 get first screen
- move.l ib_ActiveScreen(a6),d0 get Active screen
- cmp.l a1,d0 top screen active one?
- bne winret0 no - don't look for layer
- moveq #0,d0
- moveq #0,d1
- move.l layers,a6 get layers library
- lea sc_LayerInfo(a1),a0 get layer info
- move.l a0,-(sp)
- jsr LockLayerInfo(a6) lock the layer info
- move.w sc_MouseX(a1),d0 get X pointer
- move.w sc_MouseY(a1),d1 get Y pointer
- move.l (sp),a0 get pointer back
- jsr WhichLayer(a6) find active layer
- move.l (sp)+,a0 get pointer back
- move.l d0,-(sp) save result
- jsr UnlockLayerInfo(a6)
- move.l (sp)+,d0
- tst.l d0 get one?
- bne findwin yes
- rts
-
- findwin
- movea.l intuit,a6 get intuition base
- movea.l ib_ActiveScreen(a6),a0 get active screen
-
- move.l sc_FirstWindow(a0),a1 get first window
- nextlwin
- cmp.l wd_WLayer(a1),d0 right one?
- beq inwind yes
- move.l wd_NextWindow(a1),d1 get next window
- beq.s winret0 no more
- movea.l d1,a1
- bra nextlwin
-
- winret0
- moveq #0,d0
- rts
- inwind
- move.l d0,d1 return layer in d1
- move.l a1,d0
- rts
-
-
- ** fall through for scrren cycle and WB to front
-
- flipscreen
- lea pause,a1 new ioreq
- move.l a5,a0 old ioreq
- moveq #IOTV_SIZE/4-1,d0
- copyreq move.l (a0)+,(a1)+
- dbra d0,copyreq
- lea pause,a1
- MOVE.W #TR_ADDREQUEST,IO_COMMAND(A1) IO_COMMAND = TR_ADDREQUEST(9)
- MOVE.l #0,IO_SIZE+TV_SECS(A1) TV_SECS = $01(01 seconds) ||dj
- MOVE.L #10000,IO_SIZE+TV_MICRO(A1) TV_MICRO= 10 ms
- movea.l 4,a6 set Exec base
- JSR DoIO(A6) wait
-
-
- movea.l intuit,a6
- cmp.b #'s',action flip screen?
- beq.s flscr yes
- jsr WBenchToFront(a6) get WB
- bra.s actwbwin
- flscr
- moveq #0,d0
- move.l ib_FirstScreen(a6),a0 get first screen
- jsr ScreenToBack(a6)
- actwbwin
- move.l ib_FirstScreen(a6),a0 get first screen
- move.l sc_FirstWindow(a0),d0 get window
- beq SetAndPrintTime no window
- move.l d0,a0
- jsr ActivateWindow(a6) activate 1st window
- bra SetAndPrintTime
-
- notinput move.l d3,d0 restore
- AND.L D6,D0 ; was it the timeoutSig(D6)?
- BEQ.S isItAWindowSig ; if it wasn't branch
- BRA SetAndPrintTime
- isItAWindowSig:
- AND.L D4,D3 ; was what woke the Wait up a windowSig(D4)?
- BEQ WhileMoreMessages ; if not restart the main loop
- ; keep doing the loop While there are window messages
- WhileMoreMessages:
- movea.l 4,a6 set to Exec base
- MOVEA.L wd_UserPort(A3),A0 A0 = window's UserPort
- JSR GetMsg(A6) ; call GetMsg
- TST.L D0 ; D0 = message
- BEQ SetAndPrintTime ; no more messages so see if any timer messages
- MOVEA.L D0,A1
- move.l im_Class(a1),class save class
- move.w im_Code(a1),code1 save code
- JSR ReplyMsg(A6) call ReplyMessage
- cmpi.l #MENUPICK,class menu?
- bne refres no
-
- bsr menuscan do changes
-
- cmpi.w #MENUNULL,code1 item picked?
- beq refres no
- moveq #0,d0 clear
- move.w code1,d0 get code
- andi.w #$7ff,d0 get item and menu numbers
- lsr #5,d0 remove menu number
- cmpi.w #0,d0 item 0?
- beq donewcli yes - open cli
- cmpi.w #17,d0 quit?
- beq ClosedWindow yes
- cmpi.w #2,d0 colour?
- bne.s tchip no
- moveq #0,d0 clear
- move.w code1,d0 get code again
- lsr #8,d0 get
- lsr #3,d0 subcode
- cmpi.w #11,d0 got one?
- bhi refres no
- lea newcol,a0 new colours
- lsl #1,d0 * 2
- move.w 0(a0,d0.w),Date_Text set new colours
- move.w 0(a0,d0.w),colours save for save
- bra refres
-
- tchip cmpi.w #1,d0 change memory display?
- bne chpri no
-
- ***** swap memory display *************
-
- eor.b #1,memory set to opposite
- movea.l A3,A0 window
- movea.l intuit,A6
- jsr ClearMenuStrip(a6) remove menu
- lea window,a1
- cmpi.b #memtot,memory total memory display?
- beq.s 1$ yes
-
- ******* set up window for chip/fast memory display *********
-
- lea sepmsg,a2 new message text
- move.l #itext1b,memtext new text
- move.l #(312-184),d2 set new width
- move.l #-128,d0 move it
- cmpi.w #128,wd_LeftEdge(a3) neg?
- bcs 3$ yes
- bra.s 2$
- 3$ moveq #0,d0
-
- 2$ MOVEA.L A3,A0
- moveq #0,d1 Dy
- JSR MoveWindow(A6) Move
-
- movea.l a3,a0
- move.l d2,d0 Dx
- moveq #0,d1 Dy
- JSR SizeWindow(A6) alter size
-
- bra setmen
-
- ******** set up window for total memory display
-
- 1$ moveq #0,d0
- moveq #0,d1
-
- move.l #itext1,memtext new text
- move.l #(184-312),d0 set new width - dx
- lea totmsg,a2 new message text
-
- movea.l a3,a0
- moveq #0,d1 Dy
- JSR SizeWindow(A6) alter size
-
- MOVEA.L A3,A0
- move.l #128,d0 Dx value
- moveq #0,d1 Dy
- JSR MoveWindow(A6) Move
-
- setmen lea Date_Text,a0 message structure
- move.l a2,it_IText(a0) set up message address
- movea.l a3,a0
- lea menu0,a1 menu structure
- jsr SetMenuStrip(a6) attach menu
-
- bra refres
-
- chpri
-
- testref
-
- testblank
-
- testpoint
-
- testmouse
-
- testsun
-
- testclickf
-
- testcycle
-
- ********* key load routine
- cmpi.w #15,d0 load keys??
- bne testsave no
-
- ********* open window
-
- lea keywindow,a0
- movea.l intuit,A6
- JSR OpenWindow(A6) ; call OpenWindow
-
- move.l d0,windowkey save window
- beq WhileMoreMessages
- move.l windowkey,a0
-
- * get Window->UserPort->mp_SigBit into D0
- MOVEA.L wd_UserPort(A0),A1 A1 = ClockWindow->UserPort
- MOVEQ #0,D0
- MOVE.B MP_SIGBIT(A1),D0 D0 = the ClockWindow's mp_SigBit
- MOVEQ #1,D1
- LSL.L D0,D1 ; D1 = windowSigs
- move.l D1,keywait ; waitFlags
-
- *
-
- MOVEA.L wd_RPort(A0),A0 window's RPort
- LEA keytext,A1 message structure
- MOVEQ #0,D0
- MOVEQ #0,D1
- movea.l intuit,A6
- JSR PrintIText(A6) ; call PrintIText
- clr.b keysw
- dokeywait
- MOVE.L keywait,D0 ; D0 = waitFlags
- movea.l 4,a6 Exec base
- JSR Wait(A6) ; call Wait
- getkeymsg
- move.l windowkey,a1
- movea.l 4,a6 set to Exec base
- MOVEA.L wd_UserPort(a1),A0 A0 = window's UserPort
- JSR GetMsg(A6) ; call GetMsg
- TST.L D0 ; D0 = message
- bne.s 1$
- tst.b keysw time to close window?
- bne closekeywin yes
- bra dokeywait
-
- 1$ MOVEA.L D0,A1
- move.l im_Class(a1),class save class
- move.w im_Code(a1),code1 save code
- move.l im_IAddress(a1),a2 save gadget adderss
- JSR ReplyMsg(A6) call ReplyMessage
- closekey
- cmp.l #ACTIVEWINDOW,class
- bne.s dokeycl
- movea.l intuit,A6
- move.l windowkey,a1
- lea gad0,a0
- move.l #0,a2
- jsr ActivateGadget(a6)
- bra getkeymsg
- dokeycl
- * cmpi.l #GADGETUP,class gadget selected?
- * bne closekeywin no
- move.w gg_GadgetID(a2),d0 get gadget number
- cmp.b #1,d0 cancel?
- bne 1$
- not.b keysw
- bra getkeymsg
-
- 1$ lea dosname,A1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- move.l d0,a6 ok?
- beq WhileMoreMessages no
- lea keyfile,a0 name of save string
- move.l a0,d1 move into right reg
- move.l #ACCESS_READ,d2 old file
- jsr Lock(a6) Open
- tst.l d0 file there?
- bne.s unlock yes
-
- movem.l a3/d2-d3,-(sp)
- move.l intuit,a6 intuition base
- move.l windowpoint,a0
- lea fileerrortext,a1
- lea oktext,a2
- lea oktext,a3
- moveq #0,d0 flags
- moveq #0,d1 "
- move.l #200,d2 width
- move.l #60,d3 height
- jsr AutoRequest(a6)
- movem.l (sp)+,a3/d2-d3
-
- move.l doslib,a6 dos base
- move.l a6,a1
- MOVEA.L 4,A6 ; load exec library address
- JSR CloseLibrary(A6) ; call CloseLibrary
-
- move.l intuit,a6 intuition base
- move.l windowkey,a0
- jsr ActivateWindow(a6) activate the window
-
- bra getkeymsg
- unlock
- move.l d0,d1 move into right reg
- jsr UnLock(a6) Open
- bsr freekeymem free old key memory
- bsr readkeys get new keys
- doskclose
- move.l doslib,a6 dos base
- move.l a6,a1
- MOVEA.L 4,A6 ; load exec library address
- JSR CloseLibrary(A6) ; call CloseLibrary
-
-
- closekeywin
- move.l windowkey,a0
- movea.l intuit,A6
- JSR CloseWindow(A6) close window
-
- bra WhileMoreMessages
-
- ********* save routine
-
- testsave cmpi.w #16,d0 save?
- beq dosave
-
- cmpi.w #16,d0 valid?
- bls WhileMoreMessages yes
-
- move.b #1,owsw
- MOVEA.L wd_RPort(A3),A0 window's RPort
- LEA ouch,A1 silly message structure
- MOVEQ #0,D0
- MOVEQ #0,D1
- movea.l intuit,A6
- JSR PrintIText(A6) ; call PrintIText
-
- bra WhileMoreMessages
-
-
- dosave
- moveq #0,d0
- move.w #CHECKED,d0
- and.w suncheck,d0 do sun mouse?
- beq clrsun no
- move.b #$ff,sunswitch
- bra cyccheck
- clrsun
- clr.b sunswitch
- cyccheck
- move.w #CHECKED,d0
- and.w cyclecheck,d0 do sun mouse?
- beq clrcycle no
- move.b #$ff,cycleswitch
- bra keych
- clrcycle
- clr.b cycleswitch
- keych
- move.w #CHECKED,d0
- and.w keycheck,d0 do sun mouse?
- beq clrkey no
- move.b #$ff,keyswitch
- bra popch
- clrkey
- clr.b keyswitch
- popch
- move.w #CHECKED,d0
- and.w wtfcheck,d0 do sun mouse?
- beq clrpop no
- move.b #$ff,popswitch
- bra mapch
- clrpop
- clr.b popswitch
- mapch
- move.w #CHECKED,d0
- and.w mapcheck,d0 do sun mouse?
- beq clrmap no
- move.b #$ff,mapswitch
- bra dowrite
- clrmap
- clr.b mapswitch
- dowrite
- LEA dosname,A1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- TST.L D0 ok?
- beq refres no
- MOVE.L D0,a6 save
-
- lea savefile,a0 name of save string
- move.l a0,d1 move into right reg
- move.l #MODE_OLDFILE,d2 old file
- jsr Open(a6) Open
- tst.l d0 file there?
- bne.s 1$ yes, got file handle
- lea savefile,a0 name of save string
- move.l a0,d1 move into right reg
- move.l #MODE_NEWFILE,d2 new file
- jsr Open(a6) Open
- tst.l d0 got one ?
- beq refres no
- 1$ move.l d3,-(a7) save d3
- move.w wd_LeftEdge(a3),windowleft set up window position
- move.w wd_TopEdge(a3),windowtop "
- lea diskbuffer,a0
- move.l a0,d2 data
- move.l #diskbufferl,d3 data length
- move.l d0,d1 file handle
- move.l d0,-(a7) save file handle
-
- jsr Write(a6) write it out
- move.l (a7)+,d1 restore file handle
- jsr Close(a6) close file
- MOVE.L a6,a1 dos Library
- movea.l 4,a6 Exec base
- jsr CloseLibrary(A6) call CloseLibrary
- move.l (a7)+,d3 restore d3
- bra refres carry on
-
-
- ************** do newcli
-
- ************** Open dos library
-
- donewcli LEA dosname,A1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- TST.L D0 ok?
- beq.s refres no
- MOVE.L D0,a6 save
-
- move.l d3,-(a7) save d3
- lea nilname,a0 name of nil string
- move.l a0,d1 move into right reg
- move.l #MODE_NEWFILE,d2 new file
- jsr Open(a6) Open
- move.l d0,d3 save out handle
- moveq #0,d2 input handle
- lea newcli,a0 newcli command string
- move.l a0,d1
- jsr Execute(a6) Execute
- move.l (a7)+,d3 restore d3
- * close dos library
- MOVE.L a6,a1 dos Library
- movea.l 4,a6 Exec base
- jsr CloseLibrary(A6) call CloseLibrary
- bra SetAndPrintTime get timer events
-
- refres move.b #0,oldsecs force refresh
-
- ************************************
-
- PrintTime:
- tst.b owsw ouch?
- beq noow no
- clr.b owsw off
- bra treturn
-
- noow tst.l tswitch do display
- beq treturn no
- cmpi.b #memtot,memory total memory?
- beq.s 2$ yes
- lea buffer2+8,a0 seconds
- bra.s 3$
- 2$ lea buffer+8,a0 seconds
- 3$ move.b oldsecs,d1
- move.l a0,-(sp) keep a0
- cmp.b (a0),d1 do display?
- beq nodisable no
- tst.w blanktime off?
- beq tespoint yes
- tst.b blankdone already blank?
- bne tespoint yes
-
- move.w blanktimer,d0
- cmp.w blanktime,d0 time to blank?
- bcs add1blank no
- lea newscreen,a0
- move.l intuit,a6
- jsr OpenScreen(a6)
- move.l d0,blankscreen keep
- beq showtime didn't work
-
- lea graphicsname,a1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- TST.L D0 ok?
- beq showtime yes
- move.l d0,a6 graphics base
- move.l blankscreen,a1 get screen
- lea sc_ViewPort(a1),a0 get viewport
- move.l d2,-(sp)
- moveq #0,d1 R
- moveq #0,d2 G
- moveq #0,d3 B
- moveq #0,d0 Register
- jsr SetRGB4(a6) nice black for CL
- movea.l a6,A1 graphics Library
- movea.l 4,a6 exec base
- JSR CloseLibrary(A6) call CloseLibrary
- move.l (sp)+,d2
- not.b blankdone set to blanked
-
- * move.w #$0020,$dff000+$96 turn off sprite dma
- tst.w pointtime pointer blank on?
- bne showtime yes
-
- bra killpoint
-
-
- add1blank
- addq.w #1,blanktimer add 1
-
- tespoint
- tst.w pointtime off?
- beq showtime yes
- move.w pointtimer,d0
- cmp.w pointtime,d0 time to blank?
- bcs add1point no
-
- killpoint
- lea graphicsname,a1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- tst.l d0
- beq showtime yes
- move.l d0,a6 ok?
- move.l gb_copinit(a6),a0 copper start-up
- lea copinit_sprstrtup(a0),a1 sprite data
- clrsprite
- tst.b pointdone pointer blank already?
- bne checkpoint yes
- not.b pointdone set switch
- redopointer
- moveq #0,d0
- move.w 2(a1),spritesave high bytes
- move.w 6(a1),spritesave+2 get rest of address
- move.w spriteblank,2(a1) top
- move.w spriteblank+2,6(a1) bottom
-
- movea.l a6,A1 graphics Library
- movea.l 4,a6 exec base
- JSR CloseLibrary(A6) call CloseLibrary
-
- * move.w #$0020,$dff000+$96 turn off sprite dma
- bra showtime
- checkpoint
- move.w 2(a1),d1 high bytes
- swap d1
- move.w 6(a1),d1 get rest of address
- cmp.l spriteblank,d1 still my blank pointer?
- bne redopointer
- bra showtime
-
-
- add1point
- addq.w #1,pointtimer
- bra showtime
-
- nodisable
- move.l (sp)+,a0
- cmpi.b #memtot,memory total memory?
- beq.s totmem yes
- move.l oldchip,d0
- cmp.l chipavail,d0 do display?
- bne.s showtime2 yes
- move.l oldfast,d0
- cmp.l fastavail+1,d0 do display?
- beq treturn no
- bra.s showtime2 do print
- totmem move.l oldmem,d0
- cmp.l avail+1,d0 do display?
- beq treturn no, return
- bra.s showtime2
- showtime
- move.l (sp)+,a0
- showtime2
- move.b (a0),oldsecs
- move.l avail+1,oldmem
- move.l chipavail,oldchip save for next test
- move.l fastavail+1,oldfast save for next test
- MOVEA.L wd_RPort(A3),A0 window's RPort
- LEA Date_Text(PC),A1 Date_Text structure
- MOVEQ #0,D0
- MOVEQ #0,D1
- movea.l intuit,A6
- JSR PrintIText(A6) ; call PrintIText
- moveq #0,d0
- move.w newminutes,d0
- cmp.w oldminutes,d0 do popup?
- beq.s nopop no
- move.w #CHECKED,d0
- and.w wtfcheck,d0 do popup?
- beq nopop no
- move.w newminutes,oldminutes
- movea.l layers,a6 layers base
- movea.l layerinfo,a0 screen's layer info
- movea.l layer,a1 window's layer
-
- jsr UpfrontLayer(a6) pop
- nopop:
- treturn:
- JMP (A4) ; normally jumps to WhileMoreMessages
-
- *****************************
-
- SetAndPrintTime:
- MOVEA.L D5,A0 ; get message form timer port
- movea.l 4,a6 set Exec base
- JSR GetMsg(A6) ; call GetMsg
- TST.L D0 ; D0 = message
- BEQ MainLoop ; no more messages so start Waiting
-
- InitializeTime:
-
- ************** initialize the buffer
-
- cmpi.b #memtot,memory display total memory?
- beq.s 1$ yes
- lea buffer2+1,a2
- jsr timeclear clear buffer
- bra.s 2$
- 1$ lea buffer+1,a2 start of area to clear
- jsr timeclear clear buffer
- ; set the timeRequest to wait for refresh time
- 2$ MOVE.l #0,IO_SIZE+TV_SECS(A5) TV_SECS = $01(01 seconds) ||dj
- MOVE.L refrate,IO_SIZE+TV_MICRO(A5) TV_MICRO= 200 ms
- ; get the current time. It will be on the stack
- SUBQ.L #4,A7
- LEA (A7),A1 ; address of micros
- SUBQ.L #4,A7
- LEA (A7),A0 ; address of seconds
- movea.l intuit,A6
- JSR CurrentTime(A6) ; call CurrentTime
-
- MOVE.L (A7)+,D0 ; secs
- MOVE.L (A7)+,D1 ; micros
- move.l d0,tswitch save because of mach11
-
- CLR.W -(A7) ; push a zero word onto the stack => AM
- DIVU #-$5740,D0 ; secs/#secs_in_12hrs
- LSR.B #1,D0 ; test least sig. bit by shifting into C bit
- BCC.S AM
- ; it is PM
- MOVE.W #$C,(A7) ; top of stack now 12 => PM
- AM:
- SWAP D0 ;"n lower half of D0 = #of secs in the half day
- MOVE.L D0,D1 ; save D0 into D1
- MOVEQ #0,D0
- MOVE.W D1,D0 ;
- DIVU #$3C,D0 ; #of_secs_in_half_day/60
- MOVE.W D0,-(A7) ; save the #of minutes*hrs in the half day
- SWAP D0 ; D0.W = # of secs in the minute
- move.w d0,seconds save seconds ||dj
-
- ******** start the timer running
-
- MOVEA.L A5,A1
- movea.l 4,a6 set Exec base
- JSR SendIO(A6) ; call SendIO
-
- *************** Find out available memory
- move.l #1,d1 memory type = PUBLIC
- jsr AvailMem(A6) ; call AvailMem
- move.l d0,totalmemory save all memory
- move.l #2,d1 memory type = PUBLIC
- jsr AvailMem(A6) ; call AvailMem
- move.l d0,chipmemory save all memory
-
- ******* reformat memory
-
- cmpi.b #memtot,memory total memory?
- bne.s 1$ no
- lea avail+1,a2 memory display area
- move.l totalmemory,d0 move in total memory
- bsr formatmem format memory d isplay
- bra.s 2$
- 1$ move.l chipmemory,d0 move in chip memory
- lea chipavail,a2
- bsr formatmem format memory display
- move.l totalmemory,d0 get total
- sub.l chipmemory,d0 get fast memory
- lea fastavail+1,a2 fast memory
- bsr formatmem
-
- ****** figure out what time it is and load it in the buffer
-
- 2$ cmpi.b #memtot,memory total memopry?
- bne.s 3$ no
- lea buffer,a2
- bra.s 4$
- 3$ lea buffer2,a2
- 4$ move.w seconds,d1 get seconds
- ext.l d1
- divu #$a,d1 rem = ones digit; quot = tens ||dj
- add.b d1,7(a2) put in 10s seconds ||dj
- swap d1 get remainder ||
- add.b d1,8(a2) put in ones seconds ||
- MOVEQ #0,D0
- MOVE.W (A7)+,D0 ; D0 has # of minutes*hrs in half day
- DIVU #$3C,D0 ; divide it by 60; rem = minutes, quot = hrs
- MOVEQ #0,D1
- MOVE.W (A7)+,D1 ; D1 = (0=AM), (12=PM)
- ADD.W D0,D1 ; add quot to D1 giving # of hrs in the day
- SWAP D0 ; get the rem = minutes
- move.w d0,newminutes save for popup ||dj
- EXT.L D0
- DIVU #$A,D0 ; divide by 10; rem = ones digit, quot = tens digit
- ADD.B D0,4(A2) ; add tens digit to buffer[4]
- SWAP D0
- ADD.B D0,5(A2) add ones digit to buffer[5]
- cmpi.w #12,d1 is it pm?
- bgt movepm yes
- blt moveam
- move.b #'P',ampm1 set to pm since it's 12
- move.b #'P',ampm2 set to pm since it's 12
- bra.s dohours
- moveam move.b #'A',ampm1 set to am
- move.b #'A',ampm2 set to am
- bra.s dohours
- movepm move.b #'P',ampm1 set to pm
- move.b #'P',ampm2 set to pm
- subi.w #12,d1 make it < 12
- dohours DIVU #$A,D1 divide hours by 10; rem = ones digit, quot = tens digit
- ADD.B D1,1(A2) add tens digit to buffer[1]
- SWAP D1
- ADD.B D1,2(A2) add ones digit to buffer[2]
- cmpi.b #'0',1(a2) 1st digit zero?
- bne.s 1$ no - carry on
- cmpi.b #'0',2(a2) 2nd digit zero?
- bne.s 2$ no
- move.b #'1',1(a2) set to 12 am
- move.b #'2',2(a2) "
- bra.s 1$
- 2$ move.b #' ',1(a2) blank 1st digit
- 1$ BRA.L PrintTime ; PrintTime will return
-
-
- *
- *
- *********************************************************
- * *
- * Input handler *
- * *
- *********************************************************
- *
- *
-
-
-
- intcode movem.l a0-a6/d1-d7,-(a7) save
-
- nextevent
- cmp.b #IECLASS_TIMER,ie_Class(a0) ignore timer
- beq intdone
- bra noinsave
-
- * save to inspect
-
- lea event,a1
- move.l ie_TimeStamp(a0),ie_TimeStamp(a1) move
- move.l ie_TimeStamp+4(a0),ie_TimeStamp+4(a1) move
-
- noinsave
- tst.b escsw escape from processing input event?
- beq.s procevent no
- cmp.b #IECLASS_RAWKEY,ie_Class(a0) got a key?
- bne.s 1$ no
- cmpi.w #$5f,ie_Code(a0) qualifier key?
- bhi.s procevent yes
- 2$ clr.b escsw clear switch
- bra blanktests
- 1$
- cmp.b #IECLASS_RAWMOUSE,ie_Class(a0) is it mouse?
- bne.s procevent no
- move.w ie_Code(a0),d0 get code
- cmp.w #IECODE_NOBUTTON,d0 mouse button?
- bne.s 2$ yes
-
- procevent
- cmp.b #IECLASS_RAWKEY,ie_Class(a0) got a key?
- bne notkey
-
- move.w #CHECKED,d0
- and.w mapcheck,d0 do keymap?
- beq.s procqual no
-
- cmpi.w #$0,ie_Code(a0) ` key?
- bne.s procqual no
- move.w ie_Qualifier(a0),d0 get qualifier
- and.w #$ffff-IEQUALIFIER_RELATIVEMOUSE,d0 set off unwanted bits
- cmpi.w #IEQUALIFIER_CONTROL,d0 got ctrl?
- bne.s tesrep no
- move.b #IECLASS_NULL,ie_Class(a0) remove
-
- not.b escsw set switch
-
- *
- * Test to see if it's a window size
- *
- procqual
- move.w ie_Qualifier(a0),d0 get qualifier
- and.w #$ffff-IEQUALIFIER_RELATIVEMOUSE,d0 set off unwanted bits
-
- cmpi.w #IEQUALIFIER_LCOMMAND+IEQUALIFIER_LSHIFT+IEQUALIFIER_CONTROL,d0
- bne.s tesrep no
- cmpi.w #$4d,ie_Code(a0) up arrow?
- bne.s tdowna no
- move.b #'>',action increase
- move.b #IECLASS_NULL,ie_Class(a0) remove
- bra signaltask
-
- tdowna cmpi.w #$4c,ie_Code(a0) up arrow?
- bne.s tesrep no
- move.b #'<',action decrease
- move.b #IECLASS_NULL,ie_Class(a0) remove
- bra signaltask
-
-
-
- *
- *
- *** Test to see if the key should be mapped to somthing else.
- *
- *
- tesrep
- move.w #CHECKED,d0
- and.w mapcheck,d0 do keymap?
- beq endmap no
-
- move.l firstkey,d0 address of first buffer
- mapkeylook
- beq endmap no mapping to be done
- move.l d0,a1
- move.w ie_Code(a0),d0 get key
- cmp.b 8(a1),d0 keys match?
- beq.s gotkeymap yes
- nextmapbuf
- move.l 2(a1),d0 next buffer
- bra.s mapkeylook
- gotkeymap
- move.w ie_Qualifier(a0),d0 get qualifier
-
- and.w #$01ff,d0 set off unwanted bits
- cmp.w 6(a1),d0 qualifiers match?
- bne.s nextmapbuf no
- btst #IEQUALIFIERB_REPEAT-8,ie_Qualifier(a0) got repeat?
- beq.s 2$ no
- move.b #IECLASS_NULL,ie_Class(a0) remove
- bra blanktests
-
- 2$ move.l a1,mapbuffer save buffer address
- adda.l #9,a1 start of string
- 1$ cmpi.b #$fe,(a1)+ end?
- bne.s 1$
- cmpi.b #'r',0(a1) keep character?
- bne.s keepch yes
- move.b #IECLASS_NULL,ie_Class(a0) remove l button
- keepch move.b #'m',action set to key map
- bra signaltask
- endmap
-
- cmpi.w #$64,ie_Code(a0) is it L-alt?
- bne laltup no
-
- move.w ie_Qualifier(a0),d0 get qualifier
- and.w #$ffff-IEQUALIFIER_RELATIVEMOUSE,d0 set off unwanted bits
- cmpi.w #IEQUALIFIER_LCOMMAND,d0
- beq seti
- tst.b lamiga L-A down?
- beq setlalt no
- seti
- move.b #$ff,lsw set switch left
- setlalt
- move.b #$ff,lalt yes
- bra blanktests
- laltup
- cmpi.w #$64+IECODE_UP_PREFIX,ie_Code(a0) L-alt-up?
- bne latest no
- move.b #0,lalt reset
- move.b #0,lsw reset
- bra blanktests
- latest
- cmpi.w #$66,ie_Code(a0) is it L-A?
- bne amiup no
- move.b #$ff,lamiga set
- tst.b lalt L-alt down?
- beq blanktests no
- move.b #$ff,lsw set switch
- amiup
- cmpi.w #$66+IECODE_UP_PREFIX,ie_Code(a0) L-ami-up?
- bne mtest no
- clr.b lamiga
-
- mtest
- cmpi.w #$37,ie_Code(a0) is it m?
- bne ntest no
- move.w ie_Qualifier(a0),d0 get qualifier
- and.w #$ffff-(IEQUALIFIER_RELATIVEMOUSE+IEQUALIFIER_REPEAT),d0 set off unwanted bits
- cmpi.w #IEQUALIFIER_LCOMMAND,d0
- bne testkeysw
- btst #IEQUALIFIERB_REPEAT-8,ie_Qualifier(a0) got repeat?
- beq.s 1$ no
- move.b #IECLASS_NULL,ie_Class(a0) remove the m
- bra blanktests
-
- 1$ moveq #0,d0
- move.w #CHECKED,d0
- and.w cyclecheck,d0 do screen cycle?
- beq testkeysw no
- move.b #IECLASS_NULL,ie_Class(a0) remove the m
- bra doscreen
-
-
- ntest
- cmpi.w #$36,ie_Code(a0) is it n?
- bne testkeysw no
- move.w ie_Qualifier(a0),d0 get qualifier
- and.w #$ffff-(IEQUALIFIER_RELATIVEMOUSE+IEQUALIFIER_REPEAT),d0 set off unwanted bits
- cmpi.w #IEQUALIFIER_LCOMMAND,d0
- bne testkeysw
- btst #IEQUALIFIERB_REPEAT-8,ie_Qualifier(a0) got repeat?
- beq.s 1$ no
- move.b #IECLASS_NULL,ie_Class(a0) remove the n
- bra blanktests
-
- 1$ moveq #0,d0
- move.w #CHECKED,d0
- and.w cyclecheck,d0 do screen cycle?
- beq testkeysw no
- move.b #IECLASS_NULL,ie_Class(a0) remove the n
- move.b #'b',action signal workbench to front
- bra dowb
-
- testkeysw
- moveq #0,d0
- move.w #CHECKED,d0
- and.w keycheck,d0 do key to front?
- beq blanktests nope
- tst.b lsw got icon?
- bne blanktests maybe
- cmpi.b #'l',mouseleft left down ?
- beq blanktests yes don't do activate to avoid
- * freeze when icon is picked up
-
- move.l a0,-(sp)
- bsr windowpointer find where pointer is
- tst.l d0 got window?
- beq resa0 no
- move.l d0,a0 window
- move.l intuit,a6
- movea.l ib_ActiveWindow(a6),a1 get active window
- cmp.l a1,d0 already active?
- beq resa0 yes
-
- jsr ActivateWindow(a6)
- resa0 move.l (sp)+,a0
-
- bra blanktests
-
- notkey
- cmp.b #IECLASS_RAWMOUSE,ie_Class(a0) mouse event?
- bne blanktests no
-
- cmpi.w #IECODE_LBUTTON,ie_Code(a0) left mouse button?
- bne nothid no
- *
- * Don't allow user to touch hidden windows.
- *
-
- move.l a0,-(sp)
- bsr windowpointer find where pointer is
- move.l (sp)+,a0
- tst.l d0 got one?
- beq.s nothid no
- lea windowtab,a1 start of table
- move.l #windowtabl/16-1,d1 entries
- 1$ tst.l (a1) free?
- beq nothid yes
- cmp.l (a1),d0 hidden window?
- bne.s 2$ no
- move.b #IECLASS_NULL,ie_Class(a0) remove l button
- bra blanktests
- 2$ adda.l #16,a1 next entry
- dbra d1,1$
- nothid
- moveq #0,d0
- move.w #CHECKED,d0
- and.w suncheck,d0 do sun mouse?
- beq speedtest no
-
- cmpi.w #IECODE_NOBUTTON,ie_Code(a0) mouse button pressed?
- bne speedtest yes
- cmpi.b #'l',mouseleft left down ?
- beq speedtest yes
-
- move.b #'f',action set up for sun mouse cycle
- move.l insig,d0 we want to send this signal
- movea.l task,a1 to this task
- move.l 4,a6 exec base
- move.l a0,-(sp) save
- jsr Signal(a6) so it wakes up
- movea.l (sp)+,a0 restore
-
- speedtest
- move.l intuit,a6 get intuition base
- move.l ib_ActiveScreen(a6),a1 get Active screen
- cmpi.w #9,sc_MouseY(a1) is Y pointer in menu area?
- bhi notmen no
- cmpi.b #'r',mouseright right mouse button down?
- bne notmen no
- move.b #$ff,menuswitch set menuswitch
- notmen
- moveq #0,d0
- tst.b mousespeed no acceleration?
- beq buttontest no
- moveq #0,d1
- move.b mousespeed,d1 get mouse speed
- add.w #4,d1 get multiplyer
- moveq #0,d0
- move.w ie_X(a0),d0 get value
- incx cmp.w #1,d0 is it 1
- beq.s doynow yes - leave it alone
- cmp.w #-1,d0 is it 1
- beq.s doynow yes - leave it alone
- muls d1,d0 calculate new relative mouse
- divs #4,d0
- move.w d0,ie_X(a0) put back
- doynow moveq #0,d0
- move.w ie_Y(a0),d0 get value
- incy cmp.w #1,d0 is it 1?
- beq.s buttontest yes - leave it alone
- cmp.w #-1,d0 is it 1?
- beq.s buttontest yes - leave it alone
- muls d1,d0
- divs #4,d0
- move.w d0,ie_Y(a0) put back
-
- buttontest
- cmpi.w #IECODE_LBUTTON,ie_Code(a0) left mouse button?
- bne testright no
- *
- * code for window shrink
- *
-
- ; tst.b lamiga L-A down?
- ; beq 1$ no
- move.w ie_Qualifier(a0),d0 get qualifier
- and.w #IEQUALIFIER_LCOMMAND+IEQUALIFIER_LSHIFT+IEQUALIFIER_CONTROL,d0 set off unwanted bits
- cmpi.w #IEQUALIFIER_LCOMMAND+IEQUALIFIER_LSHIFT+IEQUALIFIER_CONTROL,d0
- bne.s 1$
- move.b #'d',action delete window
- move.b #IECLASS_NULL,ie_Class(a0) remove l button
- bra signaltask
- 1$
- cmp.b #'r',mouseright r set?
- beq wsig yes
- move.b #'l',mouseleft yes - set state
-
-
- *** do window to front here to avoid lockup
- tst.b lsw got icon?
- bne blanktests maybe
-
- dowtf bsr wtofront
-
- bra blanktests
-
- wtofront
-
- movem.l a0/a1/a2/a6,-(sp)
- move.l a0,-(sp)
- bsr windowpointer find where pointer is
- move.l (sp)+,a0
- tst.l d0 got window?
- beq wtfend no
- movea.l intuit,a6 get intuition base
- move.l d0,a2 get window
- cmp.l frontwin,d0 same window
- bne clrsw no
-
- move.l ie_TimeStamp(a0),d0 get seconds
- sub.l wtfsecs,d0 minus old secs
- beq addone increase count
- cmpi.l #1,d0 one second difference?
- bhi clrsw more
-
- move.l ie_TimeStamp+4(a0),d0 get micros
- sub.l wtfsecs+4,d0 minus old micros
- bmi addone
- beq addone
- clrsw clr.b frontswitch set count to 0
- move.l a2,frontwin save window
- move.l ie_TimeStamp(a0),wtfsecs save
- move.l ie_TimeStamp+4(a0),wtfsecs+4 save micros
- addone add.b #1,frontswitch
- moveq #0,d0 clear
- move.b wtfcount,d0 get count
- cmp.b frontswitch,d0
- bne wtfend no
- clr.b frontswitch
- clr.l wtfsecs
- clr.l wtfsecs+4
-
- movea.l ib_ActiveScreen(a6),a0 get active screen
- lea sc_LayerInfo(a0),a1 get layer info
- cmp.l li_top_layer(a1),d1 already on top layer?
- beq wtfend yes
- movea.l a2,a0 get window
- move.l wd_Flags(a0),d0 get window flags
- andi.l #BACKDROP,d0 backdrop window?
- bne wtfend yes - no window to front
- jsr WindowToFront(a6) bring it to the front
- wtfend movem.l (sp)+,a0/a1/a2/a6
- rts
-
-
- wsig
- cmpi.b #'r',revswitch reverse buttons?
- beq.s dowtb yes
- moveq #0,d0
- move.w #CHECKED,d0
- and.w cyclecheck,d0 do screencycle?
- beq blanktests no
- tst.b lsw got icon?
- bne blanktests maybe
- tst.b menuswitch got a menu perhaps
- bne blanktests don't do screen cycle
-
- move.b #'s',action set action indicator
- move.w #IECODE_RBUTTON+IECODE_UP_PREFIX,ie_Code(a0) alter to r up
- * signal code
-
- move.l insig,d0 we want to send this signal
- movea.l task,a1 to this task
- move.l 4,a6 exec base
- move.l a0,-(sp) save
- jsr Signal(a6) so it wakes up
- movea.l (sp)+,a0 restore
- bra blanktests
-
- dowtb
- move.l ie_TimeStamp(a0),wtbsecsnew save
- move.l ie_TimeStamp+4(a0),wtbsecsnew+4 save micros
-
- tst.b lsw got icon?
- bne blanktests maybe
-
- move.b #'w',action set up for window cycle
- move.w #IECODE_RBUTTON+IECODE_UP_PREFIX,ie_Code(a0) alter to r up
- signaltask
- move.l insig,d0 we want to send this signal
- movea.l task,a1 to this task
- move.l 4,a6 exec base
- move.l a0,-(sp) save
- jsr Signal(a6) so it wakes up
- movea.l (sp)+,a0 restore
- bra blanktests
-
- testright
-
- cmpi.b #'l',mouseleft left down already?
- bne testrightdown no
- cmpi.w #IECODE_RBUTTON,ie_Code(a0) right mouse button
- bne testleftup no
- move.w #IECODE_LBUTTON+IECODE_UP_PREFIX,ie_Code(a0) change to l up
- move.b #'r',mouseright set state
-
-
- cmpi.b #'r',revswitch reverse buttons?
- beq doscreen yes
- move.b #'w',action set up for window to back
- move.l ie_TimeStamp(a0),wtbsecsnew save
- move.l ie_TimeStamp+4(a0),wtbsecsnew+4 save micros
- bra signaltask
- doscreen
- move.b #'s',action set action indicator
- dowb
- moveq #0,d0
- move.w #CHECKED,d0
- and.w cyclecheck,d0 do screen?
- beq blanktests no
- tst.b lsw got icon?
- bne blanktests maybe
-
- tst.b pointdone pointer off?
- beq sigscreen no
- bsr hellopoint get pointer back
-
- sigscreen
- tst.b lsw got icon?
- bne blanktests maybe
- tst.b menuswitch got a menu perhaps
- bne blanktests don't do screen cycle
- scode
-
- * signal code
-
- move.l insig,d0 we want to send this signal
- movea.l task,a1 to this task
- move.l 4,a6 exec base
- move.l a0,-(sp) save
- jsr Signal(a6) so it wakes up
- movea.l (sp)+,a0 restore
- bra blanktests
-
- testleftup
- cmpi.w #IECODE_LBUTTON+IECODE_UP_PREFIX,ie_Code(a0) l up?
- bne testrightup no
- move.b #0,mouseleft reset
- bra blanktests
-
- testrightdown
- cmpi.w #IECODE_RBUTTON,ie_Code(a0) right mouse button?
- bne testrupnol no
- *
- * code for window expand
- *
- ; tst.b lamiga L-A down?
- ; beq 1$ no
- move.w ie_Qualifier(a0),d0 get qualifier
- and.w #IEQUALIFIER_LCOMMAND+IEQUALIFIER_LSHIFT+IEQUALIFIER_CONTROL,d0 set off unwanted bits
- cmpi.w #IEQUALIFIER_LCOMMAND+IEQUALIFIER_LSHIFT+IEQUALIFIER_CONTROL,d0
- bne.s 1$
- move.b #'e',action delete window
- move.b #IECLASS_NULL,ie_Class(a0) remove r button
- bra signaltask
- 1$
- move.b #'r',mouseright set r
- move.l intuit,a6 get intuition base
- move.l ib_ActiveScreen(a6),a1 get Active screen
- cmpi.w #9,sc_MouseY(a1) is Y pointer in menu area?
- bhi blanktests no
- cmpi.b #'r',mouseright right mouse button down?
- bne blanktests no
- move.b #$ff,menuswitch set menuswitch
-
- bra blanktests
-
- testrupnol
- cmpi.w #IECODE_RBUTTON+IECODE_UP_PREFIX,ie_Code(a0) r up?
- bne testrset
- clr.b menuswitch
- move.b #0,mouseright reset set state
- bra blanktests
- testrset
- cmpi.b #'r',mouseright r set?
- bne blanktests no
- cmpi.w #IECODE_LBUTTON+IECODE_UP_PREFIX,ie_Code(a0) l up?
- bne blanktests no
- tst.b menuswitch got a menu perhaps
- bne blanktests don't remove l up
- moveq #0,d0
- move.w #CHECKED,d0
- and.w cyclecheck,d0 do screen cycle specified?
- beq blanktests no don't remove l up
- move.b #IECLASS_NULL,ie_Class(a0) remove l button up
- bra blanktests
-
- testrightup
- cmpi.b #'r',mouseright left been down already?
- bne blanktests no
- cmpi.w #IECODE_RBUTTON+IECODE_UP_PREFIX,ie_Code(a0) r up?
- bne blanktests no
- move.b #IECLASS_NULL,ie_Class(a0) remove right mouse button up
- move.b #0,mouseright reset r button state
-
- blanktests
- tst.w blanktime off?
- beq intdone yes
- tst.b blankdone screen blank?
- beq zerblank no
-
- move.l a0,-(sp)
- move.l blankscreen,a0
- beq.s 1$
- clr.b blankdone reset switch
-
- * move.w #$8020,$dff000+$96 turn on sprite dma
- move.l intuit,a6
- jsr CloseScreen(a6) give back normal display
- 1$ move.l (sp)+,a0
- move.w #0,blanktimer zero blank timer
- bsr hellopoint
- bra intdone
-
- zerblank
- move.w #0,blanktimer zero blank timer
- cmp.b #IECLASS_RAWMOUSE,ie_Class(a0) mouse event?
- bne intdone no
-
- tst.w pointtime off?
- beq intdone yes
- tst.b pointdone pointer off?
- beq pointclr no
-
- bsr hellopoint
- pointclr
- move.w #0,pointtimer zero pointer time
- bra intdone
-
- hellopoint
- clr.b pointdone
- move.l a0,-(sp)
- lea graphicsname,a1
- MOVEQ #0,D0 ; load version number
- MOVEA.L 4,A6 ; load exec library address
- JSR OpenLibrary(A6) ; call OpenLibrary
- tst.l d0
- beq poiblank yes
- move.l d0,a6 ok?
- move.l gb_copinit(a6),a0 copper start-up
- lea copinit_sprstrtup(a0),a1 sprite data
-
- move.w spritesave,2(a1) top
- move.w spritesave+2,6(a1) bottom
-
- movea.l a6,A1 graphics Library
- movea.l 4,a6 exec base
- JSR CloseLibrary(A6) call CloseLibrary
-
-
- * move.w #$8020,$dff000+$96 turn on sprite dma
- poiblank
- move.l (sp)+,a0 restore
- poiblankn
- move.w #0,pointtimer zero pointer time
- rts
-
- intdone
- move.l ie_NextEvent(a0),d0 next event
- beq.s eventout none
- movea.l d0,a0
- bra nextevent look at next
- eventout
- tst.b eventadd add buttons?
- beq.s inputout no
- clr.b eventadd
- move.l #mouseevents,ie_NextEvent(a0) throw in buttons
- clr.b eventadd clear switch
- inputout
-
-
- movem.l (a7)+,a0-a6/d1-d7 restore
- move.l a0,d0 pass input event to next handler
- rts
-
-
- ********** subroutine to clear time buffer **********
-
- timeclear move.b #'0',(a2)+ clear
- move.b #'0',(a2)+ clear
- addq #1,a2
- move.b #'0',(a2)+ clear
- move.b #'0',(a2)+ clear
- addq #1,a2
- move.b #'0',(a2)+ clear
- move.b #'0',(a2) clear
- rts
-
- ************* subroutine to format memory display *******
-
- formatmem moveq #0,d1 clear
- move.l a2,-(a7) save a2
- MOVE.L #$30303030,(a2) clear
- move.b d0,d1 save low byte
- lsr.l #8,d0 divide by 256 first
- divu #3906,d0 get millions
- add.b d0,(a2)+ put into display buffer
- swap d0 get remainder
- ext.l d0
- divu #391,d0 get hundreds of thousands
- add.b d0,(a2)+ make it printable
- swap d0
- ext.l d0
- lsl.l #8,d0 get back the 256
- divu #10000,d0 get tens of thousands
- add.b d0,(a2)+ make it printable
- swap d0
- ext.l d0
- divu #1000,d0 get thousands
- add.b d0,(a2) make it printable
- moveq #3,d0 count
- move.l (a7)+,a2 restore
- 1$ cmpi.b #'0',(a2) is digit zero?
- bne.s 2$ no
- move.b #' ',(a2)+ blank it
- dbra d0,1$ next one
- 2$ rts
-
-
- ******** sub-routine to scan menus for changes
-
- menuscan
- * look at task priority
-
- moveq #7,d0
- moveq #0,d1
- lea priindex,a0 table of entries
- prsearch
- move.l (a0)+,a1 get address
- move.w (a1),d1 get check field
- andi.w #CHECKED,d1 is checked?
- bne gotpri yes
- dbra d0,prsearch
- bra prinochange
- gotpri
- moveq #7,d1
- sub.w d0,d1 get index
- lea newpri,a0
- moveq #0,d0
- move.b 0(a0,d1),d0 get new priority
- cmp.b priority,d0 changed?
- beq prinochange no
- move.b d0,priority save for save routine
- movea.l task,a1 my task
- movea.l 4,a6 exec base
- jsr SetTaskPri(a6) call SetTaskPri
-
- prinochange
-
- * look at refresh rate
-
- moveq #0,d1
- move.w ref1,d1
- moveq #0,d0
- andi.w #CHECKED,d1 is it checked?
- bne gotref yes
-
- move.w ref2,d1
- moveq #4,d0
- andi.w #CHECKED,d1 is it checked?
- bne gotref yes
-
- move.w ref3,d1
- moveq #8,d0
- andi.w #CHECKED,d1 is it checked?
- bne gotref yes
-
- moveq #12,d0
- gotref
-
- lea newref,a0 refresh table
- move.l 0(a0,d0),d1
- cmp.l refrate,d1 new refresh rate?
- beq norefchange
- move.l d1,refrate
- norefchange
-
- * look at window to front
-
- moveq #3,d0
- moveq #0,d1
- lea frontcheckr,a0 table of entries
- frsearch
- move.l (a0)+,a1 get address
- move.w (a1),d1 get check field
- andi.w #CHECKED,d1 is checked?
- bne gotwtf yes
- dbra d0,frsearch
- bra wtfnochange
- gotwtf
- moveq #3,d1
- sub.w d0,d1 get index
- cmp.b wtfcount,d1 changed?
- beq wtfnochange no
- move.b d1,wtfcount save
-
- wtfnochange
-
-
- * look at window to back
-
- moveq #3,d0
- moveq #0,d1
- lea backcheckr,a0 table of entries
- basearch
- move.l (a0)+,a1 get address
- move.w (a1),d1 get check field
- andi.w #CHECKED,d1 is checked?
- bne gotwtb yes
- dbra d0,basearch
- bra wtbnochange
- gotwtb
- moveq #3,d1
- sub.w d0,d1 get index
- cmp.b wtbcount,d1 changed?
- beq wtbnochange no
- move.b d1,wtbcount save
-
- wtbnochange
-
- * look at screen blank
-
-
- moveq #5,d0
- moveq #0,d1
- lea blankcheckr,a0 table of entries
- blsearch
- move.l (a0)+,a1 get address
- move.w (a1),d1 get check field
- andi.w #CHECKED,d1 is checked?
- bne gotbla yes
- dbra d0,blsearch
- bra blanknochange
- gotbla
- moveq #5,d1
- sub.w d0,d1 get index
- lsl.l #1,d1
- lea newblank,a0
- move.w 0(a0,d1),d0 get new blank time
- cmp.w blanktime,d0 changed?
- beq blanknochange no
-
- move.w d0,blanktime new screen blank time
- clr.w blanktimer start new interval
- blanknochange
-
- * look at pointer blank
-
- moveq #5,d0
- moveq #0,d1
- lea pointcheckr,a0 table of entries
- posearch
- move.l (a0)+,a1 get address
- move.w (a1),d1 get check field
- andi.w #CHECKED,d1 is checked?
- bne gotpoi yes
- dbra d0,posearch
- bra pointnochange
- gotpoi
- moveq #5,d1
- sub.w d0,d1 get index
- lsl.l #1,d1
- lea newpoint,a0
- move.w 0(a0,d1),d0 get new blank time
- cmp.w pointtime,d0 changed?
- beq pointnochange no
-
- move.w d0,pointtime new screen blank time
- clr.w pointtimer start new interval
- pointnochange
-
- * look at mouse speed
-
- moveq #5,d0
- moveq #0,d1
- lea mousecheck,a0 table of entries
- mosearch
- move.l (a0)+,a1 get address
- move.w (a1),d1 get check field
- andi.w #CHECKED,d1 is checked?
- bne gotmou yes
- dbra d0,mosearch
- bra mousenochange
- gotmou
- moveq #5,d1
- sub.w d0,d1 get index
- lea newmouse,a0
- move.b 0(a0,d1),d0 get new blank time
- cmp.b mousespeed,d0 changed?
- beq mousenochange no
-
- move.b d0,mousespeed new mouse speed
- mousenochange
-
- rts
-
- ****
- ******** Subroutine to read key definition file
-
-
- readkeys
- movem.l a0-a6/d1-d7,-(sp)
- move.l doslib,a6 dos base
- lea firstkey-2,a5 pointer to previous buffer
- lea keyfile,a0 name of save string
- move.l a0,d1 move into right reg
- move.l #MODE_OLDFILE,d2 old file
- jsr Open(a6) Open
- tst.l d0 file there?
- beq kret no
- move.l d0,keyhandle file handle
- moveq #0,d5
- nextbuffer
- move.l doslib,a6 put dos base back
- move.l #1000,d4 length expected
- lea keybuffer,a4
- moveq #0,d6 zero count
- readink
- addq #1,d6 increment count
- move.l a4,d2 data
- move.l #1,d3 data length
- move.l keyhandle,d1 handle
- jsr Read(a6) read it in
-
- tst.l d0 test result
- beq closeink eof
- bmi closeink error
- cmpi.b #$0a,(a4) end of line?
- beq gotline
- adda #1,a4 next
- dbra d4,readink
-
- gotline
- addq #1,d5 keep count
- cmpi.w #9,d6 minimum permissable length
- bcs keyerror get next
- move.l 4,a6 ExecBase
- add.w #9,d6 buffer size difference
- move.l d6,d0
- move.l #MEMF_CLEAR+MEMF_PUBLIC,d1
- jsr AllocMem(A6)
- tst.l d0 got some?
- beq closeink no **** error ***
- move.l d0,2(a5) store current buffer address in previous
- move.l d0,a5 make previous the current
- move.l d0,d7 save start
- move.w d6,(a5) store length
- adda.l #4,a5 room for pointer to next
- **
- ** test for qualifiers
- **
- lea keybuffer+1,a3 get first qualifier
- move.w #0,2(a5) set to no qualifier ** remove RELATIVE MOUSE
- cmpi.w #'\\',keybuffer no qualifiers?
- beq testkeycode
-
- nextqual
- lea qualifiers,a2 get all qualifiers
- qualloop
- cmpi.b #$ff,(a2) end yet?
- beq keyerror ****** error *********
- clc (a3),(a2),3 are these the same
- beq.s gotqual yes
- adda.l #6,a2 next qualifier
- bra.s qualloop
- gotqual
- move.w 4(a2),d0 get qualifier
- or.w d0,2(a5) set bit for qualifier
- nextqual2
- adda.l #3,a3 next key qualifier
- cmpi.b #'\',(a3) end of qualifiers?
- beq testkeycode yes
- cmpi.b #',',(a3) correct delimiter?
- bne keyerror no ******** error ********
- adda.l #1,a3 next one
- bra.s nextqual
- testkeycode
- adda.l #1,a3 get to key field
- cmpi.b #'\',1(a3) is it a 1 letter sequence?
- beq.s doonekey yes
- cmpi.b #'\',3(a3) is it a 3 letter sequence?
- beq testspecial yes - test for special key
- bra keyerror ************ error ***********
- doonekey
- move.b (a3),d0
- bsr rawtrans
-
- move.b d0,4(a5) move in raw key code
- adda.l #1,a3 next field
- bra movestring move in string
-
- ** translate key into raw key code
- ** d0 contains key for translation
-
- rawtrans
- move.l a0,-(sp)
- lea rawkeys,a0 get raw key codes
- 1$ cmpi.b #$ff,(a0) end of table - unknown key
- beq noraw ******** error ********
- cmp.b (a0),d0 found?
- beq.s foundraw yes
- adda.l #2,a0 next
- bra.s 1$
- foundraw
- moveq #0,d0
- move.b 1(a0),d0 set up character
- move.l (sp)+,a0
- rts
- noraw
- move.l (sp)+,a0
- moveq #0,d0
- rts
-
-
- ** translate special key into raw key code
-
- testspecial
- lea funnykeys,a2 get special keys
- nextspec
- cmpi.b #$ff,(a2) end?
- beq keyerror yes *********** error *********
- clc (a3),(a2),3 equal?
- beq gotfunny yes
- adda.l #4,a2 next entry
- bra nextspec
- gotfunny
- move.b 3(a2),4(a5) move in funny key code
- adda.l #3,a3 next field
- **
- ** move string into buffer
- **
- movestring
- move.l #950,d6 set a maximum to avoid loop
- adda.l #5,a5 string area
- cmpi.b #'\',(a3) got delimeter?
- bne keyerror no ********** error **********
- adda.l #1,a3 first character
- movechar
- cmpi.b #'\',(a3) got delimeter?
- beq stringend finished
- cmpi.b #$0a,(a3) end?
- beq stringend finished
- cmpi.b #'^',(a3) got ctrl?
- bne.s notctrl no
- adda.l #1,a3 next character
- cmpi.b #'^',(a3) allow ^
- beq.s notctrl no
- cmpi.b #'\',(a3) allow \
- beq.s notctrl no
- andi.b #$1f,(a3) convert
- notctrl
- move.b (a3)+,(a5)+ move it in
- dbra d6,movechar
- bra keyerror
-
- stringend
- move.b #$fe,(a5)+ end of buffer
- move.b 1(a3),(a5) move in keep/replace field
- ori.b #$20,(a5) make it small
- move.b 3(a3),1(a5) move in command/string field
- ori.b #$20,1(a5) make it small
- cmpi.b #'\',4(a3) is there a delay field?
- bne.s 1$ no
- move.b 5(a3),2(a5) move in delay
- 1$ move.b #$ff,3(a5) end of buffer
- move.l d7,a5 back to start of buffer
- bra nextbuffer
- keyerror
- move.l intuit,a6 intuition base
- move.l windowpoint,a0
- lea keyerrortext,a1
- lea oktext,a2
- lea oktext,a3
- moveq #0,d0 flags
- moveq #0,d1 "
- move.l #300,d2 width
- move.l #70,d3 height
- divu #10,d5 convert to decimal
- or.b #$30,d5 convert to ascii
- move.b d5,statement move to message
- swap d5
- or.b #$30,d5 convert to ascii
- move.b d5,statement+1 move to message
- jsr AutoRequest(a6)
-
- closeink
- move.l doslib,a6
- move.l keyhandle,d1
- jsr Close(a6) close file
- kret movem.l (sp)+,a0-a6/d1-d7
- rts
-
- **
- ** Subroutine to free memory used by key mapping routines
- **
-
- freekeymem
- movem.l a0-a6/d1-d7,-(sp)
- tst.l firstkey any keys?
- beq.s freekeyout
- move.l 4,a6 get execbase
- move.l firstkey,a1 address of first buffer
- 1$ moveq #0,d0
- move.w (a1),d0 length
- move.l 2(a1),d7 next buffer
- jsr FreeMem(A6) call FreeMem
- tst.l d7 end?
- beq.s freekeyout yes
- move.l d7,a1 next one
- bra.s 1$
- freekeyout
- clr.l firstkey
- movem.l (sp)+,a0-a6/d1-d7
- rts
-
- ********** Subroutine to submit characters to the input device
-
- * a0=address of string
- * d0=length of string
- * d7=delay between each character.
-
- subchars
- movem.l a1-a3/d6,-(sp)
- move.l a0,a3 string
- move.l d0,d6 length
- subq #1,d6
- nextinchar
- move.b (a3),d0 set up for raw translate
- bsr rawtrans translate to raw keys
- setbyte2
- lea event,a2
- lea inputreq,a1 IOReq
- move.w #$8000,ie_Qualifier(a2) set to no shift
- move.b d0,ie_Code+1(a2)
- and.b #$80,d0 shifted?
- beq.s norcode2 no
- and.b #$7f,ie_Code+1(a2) turn off shift bit
- or.w #IEQUALIFIER_LSHIFT,ie_Qualifier(a2) set to shifted
- norcode2
- move.b #IECLASS_RAWKEY,ie_Class(a2)
- move.l a2,IO_DATA(a1)
- move.l #ie_SIZEOF,IO_LENGTH(a1) set length
- move.w #IND_WRITEEVENT,IO_COMMAND(a1)
- jsr DoIO(a6)
- adda.l #1,a3 next byte
- tst.l d7 delay?
- bne delinp
- nexsub dbra d6,nextinchar no
- movem.l (sp)+,a1-a3/d6
- rts
- *******
- *** Delay submission of characters
- delinp
- movem.l a0/a5/a1,-(sp)
- lea pause,a1 new ioreq
- move.l a5,a0 old ioreq
- moveq #IOTV_SIZE/4-1,d0
- 1$
- move.l (a0)+,(a1)+
- dbra d0,1$
- lea pause,a1
- MOVE.W #TR_ADDREQUEST,IO_COMMAND(A1) IO_COMMAND = TR_ADDREQUEST(9)
- MOVE.l #0,IO_SIZE+TV_SECS(A1) TV_SECS = $01(01 seconds) ||dj
- MOVE.L d7,IO_SIZE+TV_MICRO(A1) TV_MICRO= specified time
- movea.l 4,a6 set Exec base
- JSR DoIO(A6) wait
-
- movem.l (sp)+,a0/a5/a1
- bra nexsub
-
- *************************************************************************
- * *
- * *
- * *
- * Date subroutine *
- * *
- *************************************************************************
- *
- *
- *
- dosregs reg d0-d7/a0-a6 ;registers from dos entry point
- EBASE equr a6 ;exec.library
- DBASE equr a4 ;dos.library
- *
- *
- getdate
- movem.l dosregs,-(sp) ;save registers at entry time
- *
- * open libraries which will be used thoughout the application
- *
- move.l 4,EBASE ;exec.library is provided to us
- lea dosname,a1
- moveq #0,d0
- jsr OpenLibrary(a6)
- move.l d0,a6 save dos library
- *
- * get system date and time. the first two longwords returned
- * represent the number of days since January 1, 1978, and the
- * number of seconds since midnight.
- *
- move.l #dosdate,d1
- jsr DateStampx(a6)
- *
- * calculate the current year
- *
- move.l dosdate,d4 ;number of days since 78-01-01
- addq.l #1,d4 ;correction offset
- moveq #2,d5 ;counter for leap years
- moveq #78,d2 ;counter for year
- year1 move.l #365,d3 ;assume this year has 365 days
- and.b #$03,d5 ;but if leap year...
- bne.s year2
- addq.l #1,d3 ;make it 366
- year2 cmp.l d3,d4 ;have we found correct year?
- ble.s year3
- sub.l d3,d4 ;no, reduce by 365 or 366
- addq.w #1,d2 ;try next year
- addq.b #1,d5 ;bump leap year modulo 4
- bra.s year1
- year3 move.l d2,d1 ;this is 19xx
- lea dyy,a0 ;receiving area
- bsr binasc ;fill in xx part
- *
- * calculate the current month
- *
- lea days,a2 ;regular table of days in each month
- and.b #$03,d5
- bne.s month1
- lea dayslp,a2 ;alternate version for leap year
- month1 moveq #1,d2 ;counter for month
- month2 cmp.w (a2),d4 ;have we found proper month?
- ble.s month3
- sub.w (a2)+,d4 ;no, reduce # days
- addq.b #1,d2 ;count month
- bra.s month2
- month3 move.l d2,d1 ;this is the month
- subq #1,d1 make it an offset
- lsl.l #2,d1 *4
- lea months(d1),a0 get month
- mvc (a0),mmm,3 move in month
-
-
- * lea dmm,a0 ;receiving area
- * bsr binasc ;store 2 ascii digits
- *
- * the current day is whatever is left over
- *
- move.l d4,d1 ;this is the day
- lea ddd,a0 ;receiving area
- bsr binasc ;store 2 ascii digits
- *
- * calculate hours
- *
- lea thh,a0 ;receiving area
- move.l dosdate+4,d1 ;number of minutes since midnight
- divu #60,d1 ;calculate number of hours
- move.l d1,d2 ;save remainder
- bsr binasc
- addq.l #1,a0 ;skip over colon
- move.l d2,d1 ;get minutes
- swap d1
- bsr binasc
- *
- *
- wrapup
- *
- *
- MOVE.L a6,a1 dos Library
- movea.l 4,a6 Exec base
- jsr CloseLibrary(A6) call CloseLibrary
- *
- Finish
- cmpi.b #'0',ddd 1st byte 0?
- bne.s 1$ no
- move.b #' ',ddd make it blank
-
- 1$ movem.l (sp)+,dosregs ;restore registers as of entry
- rts
- *
- *************************************************************************
- * *
- * binasc -- output 2 ascii digits *
- * *
- *************************************************************************
- *
- * a0 pointer to receiving area
- * d1 binary value to convert
- * d0 scratch
- *
- binasc move.b #'0',d0 ;ascii zero
- ext.l d1
- divu #10,d1 ;10's digit
- add.b d0,d1
- move.b d1,(a0)+
- swap d1 ;1's digit
- add.b d0,d1
- move.b d1,(a0)+
- rts
- cnop 0,2
- months
- dc.b 'Jan '
- dc.b 'Feb '
- dc.b 'Mar '
- dc.b 'Apr '
- dc.b 'May '
- dc.b 'Jun '
- dc.b 'Jul '
- dc.b 'Aug '
- dc.b 'Sep '
- dc.b 'Oct '
- dc.b 'Nov '
- dc.b 'Dec '
- *
- * days in each month (normal year)
- *
- days dc.w 31
- dc.w 28
- dc.w 31
- dc.w 30
- dc.w 31
- dc.w 30
- dc.w 31
- dc.w 31
- dc.w 30
- dc.w 31
- dc.w 30
- dc.w 31
- *
- * days in each month (leap year)
- *
- dayslp dc.w 31
- dc.w 29
- dc.w 31
- dc.w 30
- dc.w 31
- dc.w 30
- dc.w 31
- dc.w 31
- dc.w 30
- dc.w 31
- dc.w 30
- dc.w 31
- *
- * dos stuff
- *
- cnop 0,4
- dosdate ds.l 3 ;internal date/time
- pchand ds.l 1
- pcfile dc.b 'df0:pc/pcdate',0
- *
- * date and time record
- *
- cnop 0,4
- datefield
- ddd dc.b 'dd '
- mmm dc.b 'mmm 19'
- dyy dc.b 'yy'
- dc.b $0a
- dc.b 'time '
- thh dc.b 'hh:'
- tmm dc.b 'mm'
- dc.b $0a
-
- ********
- *************** Window for reading new keys *************
- cnop 0,2
- keywindow
- dc.w 100 left edge
- dc.w 20 top edge
- dc.w 300 width
- dc.w 40 Height
- dc.b 3 detail pen
- dc.b 2 block pen
- dc.l GADGETUP+ACTIVEWINDOW IDCMPflags
- dc.l WINDOWDRAG+NOCAREREFRESH+ACTIVATE flags
- dc.l gad0 first gadget
- dc.l 0 check mark
- dc.l 0 title
- dc.l 0 screen
- dc.l 0 bit map
- dc.w 0 minimum width
- dc.w 0 minimum height
- dc.w 0 max width
- dc.w 0 max height
- dc.w 1 workbench
-
-
- gad0 dc.l gad1 next gadget
- dc.w 8 left edge
- dc.w 25 top edge
- dc.w 286 width
- dc.w 8 height
- dc.w GADGHCOMP flags
- dc.w RELVERIFY activation flags
- dc.w STRGADGET type
- dc.l border border structure
- dc.l 0 SelectRender
- dc.l 0 GadgetText
- dc.l 0 MutualExclude
- dc.l stringinfo SpecialInfo
- dc.w 0 GadgetID
- dc.l 0 UserData
-
- border
-
- dc.w 0 left edge
- dc.w 0 top edge
- dc.b 2 front pen
- dc.b 0 back pen
- dc.b RP_JAM1 drawing mode
- dc.b 5 no. of coordinates
- dc.l coords pointer to coordinates
- dc.l 0 next border
-
- coords dc.w -4,-2
- dc.w -4,9
- dc.w 286,9
- dc.w 286,-2
- dc.w -4,-2
-
-
- cnop 0,2
- stringinfo
-
- dc.l keyfilebuf si_Buffer ; the buffer containing the start and final string
- dc.l undobuf si_UndoBuffer ; optional buffer for undoing current entry
- dc.w 0 si_BufferPos ; character position in Buffer
- dc.w 80 si_MaxChars ; max number of chars in Buffer (including NULL)
- dc.w 0 si_DispPos ; Buffer position of first displayed character
-
- ; Intuition initializes and maintains these variables for you
- dc.w 0 si_UndoPos ; character position in the undo buffer
- dc.w 0 si_NumChars ; number of characters currently in Buffer
- dc.w 0 si_DispCount ; number of whole characters visible in Container
- dc.w 1 si_CLeft ; topleft offset of the container
- dc.w 0 si_CTop ; topleft offset of the container
- dc.l 0 si_LayerPtr ; the RastPort containing this Gadget
-
- dc.l 0 si_AltKeyMap
-
-
- cnop 0,2 align
- keytext
- DC.B 3,0,1,0
- DC.W 2,12
- DC.L 0,keymsg,0
-
- cnop 0,2 align
-
- keymsg dc.b ' Enter filename:',0
- cnop 0,2 align
-
- gad1 dc.l 0 next gadget
- dc.w 230 left edge
- dc.w 12 top edge
- dc.w 48 width
- dc.w 8 height
- dc.w GADGHCOMP flags
- dc.w RELVERIFY activation flags
- dc.w BOOLGADGET type
- dc.l 0 border structure
- dc.l 0 SelectRender
- dc.l gad1text GadgetText
- dc.l 0 MutualExclude
- dc.l 0 SpecialInfo
- dc.w 1 GadgetID
- dc.l 0 UserData
-
- *
- cnop 0,2
- gad1text dc.b 2,1,RP_JAM2,0
- dc.w 0,0
- dc.l 0,g1text,0
-
- cnop 0,2
- g1text dc.b 'Cancel',0
-
-
-
- ***************************************************
- ****************** window structure **********************
-
-
-
- window dc.w 343 left edge
- dc.w 1 top edge
- dc.w 184 width
- newwindowheight
- dc.w 7 Height
- dc.b 0 detail pen
- dc.b 1 block pen
- dc.l ACTIVEWINDOW+INACTIVEWINDOW+MOUSEBUTTONS+MENUPICK IDCMPflags
- dc.l WINDOWDRAG+NOCAREREFRESH+BORDERLESS flags
- dc.l 0 first gadget
- dc.l 0 check mark
- dc.l 0 title
- dc.l 0 screen
- dc.l 0 bit map
- dc.w 0 minimum width
- dc.w 0 minimum height
- dc.w 0 max width
- dc.w 0 max height
- dc.w 1 workbench
-
-
- ******************** menu structures ********************
-
-
- menu0 dc.l 0 next menu
- dc.w 270 left
- dc.w 0 top
- dc.w 62 width
- dc.w 0 height
- dc.w MENUENABLED flags
- dc.l menu0name name
- dc.l menuitem0 1st item
- dc.w 0,0,0,0 internal
-
- mendep equ 11 menu depth
- mainw equ 140
- menuitem0 dc.l menuitem1 next menu item
- dc.w -110 left
- dc.w 0 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname0 item fill
- dc.l 0 select fill
- dc.b 'n' command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname0 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext0 text
- dc.l 0 next text
-
- itext0 dc.b ' NewCLI ',0
-
- menuitem1 dc.l menuitem2 next menu item
- dc.w -110 left
- dc.w mendep top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname1 item fill
- dc.l 0 select fill
- dc.b 'd' command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 Nfont
- memtext dc.l itext1 text
- dc.l 0 next text
-
- itext1 dc.b ' Chip/Fast ',0
- itext1b dc.b ' Total Memory ',0
- menuitem2 dc.l menuitem3 next menu item
- dc.w -110 left
- dc.w mendep*2 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l sub1 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname2 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext2 text
- dc.l 0 next text
-
- itext2 dc.b ' Colour ',0
-
-
-
- menuitem3 dc.l menuitem4 next menu item
- dc.w -110 left
- dc.w mendep*3 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l subp1 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname3 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext3 text
- dc.l 0 next text
-
- itext3 dc.b ' Priority ',0
-
- priw equ 24+CHECKWIDTH
-
- subp1 dc.l subp2 next menu item
- dc.w -2*priw left
- dc.w 0 top
- dc.w priw width
- dc.w mendep height
- prich1 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffe mutual exclude
- dc.l subnamep1 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamep1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextp1 text
- dc.l 0 next text
-
- subtextp1 dc.b '-3 ',0
-
-
- subp2 dc.l subp3 next menu item
- dc.w -2*priw left
- dc.w mendep top
- dc.w priw width
- dc.w mendep height
- prich2 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffd mutual exclude
- dc.l subnamep2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamep2 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextp2 text
- dc.l 0 next text
-
- subtextp2 dc.b '-2 ',0
-
- subp3 dc.l subp4 next menu item
- dc.w -2*priw left
- dc.w mendep*2 top
- dc.w priw width
- dc.w mendep height
- prich3 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffb mutual exclude
- dc.l subnamep3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamep3 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextp3 text
- dc.l 0 next text
-
- subtextp3 dc.b '-1 ',0
-
-
- subp4 dc.l subp5 next menu item
- dc.w -2*priw left
- dc.w mendep*3 top
- dc.w priw width
- dc.w mendep height
- prich4 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fff7 mutual exclude
- dc.l subnamep4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamep4 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextp4 text
- dc.l 0 next text
-
- subtextp4 dc.b ' 0 ',0
-
-
- subp5 dc.l subp6 next menu item
- dc.w -priw left
- dc.w 0 top
- dc.w priw width
- dc.w mendep height
- prich5 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffef mutual exclude
- dc.l subnamep5 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamep5 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextp5 text
- dc.l 0 next text
-
- subtextp5 dc.b '+1 ',0
-
-
- subp6 dc.l subp7 next menu item
- dc.w -priw left
- dc.w mendep top
- dc.w priw width
- dc.w mendep height
- prich6 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffdf mutual exclude
- dc.l subnamep6 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamep6 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextp6 text
- dc.l 0 next text
-
- subtextp6 dc.b '+2 ',0
-
-
- subp7 dc.l subp8 next menu item
- dc.w -priw left
- dc.w mendep*2 top
- dc.w priw width
- dc.w mendep height
- prich7 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffbf mutual exclude
- dc.l subnamep7 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamep7 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextp7 text
- dc.l 0 next text
-
- subtextp7 dc.b '+3 ',0
-
-
- subp8 dc.l 0 next menu item
- dc.w -priw left
- dc.w mendep*3 top
- dc.w priw width
- dc.w mendep height
- prich8 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ff7f mutual exclude
- dc.l subnamep8 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamep8 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextp8 text
- dc.l 0 next text
-
- subtextp8 dc.b '+4 ',0
-
-
-
- colourw equ 74
-
- sub1 dc.l sub2 next menu item
- dc.w -colourw*2 left
- dc.w 0 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname1 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext1 text
- dc.l 0 next text
-
- subtext1 dc.b 'Colour 1 ',0
-
-
- sub2 dc.l sub3 next menu item
- dc.w -colourw*2 left
- dc.w mendep top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname2 dc.b 2 front pen
- dc.b 1 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext2 text
- dc.l 0 next text
-
- subtext2 dc.b 'Colour 2 ',0
-
-
- sub3 dc.l sub4 next menu item
- dc.w -colourw*2 left
- dc.w mendep*2 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname3 dc.b 3 front pen
- dc.b 1 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext3 text
- dc.l 0 next text
-
- subtext3 dc.b 'Colour 3 ',0
-
-
- sub4 dc.l sub5 next menu item
- dc.w -colourw*2 left
- dc.w mendep*3 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname4 dc.b 1 front pen
- dc.b 0 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext4 text
- dc.l 0 next text
-
- subtext4 dc.b 'Colour 4 ',0
-
-
- sub5 dc.l sub6 next menu item
- dc.w -colourw*2 left
- dc.w mendep*4 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname5 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname5 dc.b 2 front pen
- dc.b 0 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext5 text
- dc.l 0 next text
-
- subtext5 dc.b 'Colour 5 ',0
-
-
- sub6 dc.l sub7 next menu item
- dc.w -colourw*2 left
- dc.w mendep*5 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname6 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname6 dc.b 3 front pen
- dc.b 0 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext6 text
- dc.l 0 next text
-
- subtext6 dc.b 'Colour 6 ',0
-
-
- sub7 dc.l sub8 next menu item
- dc.w -colourw left
- dc.w 0 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname7 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname7 dc.b 0 front pen
- dc.b 2 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext7 text
- dc.l 0 next text
-
- subtext7 dc.b 'Colour 7 ',0
-
-
- sub8 dc.l sub9 next menu item
- dc.w -colourw left
- dc.w mendep top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname8 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname8 dc.b 1 front pen
- dc.b 2 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext8 text
- dc.l 0 next text
-
- subtext8 dc.b 'Colour 8 ',0
-
-
- sub9 dc.l sub10 next menu item
- dc.w -colourw left
- dc.w mendep*2 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname9 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname9 dc.b 3 front pen
- dc.b 2 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext9 text
- dc.l 0 next text
-
- subtext9 dc.b 'Colour 9 ',0
-
-
- sub10 dc.l sub11 next menu item
- dc.w -colourw left
- dc.w mendep*3 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname10 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname10 dc.b 0 front pen
- dc.b 3 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext10 text
- dc.l 0 next text
-
- subtext10 dc.b 'Colour 10',0
-
-
- sub11 dc.l sub12 next menu item
- dc.w -colourw left
- dc.w mendep*4 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname11 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname11 dc.b 1 front pen
- dc.b 3 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext11 text
- dc.l 0 next text
-
- subtext11 dc.b 'Colour 11',0
-
-
- sub12 dc.l 0 next menu item
- dc.w -colourw left
- dc.w mendep*5 top
- dc.w colourw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHBOX flags
- dc.l 0 mutual exclude
- dc.l subname12 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subname12 dc.b 2 front pen
- dc.b 3 back pen
- dc.b RP_JAM2 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subtext12 text
- dc.l 0 next text
-
- subtext12 dc.b 'Colour 12',0
-
- menuitem4 dc.l menuitem5 next menu item
- dc.w -110 left
- dc.w mendep*4 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l subr1 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname4 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext4 text
- dc.l 0 next text
-
- itext4 dc.b ' Refresh ',0
- refw equ 80+CHECKWIDTH
- subr1 dc.l subr2 next menu item
- dc.w -refw left
- dc.w 0 top
- dc.w refw width
- dc.w mendep height
- ref1 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fe mutual exclude
- dc.l subnamer1 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamer1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextr1 text
- dc.l 0 next text
-
- subtextr1 dc.b '10 per sec',0
-
-
- subr2 dc.l subr3 next menu item
- dc.w -refw left
- dc.w mendep top
- dc.w refw width
- dc.w mendep height
- ref2 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fd mutual exclude
- dc.l subnamer2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamer2 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextr2 text
- dc.l 0 next text
-
- subtextr2 dc.b ' 5 per sec',0
-
-
- subr3 dc.l subr4 next menu item
- dc.w -refw left
- dc.w mendep*2 top
- dc.w refw width
- dc.w mendep height
- ref3 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fb mutual exclude
- dc.l subnamer3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamer3 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextr3 text
- dc.l 0 next text
-
- subtextr3 dc.b ' 2 per sec',0
-
-
- subr4 dc.l 0 next menu item
- dc.w -refw left
- dc.w mendep*3 top
- dc.w refw width
- dc.w mendep height
- ref4 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $f7 mutual exclude
- dc.l subnamer4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamer4 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextr4 text
- dc.l 0 next text
-
- subtextr4 dc.b ' 1 per sec',0
-
- menuitem5 dc.l menuitem6 next menu item
- dc.w -110 left
- dc.w mendep*5 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname5 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l subb1 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname5 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext5 text
- dc.l 0 next text
-
- itext5 dc.b ' Blank Screen ',0
-
- blaw equ 32+CHECKWIDTH
-
- subb1 dc.l subb2 next menu item
- dc.w -2*blaw left
- dc.w 0 top
- dc.w blaw width
- dc.w mendep height
- blach1 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffe mutual exclude
- dc.l subnameb1 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameb1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextb1 text
- dc.l 0 next text
-
- subtextb1 dc.b 'OFF ',0
-
-
- subb2 dc.l subb3 next menu item
- dc.w -2*blaw left
- dc.w mendep top
- dc.w blaw width
- dc.w mendep height
- blach2 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffd mutual exclude
- dc.l subnameb2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameb2 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextb2 text
- dc.l 0 next text
-
- subtextb2 dc.b ' 5 ',0
-
- subb3 dc.l subb4 next menu item
- dc.w -2*blaw left
- dc.w mendep*2 top
- dc.w blaw width
- dc.w mendep height
- blach3 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffb mutual exclude
- dc.l subnameb3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameb3 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextb3 text
- dc.l 0 next text
-
- subtextb3 dc.b '10 ',0
-
-
- subb4 dc.l subb5 next menu item
- dc.w -blaw left
- dc.w 0 top
- dc.w blaw width
- dc.w mendep height
- blach4 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fff7 mutual exclude
- dc.l subnameb4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameb4 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextb4 text
- dc.l 0 next text
-
- subtextb4 dc.b '20 ',0
-
-
- subb5 dc.l subb6 next menu item
- dc.w -blaw left
- dc.w mendep top
- dc.w blaw width
- dc.w mendep height
- blach5 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffef mutual exclude
- dc.l subnameb5 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameb5 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextb5 text
- dc.l 0 next text
-
- subtextb5 dc.b '30 ',0
-
-
- subb6 dc.l 0 next menu item
- dc.w -blaw left
- dc.w mendep*2 top
- dc.w blaw width
- dc.w mendep height
- blach6 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffdf mutual exclude
- dc.l subnameb6 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameb6 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextb6 text
- dc.l 0 next text
-
- subtextb6 dc.b '40 ',0
-
-
-
- menuitem6 dc.l menuitem7 next menu item
- dc.w -110 left
- dc.w mendep*6 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname6 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l subo1 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname6 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext6 text
- dc.l 0 next text
-
- itext6 dc.b ' Blank Pointer ',0
-
-
- subo1 dc.l subo2 next menu item
- dc.w -2*blaw left
- dc.w 0 top
- dc.w blaw width
- dc.w mendep height
- poich1 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffe mutual exclude
- dc.l subnameo1 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameo1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtexto1 text
- dc.l 0 next text
-
- subtexto1 dc.b 'OFF ',0
-
-
- subo2 dc.l subo3 next menu item
- dc.w -2*blaw left
- dc.w mendep top
- dc.w blaw width
- dc.w mendep height
- poich2 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffd mutual exclude
- dc.l subnameo2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameo2 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtexto2 text
- dc.l 0 next text
-
- subtexto2 dc.b ' 5 ',0
-
- subo3 dc.l subo4 next menu item
- dc.w -2*blaw left
- dc.w mendep*2 top
- dc.w blaw width
- dc.w mendep height
- poich3 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffb mutual exclude
- dc.l subnameo3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameo3 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtexto3 text
- dc.l 0 next text
-
- subtexto3 dc.b '10 ',0
-
-
- subo4 dc.l subo5 next menu item
- dc.w -blaw left
- dc.w 0 top
- dc.w blaw width
- dc.w mendep height
- poich4 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fff7 mutual exclude
- dc.l subnameo4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameo4 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtexto4 text
- dc.l 0 next text
-
- subtexto4 dc.b '20 ',0
-
-
- subo5 dc.l subo6 next menu item
- dc.w -blaw left
- dc.w mendep top
- dc.w blaw width
- dc.w mendep height
- poich5 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffef mutual exclude
- dc.l subnameo5 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameo5 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtexto5 text
- dc.l 0 next text
-
- subtexto5 dc.b '30 ',0
-
-
- subo6 dc.l 0 next menu item
- dc.w -blaw left
- dc.w mendep*2 top
- dc.w blaw width
- dc.w mendep height
- poich6 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffdf mutual exclude
- dc.l subnameo6 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnameo6 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtexto6 text
- dc.l 0 next text
-
- subtexto6 dc.b '40 ',0
-
-
-
- menuitem7 dc.l menuitem8 next menu item
- dc.w -110 left
- dc.w mendep*7 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname7 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l subm1 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname7 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext7 text
- dc.l 0 next text
-
- itext7 dc.b ' Mouse Speed ',0
-
-
- subm1 dc.l subm2 next menu item
- dc.w -2*blaw left
- dc.w 0 top
- dc.w blaw width
- dc.w mendep height
- mouch1 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffe mutual exclude
- dc.l subnamem1 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamem1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextm1 text
- dc.l 0 next text
-
- subtextm1 dc.b '1 ',0
-
-
- subm2 dc.l subm3 next menu item
- dc.w -2*blaw left
- dc.w mendep top
- dc.w blaw width
- dc.w mendep height
- mouch2 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffd mutual exclude
- dc.l subnamem2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamem2 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextm2 text
- dc.l 0 next text
-
- subtextm2 dc.b '2 ',0
-
- subm3 dc.l subm4 next menu item
- dc.w -2*blaw left
- dc.w mendep*2 top
- dc.w blaw width
- dc.w mendep height
- mouch3 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fffb mutual exclude
- dc.l subnamem3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamem3 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextm3 text
- dc.l 0 next text
-
- subtextm3 dc.b '3 ',0
-
-
- subm4 dc.l subm5 next menu item
- dc.w -blaw left
- dc.w 0 top
- dc.w blaw width
- dc.w mendep height
- mouch4 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fff7 mutual exclude
- dc.l subnamem4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamem4 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextm4 text
- dc.l 0 next text
-
- subtextm4 dc.b '4 ',0
-
-
- subm5 dc.l subm6 next menu item
- dc.w -blaw left
- dc.w mendep top
- dc.w blaw width
- dc.w mendep height
- mouch5 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffef mutual exclude
- dc.l subnamem5 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamem5 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextm5 text
- dc.l 0 next text
-
- subtextm5 dc.b '5 ',0
-
-
- subm6 dc.l 0 next menu item
- dc.w -blaw left
- dc.w mendep*2 top
- dc.w blaw width
- dc.w mendep height
- mouch6 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $ffdf mutual exclude
- dc.l subnamem6 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subnamem6 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextm6 text
- dc.l 0 next text
-
- subtextm6 dc.b '6 ',0
-
-
- menuitem8 dc.l menuitem9 next menu item
- dc.w -110 left
- dc.w mendep*8 top
- dc.w mainw width
- dc.w mendep height
- frontcheck dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l 0 mutual exclude
- dc.l itemname8 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l subf1 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname8 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext8 text
- dc.l 0 next text
-
- itext8 dc.b ' Click to Front',0
-
- frontf equ 70+CHECKWIDTH
-
- subf1 dc.l subf2 next menu item
- dc.w -frontf left
- dc.w 0 top
- dc.w frontf width
- dc.w mendep height
- frontf1 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fe mutual exclude
- dc.l subenamef1 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
-
- cnop 0,2 align
-
- subenamef1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextf1 text
- dc.l 0 next text
-
- subtextf1 dc.b 'OFF ',0
-
-
- subf2 dc.l subf3 next menu item
- dc.w -frontf left
- dc.w mendep top
- dc.w frontf width
- dc.w mendep height
- frontf2 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fd mutual exclude
- dc.l subenamef2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subenamef2 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextf2 text
- dc.l 0 next text
-
- subtextf2 dc.b '1 Click ',0
-
-
- subf3 dc.l subf4 next menu item
- dc.w -frontf left
- dc.w mendep*2 top
- dc.w frontf width
- dc.w mendep height
- frontf3 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fb mutual exclude
- dc.l subenamef3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subenamef3 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextf3 text
- dc.l 0 next text
-
- subtextf3 dc.b '2 Clicks',0
-
-
- subf4 dc.l 0 next menu item
- dc.w -frontf left
- dc.w mendep*3 top
- dc.w frontf width
- dc.w mendep height
- frontf4 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $f7 mutual exclude
- dc.l subenamef4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subenamef4 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextf4 text
- dc.l 0 next text
-
- subtextf4 dc.b '3 Clicks',0
-
-
-
- menuitem9 dc.l menuitem10 next menu item
- dc.w -110 left
- dc.w mendep*9 top
- dc.w mainw width
- dc.w mendep height
- backcheck dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l 0 mutual exclude
- dc.l itemname9 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l subu1 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname9 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext9 text
- dc.l 0 next text
-
- itext9 dc.b ' Click to Back ',0
-
-
- backf equ 70+CHECKWIDTH
-
- subu1 dc.l subu2 next menu item
- dc.w -backf left
- dc.w 0 top
- dc.w backf width
- dc.w mendep height
- backf1 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fe mutual exclude
- dc.l subenameu1 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
-
- cnop 0,2 align
-
- subenameu1 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextu1 text
- dc.l 0 next text
-
- subtextu1 dc.b 'OFF ',0
-
-
- subu2 dc.l subu3 next menu item
- dc.w -backf left
- dc.w mendep top
- dc.w backf width
- dc.w mendep height
- backf2 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fd mutual exclude
- dc.l subenameu2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subenameu2 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextu2 text
- dc.l 0 next text
-
- subtextu2 dc.b '1 Click ',0
-
-
- subu3 dc.l subu4 next menu item
- dc.w -backf left
- dc.w mendep*2 top
- dc.w backf width
- dc.w mendep height
- backf3 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $fb mutual exclude
- dc.l subenameu3 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subenameu3 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextu3 text
- dc.l 0 next text
-
- subtextu3 dc.b '2 Clicks',0
-
-
- subu4 dc.l 0 next menu item
- dc.w -backf left
- dc.w mendep*3 top
- dc.w backf width
- dc.w mendep height
- backf4 dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT flags
- dc.l $f7 mutual exclude
- dc.l subenameu4 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subenameu4 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l subtextu4 text
- dc.l 0 next text
-
- subtextu4 dc.b '3 Clicks',0
-
-
- menuitem10 dc.l menuitem11 next menu item
- dc.w mainw-110 left
- dc.w mendep*0 top
- dc.w mainw width
- dc.w mendep height
- suncheck dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT+MENUTOGGLE flags
- dc.l 0 mutual exclude
- dc.l itemname10 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname10 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH
- dc.w 2 top
- dc.l 0 font
- dc.l itext10 text
- dc.l 0 next text
-
- itext10 dc.b ' Sun Mouse ',0
-
-
-
- menuitem11 dc.l menuitem12 next menu item
- dc.w mainw-110 left
- dc.w mendep*1 top
- dc.w mainw width
- dc.w mendep height
- cyclecheck dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT+MENUTOGGLE flags
- dc.l 0 mutual exclude
- dc.l itemname11 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname11 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l itext11 text
- dc.l 0 next text
-
- itext11 dc.b ' Screen Cycle ',0
-
-
- menuitem12 dc.l menuitem13 next menu item
- dc.w mainw-110 left
- dc.w mendep*2 top
- dc.w mainw width
- dc.w mendep height
- keycheck dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT+MENUTOGGLE flags
- dc.l 0 mutual exclude
- dc.l itemname12 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname12 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l itext12 text
- dc.l 0 next text
-
- itext12 dc.b ' Key Activate ',0
-
-
- menuitem13 dc.l menuitem14 ext menu item
- dc.w mainw-110 left
- dc.w mendep*3 top
- dc.w mainw width
- dc.w mendep height
- wtfcheck dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT+MENUTOGGLE flags
- dc.l 0 mutual exclude
- dc.l itemname13 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname13 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l itext13 text
- dc.l 0 next text
-
- itext13 dc.b ' Pop to Front ',0
-
- menuitem14 dc.l menuitem15 ext menu item
- dc.w mainw-110 left
- dc.w mendep*4 top
- dc.w mainw width
- dc.w mendep height
- mapcheck dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP+CHECKIT+MENUTOGGLE flags
- dc.l 0 mutual exclude
- dc.l itemname14 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname14 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w CHECKWIDTH left
- dc.w 2 top
- dc.l 0 font
- dc.l itext14 text
- dc.l 0 next text
-
- itext14 dc.b ' Map Keys ',0
-
-
-
- menuitem15 dc.l menuitems next menu item
- dc.w mainw-110 left
- dc.w mendep*5 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemname15 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemname15 dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 0 left
- dc.w 2 top
- dc.l 0 font
- dc.l itext15 text
- dc.l 0 next text
-
- itext15 dc.b ' Load keys ',0
-
-
- menuitems dc.l menuitemq next menu item
- dc.w mainw-110 left
- dc.w mendep*6 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemnames item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemnames dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itexts text
- dc.l 0 next text
-
- itexts dc.b ' Save ',0
-
-
- menuitemq dc.l menuitemc next menu item
- dc.w mainw-110 left
- dc.w mendep*7 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHCOMP flags
- dc.l 0 mutual exclude
- dc.l itemnameq item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemnameq dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itextq text
- dc.l 0 next text
-
- itextq dc.b ' Quit ',0
-
-
- menuitemc dc.l 0 next menu item
- dc.w mainw-110 left
- dc.w mendep*8 top
- dc.w mainw width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHNONE flags
- dc.l 0 mutual exclude
- dc.l itemnamec item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l subcredit sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- itemnamec dc.b 0 front pen
- dc.b 1 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l itextc text
- dc.l 0 next text
-
- itextc dc.b ' Credits ',0
-
- subcredit dc.l s2credit next menu item
- dc.w 15 left
- dc.w 2+mendep top
- dc.w subcrtextl width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHNONE flags
- dc.l 0 mutual exclude
- dc.l subcreditm item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subcreditm dc.b 3 front pen
- dc.b 0 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l subcrtext text
- dc.l 0 next text
-
-
- s2credit dc.l 0 next menu item
- dc.w 15 left
- dc.w 2+mendep*2 top
- dc.w subcrtextl width
- dc.w mendep height
- dc.w ITEMTEXT+ITEMENABLED+HIGHNONE flags
- dc.l 0 mutual exclude
- dc.l subcredit2 item fill
- dc.l 0 select fill
- dc.b 0 command
- dc.l 0 sub item
- dc.w 0 next select
-
- cnop 0,2 align
-
- subcredit2 dc.b 2 front pen
- dc.b 0 back pen
- dc.b RP_JAM1 draw mode
- dc.w 2 left
- dc.w 2 top
- dc.l 0 font
- dc.l s2text text
- dc.l 0 next text
-
- cnop 0,2
- subcrtext dc.b ' David Jenkins ',0
- subcrtextl equ *-subcrtext-1
- cnop 0,2
- s2text dc.b ' ',$a9,' 1988 ',0
-
- newref dc.l 100000,200000,500000,999999 other refresh rates
- newblank dc.w 0,300,600,1200,1800,2400 screen blank time
- newpoint dc.w 0,5,10,20,30,40 pointer blank time
- newmouse dc.b 0,1,2,3,4,5 mouse speeds
- priindex dc.l prich1,prich2,prich3,prich4,prich5,prich6,prich7,prich8
- mousecheck dc.l mouch1,mouch2,mouch3,mouch4,mouch5,mouch6
- frontcheckr dc.l frontf1,frontf2,frontf3,frontf4
- backcheckr dc.l backf1,backf2,backf3,backf4
- blankcheckr dc.l blach1,blach2,blach3,blach4,blach5,blach6
- pointcheckr dc.l poich1,poich2,poich3,poich4,poich5,poich6
- ************ words *********************************
-
- seconds dc.w 0
- newminutes dc.w 0
- oldminutes dc.w 0
- newcol dc.w $0001,$0201,$0301,$0100,$0200,$0300,$0002,$0102,$0302
- dc.w $0003,$0103,$0203
-
- ************ bytes + bits and pieces **********
-
- tim dc.b 'tim'
- dat dc.b 'dat'
- cnop 0,2
- layersname dc.b 'layers.library',0
- cnop 0,2
- menu0name dc.b 'ClockDJ',0
- cnop 0,2
- savefile dc.b 'sys:clockdj.config',0
- cnop 0,2
- keyfilebuf equ *
- keyfile dc.b 'sys:clockdj.keys',0
- dcb.b 64,0
- cnop 0,2
- TimerPortName:
- DC.B 'timer',0
- cnop 0,2
- TimerName:
- DC.B 'timer.device',0,0
- cnop 0,2
- IntuitionName:
- DC.B 'intuition.library',0
- endmsg dc.b 0
- oldsecs dc.b 0
- cnop 0,2
- dosname dc.b 'dos.library',0
- cnop 0,2
- graphicsname
- dc.b 'graphics.library',0
- code1 dc.w 0
- newcli dc.b 'newcli >nil: <nil: "con:0/150/640/50/ clockdj "',0
- newrest dcb.b 81-(*-newcli),0
- nilname dc.b 'nil:',0
- memtot equ 0
- newpri dc.b -3,-2,-1,0,1,2,3,4
- owsw dc.b 0
- CNOP 0,2
-
- inputname dc.b 'input.device',0
- cnop 0,2
- inputportname dc.b 'input.portdj',0
- cnop 0,2
- IntName DC.B 'input handler DJ',0
- CNOP 0,2
-
-
- ********** IntuiText structures ****************
-
- cnop 0,2 align
- Date_Text:
- DC.B 0,1,1,0
- DC.W 0,0
- DC.L 0,totmsg,0
-
-
- cnop 0,2 align
-
- ouch DC.B 3,0,1,0
- DC.W 0,0
- DC.L 0,ouchmsg,0
- cnop 0,2
- ouchmsg dc.b 'OUCH!',0 for Steve the Awkward
-
- cnop 0,2 align
- keyerrortext
- DC.B 3,0,0,0
- DC.W 8,10
- DC.L 0,keyermsg,keyerrortext2
-
- cnop 0,2
- keyermsg
- dc.b 'Error in key definitions.',0
- cnop 0,2 align
- keyerrortext2
- DC.B 3,0,0,0
- DC.W 8,20
- DC.L 0,keyermsg2,0
-
- cnop 0,2
- keyermsg2
- dc.b 'Statement number '
- statement
- dc.b ' ',0
-
- cnop 0,2 align
- fileerrortext
- DC.B 3,0,0,0
- DC.W 8,10
- DC.L 0,fileermsg,0
-
- cnop 0,2
- fileermsg
- dc.b 'File not found.',0
-
- cnop 0,2 align
-
- oktext DC.B 2,0,0,0
- DC.W 6,3
- DC.L 0,okmsg,0
- cnop 0,2
- okmsg dc.b 'OK',0
-
-
-
- ********* text for IntuiText *************
-
- cnop 0,2 align avail
- totmsg dc.b ' '
- avail dc.b ' 0000K'
- dc.b ' '
- buffer:
- dc.B ' 00:00:00 '
- ampm1 dc.b 'AM ',0
-
- *********************************************
-
- ******** more text for IntuiText ************
-
- cnop 0,2 align avail
- dc.b 0
- sepmsg dc.b ' '
- dc.b ' Chip:'
- chipavail dc.b '0000K'
- dc.b ' Fast:'
- fastavail dc.b ' 0000K '
- buffer2:
- dc.B ' 00:00:00 '
- ampm2 dc.b 'AM ',0
-
- *********************************************
-
- **** new screen for screen blanking
-
- newscreen
-
- dc.w 0 ns_LeftEdge ; initial Screen dimensions
- dc.w 0 ns_TopEdge ; initial Screen dimensions
- dc.w 320 ns_Width ; initial Screen dimensions
- dc.w 200 ns_Height ; initial Screen dimensions
- dc.w 1 ns_Depth ; initial Screen dimensions
- dc.b 0 ns_DetailPen ; default rendering pens (for Windows too)
- dc.b 0 ns_BlockPen ; default rendering pens (for Windows too)
- dc.w 0 ns_ViewModes ; display "modes" for this Screen
- dc.w CUSTOMSCREEN+SCREENQUIET ns_Type Screen Type specifier
- dc.l 0 ns_Font ; default font for Screen and Windows
- dc.l 0 ns_DefaultTitle ; Title when Window doesn't care
- dc.l 0 ns_Gadgets ; Your own initial Screen Gadgets
-
-
- mouseevents
- dc.l 0 ie_NextEvent
- dc.b IECLASS_RAWMOUSE ie_Class
- dc.b 0 ie_SubClass
- dc.w IECODE_RBUTTON+IECODE_UP_PREFIX ie_Code
- dc.w 0 ie_Qualifier
- dc.w 0 ie_X
- dc.w 0 ie_Y
- dc.l 0 tv_Seconds
- dc.l 0 tv_Micros
- mouseeventsl equ *-mouseevents
-
- ******* this is the save record. Keep it together! ************
- * *
- cnop 0,2 *
- diskbuffer equ * *
- windowleft dc.w 343 *
- windowtop dc.w 1 *
- refrate dc.l 200000 default refresh rate *
- colours dc.b 0,1 default colours *
- memory dc.b 0 default total *
- priority dc.b 2 *
- pointtime dc.w 10 default pointer blank time *
- blanktime dc.w 600 default screen blank time *
- mousespeed dc.b 0 *
- sunswitch dc.b 0 *
- wtfcount dc.b 0 *
- wtbcount dc.b 0 *
- cycleswitch dc.b 0 *
- keyswitch dc.b 0 *
- popswitch dc.b 0
- mapswitch dc.b 0
- windowheight dc.b 7 *
- diskbufferl equ *-diskbuffer *
- * *
- *****************************************************************
-
- *
- *
- * Raw key definitions
- *
- *
- cnop 0,2
- rawkeys dc.b '`',$00
- dc.b '1',$01
- dc.b '2',$02
- dc.b '3',$03
- dc.b '4',$04
- dc.b '5',$05
- dc.b '6',$06
- dc.b '7',$07
- dc.b '8',$08
- dc.b '9',$09
- dc.b '0',$0a
- dc.b '-',$0b
- dc.b '=',$0c
- dc.b '\',$0d
- dc.b 'q',$10
- dc.b 'w',$11
- dc.b 'e',$12
- dc.b 'r',$13
- dc.b 't',$14
- dc.b 'y',$15
- dc.b 'u',$16
- dc.b 'i',$17
- dc.b 'o',$18
- dc.b 'p',$19
- dc.b '[',$1a
- dc.b ']',$1b
- dc.b 'a',$20
- dc.b 's',$21
- dc.b 'd',$22
- dc.b 'f',$23
- dc.b 'g',$24
- dc.b 'h',$25
- dc.b 'j',$26
- dc.b 'k',$27
- dc.b 'l',$28
- dc.b ';',$29
- dc.b '''',$2a
- dc.b 'z',$31
- dc.b 'x',$32
- dc.b 'c',$33
- dc.b 'v',$34
- dc.b 'b',$35
- dc.b 'n',$36
- dc.b 'm',$37
- dc.b ',',$38
- dc.b '.',$39
- dc.b '/',$3a
- dc.b ' ',$40
- dc.b 13,$44 cr
- dc.b 10,$44 lf
- dc.b 08,$41 bs
- dc.b 09,$42 ht
- dc.b 27,$45 esc
- rawkeysupper dc.b '~',$80
- dc.b '!',$81
- dc.b '@',$82
- dc.b '#',$83
- dc.b '$',$84
- dc.b '%',$85
- dc.b '^',$86
- dc.b '&',$87
- dc.b '*',$88
- dc.b '(',$89
- dc.b ')',$8a
- dc.b '_',$8b
- dc.b '+',$8c
- dc.b '|',$8d
- dc.b 'Q',$90
- dc.b 'W',$91
- dc.b 'E',$92
- dc.b 'R',$93
- dc.b 'T',$94
- dc.b 'Y',$95
- dc.b 'U',$96
- dc.b 'I',$97
- dc.b 'O',$98
- dc.b 'P',$99
- dc.b '{',$9a
- dc.b '}',$9b
- dc.b 'A',$a0
- dc.b 'S',$a1
- dc.b 'D',$a2
- dc.b 'F',$a3
- dc.b 'G',$a4
- dc.b 'H',$a5
- dc.b 'J',$a6
- dc.b 'K',$a7
- dc.b 'L',$a8
- dc.b ':',$a9
- dc.b '"',$aa
- dc.b 'Z',$b1
- dc.b 'X',$b2
- dc.b 'C',$b3
- dc.b 'V',$b4
- dc.b 'B',$b5
- dc.b 'N',$b6
- dc.b 'M',$b7
- dc.b '<',$b8
- dc.b '>',$b9
- dc.b '?',$ba
- dc.b $ff
- cnop 0,2
-
- funnykeys dc.b 'f01',$50
- dc.b 'f02',$51
- dc.b 'f03',$52
- dc.b 'f04',$53
- dc.b 'f05',$54
- dc.b 'f06',$55
- dc.b 'f07',$56
- dc.b 'f08',$57
- dc.b 'f09',$58
- dc.b 'f10',$59
- dc.b 'esc',$45
- dc.b 'del',$46
- dc.b 'tab',$42
- dc.b 'bsp',$41
- dc.b 'ret',$44
- dc.b 'hel',$5f
- dc.b 'kp0',$0f
- dc.b 'kp1',$1d
- dc.b 'kp2',$1e
- dc.b 'kp3',$1f
- dc.b 'kp4',$2d
- dc.b 'kp5',$2e
- dc.b 'kp6',$2f
- dc.b 'kp7',$3d
- dc.b 'kp8',$3e
- dc.b 'kp9',$3f
- dc.b 'kp-',$4a
- dc.b 'kp(',$5a
- dc.b 'kp)',$5b
- dc.b 'kp/',$5c
- dc.b 'kp*',$5d
- dc.b 'kp+',$5e
- dc.b 'ent',$43
- dc.b 'kp.',$3c
- dc.b 'upa',$4c
- dc.b 'lea',$4f
- dc.b 'ria',$4e
- dc.b 'doa',$4d
- dc.b $ff
-
- cnop 0,2
- qualifiers
- dc.b 'lsh'
- dc.w IEQUALIFIER_LSHIFT
- dc.b 'rsh'
- dc.w IEQUALIFIER_RSHIFT
- dc.b 'clo'
- dc.w IEQUALIFIER_CAPSLOCK
- dc.b 'ctl'
- dc.w IEQUALIFIER_CONTROL
- dc.b 'lal'
- dc.w IEQUALIFIER_LALT
- dc.b 'ral'
- dc.w IEQUALIFIER_RALT
- dc.b 'lam'
- dc.w IEQUALIFIER_LCOMMAND
- dc.b 'ram'
- dc.w IEQUALIFIER_RCOMMAND
- dc.b $ff
-
-
- cnop 0,2
- event dcb.b ie_SIZEOF,0 save area for inspection
-
- section data,bss
- datarea
- keybuffer ds.l 254 buffer to read key file
- cnop 0,4
- inthandler ds.b IS_SIZE interrupt handler
- inputport ds.l 1 port address
- cnop 0,4
- inputreq ds.l IO_SIZE
- insig ds.l 1
- cnop 0,2
- pause ds.b IOTV_SIZE ioreq for delay
- layer ds.l 1
- layers ds.l 1
- layerinfo ds.l 1
- tswitch ds.l 1
- oldmem ds.l 1
- class ds.l 1
- intuit ds.l 1
- doslib ds.l 1
- timer ds.l 1
- totalmemory ds.l 1
- chipmemory ds.l 1
- oldchip ds.l 1
- oldfast ds.l 1
- task ds.l 1 task pointer
- wtfsecs ds.l 2
- wtbsecs ds.l 2
- wtbsecsnew ds.l 2
- frontwin ds.l 1
- backwin ds.l 1
- blankscreen ds.l 1
- spritesave ds.l 1
- spriteblank ds.l 1
- mapbuffer ds.l 1 address of key map buffer
- firstkey ds.l 1 address of first key translate buffer
- keyhandle ds.l 1
- windowkey ds.l 1 address of key load window
- keywait ds.l 1 wait flag
- windowpoint ds.l 1
- windowtab ds.l 240
- windowtabl equ *-windowtab
- blanktimer ds.w 1
- pointtimer ds.w 1
- mouseleft ds.b 1
- mouseright ds.b 1
- action ds.b 1
- revswitch ds.b 1
- eventadd ds.b 1
- frontswitch ds.b 1 *
- backswitch ds.b 1 *
- blankdone ds.b 1
- pointdone ds.b 1
- lsw ds.b 1
- lalt ds.b 1
- lamiga ds.b 1
- menuswitch ds.b 1
- keysw ds.b 1
- escsw ds.b 1
- ssw ds.b 1
- undobuf ds.b 81
-
- end
-