/[PAMELA software]/yoda/techmodel/forroutines/tracker/readraw/trkunpack.f
ViewVC logotype

Annotation of /yoda/techmodel/forroutines/tracker/readraw/trkunpack.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 6.4 - (hide annotations) (download)
Tue Jun 27 10:25:42 2006 UTC (18 years, 5 months ago) by kusanagi
Branch: MAIN
CVS Tags: YODA6_3/13, YODA6_3/12, YODA6_3/11, YODA6_3/10, YODA6_3/06, YODA6_3/04, YODA6_3/05, YODA6_3/07, YODA6_3/08, YODA6_3/09
Changes since 6.3: +30 -18 lines
Final release for the Traker's routines.

1 kusanagi 5.1 *************************************************************************
2     * 20/1/2006 modified by elena vannuccini to code error flag
3     * 10/9/2005 modified by david fedele to read buffer-data
4     * instead raw-data-file
5     * 29/11/2005 modified by david fedele to include crc control
6 kusanagi 6.3 * 24/06/2006 modified by elena vannuccini
7 kusanagi 6.4 * 25/06/2006 modified by david fedele
8 kusanagi 5.1 *************************************************************************
9 kusanagi 1.1
10 kusanagi 6.3 subroutine trkeventpkt(YODAflag,buffer,length_buffer,curpos)
11 kusanagi 5.1
12     include '../common/commontracker.f'
13     include '../common/common_readraw.f'
14     include '../common/level0.f'
15 kusanagi 1.1
16 kusanagi 6.3 logical ALARMS
17     integer runerror !readevent error flag
18     integer*1 crctemp
19    
20     * -------------------
21     * initializations
22 kusanagi 4.1 * ---------------------------------------------------
23     * the general flag YODAflag contains information
24 kusanagi 5.1 * about the integrity of the DSP packets.
25 kusanagi 4.1 *
26 kusanagi 5.1 * If some packets are missing or the crc check fails,
27     * YODAflag is asserted
28 kusanagi 4.1 * ---------------------------------------------------
29 kusanagi 5.1 YODAflag=1 !bad by default
30 kusanagi 1.1 call initlevel0
31 kusanagi 5.1 ALARMS=.false.
32     npkt=0 !#good DSP packets
33     startcrc=0
34     stopcrc=0
35     crctemp=0
36     * -------------------
37    
38 kusanagi 6.3 * ===================================
39     if(length_buffer.gt.MAXBUFFLEN)then
40     print*,'trkeventpkt: buffer() size must be at least '
41     $ ,length_buffer,' !!!!'
42     goto 2222
43     endif
44     * ===================================
45    
46    
47 kusanagi 5.1 do iview=1,nviews !loop on DSPs
48     call searchtrkheader(runerror,buffer,length_buffer,curpos,
49     $ startcrc)
50 kusanagi 4.1 if(runerror.eq.1.or.runerror.eq.-1) then
51     * --------------------------------------------------
52 kusanagi 5.1 * no DSP packet has been found ==> go to end
53 kusanagi 4.1 * --------------------------------------------------
54     goto 2222 !go to end
55 kusanagi 1.1 endif
56 kusanagi 5.1
57 kusanagi 1.1 if(checkheader.ne.2) then
58 kusanagi 4.1 print*,'>>>> ERROR <<<< (trkeventpkt)'
59     print*,'>>>> CPU packet type ',!pkt_type,
60     $ ' does not match DSP packet type ',checkheader
61 kusanagi 1.1 DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)
62     DSPnumber_temp = iand(header(1),z'000f')
63 kusanagi 4.1 print*,' -----------------------------------'
64     $ ,iview
65     print*,' DSP number-----',int(DSPnumber_temp)
66     print*,' DAQ mode-------',int(DAQmode_temp)
67     print*,' -----------------------------------'
68 kusanagi 1.1 goto 2525 !next view (==> search another DSP header)
69     endif
70    
71 kusanagi 5.1 call unpackdata(runerror,buffer,length_buffer,curpos,
72     $ startcrc,stopcrc,crctemp)
73 kusanagi 4.1 if(runerror.eq.-1.or.runerror.eq.1)then
74 kusanagi 6.4 goto 2222 !go to end
75     else if(runerror.eq.2) then
76     crc_dat=2 !flag for corrupted packet
77 kusanagi 4.1 endif
78    
79 kusanagi 5.1 npkt = npkt + 1
80 kusanagi 1.1 call fillview(iview)
81 kusanagi 6.4 *--------CRC check
82     if(crc(iview).eq.0.or.crc(iview).eq.2) then !OK
83 kusanagi 5.1 *----------- ALARMS
84 kusanagi 6.4 if(
85     $ fl1(iview).ne.0.or.
86     $ fl2(iview).ne.0.or.
87     $ fl3(iview).ne.0.or.
88     $ fl4(iview).ne.0.or.
89     $ fl5(iview).ne.0.or.
90     $ fl6(iview).ne.0.or.
91     $ fc(iview).ne.0.or.
92     $ DATAlength(iview).eq.0.or.
93     $ .false.)ALARMS=.true.
94 kusanagi 5.1 endif
95 kusanagi 6.4
96 kusanagi 1.1 2525 continue
97     enddo !end loop on views
98 kusanagi 5.1
99 kusanagi 1.1 2222 continue
100    
101 kusanagi 5.1 if(npkt.eq.nviews)YODAflag=0
102     if(YODAflag.eq.0.and.(ALARMS.eqv..false.))good0=1
103    
104 kusanagi 1.1 return
105     end
106    
107 kusanagi 5.1 * **********************************************************
108     * * *
109     * * *
110     * * *
111     * * *
112     * * *
113     * **********************************************************
114 kusanagi 1.1
115 kusanagi 5.1 subroutine trkcalibpkt(YODAflag,buffer,length_buffer,curpos
116     $ )
117    
118     include '../common/commontracker.f'
119     include '../common/common_readraw.f'
120     include '../common/trk_calib_parameters.f'
121 kusanagi 6.3
122     logical ALARMs
123     integer runerror !readevent error flag
124     integer*1 crctemp
125 kusanagi 1.1
126 kusanagi 6.3 * -------------------
127     * initializations
128 kusanagi 5.1 * ---------------------------------------------------
129     * the general flag YODAflag contains information
130     * about the integrity of the DSP packets.
131     *
132     * If some packets are missing or the crc check fails,
133     * YODAflag is asserted
134     * ---------------------------------------------------
135     YODAflag = 1 !bad by default
136     call initcalib
137     ALARMS=.false.
138     npkt=0 !#good DSP packets
139     startcrc=0
140     stopcrc=0
141     crctemp=0
142     * -------------------
143 kusanagi 2.2
144 kusanagi 6.4 * ===================================
145     if(length_buffer.gt.MAXBUFFLEN)then
146     print*,'trkeventpkt: buffer() size must be at least '
147     $ ,length_buffer,' !!!!'
148     goto 2222
149     endif
150     * ===================================
151    
152 kusanagi 5.1 do iview=1,nplanes !loop on views (DSP pkt)
153 kusanagi 2.2
154 kusanagi 5.1 call searchtrkheader(runerror,buffer,length_buffer,curpos,
155     $ startcrc)
156 kusanagi 2.2
157 kusanagi 5.1 if(runerror.eq.1.or.runerror.eq.-1) then
158 kusanagi 1.1 goto 2222 !end loop on views (DSP pkt)
159     endif
160 kusanagi 5.1
161 kusanagi 1.1 if(checkheader.ne.3) then
162 kusanagi 4.1 print*,'>>>> ERROR <<<< (trkcalibpkt)'
163     print*,'>>>> CPU packet type ',!pkt_type,
164     $ ' does not match DSP type ',checkheader
165 kusanagi 1.1 DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)
166     DSPnumber_temp = iand(header(1),z'000f')
167 kusanagi 4.1 print*,' -----------------------------------'
168     $ ,iview
169     print*,' DSP number-----',int(DSPnumber_temp)
170     print*,' DAQ mode-------',int(DAQmode_temp)
171     print*,' -----------------------------------'
172 kusanagi 1.1 goto 2424 !next view (==> search another DSP header)
173     endif
174    
175 kusanagi 5.1 call unpackcalibration(runerror,buffer,length_buffer,curpos,
176     $ startcrc,stopcrc,crctemp)
177     if(runerror.eq.-1.or.runerror.eq.1)then
178     goto 2222 !end
179 kusanagi 4.1 endif
180 kusanagi 5.1
181 kusanagi 2.2
182 kusanagi 5.1 npkt = npkt + 1
183     call fillview_cal(iview) !
184     *--------CRC check
185     if( crc_hcal(iview).eq.0.and.
186     $ crc_cal(iview,1).eq.0.and.
187     $ crc_cal(iview,2).eq.0.and.
188     $ crc_cal(iview,3).eq.0.and.
189     $ .true.)then
190     *----------- ALARMS
191     if( ncalib_event(iview).ne.0.or.
192     $ cal_flag(iview).ne.0.or.
193     $ .false.)ALARMS=.true.
194     endif
195 kusanagi 1.1
196     2424 continue
197     enddo ! end loop on views (calibration pkt)
198 kusanagi 5.1
199 kusanagi 6.4 2222 continue
200    
201 kusanagi 5.1 if(npkt.eq.nplanes)YODAflag=0
202     if(YODAflag.eq.0.and.(ALARMS.eqv..false.))good0=1
203    
204 kusanagi 1.1 return
205     end
206    
207 kusanagi 5.1 * **********************************************************
208     * * *
209     * * *
210     * * *
211     * * *
212     * * *
213     * **********************************************************
214 kusanagi 1.1
215 kusanagi 5.1 subroutine searchtrkheader(runerror,buffer,length_buffer,
216     $ curpos,startcrc)
217 kusanagi 1.1 C.............................................................
218     C Search for a valid tracker DSP header (=>one view)
219     C and return the type of header
220     C.............................................................
221    
222 kusanagi 5.1 include '../common/commontracker.f'
223     include '../common/common_readraw.f'
224    
225 kusanagi 1.1 integer runerror !readevent error flag
226    
227     c--------------------------------------------------
228     c N.B.13 bit packing is done for each DSP header+datablock,
229     C so each DSP 13 bit
230     c first word starts at the beginnig of a 16 bit word
231     c--------------------------------------------------
232 kusanagi 5.1
233 kusanagi 1.1 9100 continue
234     runerror=0 !error flag initialization
235     checkheader=0
236    
237     c--------------------------------------------------
238     c looks for a DSP header beginning
239     C (a word beginning with 1110)
240     c--------------------------------------------------
241    
242 kusanagi 5.1 call findstart(runerror,buffer,length_buffer,curpos)
243    
244 kusanagi 4.1 if(runerror.eq.1) goto 200 !end
245     if(runerror.eq.-1)goto 200 !end
246 kusanagi 1.1 c--------------------------------------------------
247     c the first word could be a DSP header first word:
248     C reads 13 8-bit words and
249     c writes them in 16 13-bit words to check for all
250     C DSP header features
251     c--------------------------------------------------
252 kusanagi 5.1
253     call hunpacker(header,runerror,buffer,length_buffer,curpos,
254     $ startcrc)
255    
256 kusanagi 4.1 if(runerror.eq.1) goto 200 !end
257     if(runerror.eq.-1)goto 200 !end
258 kusanagi 1.1 c--------------------------------------------------
259     c extracts and controls header:
260     c--------------------------------------------------
261     C last header word must be:
262     c |0001|1100|0000|0000| for acquisition
263     c |0001|1111|1111|1111| for calibration
264     c--------------------------------------------------
265 kusanagi 4.1 if(iand(header(16),z'ffff').eq.z'1c00') then
266     checkheader=2 ! event packet
267     elseif(iand(header(16),z'ffff').eq.z'1fff') then
268 kusanagi 1.1 checkheader=3 ! calibration packet
269     else
270     checkheader=1 ! not a valid DSP header
271     endif
272     c--------------------------------------------------
273     c first header word must be:
274     c |0001|110x|xxxx|xxxx|
275     c--------------------------------------------------
276     if(iand(header(1),z'fe00').ne.z'1c00')
277     $ checkheader=1 !not a valid DSP header
278     c--------------------------------------------------
279     c intermediate header words must be:
280     c |0001|010x|xxxx|xxxx|
281     c--------------------------------------------------
282     do i=2,15
283     if(iand(header(i),z'fc00').ne.z'1400')
284     $ checkheader=1 !not a valid DSP header
285     enddo
286     c--------------------------------------------------
287     c if checkheader = 1
288     c then this is not a DSP header (or some
289     c noise lurks around) so go a word ahead and
290     c try again
291     c--------------------------------------------------
292 kusanagi 5.1 if(checkheader.eq.1) then
293     curpos=curpos-(13*2)+1 !goes back 13 words, then half 16 bit word ahead
294 kusanagi 1.1 goto 9100
295     endif
296 kusanagi 5.1
297 kusanagi 1.1 200 continue
298     end
299    
300 kusanagi 5.1 * **********************************************************
301     * * *
302     * * *
303     * * *
304     * * *
305     * * *
306     * **********************************************************
307 kusanagi 1.1
308 kusanagi 5.1 subroutine unpackcalibration(runerror,buffer,length_buffer,curpos,
309     $ startcrc,stopcrc,crctemp)
310 kusanagi 1.1
311     *.............................................................
312     * decode calibration data
313     * header + data(PED SIG BAD) + trailer
314     *............................................................
315 kusanagi 5.1 include '../common/commontracker.f'
316     include '../common/common_readraw.f'
317 kusanagi 1.1
318 kusanagi 5.1 integer*1 crctemp
319     integer*1 crc_trail
320    
321 kusanagi 1.1 integer runerror !readevent error flag
322     integer*2 templ(nstrips_ladder)
323     real*4 tempf(nstrips_ladder)
324    
325    
326 kusanagi 5.1
327 kusanagi 1.1 12 format(z4)
328    
329     *-----------------------------------------------------------
330     * HEADER
331     * (N.B. during test 2003 the header of calibration packets
332     * was only partially filled)
333     *
334     * the following is the final calibration header
335     *-----------------------------------------------------------
336     DAQmode_cal = ishft(iand(header(1),z'03f0'),-4)
337     DSPnumber_cal = iand(header(1),z'000f')
338     dataword = ior(ishft(iand(header(2),z'03ff')
339     $ ,10),iand(header(3),z'03ff'))
340     calibrationnumber = iand(header(4),z'03ff')
341     nused_event = iand(header(5),z'03ff')
342     ped_1 = iand(header(6),z'03ff')
343     ped_2 = iand(header(7),z'03ff')
344     ped_3 = iand(header(8),z'03ff')
345     ped_1 = ped_1 * 4
346     ped_2 = ped_2 * 4
347     ped_3 = ped_3 * 4
348     sig_1 = iand(header(9),z'03ff')
349     sig_2 = iand(header(10),z'03ff')
350     sig_3 = iand(header(11),z'03ff')
351     nbad_1 = iand(header(12),z'03ff')
352     nbad_2 = iand(header(13),z'03ff')
353     nbad_3 = iand(header(14),z'03ff')
354     ff = ishft(iand(header(15),z'0300'),-8)
355     checksum_cal = iand(header(15),z'00ff')
356     c-----------------------------------------------------------
357     c the checksum is a 8-bit word calculated as the
358     c XOR of the 16-bit data words,
359     c hence the XOR between the two halfs
360     C----------------------------------------------------------
361 kusanagi 5.1
362     runerror=0
363     c$$$
364     c$$$ print*,'-----------------------------------'
365     c$$$ print*,'unpackcalibration: readtrailer --- ',
366     c$$$* $ trailer,runerror,buffer,length_buffer,curpos,
367     c$$$ $ startcrc,stopcrc,crctemp
368     c$$$ print*,'-----------------------------------'
369     call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
370     $ startcrc,stopcrc,crctemp)
371    
372     crc_trail=iand(trailer(3),z'00ff')
373    
374     c$$$ print *,'@@@@@@@@@@@@@ ',crctemp,crc_trail
375    
376     if (crctemp.eq.crc_trail)then
377     crc_hcalib=0
378     else
379     crc_hcalib=1
380     endif
381    
382 kusanagi 1.1 do il=1,3 !loop on ladders
383 kusanagi 5.1 startcrc=curpos
384     call readped(tempf,runerror,buffer,length_buffer,curpos)
385 kusanagi 1.1 do is=1,nstrips_ladder
386     iss=is+nstrips_ladder*(il-1)
387     DSPped_o(DSPnumber_cal,iss)=tempf(is)
388     enddo
389 kusanagi 5.1
390     call readsig(tempf,runerror,buffer,length_buffer,curpos)
391 kusanagi 1.1 do is=1,nstrips_ladder
392     iss=is+nstrips_ladder*(il-1)
393     DSPsig_o(DSPnumber_cal,iss)=tempf(is)
394     enddo
395 kusanagi 5.1
396     call readbad(templ,runerror,buffer,length_buffer,curpos)
397 kusanagi 1.1 do is=1,nstrips_ladder
398     iss=is+nstrips_ladder*(il-1)
399     DSPbad_o(DSPnumber_cal,iss)=templ(is)
400     enddo
401 kusanagi 5.1
402 kusanagi 1.1 11 format(i1,' ',z4)
403 kusanagi 5.1
404     call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
405     $ startcrc,stopcrc,crctemp)
406 kusanagi 1.1
407 kusanagi 5.1 crc_trail=iand(trailer(3),z'00ff')
408 kusanagi 1.1
409 kusanagi 5.1 if (crctemp.eq.crc_trail)then
410     crc_calib(il)=0
411     else
412     crc_calib(il)=1
413     endif
414    
415 kusanagi 1.1 enddo !end loop on ladders
416    
417     return
418     end
419    
420 kusanagi 5.1 * **********************************************************
421     * * *
422     * * *
423     * * *
424     * * *
425     * * *
426     * **********************************************************
427    
428     subroutine unpackdata(runerror,buffer,length_buffer,curpos,
429     $ startcrc,stopcrc,crctemp)
430 kusanagi 1.1
431     *.............................................................
432     * decode event data
433     * header + data + trailer
434     *............................................................
435    
436 kusanagi 5.1 include '../common/commontracker.f'
437     include '../common/common_readraw.f'
438     include '../common/level0.f'
439    
440     integer*1 crctemp
441     integer*1 crcdat
442    
443 kusanagi 1.1 integer runerror !readevent error flag
444 kusanagi 6.2 c integer l_tra
445 kusanagi 1.1
446 kusanagi 5.1 integer bid1_dat,bid2_dat,bid3_dat,bid4_dat,bid5_dat,bid6_dat
447     $ ,bid7_dat,bid_dat_sum
448    
449 kusanagi 4.1
450 kusanagi 1.1 12 format(z4)
451    
452     *-----------------------------------------------------------
453     * HEADER
454     *-----------------------------------------------------------
455    
456     DAQmode_dat = ishft(iand(header(1),z'03f0'),-4)
457     DSPnumber_dat = iand(header(1),z'000f')
458     C ------------------------------------------------------
459 kusanagi 5.1 c words 2 and 3 give the number of transmitted 16-bit
460 kusanagi 1.1 c words ( 13 header words + data )
461     c NB: data are packed from 13-bit to 16-bit words,
462     c so the stream is complited with zeros in order to have
463     c a number of bits multiple of 16
464 kusanagi 4.1 C ------------------------------------------------------
465 kusanagi 1.1 l_tra = ior(ishft(iand(header(2),z'03ff')
466     $ ,10),iand(header(3),z'03ff'))
467     l_tra=l_tra-13
468     C ------------------------------------------------------
469     eventn_dat = ior(ishft(iand(header(4),z'03ff')
470     $ ,10),iand(header(5),z'03ff'))
471     nclust_dat = ishft(iand(header(6),z'0380'),-7)
472     cutc_dat = ishft(iand(header(6),z'0070'),-4)
473     cutcl_dat = iand(header(6),z'000f')
474     addrcluster_dat(1) = iand(header(7),z'03ff')
475     signcluster_dat(1) = iand(header(8),z'03ff')
476     addrcluster_dat(2) = iand(header(9),z'03ff')
477     signcluster_dat(2) = iand(header(10),z'03ff')
478     addrcluster_dat(3) = iand(header(11),z'03ff')
479     signcluster_dat(3) = iand(header(12),z'03ff')
480     fc_dat = ishft(iand(header(13),z'0300'),-8)
481     compressiontime_dat = iand(header(13),z'00ff')
482 kusanagi 6.1 c fl5_dat = ishft(iand(header(14),z'0300'),-8)
483     c fl4_dat = ishft(iand(header(14),z'0300'),-6)
484     c fl3_dat = ishft(iand(header(14),z'0300'),-4)
485     c fl2_dat = ishft(iand(header(14),z'0300'),-2)
486     c fl1_dat = iand(header(14),z'0300')
487     c fl6_dat = ishft(iand(header(15),z'0300'),-8)
488     fl5_dat = iand(ishft(header(14),-8),z'0003')
489     fl4_dat = iand(ishft(header(14),-6),z'0003')
490     fl3_dat = iand(ishft(header(14),-4),z'0003')
491     fl2_dat = iand(ishft(header(14),-2),z'0003')
492     fl1_dat = iand(header(14),z'0003')
493     fl6_dat = iand(ishft(header(15),-8),z'0003')
494 kusanagi 1.1 checksum_dat = iand(header(15),z'00ff')
495 kusanagi 4.1
496 kusanagi 1.1 c-----------------------------------------------------------
497     c the cheacksum is a 8-bit word calculated as the
498     c XOR of the 16-bit data words,
499     c hence the XOR between the two halfs
500     C----------------------------------------------------------
501     runerror=0
502 kusanagi 2.2 nqualcosa=0
503     if(l_tra.eq.0)then
504     goto 18 !empty buffer
505     endif
506 kusanagi 6.2
507 kusanagi 6.4 if(l_tra.gt.MAXBUFFLEN .or.(curpos+l_tra-1).ge.MAXBUFFLEN )then
508 kusanagi 6.2 print*,'unpackdata: '
509 kusanagi 6.3 $ ,'tracker buffer length l_tra ',l_tra
510     $ ,' exceeds tracker buffer dimensions '
511     print*,'(packet corrupted)'
512 kusanagi 6.4 cc runerror=1
513     runerror=2
514 kusanagi 6.2 goto 50
515     endif
516 kusanagi 5.1 call dunpacker(l_tra,b_tra,runerror,buffer,length_buffer,curpos)
517 kusanagi 6.2 if(runerror.eq.1.or.runerror.eq.-1) then
518 kusanagi 4.1 goto 50 !go to end
519     endif
520    
521 kusanagi 1.1 nqualcosa = (real(l_tra))/13*16
522     xx = b_tra(nqualcosa)
523     if (xx.eq.0) nqualcosa=nqualcosa -1
524 kusanagi 2.2
525     18 datalength_dat= nqualcosa
526 kusanagi 1.1 11 format(i1,' ',z4)
527 kusanagi 5.1
528     call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
529     $ startcrc,stopcrc,crctemp)
530 kusanagi 1.1
531     ***************************************************************
532     * TRAILER *
533     ***************************************************************
534    
535     pnum_dat=ishft(iand(trailer(1),z'f000'),-12)
536     cmdnum_dat=ishft(iand(trailer(1),z'0f00'),-8)
537     bid1_dat=ishft(iand(trailer(1),z'00c0'),-6)
538     bid2_dat=ishft(iand(trailer(1),z'0030'),-4)
539     bid3_dat=ishft(iand(trailer(1),z'000c'),-2)
540     bid4_dat=iand(trailer(1),z'0003')
541     bid5_dat=ishft(iand(trailer(2),z'c000'),-14)
542     bid6_dat=ishft(iand(trailer(2),z'3000'),-12)
543     bid7_dat=ishft(iand(trailer(2),z'0c00'),-10)
544     alarm_dat=ishft(iand(trailer(2),z'0300'),-8)
545     aswr_dat=ior(ishft(iand(trailer(2),z'00ff'),8)
546     $ ,ishft(iand(trailer(3),z'ff00'),-8))
547 kusanagi 5.1 crcdat=iand(trailer(3),z'00ff')
548 kusanagi 1.1
549 kusanagi 5.1 c$$$ print*,'######################',crcdat,crctemp
550 kusanagi 1.1
551    
552 kusanagi 5.1 if(crcdat.eq.crctemp)then
553     crc_dat=0
554     else
555     crc_dat=1
556 kusanagi 1.1 endif
557 kusanagi 4.1
558 kusanagi 5.1 bid_dat_sum = (bid1_dat + bid2_dat + bid3_dat + bid4_dat +
559     & bid5_dat + bid6_dat + bid7_dat)
560 kusanagi 1.1
561 kusanagi 5.1 bid_dat = bid_dat_sum/7
562 kusanagi 1.1
563 kusanagi 4.1 50 return
564 kusanagi 1.1 end
565    
566 kusanagi 5.1 * **********************************************************
567     * * *
568     * * *
569     * * *
570     * * *
571     * * *
572     * **********************************************************
573 kusanagi 1.1
574     subroutine initlevel0
575    
576 kusanagi 5.1 include '../common/commontracker.f'
577     include '../common/level0.f'
578    
579     good0=0
580     TOTDATAlength = 0
581 kusanagi 1.1
582     do i=1, nviews
583    
584     DAQmode(i) = 0
585     DSPnumber(i) = 0
586     eventn(i) = 0
587     nclust(i) = 0
588     cutc(i) = 0
589     cutcl(i) = 0
590     addrcluster(i,1) = 0
591     signcluster(i,1) = 0
592     addrcluster(i,2) = 0
593     signcluster(i,2) = 0
594     addrcluster(i,3) = 0
595     signcluster(i,3) = 0
596     fc(i) = 0
597     compressiontime(i) = 0
598     fl5(i) = 0
599     fl4(i) = 0
600     fl3(i) = 0
601     fl2(i) = 0
602     fl1(i) = 0
603     fl6(i) = 0
604     checksum(i) = 0
605     DATAlength(i) = 0
606     pnum(i)= 0
607     cmdnum(i)= 0
608     bid(i) = 1
609     alarm(i)= 0
610     aswr(i) = 0
611 kusanagi 5.1 crc(i)=0
612    
613 kusanagi 1.1 enddo
614    
615    
616     return
617     end
618    
619 kusanagi 5.1 * **********************************************************
620     * * *
621     * * *
622     * * *
623     * * *
624     * * *
625     * **********************************************************
626 kusanagi 1.1
627     subroutine fillview(i)
628     c -----------------------------------------------------
629     c fill variables related to view i
630     c which will be stored in the level0 nt-ple
631     c at the end of loop on views
632     c ----------------------------------------------------
633    
634 kusanagi 5.1 include '../common/commontracker.f'
635     include '../common/level0.f'
636     include '../common/common_readraw.f'
637    
638 kusanagi 1.1
639     DAQmode(i) = DAQmode_dat
640     DSPnumber(i) = DSPnumber_dat
641     eventn(i) = eventn_dat
642     nclust(i) = nclust_dat
643     cutc(i) = cutc_dat
644     cutcl(i) = cutcl_dat
645     addrcluster(i,1) = addrcluster_dat(1)
646     signcluster(i,1) = signcluster_dat(1)
647     addrcluster(i,2) = addrcluster_dat(2)
648     signcluster(i,2) = signcluster_dat(2)
649     addrcluster(i,3) = addrcluster_dat(3)
650     signcluster(i,3) = signcluster_dat(3)
651     fc(i) = fc_dat
652     compressiontime(i) = compressiontime_dat
653     fl5(i) = fl5_dat
654     fl4(i) = fl4_dat
655     fl3(i) = fl3_dat
656     fl2(i) = fl2_dat
657     fl1(i) = fl1_dat
658     fl6(i) = fl6_dat
659     checksum(i) = checksum_dat
660     DATAlength(i) = datalength_dat
661 kusanagi 5.1 crc(i) = crc_dat
662 kusanagi 1.1
663     c -----------------------------------------------------------------------
664     c filling TRAILER variables
665     c ----------------------------------------------------------------------
666    
667     pnum(i)= pnum_dat
668     cmdnum(i)= cmdnum_dat
669     bid(i) = bid_dat
670     alarm(i)= alarm_dat
671     aswr(i) = aswr_dat
672    
673     do idat=1,datalength_dat
674     id = TOTDATAlength + idat
675     datatracker(id) = b_tra(idat)
676     enddo
677     TOTDATAlength = TOTDATAlength + datalength_dat
678 kusanagi 2.2
679 kusanagi 1.1 return
680     end
681    
682 kusanagi 5.1 * **********************************************************
683     * * *
684     * * *
685     * * *
686     * * *
687     * * *
688     * **********************************************************
689    
690     subroutine fillview_cal(i)
691     c -----------------------------------------------------
692     c fill variables related to view i
693     c which will be stored in the calibration nt-ple
694     c at the end of loop on views
695     c ----------------------------------------------------
696    
697     include '../common/commontracker.f'
698     include '../common/trk_calib_parameters.f'
699     include '../common/common_readraw.f'
700    
701     DAQmode(i) = DAQmode_cal
702     DSPnumber(i) = DSPnumber_cal
703     calibnumber(i) = calibrationnumber
704     ncalib_event(i)= nused_event
705     ped_l1(i) = ped_1
706     ped_l2(i) = ped_2
707     ped_l3(i) = ped_3
708     sig_l1(i) = sig_1
709     sig_l2(i) = sig_2
710     sig_l3(i) = sig_3
711     nbad_l1(i) = nbad_1
712     nbad_l2(i) = nbad_2
713     nbad_l3(i) = nbad_3
714     cal_flag(i) = ff
715    
716     do is=1,nstrips_view
717     DSPbad_par(i,is) = DSPbad_o(DSPnumber_cal,is)
718     DSPped_par(i,is) = DSPped_o(DSPnumber_cal,is)
719     DSPsig_par(i,is) = DSPsig_o(DSPnumber_cal,is)
720     enddo
721    
722     crc_hcal(i) = crc_hcalib
723     crc_cal(i,1) = crc_calib(1)
724     crc_cal(i,2) = crc_calib(2)
725     crc_cal(i,3) = crc_calib(3)
726    
727     return
728     end
729    
730     * **********************************************************
731     * * *
732     * * *
733     * * *
734     * * *
735     * * *
736     * **********************************************************
737    
738     subroutine initcalib
739     include '../common/commontracker.f'
740     include '../common/trk_calib_parameters.f'
741    
742     good0=0
743    
744     do i=1,nplanes
745    
746     DAQmode(i) = 0
747     DSPnumber(i) = 0
748     calibnumber(i) = 0
749     ncalib_event(i)= 0
750     ped_l1(i) = 0
751     ped_l2(i) = 0
752     ped_l3(i) = 0
753     sig_l1(i) = 0
754     sig_l2(i) = 0
755     sig_l3(i) = 0
756     nbad_l1(i) = 0
757     nbad_l2(i) = 0
758     nbad_l3(i) = 0
759     cal_flag(i) = 0
760    
761     do is=1,nstrips_view
762     DSPbad_par(i,is) = 0
763     DSPped_par(i,is) = 0
764     DSPsig_par(i,is) = 0
765     enddo
766     crc_hcal(i) = 0
767     crc_cal(i,1) = 0
768     crc_cal(i,2) = 0
769     crc_cal(i,3) = 0
770     enddo
771    
772     return
773 kusanagi 6.2 end

  ViewVC Help
Powered by ViewVC 1.1.23