/[PAMELA software]/yoda/techmodel/forroutines/trigger/triggerunpack.for
ViewVC logotype

Diff of /yoda/techmodel/forroutines/trigger/triggerunpack.for

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 1.1 by kusanagi, Sat Jan 29 00:30:46 2005 UTC revision 6.1 by kusanagi, Wed Feb 15 15:05:56 2006 UTC
# Line 1  Line 1 
1  C--------------------------------------------------------------------  C--------------------------------------------------------------------
2        SUBROUTINE TRIGGERUNPACK(vecta,lung,me)        SUBROUTINE TRIGGERUNPACK(vecta,lung,me)
3    
4  C                                            D.Campana,  Dec. 04  C                                            D.Campana,  Feb. 06
5  C---------------------------------------------------------------------  C---------------------------------------------------------------------
6    
7        IMPLICIT NONE        IMPLICIT NONE
8  C  C
9        integer lung        integer lung
10        integer*1 vecta(lung)        integer*1 vecta(lung)
11          integer*2 ibuf
12        integer me        integer me
13        integer*2 check, crctrig        integer*2 check, crctrig
14        integer ic0,sup,inf        integer ic0,sup,inf
# Line 54  c           Line 55  c          
55  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
56  c Check consistency of CRC.  c Check consistency of CRC.
57  c  c
58        if (vecta(ic).lt.0) vecta(ic)=vecta(ic)+256        ibuf=0
59          do bit = 0, 7        
60             bi = ibits(vecta(ic),bit,1)
61             if (bi.eq.1) ibuf = ibset(ibuf,bit)
62          enddo
63    c
64        check = 0        check = 0
65        inf = ic0        inf = ic0
66        sup = ic - 1        sup = ic - 1
67        do i = inf,sup        do i = inf,sup
68           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
69        enddo        enddo
70        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
71  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
72           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
73        endif        endif
74  c  c
75        ic = ic + 1          ic = ic + 1  
# Line 87  c           Line 91  c          
91  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
92  c Check consistency of CRC.  c Check consistency of CRC.
93  c  c
94        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
95          do bit = 0, 7        
96             bi = ibits(vecta(ic),bit,1)
97             if (bi.eq.1) ibuf = ibset(ibuf,bit)
98          enddo
99    c
100        check = 0        check = 0
101        inf = ic0        inf = ic0
102        sup = ic - 1        sup = ic - 1
103        do i = inf,sup        do i = inf,sup
104           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
105        enddo        enddo
106        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
107  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
108           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
109        endif        endif
110  c  c
111  c      c    
# Line 115  c     Line 122  c    
122                 if (bi.eq.1) trigrate(i) = ibset(trigrate(i),15-bit)                 if (bi.eq.1) trigrate(i) = ibset(trigrate(i),15-bit)
123              endif              endif
124           enddo           enddo
125           ratetrig(i) = trigrate(i)/0.06  !    rate di trigger in Hz    c         ratetrig(i) = trigrate(i)/0.06  !    rate di trigger in Hz  
126             ratetrig(i) = trigrate(i)/4.0  !    rate di trigger in Hz  
127           ic = ic + 2           ic = ic + 2
128        enddo        enddo
129    
# Line 130  c           Line 138  c          
138  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
139  c Check consistency of CRC.  c Check consistency of CRC.
140  c  c
141        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
142          do bit = 0, 7        
143             bi = ibits(vecta(ic),bit,1)
144             if (bi.eq.1) ibuf = ibset(ibuf,bit)
145          enddo
146    c
147        check = 0        check = 0
148        inf = ic0        inf = ic0
149        sup = ic - 1        sup = ic - 1
150        do i = inf,sup        do i = inf,sup
151           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
152        enddo        enddo
153        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
154  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
155           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
156        endif        endif
157  c  c
158  c  c
# Line 169  c           Line 180  c          
180  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
181  c Check consistency of CRC.  c Check consistency of CRC.
182  c  c
183        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
184          do bit = 0, 7        
185             bi = ibits(vecta(ic),bit,1)
186             if (bi.eq.1) ibuf = ibset(ibuf,bit)
187          enddo
188    c
189        check = 0        check = 0
190        inf = ic0        inf = ic0
191        sup = ic - 1        sup = ic - 1
192        do i = inf,sup        do i = inf,sup
193           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
194        enddo        enddo
195        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
196  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
197           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
198        endif        endif
199  c  c
200  c  c
# Line 208  c           Line 222  c          
222  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
223  c Check consistency of CRC.  c Check consistency of CRC.
224  c  c
225        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
226          do bit = 0, 7        
227             bi = ibits(vecta(ic),bit,1)
228             if (bi.eq.1) ibuf = ibset(ibuf,bit)
229          enddo
230    c
231        check = 0        check = 0
232        inf = ic0        inf = ic0
233        sup = ic - 1        sup = ic - 1
234        do i = inf,sup        do i = inf,sup
235           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
236        enddo        enddo
237        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
238  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
239           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
240        endif        endif
 c  
241  C  C
242        ic = ic + 1        ic = ic + 1
243        ic0 = ic        ic0 = ic
# Line 252  c           Line 268  c          
268  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
269  c Check consistency of CRC.  c Check consistency of CRC.
270  c  c
271        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
272          do bit = 0, 7        
273             bi = ibits(vecta(ic),bit,1)
274             if (bi.eq.1) ibuf = ibset(ibuf,bit)
275          enddo
276    c
277        check = 0        check = 0
278        inf = ic0        inf = ic0
279        sup = ic - 1        sup = ic - 1
280        do i = inf,sup        do i = inf,sup
281           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
282        enddo        enddo
283        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
284  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
285           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
286        endif        endif
287  c  c
288  c  c
# Line 289  c      print *,pmtcount2(9) ,pmtcount2(1 Line 308  c      print *,pmtcount2(9) ,pmtcount2(1
308  c      print *,pmtcount2(13),pmtcount2(14),pmtcount2(15),pmtcount2(16)  c      print *,pmtcount2(13),pmtcount2(14),pmtcount2(15),pmtcount2(16)
309  c      print *,pmtcount2(17),pmtcount2(18),pmtcount2(19),pmtcount2(20)  c      print *,pmtcount2(17),pmtcount2(18),pmtcount2(19),pmtcount2(20)
310  c      print *,pmtcount2(21),pmtcount2(22),pmtcount2(23),pmtcount2(24)  c      print *,pmtcount2(21),pmtcount2(22),pmtcount2(23),pmtcount2(24)
311  c  
312  c            c          
313  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
314  c Check consistency of CRC.  c Check consistency of CRC.
315  c  c
316        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
317          do bit = 0, 7        
318             bi = ibits(vecta(ic),bit,1)
319             if (bi.eq.1) ibuf = ibset(ibuf,bit)
320          enddo
321    c
322        check = 0        check = 0
323        inf = ic0        inf = ic0
324        sup = ic - 1        sup = ic - 1
325        do i = inf,sup        do i = inf,sup
326           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
327        enddo        enddo
328        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
329  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
330           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
331        endif        endif
332  c  c
 c  
333            
334        ic = ic + 1        ic = ic + 1
335        ic0 = ic        ic0 = ic
# Line 372  c           Line 393  c          
393  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
394  c Check consistency of CRC.  c Check consistency of CRC.
395  c  c
396        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
397          do bit = 0, 7        
398             bi = ibits(vecta(ic),bit,1)
399             if (bi.eq.1) ibuf = ibset(ibuf,bit)
400          enddo
401    c
402        check = 0        check = 0
403        inf = ic0        inf = ic0
404        sup = ic - 1        sup = ic - 1
405        do i = inf,sup        do i = inf,sup
406           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
407        enddo        enddo
408        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
409  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
410           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
411        endif        endif
412  c  c
413  c  c
# Line 480  c           Line 504  c          
504  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
505  c Check consistency of CRC.  c Check consistency of CRC.
506  c  c
507        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
508          do bit = 0, 7        
509             bi = ibits(vecta(ic),bit,1)
510             if (bi.eq.1) ibuf = ibset(ibuf,bit)
511          enddo
512    c
513        check = 0        check = 0
514        inf = ic0        inf = ic0
515        sup = ic - 1        sup = ic - 1
516        do i = inf,sup        do i = inf,sup
517           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
518        enddo        enddo
519        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
520  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
521           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
522        endif        endif
523  c  c
524  c  c
# Line 518  c Line 545  c
545  c     vecta(ic) is the CRC  c     vecta(ic) is the CRC
546  c Check consistency of CRC.  c Check consistency of CRC.
547  c  c
548        if(vecta(ic).lt.0)vecta(ic)=vecta(ic)+256        ibuf=0
549          do bit = 0, 7        
550             bi = ibits(vecta(ic),bit,1)
551             if (bi.eq.1) ibuf = ibset(ibuf,bit)
552          enddo
553    c
554        check = 0        check = 0
555        inf = ic0        inf = ic0
556        sup = ic - 1        sup = ic - 1
557        do i = inf,sup        do i = inf,sup
558           check=crctrig(check,vecta(i))           check=crctrig(check,vecta(i))
559        enddo        enddo
560        if (check.ne.vecta(ic)) then        if (check.ne.ibuf) then
561  c         print *,'crc sbagliato ',vecta(ic), check  c         print *,'crc wrong ',ibuf, check
562           me = 1           me = 1
       else  
 c         print *,'crc corretto ',vecta(ic)  
563        endif        endif
564  c  c
   
565        RETURN        RETURN
566        END        END
   
   
   

Legend:
Removed from v.1.1  
changed lines
  Added in v.6.1

  ViewVC Help
Powered by ViewVC 1.1.23