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

Annotation of /calo/unpacking/ocalunpack.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1 - (hide annotations) (download)
Mon Dec 5 16:23:21 2005 UTC (18 years, 11 months ago) by mocchiut
Branch point for: MAIN, unpacking
Initial revision

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

  ViewVC Help
Powered by ViewVC 1.1.23