/[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.3 - (hide annotations) (download)
Mon Jun 26 14:41:24 2006 UTC (18 years, 5 months ago) by kusanagi
Branch: MAIN
CVS Tags: YODA6_3/03
Changes since 6.2: +27 -66 lines
Small fix. Waiting the major release.

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

  ViewVC Help
Powered by ViewVC 1.1.23