chiark / gitweb /
reserve /^ [^ ;]/ for statements inserted for debugging purposes
[trains.git] / detpic / points.asm
1 ;======================================================================
2 ; POINTS
3
4   include common.inc
5
6 ;======================================================================
7 ; VARIABLES, HARDWARE, ETC
8 ;
9 ;               Timer 3         pointmsg        pointslave      cducharging
10 ;
11 ; S Idle        Off             undefined       undefined       undefined
12 ; S Firing      Counting up     100PPPPP        undefined       undefined
13 ; M Idle        Off             00000000        0000 0000       0x00
14 ; M Firing      Counting up     100PPPPP        0000 0000       0x00
15 ; M Telling     Off             100PPPPP        00SS Sss0       0x00
16 ; M Told        Off             100PPPPP        0000 0000       0x00
17 ; M Charging    Off             00000000        0000 0000       >0
18 ;
19 ;  notes:       firing          see             ie, slave*2     Counts down
20 ;                timeout         detect.asm                      in ticks
21 ;
22 ; cducharging only counts if the cdu is enabled
23 ;  (according to CDU Enable LAT bit)
24
25 cdu_timeout     equ     200 ; ms
26
27 ptix2latbit equ 0x300 ; has to be a multiple of 0x100
28 ptix2latbit_section udata ptix2latbit
29   res maxpoints * 2     ; LAT* and bit
30                         ; for unused point, 0x00 and 0x00
31
32   udata_acs
33 pointslave              res     1
34 pointmsg                res     1
35 cducharging             res     1
36
37   udata 0x340
38 slave2ptinfo            res     maxpics
39 slave2ptinfo_anypoints  equ     0
40
41 ;======================================================================
42 ; LOCAL POINTS
43 ; on slave, or master's own
44
45 ;----------------------------------------------------------------------
46 ; LOCAL POINTS - ACTUALLY DOING
47
48 near_local_do code
49 ;----------------------------------------
50 point_local_do
51 ; On slave, called during i2c receive, ie High ISR
52 ; On master, called during serial receive, ie Low ISR
53 ;               W       fire point msg          undefined
54         bt_f_if1 T3CON, TMR3ON
55         bra     point_clash
56
57         mov_wf  pointmsg        ; pointmsg = SS zz zz pp  pp pp pp pp
58
59         intrh_fsr0_save         ; point_set_pin uses FSR0, see below
60         call    point_set_pin
61         intrh_fsr0_restore
62
63         clr_f   TMR3L           ; also copies TMR3H into actual timer register
64         bs_f    T3CON, TMR3ON
65         return
66
67 ;----------
68 point_clash
69         panic   morse_PB
70
71 points_section code
72 ;----------------------------------------
73 points_local_intrl
74         bt_f_if0 PIR2, TMR3IF
75         return
76         ; OK, it's us, and we're done changing a point:
77
78         bt_f_if0 T3CON, TMR3ON
79         bra     point_spurious_intr
80
81         rcall   point_set_pin
82         intrh_mask
83         bc_f    T3CON, TMR3ON
84         bc_f    PIR2, TMR3IF
85         intrh_unmask
86
87         mov_lw  b'00100000'
88         call    message_for_master
89         intrl_handled_nostack
90
91 ;----------
92 point_spurious_intr
93         panic   morse_PI
94
95 ;----------
96 point_set_pin
97 ; Toggles the pin.  The effect is:
98 ;       If we were idle, sets it H (to fire) unless pt0 in which case L
99 ;       If we were firing, sets it L (to stop) unless pt0 in which case H
100 ;
101 ; Called in various contexts, including both High and Low ISR.
102 ;
103 ;  pointmsg     point to start or stop firing   preserved
104 ;  W,STATUS     any                             undefined
105 ;  FSR0         any                             undefined
106 ;  all other    any                             not interfered with
107 ;
108         mov_lw  ptix2latbit >> 8
109         mov_wf  FSR0H           ; FSR0H -> table
110         rl_fw   pointmsg        ; W = point addr, Z iff pt0
111         mov_wf  FSR0L           ; FSR0 -> &bit   [Z still iff pt0]
112         mov_fw  POSTDEC0        ; W = bit, FSR0 -> &LAT*
113         bra_z   point_nonexistent
114         mov_ff  INDF0, FSR0L    ; W = bit, FSR0L -> LAT*
115         set_f   FSR0H           ; FSR0 -> LAT*, W = bit (still)
116         xor_wff INDF0           ; pin = !pin
117         return
118
119 ;----------
120 point_nonexistent
121         panic   morse_PU
122
123 ;----------------------------------------------------------------------
124 ; LOCAL POINTS - INITIALISATION
125
126 ;----------------------------------------
127 points_local_init
128 ; Initialises tables for points
129 ; Clears TRIS* bits for all points and sets each pin to `not triggering'
130
131         rcall   point_timer_init
132
133 ;       We do this in two stages.
134 ;       Firstly, we scan the bitmap for this pic, setting
135 ;        ptix2latbit to 0xff,0x00 for used points and 0x00,0x00
136 ;        to unused ones.
137 ;       Secondly, we scan the bkptix2portnumbitnum, adjusting
138 ;        ptix2latbit to have actually correct data.
139 ;       Doing it like this avoids having to constantly recompute
140 ;        individual TBLPTR*'s.
141
142         mov_lfsr ptix2latbit-1, 0 ; FSR0 -> this bit and LAT*
143                                   ;  points just at last thing we've filled in
144
145         load_perpic_tblptr picno2ptmap, maxpoints/8
146
147         mov_lw  maxpoints/8
148         mov_wf  t               ; t = byte counter
149 ;...
150 points_init_byte_loop
151         mov_lw  8               ; W = bit counter
152         tblrd_postinc_fixup     ; TABLAT = bitmap data being processed
153 ;...
154 points_init_bit_loop
155         clr_f   PREINC0         ; FSR0 -> LAT*[current] := 0
156         rrc_f   TABLAT
157         bt_f_if1 STATUS,C
158         set_f   INDF0           ; FSR0 -still-> LAT*[current] := 0xff
159
160         clr_f   PREINC0         ; FSR0 -> bit[current] := 0
161
162         dec_w_ifnz
163         bra     points_init_bit_loop
164         dec_f_ifnz t
165         bra     points_init_byte_loop
166 ;... end of loop:
167
168 ;       We've scanned for points used on this board;
169 ;       now find the actual pins.
170
171         mov_lw  bkptix2portnumbitnum & 0xff
172         bt_f_if1 idloc1,idloc1_boarddet
173         add_lw  maxpoints
174         mov_wf  TBLPTRL
175
176         mov_lw  bkptix2portnumbitnum >> 8
177         mov_wf  TBLPTRH         ; TBLPTR* -> point port/bit data
178
179         set_f   FSR2H           ; FSR2 -> some SFR, will point to LAT/TRIS
180         mov_lfsr bitnum2bit+7, 1 ; FSR1 -> bitnum2bit+7
181         mov_lfsr ptix2latbit-1, 0 ; FSR0 -> last bit (and previous LAT*)
182
183         mov_lw  maxpoints
184         mov_wf  t               ; t = loop counter
185 ;...
186 points_init_portbit_loop
187         tblrd_postinc_fixup     ; TABLAT = portnum4 || bitnum4
188
189         bt_f_if0 PREINC0,7      ; zero?, FSR0 -> LAT*[this]
190         bra     points_init_portbit_endif_used
191 ;...
192 points_init_portbit_if_used
193         mov_fw  TABLAT
194         bra_n   point_initing_bad_point
195
196         ior_lw  0xf8            ; W -> bit value for bit
197         mov_wf  FSR1L           ; FSR1 -> bit value for bit
198
199         swap_fw TABLAT          ; W = bitnum4 || portnum4
200         and_lw  0x0f            ; W = portnum4
201         add_lw  LATA & 0xff     ; W = LAT*
202         mov_wf  POSTINC0        ; LAT*[this] := LAT, FSR0 -> bit[this]
203         mov_wf  FSR2L           ; FSR2 -> LAT*
204
205         mov_fw  INDF1           ; W = bit
206         mov_wf  POSTDEC0        ; bit[this] = bit, FSR0 -> LAT*[this]
207         com_w                   ; W = ~bit
208         and_wff INDF2           ; LAT* &= ~bit, ie pin set to L (still Z)
209         pin_vh  pall_pt0reverse ; but pt0 pin is backwards, set to H
210                                 ;  (still Z, unless we've done this already)
211         mov_lw  TRISA-LATA
212         add_wff FSR2L           ; FSR2 -> TRIS*
213         com_fw  INDF1           ; W = ~bit
214         and_wff INDF2           ; TRIS* &= ~bit, ie pin set to not Z
215
216         set_f   FSR1L           ; FSR1 -> bitnum2bit+7, again
217 points_init_portbit_endif_used
218         ; so now we move on to the next one
219         mov_fw  POSTINC0        ; FSR0 -> bit[this]
220
221         dec_f_ifnz t
222         bra     points_init_portbit_loop
223
224         return
225
226 ;----------
227 point_initing_bad_point
228         panic   morse_PF
229
230 ;----------
231 point_timer_init
232         bt_f_if1 idloc1,idloc1_master
233         bra     point_timer_init_if_master
234         ; slave:
235         mov_lw  (1<<RD16)|(1<<T3ECCP1)| points_slave_t3scale; Fcy;!TMR3ON
236         mov_wf  T3CON
237         mov_lw  points_slave_t3inith
238         bra     point_timer_init_endif_masterslave
239 point_timer_init_if_master
240         mov_lw  (1<<RD16)|(1<<T3ECCP1)| points_master_t3scale; Fcy;!TMR3ON
241         mov_wf  T3CON
242         mov_lw  points_master_t3inith
243 point_timer_init_endif_masterslave
244         mov_wf  TMR3H   ; We just leave this here.
245                         ; Since we never read TMR3L, it is never overwritten
246
247         bc_f    PIR2, TMR3IF
248         bs_f    PIE2, TMR3IE
249         bc_f    IPR2, TMR3IP
250         return
251
252 ;======================================================================
253 ; MASTER
254
255 ;----------------------------------------------------------------------
256 points_master_init
257         clr_f   pointslave
258         clr_f   pointmsg
259
260         load_tblptr picno2ptmap
261         mov_lfsr slave2ptinfo-1, 0
262         mov_lw  maxpics
263         mov_wf  t
264 points_master_init_board_loop
265         clr_f   PREINC0
266         mov_lw  maxpoints/8
267 points_master_init_byte_loop
268         tblrd_postinc_fixup
269         tst_f_ifnz TABLAT
270         bs_f    INDF0, slave2ptinfo_anypoints
271         dec_w_ifnz
272         bra     points_master_init_byte_loop
273         dec_f_ifnz t
274         bra     points_master_init_board_loop
275
276         return
277
278 ;----------------------------------------------------------------------
279 command_point
280                                         ; FSR0 -> 1 0100 TTT  O TTTTTTT
281                                         ; ie            1010 0SSS
282                                         ;               OssT tttt
283         tst_f_ifnz pointmsg
284         bra     command_point_busy
285
286         tst_f_ifnz cducharging
287         bra     command_point_cduempty
288
289         swap_fw POSTINC0                ; W =           0SSS 1010
290         and_lw  0x70                    ; W =           0SSS 0000
291         rr_w                            ; W =           00SS S000
292         mov_wf  pointslave              ; pointslave =  00SS S000
293
294         mov_fw  INDF0                   ; W =           OssT tttt  N = O
295         bra_n   command_point_badmsg
296         ; OK:                           ; W =           0ssT tttt
297         and_lw  0x1f                    ; W =           000T tttt
298         bs_w    7                       ; W =           100T tttt
299         mov_wf  pointmsg                ; pointmsg =    100T tttt
300
301         swap_fw INDF0                   ; W =           tttt 0ssT
302         and_lw  0x06                    ; W =           0000 0ss0
303         ior_wff pointslave              ; pointslave =  00SS Sss0
304
305         rr_fw   pointslave              ; W =           000S SSss
306         bra_nz  command_point_ifslave
307
308         mov_fw  pointmsg
309         goto    point_local_do
310
311 command_point_badmsg panic morse_PX
312 command_point_busy panic morse_PB
313 command_point_cduempty panic morse_PC
314
315 ;----------
316 command_point_ifslave
317         mov_lfsr slave2ptinfo, 0
318         add_wff FSR0L
319         bt_f_if1 INDF0, slave2ptinfo_anypoints
320         goto    i2c_needwrite
321         ; oops:
322         panic   morse_PS
323
324 ;----------
325 points_needwrite
326         rr_fw   pointslave              ; W =           000S SSss
327         bt_f_if1 STATUS, Z ; nothing ?
328         return
329         ; we need to write something:
330 ;...
331 ;----------
332 point_needwrite_yes
333         pop
334         goto    i2c_needwrite
335
336 ;----------
337 points_getwritebyte
338         rr_fw   pointslave
339         xor_wfw cwslave
340         bt_f_if0 STATUS, Z ; right slave ?
341         return
342         ; yes:
343         clr_f   pointslave      ; we're writing now, excellent
344         mov_fw  pointmsg
345         goto    i2c_getwritebyte_yes
346
347 ;======================================================================
348 ; CDU
349
350 ;--------------------
351 cdu_init
352         clr_f   pointslave
353         clr_f   pointmsg
354 ;...
355 ;-----
356 cdu_off
357 cdu_panichook
358         pin_l   p0_cdu_enable
359 ;...
360 ;-----
361 cdu_discharged
362         mov_lw  (cdu_timeout * 1000) / tickdiv_us + 1
363         mov_wf  cducharging
364         return
365
366 ;--------------------
367 cdu_on
368         pin_h   p0_cdu_enable
369         return
370
371 ;--------------------
372 cdu_tickdiv
373         pinlat_ifl p0_cdu_enable
374         return
375
376         tst_f_ifnz cducharging
377         dec_f_ifnz cducharging  ; so, decrement only if it was nonzero
378         return                  ; return if we either didn't decrement,
379                                 ;  or didn't reach zero
380
381         ; cducharging is already zero, from above
382         mov_lw  b'00101000' ; CHARGED
383         goto    serial_addbyte
384
385 near_gots code
386 ;--------------------
387 got_pointed
388         tst_f_ifnz cducharging
389         bra     pointed_already_charging
390
391         bt_f_if0 pointmsg, 7
392         bra     pointed_butnot_firing
393
394         clr_f   pointmsg
395         call    cdu_discharged
396         mov_lw  b'00100000' ; POINTED
397         goto    serial_addbyte
398
399 pointed_butnot_firing panic morse_PA
400 pointed_already_charging panic morse_PQ
401
402 ;======================================================================
403   include final.inc