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

Annotation of /calo/unpacking/calunpack.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.5 - (hide annotations) (download)
Thu Oct 19 09:25:53 2006 UTC (18 years, 1 month ago) by mocchiut
Branch: MAIN
CVS Tags: HEAD
Changes since 1.4: +13 -5 lines
Bug in calunpackfixed

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

  ViewVC Help
Powered by ViewVC 1.1.23