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

Contents of /calo/unpacking/calpedestal.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1.1.1 - (show annotations) (download) (vendor branch)
Mon Dec 5 16:23:20 2005 UTC (18 years, 11 months ago) by mocchiut
Branch: unpacking
CVS Tags: start, v1r00
Changes since 1.1: +0 -0 lines
Imported sources

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

  ViewVC Help
Powered by ViewVC 1.1.23