/[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 4.1 - (hide annotations) (download)
Fri May 6 14:13:17 2005 UTC (19 years, 7 months ago) by kusanagi
Branch: MAIN
CVS Tags: YODA4_3/02, YODA4_3/00, YODA4_3/01, YODA4_2/03
Branch point for: PreThermistores2
Changes since 4.0: +150 -126 lines
Upgrade from Elena Vannuccini 02 May 2005

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

  ViewVC Help
Powered by ViewVC 1.1.23