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

Annotation of /calo/unpacking/calpulse.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.3 - (hide annotations) (download)
Thu Jun 29 12:50:43 2006 UTC (18 years, 5 months ago) by mocchiut
Branch: MAIN
Changes since 1.2: +4 -2 lines
Bug fixed in reading the y planes

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

  ViewVC Help
Powered by ViewVC 1.1.23