/[PAMELA software]/yoda/techmodel/forroutines/calorimeter/calunpack.for
ViewVC logotype

Annotation of /yoda/techmodel/forroutines/calorimeter/calunpack.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 2.2 - (hide annotations) (download)
Mon Oct 18 13:01:32 2004 UTC (20 years, 1 month ago) by kusanagi
Branch: MAIN
Changes since 2.1: +782 -597 lines
Changes requests by Morchiutti

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

  ViewVC Help
Powered by ViewVC 1.1.23