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

Annotation of /yoda/techmodel/forroutines/calorimeter/calunpack.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1 - (hide annotations) (download)
Tue Jul 6 12:20:23 2004 UTC (20 years, 5 months ago) by kusanagi
Branch: MAIN
Initial revision

1 kusanagi 1.1
2     C------------------------------------------------
3     SUBROUTINE CALUNPACK(vect,dexy,dexyc,base,
4     & cal_self_trig,cal_II_trig,
5     & cal_strips_hit,cal_DSP_taberr,cal_ev_num)
6     C------------------------------------------------
7    
8     IMPLICIT NONE
9     C
10     C Normal variables definition
11     C
12     C
13     INTEGER NPLA, NCHA, LENSEV
14     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
15    
16     INTEGER ERROR
17     C
18     INTEGER i, j
19     C
20     INTEGER*2 VECT(20000)
21     C
22     integer*2 check, crc
23     C
24     INTEGER ic, k,l
25     INTEGER status
26     INTEGER inf, sup
27     INTEGER XO, YO, XE, YE
28    
29     INTEGER*2 length, length2
30    
31     INTEGER*2 st1, st2
32    
33     INTEGER*2 ival
34     PARAMETER (ival='FFFF'x)
35    
36     real dedx1(11,96),dedx2(11,96),dedx3(11,96),dedx4(11,96)
37     real dedx1c(11,96),dedx2c(11,96),dedx3c(11,96),dedx4c(11,96)
38     real base1(11,6),base2(11,6),base3(11,6),base4(11,6)
39     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,ncha)
40    
41    
42     real auto(7)
43     real cal_self_trig(4,7), cal_II_trig(4), cal_strips_hit(4),
44     & cal_DSP_taberr(4), cal_ev_num(4)
45    
46     DATA XO/241/ ! CODE_EV_R XO = 111 10001
47     DATA YO/237/ ! CODE_EV_R YO = 111 01101
48     DATA XE/234/ ! CODE_EV_R XE = 111 01010
49     DATA YE/246/ ! CODE_EV_R YE = 111 10110
50    
51     C
52     C Begin !
53     C
54     ERROR = 0
55     C
56     ic = 0
57     c
58     ic = ic + 4
59     length = ic
60     do k = 1,4
61     C
62     C Check consistency of status word.
63     C
64     ic = length + 1
65     do l = 0,15
66     write (*,41) l,vect(ic+l)
67     enddo
68     st1 = IAND(vect(ic),'00FF'x)
69     if (st1.ne.0) then
70     write (*,10) k,vect(ic)
71     ERROR = 1
72     goto 50
73     endif
74     st2 = IAND(vect(ic),'FF00'x)
75     status = ISHFT(st2,-8)
76     if (k.eq.1.and.status.ne.YE) then
77     write (*,11) k,vect(ic)
78     ERROR = 1
79     goto 50
80     endif
81     if (k.eq.2.and.status.ne.YO) then
82     write (*,11) k,vect(ic)
83     ERROR = 1
84     goto 50
85     endif
86     if (k.eq.3.and.status.ne.XE) then
87     write (*,11) k,vect(ic)
88     ERROR = 1
89     goto 50
90     endif
91     if (k.eq.4.and.status.ne.XO) then
92     write (*,11) k,vect(ic)
93     ERROR = 1
94     goto 50
95     endif
96     10 FORMAT(2X,'Error for view:',2X,I1,2X,'Status word:',2X,Z4)
97     11 FORMAT(2X,'View or command not recorgnized for view:',2X,I1,2X,
98     & 'Status word:',2X,Z4)
99     C
100     ic = ic + 1
101     length = length + (vect(ic) + 2)
102     length2 = vect(ic)
103     C
104     C Check consistency of CRC.
105     C
106     check = 0.
107     inf = (length-length2-2)+1
108     sup = length - 1
109     do i = inf,sup
110     check=crc(check,vect(i))
111     enddo
112     if (check.ne.vect(length)) then
113     print *,'Problems with CRC of view:',k
114     ERROR = 1
115     goto 50
116     endif
117     C
118     C Process data.
119     C
120     do i = 1,7
121     ic = ic + 1
122     auto(i) = vect(ic)
123     enddo
124     C
125     if (st1.eq.8) then
126     if (length2.ne.1064) then
127     print *,'Problems with view:',k,' in Raw mode length:',
128     & length2
129     ERROR = 1
130     goto 50
131     else
132     if (k.eq.1) call CALRAW(vect,ic+1,length-1,dedx1)
133     if (k.eq.2) call CALRAW(vect,ic+1,length-1,dedx2)
134     if (k.eq.3) call CALRAW(vect,ic+1,length-1,dedx3)
135     if (k.eq.4) call CALRAW(vect,ic+1,length-1,dedx4)
136     endif
137     goto 50
138     endif
139     C
140     41 FORMAT(2X,I2,2X,'word :',1x,z4)
141     ic = ic + 1
142     if (vect(ic).eq.0) then
143     if (length2.gt.1201) then
144     print *,'Problems with view:',k,
145     & ' in Compress mode length:',length2
146     ERROR = 1
147     goto 50
148     else
149     ic = ic + 1
150     cal_II_trig(k) = vect(ic)
151     ic = ic + 1
152     cal_strips_hit(k) = vect(ic)
153     ic = ic + 1
154     ic = ic + 1
155     cal_DSP_taberr(k) = vect(ic)
156     ic = ic + 1
157     cal_ev_num(k) = vect(ic)
158     if (k.eq.1) call CALCOMPRESS(vect,ic+1,length-1,dedx1,
159     & base1)
160     if (k.eq.2) call CALCOMPRESS(vect,ic+1,length-1,dedx2,
161     & base2)
162     if (k.eq.3) call CALCOMPRESS(vect,ic+1,length-1,dedx3,
163     & base3)
164     if (k.eq.4) call CALCOMPRESS(vect,ic+1,length-1,dedx4,
165     & base4)
166     endif
167     else if (vect(ic).eq.ival) then
168     if (length2.gt.2257) then
169     print *,'Problems with view:',k,' in Full mode length:',
170     & length2
171     ERROR = 1
172     goto 50
173     else
174     write(*,41) ic,vect(ic)
175     ic = ic + 1
176     cal_II_trig(k) = vect(ic)
177     ic = ic + 1
178     cal_strips_hit(k) = vect(ic)
179     ic = ic + 1
180     ic = ic + 1
181     cal_DSP_taberr(k) = vect(ic)
182     ic = ic + 1
183     cal_ev_num(k) = vect(ic)
184     print *,'ic :',ic
185     if (k.eq.1) call CALFULL(vect,ic+1,length-1,dedx1,
186     & dedx1c,base1)
187     if (k.eq.2) call CALFULL(vect,ic+1,length-1,dedx2,
188     & dedx2c,base2)
189     if (k.eq.3) call CALFULL(vect,ic+1,length-1,dedx3,
190     & dedx3c,base3)
191     if (k.eq.4) call CALFULL(vect,ic+1,length-1,dedx4,
192     & dedx4c,base4)
193     endif
194     else
195     print *,'Acq mode problems with view:',k
196     ERROR = 1
197     goto 50
198     endif
199     C
200     do i = 1,7
201     cal_self_trig(k,i) = auto(i)
202     enddo
203     c
204     50 continue
205     c
206     enddo
207     C
208     DO I = 1,11
209     DO J = 1,96
210     DEXY(2,2*I-1,97-J) = DEDX1(I,J)
211     DEXY(1,2*I-1,J) = DEDX2(I,J)
212     DEXY(2,2*I,J) = DEDX3(I,J)
213     DEXY(1,2*I,J) = DEDX4(I,J)
214     DEXYC(2,2*I-1,97-J) = DEDX1C(I,J)
215     DEXYC(1,2*I-1,J) = DEDX2C(I,J)
216     DEXYC(2,2*I,J) = DEDX3C(I,J)
217     DEXYC(1,2*I,J) = DEDX4C(I,J)
218     enddo
219     do j = 1,6
220     base(2,2*i-1,7-j) = base1(i,j)
221     base(1,2*i-1,j) = base2(i,j)
222     base(2,2*i,j) = base3(i,j)
223     base(1,2*i,j) = base4(i,j)
224     enddo
225     enddo
226    
227     RETURN
228     END
229    
230    
231     C------------------------------------------------
232     SUBROUTINE CALRAW(vect,inf,sup,dedx)
233     C------------------------------------------------
234    
235     IMPLICIT NONE
236    
237     INTEGER*2 VECT(20000)
238     INTEGER inf, sup
239     INTEGER i,j,k
240    
241     REAL dedx(11,96)
242    
243     C
244     DO I = 1,11
245     DO J = 1,96
246     DEDX(I,J) = 0.
247     ENDDO
248     ENDDO
249     C
250     k = inf
251     do j = 1,96
252     do i = 1,11
253     dedx(i,j) = vect(k)
254     k = k + 1
255     enddo
256     enddo
257     c
258     RETURN
259     END
260    
261     C------------------------------------------------
262     SUBROUTINE CALCOMPRESS(vect,inf,sup,dedx,base)
263     C------------------------------------------------
264    
265     IMPLICIT NONE
266    
267     INTEGER*2 VECT(20000)
268     C
269     INTEGER inf, sup
270     INTEGER i,j
271    
272     REAL dedx(11,96), base(11,6)
273     C
274     INTEGER*2 st, st1, st2
275     C
276     INTEGER ib
277     INTEGER ipl, ipr, ist
278     C
279     DO I = 1,11
280     DO J = 1,96
281     DEDX(I,J) = 0.
282     ENDDO
283     do j = 1,6
284     base(i,j) = 0.
285     enddo
286     ENDDO
287     C
288     do j = inf-1,inf
289     write (*,40) j,vect(j)
290     enddo
291     C
292     10 continue
293     if (i.gt.sup) RETURN
294     C
295     40 format(2x,i5,2x,'status :',1x,Z4)
296    
297     st1 = IAND(vect(i),'0800'x)
298     st1 = ISHFT(st1,-11)
299     if (st1.eq.1) then
300     ib = 1
301     else
302     st2 = IAND(vect(i),'1000'x)
303     st2 = ISHFT(st1,-12)
304     if (st2.eq.1) then
305     ib = 0
306     else
307     print *,'Problems with coding'
308     RETURN
309     endif
310     endif
311     C
312     if (ib.eq.1) then
313     C
314     st = IAND(vect(i),'00FF'x)
315     ipl = int(st/6) + 1
316     ipr = st - (ipl - 1) * 6
317     i = i + 1
318     base(ipl,ipr) = vect(i)
319     C
320     20 continue
321     if (i.gt.sup) RETURN
322     C
323     i = i + 1
324     if (vect(i).gt.16) goto 10
325     ist = vect(i)
326     i = i + 1
327     dedx(ipl,i) = vect(i)
328     C
329     else
330     C
331     st = IAND(vect(i),'00FF'x)
332     ipl = int(st/6) + 1
333     ipr = st - (ipl - 1) * 6
334     do j = 1,16
335     i = i + 1
336     dedx(ipl,j) = vect(i)
337     enddo
338     goto 10
339     C
340     endif
341    
342    
343     RETURN
344     END
345    
346    
347     C------------------------------------------------
348     SUBROUTINE CALFULL(vect,inf,sup,dedx,dedxc,base)
349     C------------------------------------------------
350    
351     IMPLICIT NONE
352    
353     INTEGER*2 VECT(20000)
354     C
355     INTEGER inf, sup
356     INTEGER i,j,k
357    
358     REAL dedx(11,96), base(11,6), dedxc(11,96)
359     C
360     C
361     C
362     DO I = 1,11
363     DO J = 1,96
364     DEDX(I,J) = 0.
365     ENDDO
366     ENDDO
367     C
368     k = inf
369     do i = 1,11
370     do j = 1,96
371     dedx(i,j) = vect(k)
372     k = k + 1
373     enddo
374     enddo
375     C
376     print *,'inf :',inf,' sup :',sup,' k :',k
377     call CALCOMPRESS(vect,k,sup,dedxc,base)
378    
379    
380     RETURN
381     END

  ViewVC Help
Powered by ViewVC 1.1.23