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

Contents of /yoda/techmodel/forroutines/calorimeter/calpedestal.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 4.0 - (show annotations) (download)
Sun Mar 6 04:33:02 2005 UTC (19 years, 9 months ago) by kusanagi
Branch: MAIN
CVS Tags: YODA4_1/00, YODA4_0/04, YODA4_0/03, YODA4_0/02, YODA4_0/01, YODA4_3/02, YODA4_3/00, YODA4_3/01, YODA4_2/01, YODA4_2/00, YODA4_2/03
Branch point for: PreThermistores2
Changes since 3.0: +0 -0 lines
Stable version 4.0 - 6 March 2005 - Maurizio Nagni

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

  ViewVC Help
Powered by ViewVC 1.1.23