/[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.2 - (hide annotations) (download)
Fri Jun 23 12:13:13 2006 UTC (18 years, 5 months ago) by kusanagi
Branch: MAIN
CVS Tags: YODA6_3/01, YODA6_3/02
Changes since 6.1: +50 -35 lines
Fixed bug on tracker buffer size.

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

  ViewVC Help
Powered by ViewVC 1.1.23