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