/[PAMELA software]/yoda/techmodel/forroutines/tracker/readraw/trkunpack.f
ViewVC logotype

Diff of /yoda/techmodel/forroutines/tracker/readraw/trkunpack.f

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

revision 2.1 by kusanagi, Fri Dec 17 12:46:23 2004 UTC revision 6.2 by kusanagi, Fri Jun 23 12:13:13 2006 UTC
# Line 1  Line 1 
1        subroutine trkeventpkt(runerror,event_file_name)  *************************************************************************
2    *     20/1/2006 modified by elena vannuccini to code error flag
3    *     10/9/2005 modified by david fedele to read buffer-data
4    *     instead raw-data-file
5    *     29/11/2005 modified by david fedele to include crc control
6    *************************************************************************
7    
8        include '../commonyoda/commontracker.f'        subroutine trkeventpkt(YODAflag,buffer,length_buffer,curpos
9        include '../commonyoda/dataformat.f'       $     )
 c      include '../commonyoda/trk_calib_parameters.f'  
       include '../commonyoda/level0.f'  
10    
11          include '../common/commontracker.f'
12          include '../common/common_readraw.f'
13          include '../common/level0.f'
14    
15    *     ---------------------------------------------------
16    *     the general flag YODAflag contains information
17    *     about the integrity of the DSP packets.
18    *    
19    *     If some packets are missing or the crc check fails,
20    *     YODAflag is asserted
21    *     ---------------------------------------------------
22    
23        integer ndummy  c$$$      integer YODAflag
       data ndummy/1000/  
       integer lun_pkt  
       parameter (lun_pkt=10)  
       integer runerror          !readevent error flag  
       integer ffd_pkt           !pkt file descriptor  
                                 !(file temporaneo)      
       character*60 event_file_name !nome file  
 c      print*,'  lun_pkt-----',int(lun_pkt);  
       open(unit=lun_pkt,  
      $     name=EVENT_FILE_NAME(1:lnblnk(EVENT_FILE_NAME)),  
      $     status='old',  
      $     form='unformatted'  
      $     )  
       ffd_pkt = FNum(lun_pkt)   !reads unix file descriptor  
24    
25          
26          logical ALARMS
27    
28        call initlevel0        
29          integer runerror          !readevent error flag
30    
31        TOTDATAlength = 0.        !total length of data buffer  c$$$      parameter (MAXBUFFLEN=z'172c8')
32        do iview=1,ndummy         !loop on views                c$$$      integer*4 length_buffer
33           call searchtrkheader(runerror,ffd_pkt)  c$$$      integer*1 buffer(MAXBUFFLEN)
34  c         if(runerror.eq.-1) goto 24  c$$$      integer curpos            !current position in buffer
35           if(runerror.eq.-1) goto 2222  c$$$      integer startcrc
36           if(runerror.eq.1) then                    c$$$      integer stopcrc
37  c            print*,' '        integer*1 crctemp
38  c            print*,'readraw: END OF CPU PACKET '  
39  c            print*,'______________________________________ '  *     -------------------
40  c     goto 9900  !end loop on files  *     initializations
41  c            goto 8800           !end loop on views (DSP pkt)        YODAflag=1                !bad by default
42              goto 2222        call initlevel0
43          ALARMS=.false.
44          npkt=0                    !#good DSP packets
45          startcrc=0  
46          stopcrc=0
47          crctemp=0              
48    *     -------------------
49    
50    *         ===================================
51              if(length_buffer.gt.MAXBUFFLEN)then
52                    print*,'trkeventpkt: buffer() size must be at least ',length_buffer,' !!!!'
53                    goto 2222
54              endif
55    *         ===================================
56    
57    
58          do iview=1,nviews         !loop on DSPs
59             call searchtrkheader(runerror,buffer,length_buffer,curpos,
60         $        startcrc)
61             if(runerror.eq.1.or.runerror.eq.-1) then                  
62    *        --------------------------------------------------
63    *        no DSP packet has been found ==> go to end
64    *        --------------------------------------------------
65                goto 2222           !go to end
66           endif           endif
67            
68           if(checkheader.ne.2) then           if(checkheader.ne.2) then
69  c            print*,'>>>> ERROR <<<< (trkeventpkt)'              print*,'>>>> ERROR <<<< (trkeventpkt)'
70  c            print*,'>>>> CPU packet type ',!pkt_type,              print*,'>>>> CPU packet type ',!pkt_type,
71  c     $           ' does not match DSP type ',checkheader       $           ' does not match DSP packet type ',checkheader
 c     goto 9909  ! next event (==> search another CPU header)  
72              DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)              DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)
73              DSPnumber_temp = iand(header(1),z'000f')              DSPnumber_temp = iand(header(1),z'000f')
74  c            print*,'  -----------------------------------'              print*,'  -----------------------------------'
75  c     $           ,iview       $           ,iview
76  c            print*,'  DSP number-----',int(DSPnumber_temp)              print*,'  DSP number-----',int(DSPnumber_temp)
77  c            print*,'  DAQ mode-------',int(DAQmode_temp)              print*,'  DAQ mode-------',int(DAQmode_temp)
78  c            print*,'  -----------------------------------'              print*,'  -----------------------------------'
79              goto 2525           !next view (==> search another DSP header)              goto 2525           !next view (==> search another DSP header)
80           endif           endif
81                    
82           call unpackdata(runerror,ffd_pkt)           call unpackdata(runerror,buffer,length_buffer,curpos,
83  c         if(runerror.eq.-1) goto 24       $        startcrc,stopcrc,crctemp)
84           if(runerror.eq.-1) goto 2222           if(runerror.eq.-1.or.runerror.eq.1)then
85  c         if(runerror.eq.1) goto 23              goto 2222           !go to end
86           if(runerror.eq.1) goto 2222           endif
87                              
88  c         print*,'  '           npkt = npkt + 1
 c         print*,'  -----------------------------------',iview  
 c         print*,'  DSP number-----',DSPnumber_dat  
 c         print*,'  DAQ mode-------',DAQmode_dat  
 c         print*,'  event number   ',eventn_dat  
           
          trk_DSP_ok(DSPnumber_dat)=1  
                     
89           call fillview(iview)           call fillview(iview)
90            *-------- CRC check
91             if(crc(iview).eq.0) then     !OK
92    *----------- ALARMS
93                if(
94         $           fl1(iview).ne.0.or.
95         $           fl2(iview).ne.0.or.
96         $           fl3(iview).ne.0.or.
97         $           fl4(iview).ne.0.or.
98         $           fl5(iview).ne.0.or.
99         $           fl6(iview).ne.0.or.
100         $           fc(iview).ne.0.or.
101         $           DATAlength(iview).eq.0.or.
102         $           .false.)ALARMS=.true.
103             endif
104                        
105   2525    continue   2525    continue
106        enddo                     !end loop on views        enddo                     !end loop on views
107                
108   2222 continue   2222 continue
109    
110        close (lun_pkt)        if(npkt.eq.nviews)YODAflag=0
111          if(YODAflag.eq.0.and.(ALARMS.eqv..false.))good0=1
112    
113        return        return
114        end        end
115    
116  *     **********************************************  *     **********************************************************
117    *     *                                                        *
118    *     *                                                        *
119    *     *                                                        *
120    *     *                                                        *
121    *     *                                                        *
122    *     **********************************************************
123    
124  c      subroutine trk_calib_pkt(runerror,ffd_pkt)        subroutine trkcalibpkt(YODAflag,buffer,length_buffer,curpos
125        subroutine trkcalibpkt(runerror,event_file_name)       $     )
126    
127        include '../commonyoda/commontracker.f'        include '../common/commontracker.f'
128        include '../commonyoda/dataformat.f'        include '../common/common_readraw.f'
129        include '../commonyoda/trk_calib_parameters.f'        include '../common/trk_calib_parameters.f'
130    
131    *     ---------------------------------------------------
132    *     the general flag YODAflag contains information
133    *     about the integrity of the DSP packets.
134    *    
135    *     If some packets are missing or the crc check fails,
136    *     YODAflag is asserted
137    *     ---------------------------------------------------
138            
139        integer ndummy  c$$$      integer YODAflag
140        data ndummy/1000/  
141                logical ALARMs
142    
143        integer runerror          !readevent error flag        integer runerror          !readevent error flag
144        integer ffd_pkt           !pkt file descriptor  c$$$      parameter (MAXBUFFLEN=z'172c8')
145                                  !(file temporaneo)      c$$$      integer*4 length_buffer
146        character*60 event_file_name !nome file  c$$$      integer*1 buffer(MAXBUFFLEN)
147        integer lun_pkt  c$$$      integer curpos            !current position in buffer
148        parameter (lun_pkt=10)  c$$$      integer startcrc
149        open(unit=lun_pkt,  c$$$      integer stopcrc
150       $     name=EVENT_FILE_NAME(1:lnblnk(EVENT_FILE_NAME)),        integer*1 crctemp
151       $     status='old',  
152       $     form='unformatted'  *     -------------------
153       $     )  *     initializations
154        ffd_pkt = FNum(lun_pkt)   !reads unix file descriptor        YODAflag = 1              !bad by default
155          call initcalib
156          ALARMS=.false.
157          npkt=0                    !#good DSP packets
158          startcrc=0  
159          stopcrc=0
160          crctemp=0        
161    *     -------------------
162    
163                do iview=1,nplanes        !loop on views (DSP pkt)
164        do iview=1,ndummy         !loop on views (DSP pkt)  
165           call searchtrkheader(runerror,ffd_pkt)           call searchtrkheader(runerror,buffer,length_buffer,curpos,
166  c         if(runerror.eq.-1) goto 24       $        startcrc)
167           if(runerror.eq.-1) goto 2222  
168           if(runerror.eq.1) then                             if(runerror.eq.1.or.runerror.eq.-1) then                  
 c            print*,' '  
 c            print*,'readraw: END OF CPU PACKET '  
 c            print*,'______________________________________ '  
169              goto 2222           !end loop on views (DSP pkt)              goto 2222           !end loop on views (DSP pkt)
170           endif           endif
171    
172           if(checkheader.ne.3) then           if(checkheader.ne.3) then
173  c            print*,'>>>> ERROR <<<< (trkcalibpkt)'              print*,'>>>> ERROR <<<< (trkcalibpkt)'
174  c            print*,'>>>> CPU packet type ',!pkt_type,              print*,'>>>> CPU packet type ',!pkt_type,
175  c     $           ' does not match DSP type ',checkheader       $           ' does not match DSP type ',checkheader
176              DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)              DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)
177              DSPnumber_temp = iand(header(1),z'000f')              DSPnumber_temp = iand(header(1),z'000f')
178  c            print*,'  -----------------------------------'              print*,'  -----------------------------------'
179  c     $           ,iview       $           ,iview
180  c            print*,'  DSP number-----',int(DSPnumber_temp)              print*,'  DSP number-----',int(DSPnumber_temp)
181  c            print*,'  DAQ mode-------',int(DAQmode_temp)              print*,'  DAQ mode-------',int(DAQmode_temp)
182  c            print*,'  -----------------------------------'              print*,'  -----------------------------------'
183              goto 2424           !next view (==> search another DSP header)              goto 2424           !next view (==> search another DSP header)
184           endif                               endif                    
185                    
186           call unpackcalibration(runerror,ffd_pkt)           call unpackcalibration(runerror,buffer,length_buffer,curpos,
187  c         if(runerror.eq.-1) goto 24       $        startcrc,stopcrc,crctemp)
188           if(runerror.eq.-1) goto 2222           if(runerror.eq.-1.or.runerror.eq.1)then
189  c         if(runerror.eq.1) goto 23              goto 2222           !end
          if(runerror.eq.1) goto 2222  
                     
           
 c         print*,'Calibration packet ==> ',iview  
           
 c         print*,'---- Calibration packet ',iview,' ----'  
 c         print*,'  DSP number       ',DSPnumber_cal  
 c         print*,'  DAQ mode         ',DAQmode_cal  
 c         print*,'  calibration run  ',calibrationnumber  
 c         print*,'  n. event used    ',nused_event  
 c         print*,'  <PED> ladder 1   ',ped_1  
 c         print*,'  <PED> ladder 2   ',ped_2  
 c         print*,'  <PED> ladder 3   ',ped_3  
 c         print*,'  <SIG> ladder 1   ',sig_1  
 c         print*,'  <SIG> ladder 2   ',sig_2  
 c         print*,'  <SIG> ladder 3   ',sig_3  
 c         print*,'  n.BAD ladder 1   ',nbad_1  
 c         print*,'  n.BAD ladder 2   ',nbad_2        
 c         print*,'  n.BAD ladder 3   ',nbad_3  
 c         print*,'  error flag       ',ff  
          if(nused_event.ne.0.or.ff.ne.0)then  
 c            print*,'*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*'  
 c            print*,'*     !!! CALIBRATION FAILURE !!!     *'  
 c            print*,'*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*'  
190           endif           endif
191                                    
192    
193             npkt = npkt + 1
194             call fillview_cal(iview) !
195    *--------CRC check
196             if(  crc_hcal(iview).eq.0.and.
197         $        crc_cal(iview,1).eq.0.and.
198         $        crc_cal(iview,2).eq.0.and.
199         $        crc_cal(iview,3).eq.0.and.
200         $        .true.)then
201    *----------- ALARMS
202                if(  ncalib_event(iview).ne.0.or.
203         $           cal_flag(iview).ne.0.or.
204         $           .false.)ALARMS=.true.
205             endif        
206    
          DAQmode(iview)=DAQmode_cal  
          DSPnumber(iview)=DSPnumber_cal  
          calibnumber(iview)=calibrationnumber  
          ncalib_event(iview)=nused_event  
          ped_l1(iview)=ped_1  
          ped_l2(iview)=ped_2  
          ped_l3(iview)=ped_3  
          sig_l1(iview)=sig_1  
          sig_l2(iview)=sig_2  
          sig_l3(iview)=sig_3  
          nbad_l1(iview)=nbad_1  
          nbad_l2(iview)=nbad_2  
          nbad_l3(iview)=nbad_3  
          cal_flag(iview)=ff  
   
          do is=1,nstrips_view  
             DSPbad_par(iview,is)=DSPbad_o(DSPnumber_cal,is)  
             DSPped_par(iview,is)=DSPped_o(DSPnumber_cal,is)  
             DSPsig_par(iview,is)=DSPsig_o(DSPnumber_cal,is)  
          enddo  
 c          
          trk_DSP_ok(DSPnumber_cal)=1  
 c----------------------------------------------------------  
 c     NVIEWS calibration packets should have been found  
 c----------------------------------------------------------  
 c                  if(n_cal_pkt.eq.nviews)then  
 c                     found_cal_pkt = .true.  
 c                     n_cal_pkt = 0  
 c                  endif  
207   2424    continue   2424    continue
208        enddo                     ! end loop on views (calibration pkt)        enddo                     ! end loop on views (calibration pkt)
  2222 continue  
209    
210        close (lun_pkt)        if(npkt.eq.nplanes)YODAflag=0
211          if(YODAflag.eq.0.and.(ALARMS.eqv..false.))good0=1
212    
213     2222 continue
214    
215        return        return
216        end        end
217    
218  ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***  *     **********************************************************
219  *  *     *                                                        *
220  *  *     *                                                        *
221  *  *     *                                                        *
222  *  *     *                                                        *
223  *  *     *                                                        *
224  *  *     **********************************************************
 *  
 *  
 ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***  
225    
226        subroutine searchtrkheader(runerror,ffd)        subroutine searchtrkheader(runerror,buffer,length_buffer,
227         $     curpos,startcrc)
228  C.............................................................  C.............................................................
229  C     Search for a valid tracker DSP header (=>one view)  C     Search for a valid tracker DSP header (=>one view)
230  C     and return the type of header  C     and return the type of header
231  C.............................................................  C.............................................................
232    
233        include '../commonyoda/commontracker.f'        include '../common/commontracker.f'
234        include '../commonyoda/dataformat.f'        include '../common/common_readraw.f'
235    
236    c$$$      parameter (MAXBUFFLEN=z'172c8')
237    c$$$      integer*4 length_buffer
238    c$$$      integer*1 buffer(MAXBUFFLEN)
239    c$$$      integer curpos            !current position in buffer
240    c$$$      integer startcrc
241    
       integer ffd               !input file descriptor  
242        integer runerror          !readevent error flag        integer runerror          !readevent error flag
243    
244  c--------------------------------------------------  c--------------------------------------------------
# Line 226  c     N.B.13 bit packing is done for eac Line 246  c     N.B.13 bit packing is done for eac
246  C     so each DSP 13 bit  C     so each DSP 13 bit
247  c     first word starts at the beginnig of a 16 bit word  c     first word starts at the beginnig of a 16 bit word
248  c--------------------------------------------------  c--------------------------------------------------
249    
250   9100 continue   9100 continue
251        runerror=0                !error flag initialization        runerror=0                !error flag initialization
252        checkheader=0        checkheader=0
# Line 234  c--------------------------------------- Line 255  c---------------------------------------
255  c     looks for a DSP header beginning  c     looks for a DSP header beginning
256  C     (a word beginning with 1110)  C     (a word beginning with 1110)
257  c--------------------------------------------------  c--------------------------------------------------
       call findstart(runerror,ffd)  
258                
259        if(runerror.eq.1) goto 200        call findstart(runerror,buffer,length_buffer,curpos)
260        if(runerror.eq.-1)then              
261           runerror=1             !in this case I dont want the        if(runerror.eq.1) goto 200 !end
262                                  !the program to crash        if(runerror.eq.-1)goto 200 !end
          goto 200  
       endif  
263  c--------------------------------------------------  c--------------------------------------------------
264  c     the first word could be a DSP header first word:  c     the first word could be a DSP header first word:
265  C     reads 13 8-bit words and  C     reads 13 8-bit words and
266  c     writes them in 16 13-bit words to check for all  c     writes them in 16 13-bit words to check for all
267  C     DSP header features  C     DSP header features
268  c--------------------------------------------------  c--------------------------------------------------
269        runerror=0          
270                call hunpacker(header,runerror,buffer,length_buffer,curpos,
271        call hunpacker(header,runerror,ffd)       $     startcrc)
272                      
273        if(runerror.eq.1) goto 200        if(runerror.eq.1) goto 200 !end
274  c      if(runerror.eq.-1) goto 200        if(runerror.eq.-1)goto 200 !end
       if(runerror.eq.-1)then  
          runerror=1             !in this case I dont want the  
                                 !the program to crash  
          goto 200  
       endif  
275  c--------------------------------------------------  c--------------------------------------------------
276  c     extracts and controls header:  c     extracts and controls header:
277  c--------------------------------------------------  c--------------------------------------------------
# Line 266  C     last header word must be: Line 279  C     last header word must be:
279  c     |0001|1100|0000|0000| for acquisition  c     |0001|1100|0000|0000| for acquisition
280  c     |0001|1111|1111|1111| for calibration  c     |0001|1111|1111|1111| for calibration
281  c--------------------------------------------------  c--------------------------------------------------
282        if(iand(header(16),z'ffff').eq.z'1c00') then !last header        if(iand(header(16),z'ffff').eq.z'1c00') then
283           checkheader=2          ! event           checkheader=2          ! event packet
284        elseif(iand(header(16),z'ffff').eq.z'1fff') then !last header        elseif(iand(header(16),z'ffff').eq.z'1fff') then
285           checkheader=3          ! calibration packet           checkheader=3          ! calibration packet
286        else        else
287           checkheader=1          ! not a valid DSP header           checkheader=1          ! not a valid DSP header
# Line 293  c     then this is not a DSP header (or Line 306  c     then this is not a DSP header (or
306  c     noise lurks around) so go a word ahead and  c     noise lurks around) so go a word ahead and
307  c     try again  c     try again
308  c--------------------------------------------------  c--------------------------------------------------
309        if(checkheader.eq.1) then        if(checkheader.eq.1) then  
310           call skipbyte(ffd)           curpos=curpos-(13*2)+1 !goes back 13 words, then half 16 bit word ahead
311           goto 9100           goto 9100
312        endif        endif
313          
314   200  continue   200  continue
315        end        end
316    
317  *.............................................................        *     **********************************************************
318    *     *                                                        *
319    *     *                                                        *
320    *     *                                                        *
321    *     *                                                        *
322    *     *                                                        *
323    *     **********************************************************
324    
325          subroutine unpackcalibration(runerror,buffer,length_buffer,curpos,
326         $     startcrc,stopcrc,crctemp)
327    
 *.............................................................        
   
       subroutine unpackcalibration(runerror,ffd)  
328  *.............................................................  *.............................................................
329  *     decode calibration data  *     decode calibration data
330  *     header + data(PED SIG BAD) + trailer  *     header + data(PED SIG BAD) + trailer
331  *............................................................  *............................................................
332        include '../commonyoda/commontracker.f'        include '../common/commontracker.f'
333        include '../commonyoda/dataformat.f'        include '../common/common_readraw.f'
334    
335        integer ffd               !input file descriptor  c$$$      parameter (MAXBUFFLEN=z'172c8')
336    c$$$      integer*4 length_buffer
337    c$$$      integer*1 buffer(MAXBUFFLEN)
338    c$$$      integer curpos            !current position in buffer
339    c$$$      integer startcrc
340    c$$$      integer stopcrc
341          integer*1 crctemp
342          integer*1 crc_trail
343    
344        integer runerror          !readevent error flag        integer runerror          !readevent error flag
 c     buffer temporanei  
345        integer*2 templ(nstrips_ladder)        integer*2 templ(nstrips_ladder)
346        real*4 tempf(nstrips_ladder)        real*4 tempf(nstrips_ladder)
347                
348    
349    
350   12   format(z4)   12   format(z4)
351    
352  *-----------------------------------------------------------  *-----------------------------------------------------------
# Line 333  c     buffer temporanei Line 360  c     buffer temporanei
360        DSPnumber_cal = iand(header(1),z'000f')        DSPnumber_cal = iand(header(1),z'000f')
361        dataword = ior(ishft(iand(header(2),z'03ff')        dataword = ior(ishft(iand(header(2),z'03ff')
362       $     ,10),iand(header(3),z'03ff'))       $     ,10),iand(header(3),z'03ff'))
 c      calibrationnumber = ior(ishft(iand(header(4)  
 c     $     ,z'03ff'),10),iand(header(5),z'03ff'))  
363        calibrationnumber = iand(header(4),z'03ff')        calibrationnumber = iand(header(4),z'03ff')
364        nused_event = iand(header(5),z'03ff')        nused_event = iand(header(5),z'03ff')
365        ped_1 = iand(header(6),z'03ff')        ped_1 = iand(header(6),z'03ff')
# Line 351  c     $     ,z'03ff'),10),iand(header(5) Line 376  c     $     ,z'03ff'),10),iand(header(5)
376        nbad_3 = iand(header(14),z'03ff')        nbad_3 = iand(header(14),z'03ff')
377        ff = ishft(iand(header(15),z'0300'),-8)        ff = ishft(iand(header(15),z'0300'),-8)
378        checksum_cal = iand(header(15),z'00ff')        checksum_cal = iand(header(15),z'00ff')
   
       runerror=0  
       call readtrailer(trailer,runerror,ffd)  
 c$$$      do i=1,3  
 c$$$         write(*,12)trailer(i)  
 c$$$      enddo  
379  c-----------------------------------------------------------  c-----------------------------------------------------------
380  c     the checksum is a 8-bit word calculated as the  c     the checksum is a 8-bit word calculated as the
381  c     XOR of the 16-bit data words,  c     XOR of the 16-bit data words,
382  c     hence the XOR between the two halfs  c     hence the XOR between the two halfs
383  C----------------------------------------------------------  C----------------------------------------------------------
       do il=1,3                 !loop on ladders  
384    
385           call readped(tempf,runerror,ffd)        runerror=0
386    c$$$      
387    c$$$      print*,'-----------------------------------'
388    c$$$      print*,'unpackcalibration: readtrailer  --- ',
389    c$$$*     $     trailer,runerror,buffer,length_buffer,curpos,
390    c$$$     $     startcrc,stopcrc,crctemp  
391    c$$$      print*,'-----------------------------------'
392          call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
393         $     startcrc,stopcrc,crctemp)
394          
395          crc_trail=iand(trailer(3),z'00ff')
396          
397    c$$$      print *,'@@@@@@@@@@@@@ ',crctemp,crc_trail
398    
399          if (crctemp.eq.crc_trail)then
400             crc_hcalib=0
401          else
402             crc_hcalib=1
403          endif
404          
405          do il=1,3                 !loop on ladders
406             startcrc=curpos
407             call readped(tempf,runerror,buffer,length_buffer,curpos)
408           do is=1,nstrips_ladder           do is=1,nstrips_ladder
409              iss=is+nstrips_ladder*(il-1)              iss=is+nstrips_ladder*(il-1)
410              DSPped_o(DSPnumber_cal,iss)=tempf(is)              DSPped_o(DSPnumber_cal,iss)=tempf(is)
 c            print*,il,iss,DSPped_o(DSPnumber,iss)  
 c            print *,DSPnumber_cal,iss,tempf(is)  
   
411           enddo           enddo
412            
413           call readsig(tempf,runerror,ffd)           call readsig(tempf,runerror,buffer,length_buffer,curpos)
414           do is=1,nstrips_ladder           do is=1,nstrips_ladder
415              iss=is+nstrips_ladder*(il-1)              iss=is+nstrips_ladder*(il-1)
416              DSPsig_o(DSPnumber_cal,iss)=tempf(is)              DSPsig_o(DSPnumber_cal,iss)=tempf(is)
 c            print*,DSPsig_o(DSPnumber,iss)  
417           enddo           enddo
418            
419           call readbad(templ,runerror,ffd)           call readbad(templ,runerror,buffer,length_buffer,curpos)
420           do is=1,nstrips_ladder           do is=1,nstrips_ladder
421              iss=is+nstrips_ladder*(il-1)              iss=is+nstrips_ladder*(il-1)
422              DSPbad_o(DSPnumber_cal,iss)=templ(is)              DSPbad_o(DSPnumber_cal,iss)=templ(is)
 c            print*,il,is,iss,DSPbad_o(DSPnumber,iss)  
423           enddo           enddo
424            
 C//// CAPIRE PERCHE` NON C'E` LA PAROLA DI FINE LADDER \\\\  
 c         call readeol(word,runerror,ffd)  
425   11      format(i1,'   ',z4)   11      format(i1,'   ',z4)
426  c         write(*,11)il,word          
427           call readtrailer(trailer,runerror,ffd)           call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
428  c$$$         do i=1,3       $        startcrc,stopcrc,crctemp)
 c$$$            write(*,12)trailer(i)  
 c$$$         enddo  
429    
430  c     print*,'fine ladder' !???           crc_trail=iand(trailer(3),z'00ff')
431                    
432             if (crctemp.eq.crc_trail)then
433               crc_calib(il)=0
434             else
435               crc_calib(il)=1
436             endif
437              
438        enddo                     !end loop on ladders        enddo                     !end loop on ladders
439                
440        return        return
441        end        end
 *.............................................................        
442    
443    *     **********************************************************
444    *     *                                                        *
445    *     *                                                        *
446    *     *                                                        *
447    *     *                                                        *
448    *     *                                                        *
449    *     **********************************************************
450    
451          subroutine unpackdata(runerror,buffer,length_buffer,curpos,
452         $     startcrc,stopcrc,crctemp)
453    
       subroutine unpackdata(runerror,ffd)  
454  *.............................................................  *.............................................................
455  *     decode event data  *     decode event data
456  *     header + data + trailer  *     header + data + trailer
457  *............................................................  *............................................................
       include '../commonyoda/commontracker.f'  
       include '../commonyoda/dataformat.f'  
       include '../commonyoda/level0.f'  
458    
459        integer ffd               !input file descriptor        include '../common/commontracker.f'
460        integer runerror          !readevent error flag        include '../common/common_readraw.f'
461        integer l_tra        include '../common/level0.f'
462    
463    c$$$      parameter (MAXBUFFLEN=z'172c8')
464    c$$$      integer*4 length_buffer
465    c$$$      integer*1 buffer(MAXBUFFLEN)
466    c$$$      integer curpos            !current position in buffer
467    c$$$      integer startcrc
468    c$$$      integer stopcrc
469          integer*1 crctemp
470          integer*1 crcdat
471    
472          integer runerror          !readevent error flag
473    c      integer l_tra
474    
475          integer bid1_dat,bid2_dat,bid3_dat,bid4_dat,bid5_dat,bid6_dat
476         $     ,bid7_dat,bid_dat_sum
477          
478          
479   12   format(z4)   12   format(z4)
480    
481  *-----------------------------------------------------------  *-----------------------------------------------------------
# Line 428  c     print*,'fine ladder' !??? Line 485  c     print*,'fine ladder' !???
485        DAQmode_dat = ishft(iand(header(1),z'03f0'),-4)        DAQmode_dat = ishft(iand(header(1),z'03f0'),-4)
486        DSPnumber_dat = iand(header(1),z'000f')        DSPnumber_dat = iand(header(1),z'000f')
487  C     ------------------------------------------------------  C     ------------------------------------------------------
488  c     words 2 and 3 give tshe number of transmitted 16-bit  c     words 2 and 3 give the number of transmitted 16-bit
489  c     words ( 13 header words + data )  c     words ( 13 header words + data )
490  c     NB: data are packed from 13-bit to 16-bit words,  c     NB: data are packed from 13-bit to 16-bit words,
491  c     so the stream is complited with zeros in order to have  c     so the stream is complited with zeros in order to have
492  c     a number of bits multiple of 16  c     a number of bits multiple of 16
493    C     ------------------------------------------------------
494        l_tra = ior(ishft(iand(header(2),z'03ff')        l_tra = ior(ishft(iand(header(2),z'03ff')
495       $     ,10),iand(header(3),z'03ff'))       $     ,10),iand(header(3),z'03ff'))
496        l_tra=l_tra-13                    l_tra=l_tra-13            
# Line 450  C     ---------------------------------- Line 508  C     ----------------------------------
508        signcluster_dat(3) = iand(header(12),z'03ff')        signcluster_dat(3) = iand(header(12),z'03ff')
509        fc_dat = ishft(iand(header(13),z'0300'),-8)        fc_dat = ishft(iand(header(13),z'0300'),-8)
510        compressiontime_dat = iand(header(13),z'00ff')        compressiontime_dat = iand(header(13),z'00ff')
511        fl5_dat = ishft(iand(header(14),z'0300'),-8)  c      fl5_dat = ishft(iand(header(14),z'0300'),-8)
512        fl4_dat = ishft(iand(header(14),z'0300'),-6)  c      fl4_dat = ishft(iand(header(14),z'0300'),-6)
513        fl3_dat = ishft(iand(header(14),z'0300'),-4)  c      fl3_dat = ishft(iand(header(14),z'0300'),-4)
514        fl2_dat = ishft(iand(header(14),z'0300'),-2)  c      fl2_dat = ishft(iand(header(14),z'0300'),-2)
515        fl1_dat = iand(header(14),z'0300')  c      fl1_dat = iand(header(14),z'0300')
516        fl6_dat = ishft(iand(header(15),z'0300'),-8)  c      fl6_dat = ishft(iand(header(15),z'0300'),-8)
517          fl5_dat = iand(ishft(header(14),-8),z'0003')
518          fl4_dat = iand(ishft(header(14),-6),z'0003')
519          fl3_dat = iand(ishft(header(14),-4),z'0003')
520          fl2_dat = iand(ishft(header(14),-2),z'0003')
521          fl1_dat = iand(header(14),z'0003')
522          fl6_dat = iand(ishft(header(15),-8),z'0003')
523        checksum_dat = iand(header(15),z'00ff')        checksum_dat = iand(header(15),z'00ff')
524    
525  c-----------------------------------------------------------  c-----------------------------------------------------------
526  c     the cheacksum is a 8-bit word calculated as the  c     the cheacksum is a 8-bit word calculated as the
527  c     XOR of the 16-bit data words,  c     XOR of the 16-bit data words,
528  c     hence the XOR between the two halfs  c     hence the XOR between the two halfs
529  C----------------------------------------------------------  C----------------------------------------------------------
530        runerror=0        runerror=0
531        call dunpacker(l_tra,b_tra,runerror,ffd)        nqualcosa=0
532          if(l_tra.eq.0)then
533             goto 18                !empty buffer
534          endif
535          
536          if(l_tra.gt.MAXBTRALEN)then
537             print*,'unpackdata: '
538         $        ,'tracker buffer length l_tra exceeds buffer dimension '
539         $        ,l_tra,MAXBTRALEN
540             runerror=1
541             goto 50
542          endif
543          call dunpacker(l_tra,b_tra,runerror,buffer,length_buffer,curpos)
544          if(runerror.eq.1.or.runerror.eq.-1) then
545             goto 50                !go to end
546          endif
547    
548        nqualcosa = (real(l_tra))/13*16        nqualcosa = (real(l_tra))/13*16
549        xx = b_tra(nqualcosa)        xx = b_tra(nqualcosa)
550        if (xx.eq.0) nqualcosa=nqualcosa -1        if (xx.eq.0) nqualcosa=nqualcosa -1
551        datalength_dat= nqualcosa        
552  c$$$      TOTDATAlength = TOTDATAlength + datalength_dat   18   datalength_dat= nqualcosa
 c$$$      do i=1,datalength_dat    
 c$$$         id = id + 1  
 c$$$         datatracker(id) = b_tra(i)  
 c$$$      enddo  
   
   
   
553   11   format(i1,'   ',z4)   11   format(i1,'   ',z4)
554  c     write(*,11)il,word      
555        call readtrailer(trailer,runerror,ffd)        call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
556  c$$$      do i=1,3       $     startcrc,stopcrc,crctemp)
 c$$$         write(*,12)trailer(i)  
 c$$$      enddo  
557                
558  ***************************************************************        ***************************************************************      
559  *                      TRAILER                                *  *                      TRAILER                                *
# Line 499  c$$$      enddo Line 571  c$$$      enddo
571        alarm_dat=ishft(iand(trailer(2),z'0300'),-8)          alarm_dat=ishft(iand(trailer(2),z'0300'),-8)  
572        aswr_dat=ior(ishft(iand(trailer(2),z'00ff'),8)        aswr_dat=ior(ishft(iand(trailer(2),z'00ff'),8)
573       $      ,ishft(iand(trailer(3),z'ff00'),-8))       $      ,ishft(iand(trailer(3),z'ff00'),-8))
574        crc_dat=iand(trailer(3),z'00ff')        crcdat=iand(trailer(3),z'00ff')
575    
576        bid_dat_sum = (bid1_dat + bid2_dat + bid3_dat + bid4_dat +  c$$$      print*,'######################',crcdat,crctemp
      &     bid5_dat + bid6_dat + bid7_dat)  
577    
       bid_dat = bid_dat_sum/7  
   
       if (bid_dat.ne.1.and.bid_dat.ne.2) then  
 c      write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
 c      write (*,*) 'unpack_data: TRAILER PACKET CORRUPTED'  
 c      write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
       endif  
       if (mod(bid_dat_sum,7).ne.0) then  
          bid_dat = 0  
 c         write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
 c         write (*,*) 'unpack_data: TRAILER PACKET CORRUPTED'  
 c         write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
       endif  
         
       if (alarm_dat.eq.3) then  
 c         write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
 c         write(*,*) 'unpack_data: AQUISITION ALARM'  
 c         write(*,*) '*** *** *** *** *** *** *** *** *** ***'          
578    
579          if(crcdat.eq.crctemp)then
580             crc_dat=0
581          else
582             crc_dat=1
583        endif        endif
         
          if (alarm_dat.ne.3.and.alarm_dat.ne.0) then  
 c         write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
 c         write(*,*) 'unpack_data: TRAILER PACKET CORRUPTED'  
 c         write(*,*) '*** *** *** *** *** *** *** *** *** ***'          
584    
585        endif        bid_dat_sum = (bid1_dat + bid2_dat + bid3_dat + bid4_dat +
586         &     bid5_dat + bid6_dat + bid7_dat)
587    
588          bid_dat = bid_dat_sum/7
589                
590        return   50   return
591        end        end
592    
593    *     **********************************************************
594    *     *                                                        *
595    *     *                                                        *
596    *     *                                                        *
597    *     *                                                        *
598    *     *                                                        *
599    *     **********************************************************
600    
 *.............................................................................  
601        subroutine initlevel0        subroutine initlevel0
         
        include '../commonyoda/level0.f'  
602    
603          include '../common/commontracker.f'
604          include '../common/level0.f'
605    
606          good0=0
607          TOTDATAlength = 0
608    
609        do i=1, nviews        do i=1, nviews
610                    
# Line 572  c         write(*,*) '*** *** *** *** ** Line 635  c         write(*,*) '*** *** *** *** **
635           bid(i) = 1           bid(i) = 1
636           alarm(i)= 0           alarm(i)= 0
637           aswr(i) = 0           aswr(i) = 0
638             crc(i)=0
639    
640        enddo        enddo
641    
       TOTDATAlength = 0  
       good0=.true.  
642    
643        return        return
644        end        end
645    
646    *     **********************************************************
647    *     *                                                        *
648    *     *                                                        *
649    *     *                                                        *
650    *     *                                                        *
651    *     *                                                        *
652    *     **********************************************************
653    
 *     *** *** *** *** *** *** *** *** ***  
 *  
 *  
 *  
 *  
 *  
 *  
 *     *** *** *** *** *** *** *** *** ***  
654        subroutine fillview(i)        subroutine fillview(i)
655  c     -----------------------------------------------------  c     -----------------------------------------------------
656  c     fill variables related to view i  c     fill variables related to view i
# Line 596  c     which will be stored in the level0 Line 658  c     which will be stored in the level0
658  c     at the end of loop on views  c     at the end of loop on views
659  c     ----------------------------------------------------  c     ----------------------------------------------------
660    
661        include '../commonyoda/commontracker.f'        include '../common/commontracker.f'
662        include '../commonyoda/level0.f'        include '../common/level0.f'
663        include '../commonyoda/dataformat.f'        include '../common/common_readraw.f'
664    
665    
666        DAQmode(i) = DAQmode_dat        DAQmode(i) = DAQmode_dat
667        DSPnumber(i) =  DSPnumber_dat        DSPnumber(i) =  DSPnumber_dat
# Line 622  c     ---------------------------------- Line 685  c     ----------------------------------
685        fl6(i) = fl6_dat        fl6(i) = fl6_dat
686        checksum(i) = checksum_dat        checksum(i) = checksum_dat
687        DATAlength(i) = datalength_dat        DATAlength(i) = datalength_dat
688          crc(i) = crc_dat
689    
690  c    -----------------------------------------------------------------------  c    -----------------------------------------------------------------------
691  c     filling TRAILER variables  c     filling TRAILER variables
# Line 633  c     ---------------------------------- Line 697  c     ----------------------------------
697        alarm(i)= alarm_dat        alarm(i)= alarm_dat
698        aswr(i) = aswr_dat        aswr(i) = aswr_dat
699    
 c      print*,'*-*-*-*-*-*-TRAILER-*-*-*-*-*-*'  
 c      print*,'*  PNUM   (periferal num) ',pnum_dat  
 c      print*,'*  CMDNUM (command)       ',cmdnum_dat  
 c      print*,'*  BID    (board id)      ',bid_dat  
 c      print*,'*  ALARM                  ',alarm_dat  
 c      print*,'*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'  
   
700        do idat=1,datalength_dat          do idat=1,datalength_dat  
701           id =  TOTDATAlength + idat           id =  TOTDATAlength + idat
702           datatracker(id) = b_tra(idat)           datatracker(id) = b_tra(idat)
703        enddo        enddo
704        TOTDATAlength = TOTDATAlength + datalength_dat        TOTDATAlength = TOTDATAlength + datalength_dat
705    
706          return
707          end
708    
709    *     **********************************************************
710    *     *                                                        *
711    *     *                                                        *
712    *     *                                                        *
713    *     *                                                        *
714    *     *                                                        *
715    *     **********************************************************
716    
717          subroutine fillview_cal(i)
718    c     -----------------------------------------------------
719    c     fill variables related to view i
720    c     which will be stored in the calibration nt-ple
721    c     at the end of loop on views
722    c     ----------------------------------------------------
723    
724          include '../common/commontracker.f'
725          include '../common/trk_calib_parameters.f'
726          include '../common/common_readraw.f'
727    
728          DAQmode(i)     = DAQmode_cal
729          DSPnumber(i)   = DSPnumber_cal
730          calibnumber(i) = calibrationnumber
731          ncalib_event(i)= nused_event
732          ped_l1(i)      = ped_1
733          ped_l2(i)      = ped_2
734          ped_l3(i)      = ped_3
735          sig_l1(i)      = sig_1
736          sig_l2(i)      = sig_2
737          sig_l3(i)      = sig_3
738          nbad_l1(i)     = nbad_1
739          nbad_l2(i)     = nbad_2
740          nbad_l3(i)     = nbad_3
741          cal_flag(i)    = ff
742    
743          do is=1,nstrips_view
744             DSPbad_par(i,is) = DSPbad_o(DSPnumber_cal,is)
745             DSPped_par(i,is) = DSPped_o(DSPnumber_cal,is)
746             DSPsig_par(i,is) = DSPsig_o(DSPnumber_cal,is)
747          enddo
748    
749          crc_hcal(i)    = crc_hcalib      
750          crc_cal(i,1)   = crc_calib(1)
751          crc_cal(i,2)   = crc_calib(2)
752          crc_cal(i,3)   = crc_calib(3)
753                
754        return        return
755        end        end
756    
757    *     **********************************************************
758    *     *                                                        *
759    *     *                                                        *
760    *     *                                                        *
761    *     *                                                        *
762    *     *                                                        *
763    *     **********************************************************
764    
765          subroutine initcalib
766          include '../common/commontracker.f'
767          include '../common/trk_calib_parameters.f'
768    
769          good0=0
770    
771          do i=1,nplanes
772    
773             DAQmode(i)     = 0
774             DSPnumber(i)   = 0
775             calibnumber(i) = 0
776             ncalib_event(i)= 0
777             ped_l1(i)      = 0
778             ped_l2(i)      = 0
779             ped_l3(i)      = 0
780             sig_l1(i)      = 0
781             sig_l2(i)      = 0
782             sig_l3(i)      = 0
783             nbad_l1(i)     = 0
784             nbad_l2(i)     = 0
785             nbad_l3(i)     = 0
786             cal_flag(i)    = 0
787            
788             do is=1,nstrips_view
789                DSPbad_par(i,is) = 0
790                DSPped_par(i,is) = 0
791                DSPsig_par(i,is) = 0
792             enddo
793             crc_hcal(i)    = 0
794             crc_cal(i,1)   = 0
795             crc_cal(i,2)   = 0
796             crc_cal(i,3)   = 0
797          enddo
798    
799          return
800          end

Legend:
Removed from v.2.1  
changed lines
  Added in v.6.2

  ViewVC Help
Powered by ViewVC 1.1.23