/[PAMELA software]/tracker/ground/source/trigger/triggerunpack.for
ViewVC logotype

Annotation of /tracker/ground/source/trigger/triggerunpack.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1.1.1 - (hide annotations) (download) (vendor branch)
Wed Mar 8 15:00:39 2006 UTC (18 years, 9 months ago) by pam-fi
Branch: MAIN, trk-ground
CVS Tags: R3v02, HEAD
Changes since 1.1: +0 -0 lines
First CVS release of tracker ground software (R3v02) 

1 pam-fi 1.1 C--------------------------------------------------------------------
2     SUBROUTINE TRIGGERUNPACK(vecta,lung,me)
3    
4     C D.Campana, Dec. 04
5     C---------------------------------------------------------------------
6    
7     IMPLICIT NONE
8     C
9     integer lung
10     integer*1 vecta(lung)
11     integer me
12     integer*2 check, crctrig
13     integer ic0,sup,inf
14     integer i, ic, bit, bi
15     integer pmtpl(3), trigrate(6), dltime(2), s4calcount(2)
16     integer pmtcount1(24), pmtcount2(24)
17     integer*4 patternbusy(3)
18     integer patterntrig(6), trigconf
19     integer*4 trig_evcount
20     real ratepmt(3),ratetrig(6),dltimems(2)
21     C
22     C
23     COMMON / trig / trig_evcount, pmtpl, trigrate, dltime,
24     & s4calcount, pmtcount1, pmtcount2,
25     & patternbusy, patterntrig, trigconf
26     save / trig /
27     C
28     C Begin !
29     C
30    
31     ic = 1
32     c print *,'************* Trigger Unpack ******************'
33     ic0 = ic
34     do i = 1, 3
35     pmtpl(i) = 0
36     do bit = 0, 7
37     bi = ibits(vecta(ic),bit,1)
38     if (bi.eq.1) pmtpl(i) = ibset(pmtpl(i),7-bit)
39    
40     if (bit.ge.4) then
41     bi = ibits(vecta(ic+1),bit,1)
42     if (bi.eq.1) pmtpl(i) = ibset(pmtpl(i),15-bit)
43     endif
44     enddo
45     ratepmt(i) = pmtpl(i)/0.06 ! rate di piano in Hz
46     ic = ic + 2
47     enddo
48     c print *,'----------> 1crc: ',ic
49     c print *,'pmtpl(i,(i=1,3))'
50     c print *,pmtpl(1),pmtpl(2),pmtpl(3)
51     c print *,'ratepmt(i,(i=1,3))'
52     c print *,ratepmt(1),ratepmt(2),ratepmt(3)
53     c
54     c vecta(ic) is the CRC
55     c Check consistency of CRC.
56     c
57     if (vecta(ic).lt.0) vecta(ic)=vecta(ic)+256
58     check = 0
59     inf = ic0
60     sup = ic - 1
61     do i = inf,sup
62     check=crctrig(check,vecta(i))
63     enddo
64     if (check.ne.vecta(ic)) then
65     c print *,'crc sbagliato ',vecta(ic), check
66     me = 1
67     else
68     c print *,'crc corretto ',vecta(ic)
69     endif
70     c
71     ic = ic + 1
72     ic0 = ic
73     trig_evcount = 0
74     do bit=0, 7
75     bi = ibits(vecta(ic),bit,1)
76     if (bi.eq.1) trig_evcount = ibset(trig_evcount,7-bit)
77     bi = ibits(vecta(ic+1),bit,1)
78     if (bi.eq.1) trig_evcount = ibset(trig_evcount,15-bit)
79     bi = ibits(vecta(ic+2),bit,1)
80     if (bi.eq.1) trig_evcount = ibset(trig_evcount,23-bit)
81     enddo
82     ic = ic + 3
83    
84     c print *,'----------> 2crc: ',ic
85     c print *,'evcount',evcount
86     c
87     c vecta(ic) is the CRC
88     c Check consistency of CRC.
89     c
90     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
91     check = 0
92     inf = ic0
93     sup = ic - 1
94     do i = inf,sup
95     check=crctrig(check,vecta(i))
96     enddo
97     if (check.ne.vecta(ic)) then
98     c print *,'crc sbagliato ',vecta(ic), check
99     me = 1
100     else
101     c print *,'crc corretto ',vecta(ic)
102     endif
103     c
104     c
105     ic = ic + 1
106     ic0 = ic
107     do i = 1, 6
108     trigrate(i) = 0
109     do bit = 0, 7
110     bi = ibits(vecta(ic),bit,1)
111     if (bi.eq.1) trigrate(i) = ibset(trigrate(i),7-bit)
112    
113     if (bit.ge.4) then
114     bi = ibits(vecta(ic+1),bit,1)
115     if (bi.eq.1) trigrate(i) = ibset(trigrate(i),15-bit)
116     endif
117     enddo
118     ratetrig(i) = trigrate(i)/0.06 ! rate di trigger in Hz
119     ic = ic + 2
120     enddo
121    
122     c print *,'----------> 3crc: ',ic
123     c print *,'trigrate(i,(i=1,6))'
124     c print *,trigrate(1),trigrate(2),trigrate(3)
125     c print *,trigrate(4),trigrate(5),trigrate(6)
126     c print *,'ratetrig(i,(i=1,6))'
127     c print *,ratetrig(1),ratetrig(2),ratetrig(3)
128     c print *,ratetrig(4),ratetrig(5),ratetrig(6)
129     c
130     c vecta(ic) is the CRC
131     c Check consistency of CRC.
132     c
133     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
134     check = 0
135     inf = ic0
136     sup = ic - 1
137     do i = inf,sup
138     check=crctrig(check,vecta(i))
139     enddo
140     if (check.ne.vecta(ic)) then
141     c print *,'crc sbagliato ',vecta(ic), check
142     me = 1
143     else
144     c print *,'crc corretto ',vecta(ic)
145     endif
146     c
147     c
148     ic = ic + 1
149     ic0 = ic
150     do i = 1, 2
151     dltime(i) = 0
152     do bit = 0, 7
153     bi = ibits(vecta(ic),bit,1)
154     if (bi.eq.1) dltime(i) = ibset(dltime(i),7-bit)
155     bi = ibits(vecta(ic+1),bit,1)
156     if (bi.eq.1) dltime(i) = ibset(dltime(i),15-bit)
157     enddo
158     ic = ic + 2
159     enddo
160     dltimems(1) = dltime(1) * 0.16 ! dltime in msec
161     dltimems(2) = dltime(2) * 0.01 ! dltime in msec
162    
163     c print *,'----------> 4crc: ',ic
164     c print *,'dltime(i,(i=1,2))'
165     c print *,dltime(1),dltime(2)
166     c print *,'dltimems(i,(i=1,2))'
167     c print *,dltimems(1),dltimems(2)
168     c
169     c vecta(ic) is the CRC
170     c Check consistency of CRC.
171     c
172     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
173     check = 0
174     inf = ic0
175     sup = ic - 1
176     do i = inf,sup
177     check=crctrig(check,vecta(i))
178     enddo
179     if (check.ne.vecta(ic)) then
180     c print *,'crc sbagliato ',vecta(ic), check
181     me = 1
182     else
183     c print *,'crc corretto ',vecta(ic)
184     endif
185     c
186     c
187     ic = ic + 1
188     ic0 = ic
189     do i = 1, 2
190     s4calcount(i) = 0
191     do bit = 0, 7
192     bi = ibits(vecta(ic),bit,1)
193     if (bi.eq.1) s4calcount(i) = ibset(s4calcount(i),7-bit)
194    
195     if (bit.ge.4) then
196     bi = ibits(vecta(ic+1),bit,1)
197     if (bi.eq.1) s4calcount(i) = ibset(s4calcount(i),15-bit)
198     endif
199     enddo
200     ic = ic + 2
201     enddo
202    
203     c print *,'----------> 5crc: ',ic
204     c print *,'s4calcount(i,(i=1,2))'
205     c print *,s4calcount(1),s4calcount(2)
206     c
207     c
208     c vecta(ic) is the CRC
209     c Check consistency of CRC.
210     c
211     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
212     check = 0
213     inf = ic0
214     sup = ic - 1
215     do i = inf,sup
216     check=crctrig(check,vecta(i))
217     enddo
218     if (check.ne.vecta(ic)) then
219     c print *,'crc sbagliato ',vecta(ic), check
220     me = 1
221     else
222     c print *,'crc corretto ',vecta(ic)
223     endif
224     c
225     C
226     ic = ic + 1
227     ic0 = ic
228     do i = 1, 24
229     pmtcount1(i) = 0
230     do bit = 0, 7
231     bi = ibits(vecta(ic),bit,1)
232     if (bi.eq.1) pmtcount1(i) = ibset(pmtcount1(i),7-bit)
233    
234     if (bit.ge.4) then
235     bi = ibits(vecta(ic+1),bit,1)
236     if (bi.eq.1) pmtcount1(i) = ibset(pmtcount1(i),15-bit)
237     endif
238     enddo
239     ic = ic + 2
240     enddo
241    
242     c print *,'----------> 6crc: ',ic
243     c print *,'pmtcount1(i,(i=1,24))'
244     c print *,pmtcount1(1) ,pmtcount1(2) ,pmtcount1(3) ,pmtcount1(4)
245     c print *,pmtcount1(5) ,pmtcount1(6) ,pmtcount1(7) ,pmtcount1(8)
246     c print *,pmtcount1(9) ,pmtcount1(10),pmtcount1(11),pmtcount1(12)
247     c print *,pmtcount1(13),pmtcount1(14),pmtcount1(15),pmtcount1(16)
248     c print *,pmtcount1(17),pmtcount1(18),pmtcount1(19),pmtcount1(20)
249     c print *,pmtcount1(21),pmtcount1(22),pmtcount1(23),pmtcount1(24)
250     c
251     c
252     c vecta(ic) is the CRC
253     c Check consistency of CRC.
254     c
255     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
256     check = 0
257     inf = ic0
258     sup = ic - 1
259     do i = inf,sup
260     check=crctrig(check,vecta(i))
261     enddo
262     if (check.ne.vecta(ic)) then
263     c print *,'crc sbagliato ',vecta(ic), check
264     me = 1
265     else
266     c print *,'crc corretto ',vecta(ic)
267     endif
268     c
269     c
270     ic = ic + 1
271     ic0 = ic
272     do i = 1, 24
273     pmtcount2(i) = 0
274     do bit = 0, 7
275     bi = ibits(vecta(ic),bit,1)
276     if (bi.eq.1) pmtcount2(i) = ibset(pmtcount2(i),7-bit)
277     if (bit.ge.4) then
278     bi = ibits(vecta(ic+1),bit,1)
279     if (bi.eq.1) pmtcount2(i) = ibset(pmtcount2(i),15-bit)
280     endif
281     enddo
282     ic = ic + 2
283     enddo
284     c print *,'----------> 7crc: ',ic
285     c print *,'pmtcount2(i,(i=1,24))'
286     c print *,pmtcount2(1) ,pmtcount2(2) ,pmtcount2(3) ,pmtcount2(4)
287     c print *,pmtcount2(5) ,pmtcount2(6) ,pmtcount2(7) ,pmtcount2(8)
288     c print *,pmtcount2(9) ,pmtcount2(10),pmtcount2(11),pmtcount2(12)
289     c print *,pmtcount2(13),pmtcount2(14),pmtcount2(15),pmtcount2(16)
290     c print *,pmtcount2(17),pmtcount2(18),pmtcount2(19),pmtcount2(20)
291     c print *,pmtcount2(21),pmtcount2(22),pmtcount2(23),pmtcount2(24)
292     c
293     c
294     c vecta(ic) is the CRC
295     c Check consistency of CRC.
296     c
297     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
298     check = 0
299     inf = ic0
300     sup = ic - 1
301     do i = inf,sup
302     check=crctrig(check,vecta(i))
303     enddo
304     if (check.ne.vecta(ic)) then
305     c print *,'crc sbagliato ',vecta(ic), check
306     me = 1
307     else
308     c print *,'crc corretto ',vecta(ic)
309     endif
310     c
311     c
312    
313     ic = ic + 1
314     ic0 = ic
315     do i = 1, 3
316     patternbusy(i) = 0
317     if(i.eq.1)then
318     do bit = 0, 7
319     bi = ibits(vecta(ic),bit,1)
320     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),11+bit)
321     bi = ibits(vecta(ic+1),bit,1)
322     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),3+bit)
323    
324     if (bit.ge.5) then
325     bi = ibits(vecta(ic+2),bit,1)
326     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),bit-5)
327     endif
328     enddo
329     endif
330     if(i.eq.2)then
331     do bit = 0, 7
332     if (bit.lt.5) then
333     bi = ibits(vecta(ic),bit,1)
334     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),14+bit)
335     endif
336     bi = ibits(vecta(ic+1),bit,1)
337     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),6+bit)
338    
339     if (bit.ge.2) then
340     bi = ibits(vecta(ic+2),bit,1)
341     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),bit-2)
342     endif
343     enddo
344     endif
345    
346     if(i.eq.3)then
347     do bit = 0, 7
348     if (bit.lt.2) then
349     bi = ibits(vecta(ic),bit,1)
350     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),17+bit)
351     endif
352     bi = ibits(vecta(ic+1),bit,1)
353     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),9+bit)
354     bi = ibits(vecta(ic+2),bit,1)
355     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),bit+1)
356    
357     if (bit.eq.7) then
358     bi = ibits(vecta(ic+3),bit,1)
359     if (bi.eq.1) patternbusy(i) = ibset(patternbusy(i),0)
360     endif
361     enddo
362     endif
363    
364     ic = ic + 2
365     enddo
366     ic = ic + 2
367    
368     c print *,'----------> 8crc: ',ic
369     c print *,'patternbusy(i,(i=1,3))'
370     c print *, patternbusy(1) ,patternbusy(2) ,patternbusy(3)
371     c
372     c vecta(ic) is the CRC
373     c Check consistency of CRC.
374     c
375     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
376     check = 0
377     inf = ic0
378     sup = ic - 1
379     do i = inf,sup
380     check=crctrig(check,vecta(i))
381     enddo
382     if (check.ne.vecta(ic)) then
383     c print *,'crc sbagliato ',vecta(ic), check
384     me = 1
385     else
386     c print *,'crc corretto ',vecta(ic)
387     endif
388     c
389     c
390     ic = ic + 1
391     ic0 = ic
392     do i = 1, 6
393     patterntrig(i) = 0
394     enddo
395     do i = 1, 7
396     if(i.eq.1)then
397     do bit = 0, 7
398     bi = ibits(vecta(ic),bit,1)
399     if (bi.eq.1)then
400     if(bit.ge.4)patterntrig(i) = ibset(patterntrig(i),bit-4)
401     if(bit.lt.4.and.bit.gt.0)
402     + patterntrig(i+1) = ibset(patterntrig(i+1),bit-1)
403    
404     if(bit.eq.0)patterntrig(i+2)=ibset(patterntrig(i+2),11)
405     endif
406     enddo
407     endif
408    
409     if(i.eq.2)then
410     do bit = 0, 7
411     bi = ibits(vecta(ic),bit,1)
412     if (bi.eq.1)
413     + patterntrig(i+1) = ibset(patterntrig(i+1),bit+3)
414     enddo
415     endif
416    
417     if(i.eq.3)then
418     do bit = 0, 7
419     bi = ibits(vecta(ic),bit,1)
420     if (bi.eq.1)then
421     if(bit.ge.5)then
422     patterntrig(i)=ibset(patterntrig(i),bit-5)
423     else
424     patterntrig(i+1)=ibset(patterntrig(i+1),bit+3)
425     endif
426     endif
427     enddo
428     endif
429    
430     if(i.eq.4)then
431     do bit = 0, 7
432     bi = ibits(vecta(ic),bit,1)
433     if (bi.eq.1)then
434     if(bit.ge.5)then
435     patterntrig(i)=ibset(patterntrig(i),bit-5)
436     else
437     patterntrig(i+1)=ibset(patterntrig(i+1),bit+7)
438     endif
439     endif
440     enddo
441     endif
442    
443     if(i.eq.5)then
444     do bit = 0, 7
445     bi = ibits(vecta(ic),bit,1)
446     if (bi.eq.1)then
447     if(bit.gt.0)then
448     patterntrig(i)=ibset(patterntrig(i),bit-1)
449     else
450     patterntrig(i+1)=ibset(patterntrig(i+1),bit+15)
451     endif
452     endif
453     enddo
454     endif
455    
456     if(i.eq.6)then
457     do bit = 0, 7
458     bi = ibits(vecta(ic),bit,1)
459     if (bi.eq.1)patterntrig(i)=ibset(patterntrig(i),bit+7)
460     enddo
461     endif
462    
463     if(i.eq.7)then
464     do bit = 0, 7
465     bi = ibits(vecta(ic),bit,1)
466     if (bi.eq.1)then
467     if(bit.gt.0)patterntrig(i-1)=ibset(patterntrig(i-1),bit-1)
468     endif
469     enddo
470     endif
471     ic = ic + 1
472     enddo
473    
474     c print *,'----------> 9crc: ',ic
475     c print *,'patterntrig(i,(i=1,6))'
476     c print *, patterntrig(1) ,patterntrig(2) ,patterntrig(3)
477     c print *, patterntrig(4) ,patterntrig(5) ,patterntrig(6)
478     c
479     c
480     c vecta(ic) is the CRC
481     c Check consistency of CRC.
482     c
483     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
484     check = 0
485     inf = ic0
486     sup = ic - 1
487     do i = inf,sup
488     check=crctrig(check,vecta(i))
489     enddo
490     if (check.ne.vecta(ic)) then
491     c print *,'crc sbagliato ',vecta(ic), check
492     me = 1
493     else
494     c print *,'crc corretto ',vecta(ic)
495     endif
496     c
497     c
498     ic = ic + 1
499     ic0 = ic
500     trigconf = 0
501     do i = 1, 2
502     do bit = 0, 7
503     bi = ibits(vecta(ic),bit,1)
504     if (bi.eq.1) then
505     if(i.eq.1) trigconf = ibset(trigconf,bit+2)
506     if(i.eq.2) then
507     if(bit.ge.6)trigconf = ibset(trigconf,bit-6)
508     endif
509     endif
510     enddo
511     ic = ic + 1
512     enddo
513     c print *,'----------> 10crc: ',ic
514     c print *,'ic here is ',ic
515     c print *,'trigconf'
516     c print *, trigconf
517     c
518     c vecta(ic) is the CRC
519     c Check consistency of CRC.
520     c
521     if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256
522     check = 0
523     inf = ic0
524     sup = ic - 1
525     do i = inf,sup
526     check=crctrig(check,vecta(i))
527     enddo
528     if (check.ne.vecta(ic)) then
529     c print *,'crc sbagliato ',vecta(ic), check
530     me = 1
531     else
532     c print *,'crc corretto ',vecta(ic)
533     endif
534     c
535    
536     RETURN
537     END
538    
539    
540    

  ViewVC Help
Powered by ViewVC 1.1.23