/[PAMELA software]/chewbacca/PamOffLineSW/forroutines/calorimeter/calunpack.for
ViewVC logotype

Annotation of /chewbacca/PamOffLineSW/forroutines/calorimeter/calunpack.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.3 - (hide annotations) (download)
Thu Dec 4 14:10:13 2008 UTC (16 years ago) by mocchiut
Branch: MAIN
Changes since 1.2: +7 -7 lines
Possible bug in calunpack.for fixed

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

  ViewVC Help
Powered by ViewVC 1.1.23