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

Contents of /calo/unpacking/calpulse.for

Parent Directory Parent Directory | Revision Log Revision Log


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

1 C
2 C Written by Mirko Boezio and Emiliano Mocchiutti
3 C
4 C * Version: 3.1.5 *
5 C
6 C 3.1.4 - 3.1.5: (2006-06-29) save in calpuls(section,1,1) and calpuls(section,1,2) the CRC values (transmitted and calculated) in case of CRC errors
7 C
8 C 3.1.3 - 3.1.4: (2005-05-26) the decoding is wrong!!! we are reading all strip in one plane per time and not one strip over all planes per time!!!!
9 C
10 C 3.1.2 - 3.1.3: (2005-02-23) added some printout in debugging mode.
11 C
12 C 3.1.1 - 3.1.2: (2004-12-21) changed common varie.
13 C
14 C 3.1.0 - 3.1.1: (2004-12-13) bug in filling the calpuls vector. Fixed.
15 C
16 C 3.0.0 - 3.1.0: (2004-12-10) changes in the sections order and increment
17 C iev each time calpulse is called. Cleanup of the code.
18 C
19 C 0.00.0 - 3.0.0: (2004-11-08) changes in the commons (one more common for
20 C calpulse and from calstripshit to calstriphit).
21 C
22 C - fixed compilation error
23 C
24 C------------------------------------------------
25 SUBROUTINE CALPULSE(vecta,lung,me)
26 C------------------------------------------------
27
28 IMPLICIT NONE
29 C
30 C Normal variables definition
31 C
32 INTEGER i, j, lung, me
33 INTEGER NPLA, NCHA, LENSEV
34 PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
35 C
36 INTEGER*2 VECT(60000)
37 INTEGER*1 VECTA(lung)
38 integer*2 check, crc,e2(4)
39 INTEGER*2 length, length2
40 C
41 INTEGER ERROR(4), merror(4)
42 INTEGER ic, k, ke, ic0
43 INTEGER CONTR, m
44 INTEGER inf, sup, lunga,lleng,l
45 INTEGER XO, YO, XE, YE
46 integer pstwerr(4), IEV
47 integer dump
48 integer st1b, st2b, bit,bi,icb, pari
49
50 real pperror(4)
51 REAL calpuls(4,11,96)
52
53 DATA XO/177/ ! CODE_DSP_R XO = 101 10001
54 DATA YO/173/ ! CODE_DSP_R YO = 101 01101
55 DATA XE/170/ ! CODE_DSP_R XE = 101 01010
56 DATA YE/182/ ! CODE_DSP_R YE = 101 10110
57
58 COMMON / calpul / iev, pstwerr, pperror,
59 & calpuls
60
61 save / calpul /
62 c
63
64 COMMON /VARIE/ dump, CONTR, merror
65 SAVE /VARIE/
66
67
68 C
69 C Begin !
70 C
71 if (dump.eq.0) dump = -1
72 if (iev.lt.0.or.iev.gt.9000000) iev = 0
73 call clearall
74 do i = 1, 4
75 pstwerr(i) = 0
76 pperror(i) = 0.
77 error(i) = 0
78 e2(i) = 0
79 enddo
80 me = 0
81 lleng = 0
82 ic = 0
83 c
84 pari = 0
85 IF (MOD(LUNG,2).EQ.0) THEN
86 lunga = lung / 2
87 pari = 1
88 else
89 lunga = int(lung/2) + 1
90 endif
91 c
92 if (lunga.gt.60000.and.dump.gt.0) then
93 print *,'Calorimeter WARNING: more than 30000 words!'
94 lunga = 60000
95 endif
96 c
97 length = ic
98 c
99 20 continue
100 ic = ic + length + 1
101 32 continue
102 ke = 0
103 do while (ke.eq.0)
104 C
105 C Check consistency of header.
106 C it is composed by CODE+D# (8 bits) and by SATUS WORD (8 bits)
107 c so we must split vect into the two components:
108 C
109 C ST1 is CODE + D#
110 c
111 st1b = 0
112 st2b = 0
113 do bit = 0, 7
114 bi = ibits(vecta(ic),bit,1)
115 if (bi.eq.1) st1b = ibset(st1b,bit)
116 bi = ibits(vecta(ic+1),bit,1)
117 if (bi.eq.1) st2b = ibset(st2b,bit)
118 enddo
119 c
120 C ST2 is the STATUS WORD
121 c
122 length2 = 0
123 do bit=0, 7
124 bi = ibits(vecta(ic+3),bit,1)
125 if (bi.eq.1) length2 = ibset(length2,bit)
126 bi = ibits(vecta(ic+2),bit,1)
127 if (bi.eq.1) length2 = ibset(length2,bit+8)
128 enddo
129 c the crc should be at vect(length) with
130 length = length2 + 1
131 C
132 c some checks to be sure we have found the calorimeter data:
133 c
134 c status word is always less then 129
135 c
136 if (st2b.gt.128) then
137 length = 0
138 goto 100
139 endif
140 c
141 c length of the packet must be less then 20000 if no errors
142 c are found
143 c
144 if (st2b.eq.0.and.length2.gt.lunga) then
145 length = 0
146 goto 100
147 endif
148 c
149 if (length2.le.0) then
150 length = 0
151 goto 100
152 endif
153 c
154 c is it the first section?
155 c
156 if (st1b.eq.XE.and.length2.eq.1057) then
157 c if so go out of this loop and go on recording data
158 ke = 1
159 m = ic
160 contr = 1
161 if (iev.eq.dump) then
162 print *,'1m,lunga,lleng,lung,pari',m,lunga,lleng,lung,
163 & pari
164 endif
165 call fillin(m,lunga,lleng,lung,pari,vect,vecta)
166 icb = 1
167 E2(contr) = vect(icb)
168 goto 9
169 ENDIF
170 C
171 c the same for the second section, ...
172 C
173 if (st1b.eq.XO.and.length2.eq.1057) then
174 contr = 2
175 ke = 1
176 m = ic
177 call fillin(m,lunga,lleng,lung,pari,vect,vecta)
178 icb = 1
179 E2(contr) = vect(icb)
180 goto 9
181 ENDIF
182 c
183 C ... for the third,...
184 c
185 if (st1b.eq.YE.and.length2.eq.1057) then
186 contr = 3
187 ke = 1
188 m = ic
189 call fillin(m,lunga,lleng,lung,pari,vect,vecta)
190 icb = 1
191 E2(contr) = vect(icb)
192 goto 9
193 ENDIF
194 C
195 c ...and for the last section.
196 c
197 if (st1b.eq.YO.and.length2.eq.1057) then
198 contr = 4
199 ke = 1
200 m = ic
201 call fillin(m,lunga,lleng,lung,pari,vect,vecta)
202 icb = 1
203 E2(contr) = vect(icb)
204 endif
205 C
206 100 CONTINUE
207 c
208 c increment vector of one searching for the next section
209 c
210 9 continue
211 ic = ic + 1
212 c
213 c if we run out of vector give an error and exit the subroutine
214 c
215 if (ic.gt.(lung-1)) then
216 me = 1
217 c print *,'1 me = 1'
218 call clearall
219 do i = 1, 4
220 error(i) = 129
221 e2(i) = 0
222 pstwerr(i) = 0
223 enddo
224 goto 200
225 endif
226 enddo
227 C
228 10 FORMAT(2X,'Error for view:',2X,I1,2X,'Status word:',2X,Z4)
229 11 FORMAT(2X,'View or command not recognized for view:',2X,I1,2X,
230 & 'Status word:',2X,Z4)
231 12 FORMAT(2X,'Error - did NOT find view:',2X,I1)
232 13 FORMAT(2X,'Error - eof reached, exiting')
233 21 FORMAT(2X,'CRC: ',2X,Z8)
234 C
235 K = CONTR
236 ic0 = icb
237 ic = ic - 1
238 icb = icb + 1
239 length = vect(icb) + 2
240 length2 = vect(icb)
241 lleng = (length * 2) - 1
242 C
243 C Check consistency of CRC.
244 C
245 check = 0.
246 inf = ic0
247 sup = length - 1
248 do i = inf,sup
249 check=crc(check,vect(i))
250 enddo
251 if (check.ne.vect(length)) then
252 ERROR(contr) = 132
253 c print *,'2 me = 1'
254 calpuls(k,1,1) = check
255 calpuls(k,1,2) = vect(length)
256 me = 1
257 goto 200
258 endif
259
260 if (iev.eq.dump) write(*,21)vect(length)
261 if (iev.eq.dump) write(*,21)check
262 c
263 C
264 C Process data.
265 C
266 if (k.eq.1) then
267 k = 1
268 goto 49
269 endif
270 if (k.eq.2) then
271 k = 3
272 goto 49
273 endif
274 if (k.eq.3) then
275 k = 4
276 goto 49
277 endif
278 if (k.eq.4) k = 2
279 c
280 49 continue
281 c
282 do i = 1,11
283 do j = 1,96
284 icb = icb + 1
285 if (k.eq.1) then
286 calpuls(k,i,97-j) = vect(icb)
287 else
288 calpuls(k,i,j) = vect(icb)
289 endif
290 enddo
291 enddo
292 c print *,'3 me = 0'
293 me = 0
294 c
295 50 continue
296 c
297 C
298 200 continue
299 C
300 do l = 1, 4
301 do bit=0, 31
302 if (bit.lt.16) then
303 bi = ibits(E2(L),bit,1)
304 else
305 bi = 0
306 endif
307 if (l.ne.contr) bi = 0
308 if (bi.eq.1) then
309 pstwerr(l) = ibset(pstwerr(l),bit)
310 else
311 pstwerr(l) = ibclr(pstwerr(l),bit)
312 endif
313 enddo
314 pperror(l) = float(error(l))
315 enddo
316 C
317 iev = iev + 1
318 RETURN
319 END
320
321

  ViewVC Help
Powered by ViewVC 1.1.23