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

Annotation of /calo/unpacking/calpedestal.for

Parent Directory Parent Directory | Revision Log Revision Log


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

1 mocchiut 1.1 C
2     C Written by Mirko Boezio and Emiliano Mocchiutti
3     C
4 mocchiut 1.2 C * Version: 3.1.3 *
5     C
6     C 3.1.2 - 3.1.3: (2006-06-29) save in calped(section,1,1) and calped(section,1,2) the CRC values (transmitted and calculated) in case of CRC errors
7 mocchiut 1.1 C
8     C 3.1.1 - 3.1.2: (2005-12-02) recognize RAW mode command and exit with error 130.
9     C
10     C 3.1.0 - 3.1.1: (2004-12-21) changed common varie.
11     C
12     C 3.0.01 - 3.1.0: (2004-12-10) cleanup of the code and changes in the
13     C sections order.
14     C
15     C 3.0.00 - 3.0.01: (2004-11-08) changes in the commons (one more common for
16     C calpulse and from calstripshit to calstriphit).
17     C
18     C previous - 3.0.00: (2004-10-25) cleanup, some small bugs fixed
19     C
20     C - fixed compilation error
21     C
22     C------------------------------------------------
23     SUBROUTINE CALPEDESTAL(vecta,lung,me)
24     C------------------------------------------------
25    
26     IMPLICIT NONE
27     C
28     C Normal variables definition
29     C
30     integer lung
31     INTEGER NPLA, NCHA, LENSEV
32     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
33     C
34     INTEGER*1 VECTA(lung)
35     INTEGER*2 VECT(60000)
36     C
37     integer*2 check, crc, e2(4)
38     INTEGER*2 length, length2
39     integer*4 chksum, chksum2
40     C
41     integer me, lleng
42     INTEGER i, j
43     INTEGER ERROR(4), merror(4)
44     INTEGER ic, k, ke, ic0, l
45     INTEGER contr, m
46     INTEGER inf, sup,iev
47     INTEGER XO, YO, XE, YE
48     integer st1b, st2b, bit, bi, icb
49     INTEGER lunga, pari
50     integer stwerr(4),dump, cstwerr(4)
51     C
52     REAL calped(4,11,96), calgood(4,11,96), calthr(4,11,6)
53     REAL calrms(4,11,96), calbase(4,11,6), calvar(4,11,6)
54     real perror(4), cperror(4)
55     C
56     DATA YE/182/ ! CODE_DSP_R YE = 101 10110
57     DATA YO/173/ ! CODE_DSP_R YO = 101 01101
58     DATA XE/170/ ! CODE_DSP_R XE = 101 01010
59     DATA XO/177/ ! CODE_DSP_R XO = 101 10001
60    
61     COMMON / calib / iev, cstwerr, cperror,
62     & calped, calgood, calthr, calrms,
63     & calbase, calvar
64    
65     save / calib /
66     c
67     COMMON /VARIE/ dump, contr, merror
68     SAVE /VARIE/
69    
70     C
71     C Begin !
72     C
73     if (dump.eq.0) dump = -1
74     C
75     C DEBUG: PRINT OUT THE INPUT VECTOR
76     C
77     if (iev.eq.dump) then
78     do l=1,lung
79     write(*,17)l,vecta(l)
80     enddo
81     endif
82     17 FORMAT(2X,'Elemento:',2X,I6,2X,' word:',2X,Z8)
83     C
84     if (iev.lt.0.or.iev.gt.9000000) iev = 0
85     C
86     call clearall
87     do i = 1, 4
88     cstwerr(i) = 0
89     cperror(i) = 0.
90     error(i) = 0
91     e2(i) = 0
92     stwerr(i) = 0
93     enddo
94     contr = 1
95     me = 0
96     lleng = 0
97     ic = 0
98     pari = 0
99     length = 0
100     C
101     C input length must be > 0, if not go out with error code 142
102     C
103     if (lung.le.0) then
104     if (dump.eq.iev) print *,'lung = ',lung
105     do i=1,4
106     error(i)=142
107     enddo
108     goto 200
109     endif
110     C
111     C
112     IF (MOD(LUNG,2).EQ.0) THEN
113     lunga = lung / 2
114     pari = 1
115     else
116     lunga = int(lung/2) + 1
117     endif
118     c
119     if (lunga.gt.60000.and.dump.gt.0) then
120     print *,'Calorimeter WARNING: more than 60000 words!'
121     lunga = 60000
122     endif
123     c
124     C
125     C the fafede18 packet can also contain the answer to the force RAW mode command
126     C in that case the lenght is 4 and the answer is known.
127     C
128     IF (LUNG.LE.20) THEN
129     if (dump.eq.iev) print *,' RAW MODE COMMAND? '
130     print *,'vecta(1) ',vecta(1),' ',vecta(3)
131     IF ((VECTA(1).EQ.10.AND.VECTA(3).eq.74).or.
132     & (VECTA(1).EQ.17.AND.VECTA(3).eq.81).or.
133     & (VECTA(1).EQ.22.AND.VECTA(3).eq.86).or.
134     & (VECTA(1).EQ.13.AND.VECTA(3).eq.77)) THEN
135     if (dump.eq.iev) print *,' YES! '
136     call fillin(1,lunga,lleng,lung,pari,vect,vecta)
137     if (VECTA(1).EQ.10) contr = 1
138     if (VECTA(1).EQ.17) contr = 2
139     if (VECTA(1).EQ.22) contr = 3
140     if (VECTA(1).EQ.13) contr = 4
141     E2(contr) = vect(2)
142     do i=1,4
143     error(i)=130
144     enddo
145     goto 200
146     ENDIF
147     ENDIF
148     C
149     C
150     C
151     c
152     20 CONTINUE
153     ic = ic + length + 1
154     32 continue
155     ke = 0
156     do while (ke.eq.0)
157     C
158     C Check consistency of header.
159     C it is composed by CODE+D# (8 bits) and by SATUS WORD (8 bits)
160     c so we must split vect into the two components:
161     C
162     C ST1 is CODE + D#
163     c
164     st1b = 0
165     st2b = 0
166     do bit = 0, 7
167     bi = ibits(vecta(ic),bit,1)
168     if (bi.eq.1) st1b = ibset(st1b,bit)
169     bi = ibits(vecta(ic+1),bit,1)
170     if (bi.eq.1) st2b = ibset(st2b,bit)
171     enddo
172     c
173     C ST2 is the STATUS WORD
174     c
175     length2 = 0
176     do bit=0, 7
177     bi = ibits(vecta(ic+3),bit,1)
178     if (bi.eq.1) length2 = ibset(length2,bit)
179     bi = ibits(vecta(ic+2),bit,1)
180     if (bi.eq.1) length2 = ibset(length2,bit+8)
181     enddo
182     c the crc should be at vect(length) with
183     length = length2 + 1
184     C
185     c some checks to be sure we have found the calorimeter data:
186     c
187     c status word is always less then 129
188     c
189     if (st2b.gt.128) then
190     length = 0
191     goto 100
192     endif
193     c
194     c length of the packet must be less then 20000 if no errors
195     c are found
196     c
197     if (st2b.eq.0.and.length2.gt.lunga) then
198     length = 0
199     goto 100
200     endif
201     c
202     if (length2.le.0) then
203     length = 0
204     goto 100
205     endif
206     c
207     c is it the first section?
208     c
209     if (st1b.eq.XE.and.length2.eq.4629) then
210     c if so go out of this loop and go on recording data
211     ke = 1
212     m = ic
213     contr = 1
214     call fillin(m,lunga,lleng,lung,pari,vect,vecta)
215     icb = 1
216     E2(contr) = vect(icb)
217     goto 9
218     endif
219     C
220     c the same for the second section, ...
221     c
222     if (st1b.eq.XO.and.length2.eq.4629) then
223     ke = 1
224     contr = 2
225     m = ic
226     call fillin(m,lunga,lleng,lung,pari,vect,vecta)
227     icb = 1
228     E2(contr) = vect(icb)
229     goto 9
230     endif
231     c
232     C ... for the third,...
233     c
234     if (st1b.eq.YE.and.length2.eq.4629) then
235     ke = 1
236     m = ic
237     contr = 3
238     call fillin(m,lunga,lleng,lung,pari,vect,vecta)
239     icb = 1
240     E2(contr) = vect(icb)
241     goto 9
242     endif
243     C
244     c ...and for the last section.
245     c
246     if (st1b.eq.YO.and.length2.eq.4629) then
247     contr = 4
248     ke = 1
249     m = ic
250     call fillin(m,lunga,lleng,lung,pari,vect,vecta)
251     icb = 1
252     E2(contr) = vect(icb)
253     endif
254     C
255     100 CONTINUE
256     c
257     c increment vector of one searching for the next section
258     c
259     9 continue
260     ic = ic + 1
261     c
262     c if we run out of vector give an error and exit the subroutine
263     c
264     if (ic.gt.(lung-1)) then
265     me = 1
266     call clearall
267     do i = 1, 4
268     error(i) = 129
269     e2(i) = 0
270     stwerr(i) = 0
271     enddo
272     goto 200
273     endif
274     enddo
275     C
276     10 FORMAT(2X,'Error for view:',2X,I1,2X,'Status word:',2X,Z4)
277     11 FORMAT(2X,'View or command not recognized for view:',2X,I1,2X,
278     & 'Status word:',2X,Z4)
279     12 FORMAT(2X,'Error - did NOT find view:',2X,I1)
280     13 FORMAT(2X,'Error - eov reached, exiting')
281     21 FORMAT(2X,'CRC: ',2X,Z8)
282     101 FORMAT(2X,'Status word 1:',2X,Z8)
283     102 FORMAT(2X,'CHKSUM: ',2X,Z16)
284     201 FORMAT(2X,'Status word 2:',2X,Z8)
285     C
286     K = CONTR
287     ic0 = icb
288     ic = ic - 1
289     icb = icb + 1
290     length = vect(icb) + 2
291     length2 = vect(icb)
292     lleng = (length * 2) - 1
293     C
294     C Check consistency of CRC.
295     C
296     check = 0.
297     inf = ic0
298     sup = length - 1
299     do i = inf,sup
300     check=crc(check,vect(i))
301     enddo
302     if (check.ne.vect(length)) then
303     ERROR(contr) = 132
304 mocchiut 1.2 calped(k,1,1) = check
305     calped(k,1,2) = vect(length)
306 mocchiut 1.1 goto 200
307     endif
308     C
309     if (iev.eq.dump) write(*,21)vect(length)
310     if (iev.eq.dump) write(*,21)check
311     C
312     C Process data.
313     C
314     if (k.eq.1) then
315     k = 1
316     goto 49
317     endif
318     if (k.eq.2) then
319     k = 3
320     goto 49
321     endif
322     if (k.eq.3) then
323     k = 4
324     goto 49
325     endif
326     if (k.eq.4) k = 2
327     c
328     49 continue
329     c
330     chksum = 0
331     do i = 1,11
332     do j = 1,96
333     icb = icb + 1
334     if (k.eq.1) then
335     calped(k,i,97-j) = vect(icb)
336     calgood(k,i,97-j) = vect(icb+1)
337     else
338     calped(k,i,j) = vect(icb)
339     calgood(k,i,j) = vect(icb+1)
340     endif
341     chksum = chksum + vect(icb)
342     icb = icb + 1
343     enddo
344     enddo
345     C
346     chksum2 = 0
347     do bit=0, 15
348     bi = ibits(vect(icb+1),bit,1)
349     if (bi.eq.1) chksum2 = ibset(chksum2,bit)
350     bi = ibits(vect(icb+3),bit,1)
351     if (bi.eq.1) chksum2 = ibset(chksum2,bit+16)
352     enddo
353     C
354     if (chksum.ne.chksum2) then
355     error(contr) = 140
356     endif
357     C
358     icb = icb + 4
359     chksum = 0
360     do i = 1,11
361     do j = 1,6
362     icb = icb + 1
363     if (k.eq.1) then
364     calthr(k,i,7-j) = vect(icb)
365     else
366     calthr(k,i,j) = vect(icb)
367     endif
368     chksum = chksum + vect(icb)
369     icb = icb + 1
370     enddo
371     enddo
372     c
373     chksum2 = 0
374     do bit=0, 15
375     bi = ibits(vect(icb+1),bit,1)
376     if (bi.eq.1) chksum2 = ibset(chksum2,bit)
377     bi = ibits(vect(icb+3),bit,1)
378     if (bi.eq.1) chksum2 = ibset(chksum2,bit+16)
379     enddo
380     C
381     if (chksum.ne.chksum2) then
382     error(contr) = 141
383     endif
384     C
385     icb = icb + 4
386     do i = 1,11
387     do j = 1,96
388     icb = icb + 1
389     if (k.eq.1) then
390     calrms(k,i,97-j) = vect(icb)
391     else
392     calrms(k,i,j) = vect(icb)
393     endif
394     icb = icb + 1
395     enddo
396     enddo
397     c
398     do i = 1,11
399     do j = 1,6
400     icb = icb + 1
401     if (k.eq.1) then
402     calbase(k,i,7-j) = vect(icb)
403     icb = icb + 1
404     icb = icb + 1
405     calvar(k,i,7-j) = vect(icb)
406     icb = icb + 1
407     else
408     calbase(k,i,j) = vect(icb)
409     icb = icb + 1
410     icb = icb + 1
411     calvar(k,i,j) = vect(icb)
412     icb = icb + 1
413     endif
414     enddo
415     enddo
416     me = 0
417     c
418     c
419     50 continue
420     C
421     200 continue
422     C
423     do l = 1, 4
424     do bit=0, 31
425     if (bit.lt.16) then
426     bi = ibits(E2(L),bit,1)
427     else
428     bi = 0
429     endif
430     if (bi.eq.1) then
431     stwerr(l) = ibset(stwerr(l),bit)
432     else
433     stwerr(l) = ibclr(stwerr(l),bit)
434     endif
435     enddo
436     perror(l) = float(error(l))
437     cstwerr(l) = stwerr(l)
438     cperror(l) = perror(l)
439     enddo
440     C
441     iev = iev + 1
442     C
443     RETURN
444     END
445    

  ViewVC Help
Powered by ViewVC 1.1.23