/[PAMELA software]/calo/unpacking/calunpack.for
ViewVC logotype

Annotation of /calo/unpacking/calunpack.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.2 - (hide annotations) (download)
Thu Jun 29 07:50:54 2006 UTC (18 years, 5 months ago) by mocchiut
Branch: MAIN
Changes since 1.1: +6 -1 lines
Save crc values in case of crc errors

1 mocchiut 1.1 C
2     C Written by Emiliano Mocchiutti and Mirko Boezio
3     C
4 mocchiut 1.2 C * Version: 3.4.07 *
5 mocchiut 1.1 C
6     C Changelog:
7     C
8 mocchiut 1.2 C 3.4.06 - 3.4.07: (2006-06-29) save CRC values in calselftrig(section,1) and calselftrig(section,2) in case of CRC errors
9     C
10 mocchiut 1.1 C 3.4.05 - 3.4.06: (2005-01-12) section order wrong in CLEARSEC, fixed.
11     C
12     C 3.4.04 - 3.4.05: (2005-01-05) XE is section y odd not even, fixed.
13     C
14     C 3.4.03 - 3.4.04: (2004-12-21) bug in recognising decoding errors, fixed.
15     C
16     C 3.4.02 - 3.4.03: (2004-12-17) forget to clear esci/stwerr and vector vect
17     C plus problems with lleng (truncated vect!). Fixed the
18     C clearing, workaround for lleng (to be further investigated)
19     C
20     C 3.4.01 - 3.4.02: (2004-12-10) cleanup of the code and changed sections order.
21     C
22     C 3.4.00 - 3.4.01: (2004-11-26) CA50 comes after Strips Hit, fixed.
23     C
24     C 3.3.03 - 3.4.00: (2004-11-08) changed the DSP program hence changed calunpack
25     C to better find the calorimeter sections.
26     C
27     C 3.3.02 - 3.3.03: (2004-11-08) changes in the commons (one more common for
28     C calpulse and from calstripshit to calstriphit).
29     C
30     C 3.3.01 - 3.3.02: (2004-10-19) italian name of subroutines translated to
31     C english. Forgot to clear vector in case of CRC errors,
32     C fixed. stwerr is integer not real! fixed
33     C
34     C 3.3.00 - 3.3.01: (2004-10-18) forgot to clear stwerr if no sections are found
35     C fixed.
36     C
37     C 3.2.00 - 3.3.00: (2004-10-15) enanched search of sections in case of one or
38     C more missing sections.
39     C Switched to c function "fillin" to create calorimeter words
40     C instead of fortran function "riempi": great improvement in
41     C time processing!!
42     C
43     C 3.1.00 - 3.2.00: (2004-10-13) forget to clean some variables, fixed.
44     C Reprocess event in the case we have CRC errors and a high
45     C number of error trying to understand the kind of event
46     C we are processing (raw, compress, full mode) in order to
47     C distinguish better the four section.The reprocessing happens
48     C on about the 30% of events with CRC errors (in the case of
49     C file 040827_005 the reprocessing is done on about 2% of all
50     C the events).
51     C
52     C 3.0.00 - 3.1.00: (2004-10-12) cleanup and speedup of the code, less loops
53     C same strength in finding the calorimeter sections.
54     C
55     C 2.18.4 - 3.0.00: (2004-10-07) major changes in the procedure to find the
56     C calorimeter sections and enhanced search in the case of
57     c CRC errors (to fix a bug which made the misunderstanding
58     C some kind of CRC errors with missing sections).
59     C Clean up unused variables, speeded up some loops.
60     C Zero length input vector error added.
61     C Enhanced search of the first section recorded since the
62     C starting point is very important to correctly find and
63     C interpret all the other sections.
64     C If section length is absurd and the CRC header bit = 0
65     C then search again for that section (needed to make a
66     C better search of section when in presence of CRC errors)
67     C Search all the sections and if you reach the end of vector
68     C (EOV) continue searching if you haven't find all the four
69     C section (and go out without looping if no section is
70     C present).
71     C
72     C 2.18.3 - 2.18.4: consider a bad thing if you find a section in the wrong
73     C position of the vector and try again to
74     C find the real data (if they exist).
75     C
76     C 2.18.2 - 2.18.3: vectors belonging to common must be cleared if the calo
77     C isn't found. Fixed.
78     C
79     C 2.18.1 - 2.18.2: fixed unclearing error codes if the program doesn't find
80     C the calorimeter where it should be but shifted somewhere
81     C else forgotten to clear st2c variable: fixed
82     C exit error code wrong in some cases: fixed
83     C self trigger data not saved: fixed.
84     C
85     C 2.18.0 - 2.18.1: small changes in the common varie to fix a memory leak;
86     C fixed an error in reporting error codes (stwerr,pwerror).
87     C
88     C 2.17.0 - 2.18.0: corrected bug which made unable the program to find CRC
89     C errors in the last section of the calorimeter;
90     C added a "debugging" option to dump to standard output
91     C the whole packet in hexadecimal format and other
92     C useful informations. To activate it the dump variable
93     C in the common varie must be passed with the value
94     C of iev you want to check. Do nothing if you don't want
95     C any output.
96     C
97     C------------------------------------------------
98     SUBROUTINE CALUNPACK(vecta,lung,me)
99     C------------------------------------------------
100    
101     IMPLICIT NONE
102     C
103     C PARAMETERS DEFINITION
104     C
105     C START = WHERE TO START TO LOOK FOR THE CALORIMETER, IN WORDS
106     C 1STSEC = MAXIMUM POSITION, IN BYTES, WHERE WE SUPPOSE TO FIND THE
107     C HEADER OF THE FIRST SECTION
108     C
109     INTEGER START, SEC1ST
110     INTEGER NPLA, NCHA, LENSEV
111     INTEGER*2 ival
112     C
113     PARAMETER (START=50,SEC1ST=1200)
114     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
115     PARAMETER (ival='FFFF'x)
116     C
117     C Normal variables definition
118     C
119     integer lung, SOGLIA0, SEC2ND
120     INTEGER*1 VECTA(lung)
121     INTEGER*2 vect(60000), test
122     integer*2 check, crc, e2(4)
123     INTEGER*2 length, length2
124     integer me, m, dumpo, finoa
125     INTEGER merror(4), headcor, ichc, coco
126     INTEGER i, j, iev, min, st2c, bit, bi, lleng
127     INTEGER ic, k,l, ke, ic0, icsave, chi
128     INTEGER hcchi(1000), hcic(1000),hcco
129     INTEGER contr, isfull, israw, iscomp
130     INTEGER inf, sup, em, icb
131     INTEGER XO, YO, XE, YE, icold
132     integer st1b, st2b, lunga, pari
133     integer stwerr(4),yescbra, chis, esci, icprima
134     integer seemcomp, seemfull, cberaw, yesisco, yesisfu,yesisra
135     integer ca50, ca50a, ca50b
136     C
137     real dedx1(11,96),dedx2(11,96),dedx3(11,96),dedx4(11,96)
138     real dedx1c(11,96),dedx2c(11,96),dedx3c(11,96),dedx4c(11,96)
139     real base1(11,6),base2(11,6),base3(11,6),base4(11,6)
140     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,6)
141     real auto(7)
142     real calselftrig(4,7), calIItrig(4), calstriphit(4),
143     & calDSPtaberr(4), calevnum(4)
144     real perror(4)
145     C
146     DATA YE/246/ ! CODE_EV_R YE = 111 10110
147     DATA YO/237/ ! CODE_EV_R YO = 111 01101
148     DATA XE/234/ ! CODE_EV_R XE = 111 01010
149     DATA XO/241/ ! CODE_EV_R XO = 111 10001
150     C
151     COMMON / evento / iev, stwerr, perror,
152     & dexy,dexyc,base,
153     & calselftrig,calIItrig,
154     & calstriphit,calDSPtaberr,calevnum
155     save / evento /
156     C
157     COMMON / VARIE / dumpo, CONTR, merror
158     SAVE / VARIE /
159     C
160     C Begin !
161     C
162     SOGLIA0 = 70
163     C
164     C input length must be > 0, if not go out with error code 142
165     C
166     if (lung.le.0) then
167     if (dumpo.eq.iev) print *,'lung = ',lung
168     do i=1,4
169     merror(i)=142
170     enddo
171     goto 999
172     endif
173     C
174     C no debug informations
175     C
176     if (dumpo.eq.0) dumpo=-1
177     C
178     C DEBUG: PRINT OUT THE INPUT VECTOR
179     C
180     if (iev.eq.dumpo) then
181     do l=1,lung
182     write(*,17)l,vecta(l)
183     enddo
184     endif
185     C
186     C DETERMINE LENGTH IN WORDS FROM LENGTH IN BYTES
187     C
188     IF (MOD(LUNG,2).EQ.0) THEN
189     lunga = lung / 2
190     pari = 1
191     else
192     lunga = int(lung/2) + 1
193     endif
194     SEC2ND = LUNGA
195     C
196     C IS LENGTH IS TOO LONG?
197     C
198     if (lunga.gt.60000.and.dumpo.gt.0) then
199     print *,'Calorimeter WARNING: more than 60000 words!'
200     lunga = 60000
201     endif
202     C
203     C PRE-CLEAR VARIABLES
204     C
205     yesisco = 0
206     yesisfu = 0
207     yesisra = 0
208     yescbra = 0
209     C
210     1 CONTINUE
211     c
212     C CLEAR VARIABLES
213     C
214     if (iev.lt.0.or.iev.gt.90000000) iev = 0
215     esci = 0
216     chi = 0
217     chis = 0
218     min = 0
219     lleng = 0
220     m = 0
221     pari = 0
222     icb = 0
223     em = 0
224     coco = 0
225     me = 1
226     contr = 1
227     ic = 1
228     icsave = 0
229     C
230     call clearall
231     call azero(dedx1,11*96)
232     call azero(dedx2,11*96)
233     call azero(dedx3,11*96)
234     call azero(dedx4,11*96)
235     call azero(dedx1c,11*96)
236     call azero(dedx2c,11*96)
237     call azero(dedx3c,11*96)
238     call azero(dedx4c,11*96)
239     call azero(base1,11*6)
240     call azero(base2,11*6)
241     call azero(base3,11*6)
242     call azero(base4,11*6)
243     C
244     do l = 1,4
245     e2(l) = 0
246     perror(l) = 0.
247     stwerr(l) = 0
248     merror(l) = 0
249     enddo
250     C
251     C DETERMINE WHERE TO START TO FIND THE CALORIMETER IN THE INBUT BUFFER
252     C
253     length2 = start
254     c
255     20 continue
256     C
257     if (length2.ge.-2) then
258     ic = ic + (2 * (length2 + 2))
259     else
260     if (dumpo.gt.0)
261     & print *,'Calorimeter WARNING: length errors ',ic,length2
262     endif
263     C
264     headcor = 0
265     ichc = ic
266     icprima = ic
267     hcco = 0
268     do i=1,1000
269     hcchi(i) = 0
270     hcic(i) = 0
271     enddo
272     c
273     32 continue
274     C
275     ke = 0
276     chis = chi
277     icold = ic
278     DO i = 1, 60000
279     vect(i) = 0
280     enddo
281     do while (ke.eq.0)
282     C
283     C if (iev.eq.dumpo) print *,'parto da ',ic,contr
284     C
285     C Check consistency of header.
286     C it is composed by CODE+D# (8 bits) and by SATUS WORD (8 bits)
287     c so we must split vect into the two components:
288     C
289     st1b = 0
290     st2b = 0
291     C
292     C A CALORIMETER SECTION IS MADE OF AT LEAST 4 BYTES
293     C IF WE HAVE NO ROOM FOR A SECTION GO OUT
294     C
295     if ((ic+4).gt.lung.or.esci.eq.1) then
296     if (headcor.eq.1.and.contr.lt.5) then
297     headcor=-1
298     ic=ichc
299     goto 32
300     else
301     if (headcor.eq.0.or.headcor.eq.2) then
302     chi = chi + 8 * (5 - contr)
303     endif
304     merror(contr) = 129
305     stwerr(contr) = 0
306     if (iev.eq.dumpo) print *,'put to zero here ',headcor
307     if (esci.eq.0) then
308     ic = icsave
309     else
310     ic = icprima
311     endif
312     if (headcor.eq.2) then
313     chi = chis
314     endif
315     esci = 0
316     headcor = 0
317     hcco = 0
318     ichc = 0
319     do i=1,1000
320     hcchi(i) = 0
321     hcic(i) = 0
322     enddo
323     length2 = -2
324     lleng = 0
325     length = 0
326     goto 150
327     endif
328     endif
329     C
330     C ST1B IS "CODE", ST2B IS "D#"
331     C
332     do bit = 0, 7
333     bi = ibits(vecta(ic),bit,1)
334     if (bi.eq.1) st1b = ibset(st1b,bit)
335     bi = ibits(vecta(ic+1),bit,1)
336     if (bi.eq.1) st2b = ibset(st2b,bit)
337     enddo
338     c
339     C IC+2 AND IC+3 CONTAINS THE LENGTH OF THE CALORIMETER SECTION
340     c
341     length2 = 0
342     do bit=0, 7
343     bi = ibits(vecta(ic+3),bit,1)
344     if (bi.eq.1) length2 = ibset(length2,bit)
345     bi = ibits(vecta(ic+2),bit,1)
346     if (bi.eq.1) length2 = ibset(length2,bit+8)
347     enddo
348     C
349     C calorimeter signature in DSP mode (CA50 CA50):
350     C
351     ca50 = 0
352     if (ic+24.lt.lung) then
353     ca50a = 0
354     do bit=0, 7
355     bi = ibits(vecta(ic+23),bit,1)
356     if (bi.eq.1) ca50a = ibset(ca50a,bit)
357     bi = ibits(vecta(ic+22),bit,1)
358     if (bi.eq.1) ca50a = ibset(ca50a,bit+8)
359     enddo
360     ca50b = 0
361     do bit=0, 7
362     bi = ibits(vecta(ic+25),bit,1)
363     if (bi.eq.1) ca50b = ibset(ca50b,bit)
364     bi = ibits(vecta(ic+24),bit,1)
365     if (bi.eq.1) ca50b = ibset(ca50b,bit+8)
366     enddo
367     if (ca50a.eq.ca50b.and.ca50a.eq.51792) ca50 = 1
368     endif
369    
370     C
371     c the crc should be at vect(length) with
372     C
373     length = length2 + 1
374     C
375     c some checks to be sure we have found the calorimeter data:
376     c status word is always less then 129
377     c
378     if (st2b.gt.128) then
379     length = 0
380     length2 = 0
381     goto 100
382     endif
383     c
384     c length of the packet IN WORDS must be less then HALF OF THE
385     C LENGTH IN BYTES if noT THERE ARE SOME errors
386     c
387     bi = ibits(st2b,0,1)
388     if (length2.gt.lunga.OR.LENGTH2.LE.0) then
389     if (headcor.eq.2) then
390     chi = chi + 4
391     endif
392     length = 0
393     length2 = 0
394     goto 100
395     endif
396     c
397     e2(contr) = 0
398     C
399     if (CONTR.eq.1) then
400     c
401     c is it the first section?
402     c
403     if (st1b.eq.XE.and.(ca50.eq.1.or.length2.eq.1064)) then
404     c if so go out of this loop and go on recording data
405     ke = 1
406     icsave = ic
407     m = ic
408     if (iev.eq.dumpo) then
409     print *,'1m,lunga,lleng,lung,pari',m,lunga,lleng,lung,
410     & pari
411     endif
412     call fillin(m,lunga,lleng,lung,pari,vect,vecta)
413     C
414     icb = 1
415     E2(contr) = vect(icb)
416     if (iev.eq.dumpo) then
417     print *,'headcor ',headcor
418     write(*,22)vect(icb)
419     print *,'1m,lunga,lleng,lung,pari',m,lunga,lleng,lung,
420     & pari
421     endif
422     if (headcor.eq.2) then
423     if (coco.ne.1) then
424     coco = 1
425     else
426     coco = -1
427     endif
428     if (st2b.ne.0) then
429     call counter(e2(contr),chi)
430     endif
431     endif
432     goto 100
433     endif
434     ENDIF
435     C
436     c the same for the second section, ...
437     c
438     if (CONTR.eq.2) then
439     if (st1b.eq.XO.and.(ca50.eq.1.or.length2.eq.1064)) then
440     ke = 2
441     icsave = ic
442     m = ic
443     if (iev.eq.dumpo) then
444     print *,'2m,lunga,lleng,lung,pari',m,lunga,lleng,lung,
445     & pari
446     endif
447     call fillin(m,lunga,lleng,lung,pari,vect,vecta)
448     icb = 1
449     E2(contr) = vect(icb)
450     if (iev.eq.dumpo) then
451     print *,'headcor ',headcor
452     write(*,22)vect(icb)
453     print *,'2m,lunga,lleng,lung,pari',m,lunga,lleng,lung,
454     & pari
455     endif
456     if (headcor.eq.2) then
457     if (coco.ne.2) then
458     coco = 2
459     else
460     coco = -1
461     endif
462     if ((ic-icold).ne.0) chi=chi+abs(ic-icold)
463     if (st2b.ne.0) then
464     call counter(e2(contr),chi)
465     endif
466     endif
467     goto 100
468     endif
469     ENDIF
470     c
471     C ... for the third,...
472     c
473     if (CONTR.eq.3) then
474     if (st1b.eq.YE.and.(ca50.eq.1.or.length2.eq.1064)) then
475     ke = 3
476     icsave = ic
477     m = ic
478     if (iev.eq.dumpo) then
479     print *,'3m,lunga,lleng,lung,pari',m,lunga,lleng,lung,
480     & pari
481     endif
482     call fillin(m,lunga,lleng,lung,pari,vect,vecta)
483     icb = 1
484     E2(contr) = vect(icb)
485     if (iev.eq.dumpo) then
486     print *,'headcor ',headcor
487     write(*,22)vect(icb)
488     print *,'3m,lunga,lleng,lung,pari',m,lunga,lleng,lung,
489     & pari
490     endif
491     if (headcor.eq.2) then
492     if (coco.eq.3) then
493     coco = 3
494     else
495     coco = -1
496     endif
497     if (ic-icold.ne.0) chi = chi + abs(ic-icold)
498     if (st2b.ne.0) then
499     call counter(e2(contr),chi)
500     endif
501     endif
502     goto 100
503     endif
504     ENDIF
505     C
506     c ...and for the last section.
507     c
508     if (CONTR.eq.4) then
509     if (st1b.eq.YO.and.(ca50.eq.1.or.length2.eq.1064)) then
510     ke = 4
511     icsave = ic
512     m = ic
513     call fillin(m,lunga,lleng,lung,pari,vect,vecta)
514     icb = 1
515     E2(contr) = vect(icb)
516     if (headcor.eq.2) then
517     if (coco.eq.4) then
518     coco = 4
519     else
520     coco = -1
521     endif
522     if ((ic-icold).ne.0) chi = chi + abs(ic-icold)
523     if (st2b.ne.0) then
524     call counter(e2(contr),chi)
525     endif
526     endif
527     goto 100
528     endif
529     endif
530     C
531     if (contr.gt.4) then
532     if (iev.eq.dumpo) print *,'go out here'
533     headcor = 0
534     hcco = 0
535     ichc = 0
536     do i=1,1000
537     hcchi(i) = 0
538     hcic(i) = 0
539     enddo
540     goto 200
541     endif
542     C
543     100 CONTINUE
544     c
545     c increment vector of one searching for the next section
546     c
547     ic = ic + 1
548     c
549     enddo
550     C
551     c format not used
552     c
553     10 FORMAT(2X,'Error for view:',2X,I1,2X,'Status word:',2X,Z4)
554     11 FORMAT(2X,'View or command not recognized for view:',2X,I1,2X,
555     & 'Status word:',2X,Z4)
556     12 FORMAT(2X,'Error - did NOT find view:',2X,I1)
557     13 FORMAT(2X,'Error - eof reached, exiting')
558     14 FORMAT(2X,I8,2X,I10)
559     15 FORMAT(2X,I8,2X,Z8)
560     17 FORMAT(2X,'Element:',2X,I6,2X,' word:',2X,Z8)
561     18 FORMAT(2X,'Element:',2X,I6,2X,' word:',2X,Z2,Z2)
562     21 FORMAT(2X,'CRC: ',2X,Z8)
563     22 FORMAT(2X,'vect(icb): ',2X,Z8)
564     C
565     c go on recording data
566     ic = ic - 1
567     c
568     c
569     K = CONTR
570     ic0 = icb
571     icb = icb + 1
572     length = vect(icb) + 2
573     length2 = vect(icb)
574     lleng = (length*2) - 1
575     C
576     C Check consistency of CRCs.
577     C
578     C
579     C IF THE STATUS WORD HAS THE CRC BIT ON AND WE ARE NOT IN THE
580     C HEADCOR CASE 0 (WE WERE BELIEVING THE SECTION FOUND WAS FINE)
581     C
582     if ((ibits(e2(contr),0,1).ne.0.or.
583     & (ibits(e2(contr),3,1).eq.1.and.length2.ne.1064))
584     & .and.headcor.EQ.0) then
585     headcor = 1
586     ichc = ic - 1
587     if (iev.eq.dumpo) print *,'crc st word wrong',ic,ichc,headcor
588     endif
589     C
590     C HEADOCR = 1 MEANS SEARCH AGAIN FOR THAT SECTION
591     C
592     if (headcor.eq.1) then
593     hcco = hcco + 1
594     if (st2b.ne.0) then
595     call counter(e2(contr),hcchi(hcco))
596     endif
597     C
598     if (contr.gt.1.or.yesisco.ne.0.or.yesisfu.ne.0
599     & .or.yesisra.ne.0.or.yescbra.ne.0) then
600     iscomp = 0
601     isfull = 0
602     israw = 0
603     if (yesisco.ne.0.or.yesisfu.ne.0
604     & .or.yesisra.ne.0.or.yescbra.ne.0) then
605     if (yesisra.ne.0.or.yescbra.ne.0) israw = 2
606     if (yesisco.ne.0) iscomp = 2
607     if (yesisfu.ne.0) isfull = 2
608     else
609     i = 1
610     do while(iscomp.eq.0.and.isfull.eq.0.and.israw.eq.0.and.
611     & i.lt.(contr-1))
612     if (ibits(stwerr(i),16,1).eq.1) iscomp = iscomp + 1
613     if (ibits(stwerr(i),17,1).eq.1) isfull = isfull + 1
614     if (ibits(e2(i),3,1).eq.1.and.merror(i).eq.0)
615     & israw = israw + 1
616     i = i + 1
617     enddo
618     endif
619     c
620     c how does this section look like? (note that in case of crc errors
621     c this test has no value...)
622     c
623     test = vect(icb+12)
624     seemcomp = 0
625     seemfull = 0
626     if (test.eq.ival) then
627     seemcomp = 1
628     elseif (test.eq.0) then
629     seemfull = 1
630     endif
631     c
632     c if a previous good section was raw and this header we are analyzing
633     c is not raw something strange is happening, add a weight.
634     c
635     if ((israw.ne.0.and.ibits(e2(contr),3,1).ne.1)
636     & .or.(israw.ne.0.and.length2.ne.1064)) then
637     hcco = hcco - 1
638     length=0
639     length2=0
640     lleng=0
641     ic = ic + 1
642     if (iev.eq.dumpo)
643     & print *,'not raw, search again ',ic,ichc,headcor
644     goto 32
645     endif
646     c
647     c the same with compress and full mode
648     c
649     if ((iscomp.ne.0.or.isfull.ne.0)
650     & .and.ibits(e2(contr),3,1).eq.1) then
651     hcco = hcco - 1
652     length=0
653     length2=0
654     lleng=0
655     ic = ic + 1
656     if (iev.eq.dumpo)
657     & print *,'raw in full or compress mode, search again ',ic,ichc,
658     & headcor
659     goto 32
660     endif
661    
662     if (iscomp.ne.0.and.(ibits(e2(contr),3,1).eq.1.or.
663     & seemcomp.eq.0)) hcchi(hcco) = hcchi(hcco) + 2
664     if (isfull.ne.0.and.(ibits(e2(contr),3,1).eq.1.or.
665     & seemfull.eq.0)) hcchi(hcco) = hcchi(hcco) + 2
666     endif
667     C
668     if (ibits(e2(contr),3,1).eq.1.and.length2.eq.1064) then
669     hcchi(hcco) = hcchi(hcco) - 2
670     elseif ((ibits(e2(contr),3,1).eq.1.or.israw.ne.0)
671     & .and.length2.ne.1064) then
672     hcco = hcco - 1
673     length=0
674     length2=0
675     lleng=0
676     ic = ic + 1
677     if (iev.eq.dumpo)
678     & print *,'raw bit not raw length, search again ',ic,ichc,headcor
679     goto 32
680     endif
681     C
682     hcic(hcco) = ic
683     ic = ic + 1
684     length=0
685     length2=0
686     lleng=0
687     if (iev.eq.dumpo) print *,'search again ',ic,ichc,headcor
688     goto 32
689     endif
690     C
691     C HEADCOR = - 1 MEANS STOP SEARCHING FOR THAT SECTION, SELECT
692     C THE CASE WITH LESS ERRORS, FOUND THAT SECTION AND GIVE
693     C HEADCOR = 2 (I.E. GO OUT OF THE LOOP)
694     C
695     if (headcor.eq.-1) then
696     if (iev.eq.dumpo) print *,'enter -1, ',hcco,ke
697     headcor = 2
698     if (ke.le.2.and.hcco.ge.1) then
699     finoa = 0
700     do i = 1, hcco
701     if (ke.eq.1.and.hcic(i).lt.SEC1ST) finoa = i
702     if (ke.eq.2.and.hcic(i).lt.SEC2ND) finoa = i
703     enddo
704     if (finoa.eq.0) then
705     esci = 1
706     if (iev.eq.dumpo)
707     & print *,'finoa=0! no possible solutions '
708     else
709     if (iev.eq.dumpo) print *,'ke = ',ke,' and hcco>1 ',finoa
710     call minerr(ic,hcic,hcchi,min,finoa)
711     endif
712     else
713     if (hcco.eq.0) then
714     esci = 1
715     if (iev.eq.dumpo)
716     & print *,'hcco=0! no possible solutions'
717     else
718     call minerr(ic,hcic,hcchi,min,hcco)
719     endif
720     endif
721     e2(contr) = 0
722     if (iev.eq.dumpo) then
723     print *,'stop searching'
724     print *,'ic,hcic(min),min,... ',ic,hcic(min),min,
725     & hcchi(min),hcco,coco
726     do i=1,hcco
727     print *,'i, hcchi ',i,hcchi(i)
728     enddo
729     endif
730     c
731     length=0
732     length2=0
733     lleng=0
734     esci = 0
735     MERROR(contr) = 0
736     goto 32
737     endif
738     C
739     C determine the type of data if not raw (compress or full)
740     C
741     if (headcor.eq.0.or.headcor.eq.2
742     & .and.ibits(e2(contr),3,1).ne.1) then
743     test = vect(icb+12)
744     seemcomp = 0
745     seemfull = 0
746     if (test.eq.ival) then
747     C
748     C compress mode
749     C
750     stwerr(contr) = ibset(stwerr(contr),16)
751     elseif (test.eq.0) then
752     C
753     C full mode
754     C
755     stwerr(contr) = ibset(stwerr(contr),17)
756     endif
757     endif
758     C
759     hcco = 0
760     ichc = 0
761     check = 0
762     do i=1,1000
763     hcchi(i) = 0
764     hcic(i) = 0
765     enddo
766     inf = ic0
767     sup = length - 1
768     do i = inf,sup
769     check=crc(check,vect(i))
770     enddo
771     C
772     if (iev.eq.dumpo) then
773     write(*,21)vect(length)
774     print *,' CRC position ',length
775     write(*,21)check
776     endif
777     C
778     if (check.ne.vect(length)) then
779     merror(contr) = 132
780     chi = chi + 4
781     lleng = 0
782     length2 = 0
783     length = 0
784     C
785     C clear vectors of that section in the common
786     C
787     call clearsec
788     C
789 mocchiut 1.2 calselftrig(k,1) = check
790     calselftrig(k,2) = vect(length)
791     c
792 mocchiut 1.1 if (ke.eq.1.and.headcor.ne.2) then
793     ic = 10
794     elseif (headcor.eq.2) then
795     contr = contr + 1
796     endif
797     headcor = 1
798     ichc = ic - 1
799     if (iev.eq.dumpo)
800     & print *,'crc is wrong ',ic,
801     & ' search section ',contr,' coco = ',coco
802     goto 32
803     else
804     chi = chi - 4
805     if (chi.lt.0) chi = 0
806     endif
807     C
808     headcor = 0
809     C
810     19 CONTINUE
811     C
812     C Process data.
813     C
814     call clearsec
815     do i = 1, 7
816     icb = icb + 1
817     auto(i) = vect(icb)
818     enddo
819     C
820     st2c = 0
821     if (st2b.ne.0) then
822     do bit=0, 6
823     bi = ibits(st2b,bit,1)
824     if (bit.eq.3.and.bi.ne.0) st2c = 8
825     enddo
826     endif
827     C
828     if (st2c.eq.8) then
829     if (length2.ne.1064) then
830     merror(contr) = 133
831     chi = chi + 4
832     if (iev.eq.dumpo)
833     & print *,'raw lung 4'
834     lleng = 0
835     goto 150
836     else
837     if (k.eq.1) call CALRAW(vect,icb+1,length-1,dedx1)
838     if (k.eq.2) call CALRAW(vect,icb+1,length-1,dedx2)
839     if (k.eq.3) call CALRAW(vect,icb+1,length-1,dedx3)
840     if (k.eq.4) call CALRAW(vect,icb+1,length-1,dedx4)
841     endif
842     goto 50
843     endif
844     C
845     41 FORMAT(2X,I2,2X,'word :',1x,z4)
846     test = vect(icb+5)
847     c
848     if (test.eq.ival) then
849     if (length2.gt.1201) then
850     merror(contr) = 134
851     chi = chi + 4
852     if (iev.eq.dumpo)
853     & print *,'compr lung 4'
854     lleng = 0
855     goto 150
856     else
857     icb = icb + 1
858     calIItrig(k) = vect(icb)
859     icb = icb + 1
860     calstriphit(k) = vect(icb)
861     icb = icb + 1
862     C FIRST CALORIMETER SIGNATURE: CA50
863     icb = icb + 1
864     C SECOND CALORIMETER SIGNATURE: CA50
865     icb = icb + 1
866     C test is here!
867     icb = icb + 1
868     calDSPtaberr(k) = vect(icb)
869     icb = icb + 1
870     calevnum(k) = vect(icb)
871     if (k.eq.1) call CALCOMPRESS(vect,icb+1,length-1,dedx1c,
872     & base1)
873     if (k.eq.2) call CALCOMPRESS(vect,icb+1,length-1,dedx2c,
874     & base2)
875     if (k.eq.3) call CALCOMPRESS(vect,icb+1,length-1,dedx3c,
876     & base3)
877     if (k.eq.4) call CALCOMPRESS(vect,icb+1,length-1,dedx4c,
878     & base4)
879     goto 50
880     endif
881     else if (test.eq.0) then
882     if (length2.gt.2257) then
883     merror(contr) = 135
884     chi = chi + 4
885     if (iev.eq.dumpo)
886     & print *,'full lung 4'
887     lleng = 0
888     goto 150
889     else
890     icb = icb + 1
891     calIItrig(k) = vect(icb)
892     icb = icb + 1
893     calstriphit(k) = vect(icb)
894     icb = icb + 1
895     C FIRST CALORIMETER SIGNATURE: CA50
896     icb = icb + 1
897     C SECOND CALORIMETER SIGNATURE: CA50
898     icb = icb + 1
899     C test is here!
900     icb = icb + 1
901     calDSPtaberr(k) = vect(icb)
902     icb = icb + 1
903     calevnum(k) = vect(icb)
904     if (k.eq.1) call CALFULL(vect,icb+1,length-1,dedx1,
905     & dedx1c,base1)
906     if (k.eq.2) call CALFULL(vect,icb+1,length-1,dedx2,
907     & dedx2c,base2)
908     if (k.eq.3) call CALFULL(vect,icb+1,length-1,dedx3,
909     & dedx3c,base3)
910     if (k.eq.4) call CALFULL(vect,icb+1,length-1,dedx4,
911     & dedx4c,base4)
912     goto 50
913     endif
914     else
915     merror(contr) = 136
916     chi = chi + 4
917     if (iev.eq.dumpo)
918     & print *,'decoding problems 4'
919     lleng = 0
920     goto 150
921     endif
922     c
923     50 continue
924     c
925     C
926     do i = 1,7
927     calselftrig(k,i) = auto(i)
928     enddo
929     C
930     DO I = 1,11
931     DO J = 1,96
932     DEXY(2,2*I,J) = DEDX2(I,J)
933     DEXY(1,2*I-1,J) = DEDX4(I,J)
934     DEXY(2,2*I-1,97-J) = DEDX1(I,J)
935     DEXY(1,2*I,J) = DEDX3(I,J)
936     DEXYC(2,2*I,J) = DEDX2C(I,J)
937     DEXYC(1,2*I-1,J) = DEDX4C(I,J)
938     DEXYC(2,2*I-1,97-J) = DEDX1C(I,J)
939     DEXYC(1,2*I,J) = DEDX3C(I,J)
940     enddo
941     do j = 1,6
942     base(2,2*i,j) = base2(i,j)
943     base(1,2*i-1,j) = base4(i,j)
944     base(2,2*i-1,7-j) = base1(i,j)
945     base(1,2*i,j) = base3(i,j)
946     enddo
947     enddo
948     C
949     150 continue
950     C
951     contr = contr + 1
952     C
953     c go on till we have found all the four sections
954     c
955     if (contr.lt.5) goto 20
956     c
957     200 continue
958     C
959     iscomp = 0
960     isfull = 0
961     israw = 0
962     do i = 1, 4
963     if (ibits(stwerr(i),16,1).eq.1) iscomp = iscomp + 1
964     if (ibits(stwerr(i),17,1).eq.1) isfull = isfull + 1
965     if (ibits(e2(i),3,1).eq.1) israw = israw + 1
966     enddo
967     if (iscomp.ne.0) chi = chi + 8 * (4 - iscomp)
968     if (israw.ne.0) chi = chi + 8 * (4 - israw)
969     if (isfull.ne.0) chi = chi + 8 * (4 - isfull)
970     C
971     C if chi>10 and we have information enough to understand the physic event
972     C was acquired in a certain mode (RAW, FULL or COMPRESS) then reprocess
973     C the event using this information, sometimes we miss a section due to
974     C CRC errors in the previous one but if we know what we are looking for
975     C then it is possible to save this kind of events.
976     C
977     if (chi.gt.5.and.yesisco.eq.0.and.yesisfu.eq.0
978     & .and.yesisra.eq.0.and.yescbra.eq.0) then
979     israw = 0
980     cberaw = 0
981     do i = 1, 4
982     if (ibits(e2(i),3,1).eq.1.and.merror(i).eq.0)
983     & israw = israw + 1
984     if (ibits(e2(i),3,1).eq.1.and.merror(i).eq.132)
985     & cberaw = cberaw + 1
986     enddo
987     yesisco = 0
988     yesisfu = 0
989     yesisra = 0
990     yescbra = 0
991     if (iscomp.ne.0) yesisco = 1
992     if (isfull.ne.0) yesisfu = 1
993     if (israw.ne.0) yesisra = 1
994     if (cberaw.ne.0) yescbra = 1
995     if ((yesisco+yesisfu+yesisra).eq.1.or.
996     & ((yesisco+yesisfu+yesisra).eq.0.and.yescbra.eq.1)) then
997     if (iev.eq.dumpo) then
998     print *,'************************'
999     if (iscomp.ne.0) print *,'is a compress acq.'
1000     if (isfull.ne.0) print *,'is a full acq.'
1001     if (israw.ne.0) print *,'is a raw acq.'
1002     if (israw.eq.0.and.cberaw.ne.0)
1003     & print *,'could be a raw acq.'
1004     print *,'so, SGARBUF, do it again! ',chi
1005     print *,'************************'
1006     endif
1007     SOGLIA0 = SOGLIA0 - ISCOMP - ISFULL - ISRAW
1008     goto 1
1009     endif
1010     if ((yesisco+yesisfu+yesisra+yescbra).eq.0) chi = 1000
1011     endif
1012     C
1013     if (iev.eq.dumpo)
1014     & print *,'chi <= soglia0 ?',chi,soglia0
1015     if (chi.lt.soglia0) then
1016     me = 0
1017     else
1018     me = 1
1019     do i = 1, 4
1020     merror(i) = 129
1021     e2(i) = 0
1022     stwerr(i) = 0
1023     enddo
1024     call clearall
1025     goto 999
1026     endif
1027     C
1028     C if all section are missing clear vectors and go out
1029     C
1030     if (merror(1).eq.129.and.merror(2).eq.129
1031     & .and.merror(3).eq.129.and.merror(4).eq.129) then
1032     do l = 1,4
1033     e2(l) = 0
1034     stwerr(l) = 0
1035     enddo
1036     call clearall
1037     endif
1038     c
1039     999 continue
1040     c
1041     do l = 1, 4
1042     do bit=0, 31
1043     if (bit.lt.16) then
1044     bi = ibits(E2(L),bit,1)
1045     elseif (bit.gt.17) then
1046     bi = 0
1047     elseif (bit.ge.16.and.bit.le.17) then
1048     bi = 2
1049     endif
1050     if (bi.eq.1) then
1051     stwerr(l) = ibset(stwerr(l),bit)
1052     elseif (bi.eq.0) then
1053     stwerr(l) = ibclr(stwerr(l),bit)
1054     endif
1055     enddo
1056     perror(l) = float(merror(l))
1057     enddo
1058     c
1059     if ( iev.eq.dumpo ) then
1060     if (perror(3).eq.132.and.perror(4).eq.129) then
1061     do i = 1, 2
1062     do j = 1, 22
1063     do l = 1, 96
1064     print *,'Evento ',i,j,l,dexy(i,j,l)
1065     enddo
1066     enddo
1067     enddo
1068     do l=1,lung
1069     write(*,17)l,vecta(l)
1070     enddo
1071     endif
1072     endif
1073     iev = iev + 1
1074     RETURN
1075     END
1076    
1077    
1078     C------------------------------------------------
1079     SUBROUTINE CALRAW(vect,inf,sup,dedx)
1080     C------------------------------------------------
1081    
1082     IMPLICIT NONE
1083     C
1084     INTEGER NPLA, NCHA, LENSEV
1085     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
1086     C
1087     INTEGER*2 VECT(30000)
1088     INTEGER inf, sup
1089     INTEGER i,j,k, iev
1090     INTEGER contr
1091     integer stwerr(4), dumpo, merror(4)
1092     C
1093     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,6)
1094     real calselftrig(4,7), calIItrig(4), calstriphit(4),
1095     & calDSPtaberr(4), calevnum(4)
1096     REAL dedx(11,96)
1097     real perror(4)
1098     C
1099     COMMON / evento / iev, stwerr, perror,
1100     & dexy,dexyc,base,
1101     & calselftrig,calIItrig,
1102     & calstriphit,calDSPtaberr,calevnum
1103    
1104     save / evento /
1105     c
1106     COMMON / VARIE / dumpo, CONTR, merror
1107     SAVE / VARIE /
1108     c
1109     k = inf
1110     do j = 1,96
1111     do i = 1,11
1112     DEDX(I,J) = 0.
1113     dedx(i,j) = vect(k)
1114     k = k + 1
1115     enddo
1116     enddo
1117     c
1118     RETURN
1119     END
1120    
1121     C------------------------------------------------
1122     SUBROUTINE CALCOMPRESS(vect,inf,sup,dedx,basse)
1123     C------------------------------------------------
1124    
1125     IMPLICIT NONE
1126    
1127     INTEGER NPLA, NCHA, LENSEV
1128     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
1129     C
1130     INTEGER*2 VECT(30000)
1131     INTEGER*2 st, st1
1132     INTEGER inf, sup
1133     INTEGER i,j, iev
1134     INTEGER ib
1135     INTEGER ipl, ipr, ist
1136     INTEGER merror(4)
1137     INTEGER contr
1138     integer stwerr(4),dumpo
1139     integer bit,bi
1140     C
1141     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,6)
1142     real calselftrig(4,7), calIItrig(4), calstriphit(4),
1143     & calDSPtaberr(4), calevnum(4)
1144     REAL dedx(11,96), basse(11,6)
1145     real perror(4)
1146     C
1147     COMMON / evento / IEV, stwerr,perror,
1148     & dexy,dexyc,base,
1149     & calselftrig,calIItrig,
1150     & calstriphit,calDSPtaberr,calevnum
1151    
1152     save / evento /
1153     c
1154     COMMON / VARIE / dumpo, CONTR, merror
1155     SAVE / VARIE /
1156    
1157     C
1158     DO I = 1,11
1159     DO J = 1,96
1160     if (j.le.6) basse(i,j) = 0.
1161     DEDX(I,J) = 0.
1162     ENDDO
1163     ENDDO
1164     C
1165     i = inf
1166     c
1167     10 continue
1168     if (i.gt.sup) then
1169     RETURN
1170     endif
1171     C
1172     40 format(2x,i5,2x,'status :',1x,Z4)
1173     C
1174     c
1175     st1 = 0
1176     do bit=0, 7
1177     bi = ibits(vect(i),bit+8,1)
1178     if (bi.eq.1) st1 = ibset(st1,bit)
1179     enddo
1180     43 format(2x,'vect(i) = ',Z8)
1181     if (st1.eq.8) then
1182     ib = 1
1183     else
1184     if (st1.eq.16) then
1185     ib = 0
1186     else
1187     if (iev.eq.dumpo) then
1188     print *,'i ',i
1189     write(*,43)vect(i)
1190     endif
1191     merror(contr) = 139
1192     RETURN
1193     endif
1194     endif
1195     C
1196     if (ib.eq.1) then
1197     C
1198     st = IAND(vect(i),'00FF'x)
1199     c
1200     ipl = int(st/6) + 1
1201     ipr = st - (ipl - 1) * 6 + 1
1202     i = i + 1
1203     if (i.gt.sup) RETURN
1204     basse(ipl,ipr) = vect(i)
1205     c
1206     20 continue
1207     if (i.gt.sup) RETURN
1208     C
1209     i = i + 1
1210     if (i.gt.sup) RETURN
1211     if ((vect(i)+1).gt.16.or.(vect(i)+1).lt.1) then
1212    
1213     goto 10
1214     endif
1215     ist = vect(i) + 1 + 16 * (ipr - 1)
1216     i = i + 1
1217     if (i.gt.sup) RETURN
1218     dedx(ipl,ist) = vect(i)
1219     goto 20
1220     else
1221     C
1222     st = IAND(vect(i),'00FF'x)
1223     ipl = int(st/6) + 1
1224     ipr = st - (ipl - 1) * 6 + 1
1225     do j = 1,16
1226     i = i + 1
1227     if (i.gt.sup) RETURN
1228     ist = j + 16 * (ipr - 1)
1229     dedx(ipl,ist) = vect(i)
1230     enddo
1231     i = i + 1
1232     if (i.gt.sup) RETURN
1233     goto 10
1234     C
1235     endif
1236    
1237    
1238     RETURN
1239     END
1240    
1241    
1242     C----------------------------------------------------------
1243     SUBROUTINE CALFULL(vect,inf,sup,dedx,dedxc,basse)
1244     C--------------------------------------------------------------
1245    
1246     IMPLICIT NONE
1247    
1248     INTEGER NPLA, NCHA, LENSEV
1249     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
1250     C
1251     INTEGER*2 VECT(30000)
1252     INTEGER inf, sup
1253     INTEGER i,j,k, iev
1254     INTEGER contr
1255     integer stwerr(4),dumpo,merror(4)
1256     C
1257     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,6)
1258     real calselftrig(4,7), calIItrig(4), calstriphit(4),
1259     & calDSPtaberr(4), calevnum(4)
1260     REAL dedx(11,96), basse(11,6), dedxc(11,96)
1261     real perror(4)
1262     C
1263     COMMON / evento / iev, stwerr,perror,
1264     & dexy,dexyc,base,
1265     & calselftrig,calIItrig,
1266     & calstriphit,calDSPtaberr,calevnum
1267    
1268     save / evento /
1269     c
1270     COMMON / VARIE / dumpo, CONTR, merror
1271     SAVE / VARIE /
1272     C
1273     k = inf
1274     do i = 1,11
1275     do j = 1,96
1276     DEDX(I,J) = 0.
1277     dedx(i,j) = vect(k)
1278     k = k + 1
1279     enddo
1280     enddo
1281     C
1282     call CALCOMPRESS(vect,k,sup,dedxc,basse)
1283     C
1284     10 FORMAT(2X,'Status word:',2X,Z8)
1285    
1286     RETURN
1287     END
1288    
1289    
1290     C------------------------------------------------
1291     SUBROUTINE COUNTER(ve,er)
1292     C------------------------------------------------
1293    
1294     IMPLICIT NONE
1295    
1296     INTEGER NPLA, NCHA, LENSEV
1297     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
1298     C
1299     INTEGER*2 VE, st4
1300     INTEGER er, bit, bi, iev
1301     INTEGER contr
1302     integer stwerr(4),dumpo, merror(4)
1303     C
1304     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,6)
1305     real calselftrig(4,7), calIItrig(4), calstriphit(4),
1306     & calDSPtaberr(4), calevnum(4)
1307     real perror(4)
1308     C
1309     COMMON / evento / IEV, stwerr,perror,
1310     & dexy,dexyc,base,
1311     & calselftrig,calIItrig,
1312     & calstriphit,calDSPtaberr,calevnum
1313    
1314     save / evento /
1315    
1316     COMMON / VARIE / dumpo, CONTR, merror
1317     SAVE / VARIE /
1318    
1319    
1320     st4 = 0
1321     st4 = IAND(ve,'00FF'x)
1322     if (st4.ne.0) then
1323     do bit=0, 6
1324     bi = ibits(st4,bit,1)
1325     if (bi.ne.0) then
1326     er = er + 2
1327     endif
1328     enddo
1329     endif
1330    
1331     10 FORMAT(2X,'Status word:',2X,Z4)
1332     return
1333     end
1334    
1335    
1336     C------------------------------------------------
1337     SUBROUTINE MINERR(ic,icsave,chi,min,co)
1338     C------------------------------------------------
1339    
1340     IMPLICIT NONE
1341     C
1342     INTEGER NPLA, NCHA, LENSEV
1343     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
1344     C
1345     INTEGER ic, icsave(1000), chi(1000)
1346     integer l, st, min,co
1347     INTEGER iev
1348     INTEGER contr
1349     integer stwerr(4),dumpo, merror(4)
1350     C
1351     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,6)
1352     real calselftrig(4,7), calIItrig(4), calstriphit(4),
1353     & calDSPtaberr(4), calevnum(4)
1354     real perror(4)
1355     C
1356     COMMON / evento / iev, stwerr,perror,
1357     & dexy,dexyc,base,
1358     & calselftrig,calIItrig,
1359     & calstriphit,calDSPtaberr,calevnum
1360    
1361     save / evento /
1362     C
1363     COMMON / VARIE / dumpo, CONTR, merror
1364     SAVE / VARIE /
1365    
1366     st = chi(1)
1367     min = 1
1368     if (co.gt.1) then
1369     do l = 2, co
1370     if (chi(l).lt.st) then
1371     st = chi(l)
1372     min = l
1373     endif
1374     enddo
1375     endif
1376     ic = icsave(min)
1377    
1378     return
1379     end
1380    
1381     C-----------------------------------------------------
1382     SUBROUTINE CLEARSEC
1383     C-----------------------------------------------------
1384    
1385     IMPLICIT NONE
1386     C
1387     INTEGER NPLA, NCHA, LENSEV
1388     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
1389     C
1390     INTEGER iev
1391     INTEGER contr, i,j
1392     integer stwerr(4),dumpo, merror(4)
1393     C
1394     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,6)
1395     real calselftrig(4,7), calIItrig(4), calstriphit(4),
1396     & calDSPtaberr(4), calevnum(4)
1397     real perror(4)
1398     C
1399     COMMON / evento / iev, stwerr,perror,
1400     & dexy,dexyc,base,
1401     & calselftrig,calIItrig,
1402     & calstriphit,calDSPtaberr,calevnum
1403    
1404     save / evento /
1405     c
1406     COMMON / VARIE / dumpo, CONTR, merror
1407     SAVE / VARIE /
1408     C
1409     DO I = 1,11
1410     DO J = 1,96
1411     if (contr.eq.3) then
1412     DEXY(1,2*I,J) = 0.
1413     DEXYC(1,2*I,J) = 0.
1414     endif
1415     if (contr.eq.4) then
1416     DEXY(1,2*I-1,J) = 0.
1417     DEXYC(1,2*I-1,J) = 0.
1418     endif
1419     if (contr.eq.1) then
1420     DEXY(2,2*I-1,97-J) = 0.
1421     DEXYC(2,2*I-1,97-J) = 0.
1422     endif
1423     if (contr.eq.2) then
1424     DEXY(2,2*I,J) = 0.
1425     DEXYC(2,2*I,J) = 0.
1426     endif
1427     enddo
1428     do j = 1,6
1429     if (contr.eq.1) base(2,2*i-1,7-j) = 0.
1430     if (contr.eq.4) base(1,2*i-1,j) = 0.
1431     if (contr.eq.2) base(2,2*i,j) = 0.
1432     if (contr.eq.3) base(1,2*i,j) = 0.
1433     enddo
1434     if (i.le.7) calselftrig(contr,i) = 0.
1435     enddo
1436     calIItrig(contr) = 0.
1437     calstriphit(contr) = 0.
1438     calDSPtaberr(contr) = 0.
1439     calevnum(contr) = 0.
1440     return
1441     end
1442     C

  ViewVC Help
Powered by ViewVC 1.1.23