/[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 1.1.1.1 by kusanagi, Tue Jul 6 12:20:23 2004 UTC revision 6.6 by pam-fi, Thu Nov 2 12:20:08 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    *     24/06/2006 modified by elena vannuccini
7    *     25/06/2006 modified by david fedele
8    *************************************************************************
9    
10          subroutine trkeventpkt(YODAflag,buffer,length_buffer,curpos)
11    
12          include '../common/commontracker.f'
13          include '../common/common_readraw.f'
14          include '../common/level0.f'
15    
16        include '../commonyoda/commontracker.f'        logical ALARMS
       include '../commonyoda/dataformat.f'  
 c      include '../commonyoda/trk_calib_parameters.f'  
       include '../commonyoda/level0.f'  
   
   
       integer ndummy  
       data ndummy/1000/  
         
17        integer runerror          !readevent error flag        integer runerror          !readevent error flag
18        integer ffd_pkt           !pkt file descriptor        integer*1 crctemp
                                 !(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  
   
19    
20    *     -------------------
21    *     initializations
22    *     ---------------------------------------------------
23    *     the general flag YODAflag contains information
24    *     about the integrity of the DSP packets.
25    *    
26    *     If some packets are missing or the crc check fails,
27    *     YODAflag is asserted
28    *     ---------------------------------------------------
29          YODAflag=1                !bad by default
30        call initlevel0        call initlevel0
31          ALARMS=.false.
32        TOTDATAlength = 0.        !total length of data buffer        npkt=0                    !#good DSP packets
33        do iview=1,ndummy         !loop on views                      startcrc=0  
34           call searchtrkheader(runerror,ffd_pkt)        stopcrc=0
35  c         if(runerror.eq.-1) goto 24        crctemp=0              
36           if(runerror.eq.-1) goto 2222  *     -------------------
37           if(runerror.eq.1) then                    
38              print*,' '  *     ===================================
39              print*,'readraw: END OF CPU PACKET '        if(length_buffer.gt.MAXBUFFLEN)then
40              print*,'______________________________________ '  c         print*,'trkeventpkt: buffer() size must be at least '
41  c     goto 9900  !end loop on files  c     $        ,length_buffer,' !!!!'
42  c            goto 8800           !end loop on views (DSP pkt)           goto 2222
43              goto 2222        endif
44    *     ===================================
45          
46          
47          do iview=1,nviews         !loop on DSPs
48             call searchtrkheader(runerror,buffer,length_buffer,curpos,
49         $        startcrc)
50             if(runerror.eq.1.or.runerror.eq.-1) then                  
51    *        --------------------------------------------------
52    *        no DSP packet has been found ==> go to end
53    *        --------------------------------------------------
54                goto 2222           !go to end
55           endif           endif
56            
57           if(checkheader.ne.2) then           if(checkheader.ne.2) then
58              print*,'>>>> ERROR <<<< (trkeventpkt)'              print*,'>>>> ERROR <<<< (trkeventpkt)'
59              print*,'>>>> CPU packet type ',!pkt_type,              print*,'>>>> CPU packet type ',!pkt_type,
60       $           ' does not match DSP type ',checkheader       $           ' does not match DSP packet type ',checkheader
 c     goto 9909  ! next event (==> search another CPU header)  
61              DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)              DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)
62              DSPnumber_temp = iand(header(1),z'000f')              DSPnumber_temp = iand(header(1),z'000f')
63              print*,'  -----------------------------------'              print*,'  -----------------------------------'
# Line 53  c     goto 9909  ! next event (==> searc Line 68  c     goto 9909  ! next event (==> searc
68              goto 2525           !next view (==> search another DSP header)              goto 2525           !next view (==> search another DSP header)
69           endif           endif
70                    
71           call unpackdata(runerror,ffd_pkt)           call unpackdata(runerror,buffer,length_buffer,curpos,
72  c         if(runerror.eq.-1) goto 24       $        startcrc,stopcrc,crctemp)
73           if(runerror.eq.-1) goto 2222           if(runerror.eq.-1.or.runerror.eq.1)then
74  c         if(runerror.eq.1) goto 23             goto 2222            !go to end
75           if(runerror.eq.1) goto 2222           else if(runerror.eq.2) then
76                                         crc_dat=2            !flag for corrupted packet
77           print*,'  '           endif
78           print*,'  -----------------------------------',iview  
79           print*,'  DSP number-----',DSPnumber_dat           npkt = npkt + 1
          print*,'  DAQ mode-------',DAQmode_dat  
          print*,'  event number   ',eventn_dat  
           
          trk_DSP_ok(DSPnumber_dat)=1  
                     
80           call fillview(iview)           call fillview(iview)
81    *--------CRC check
82             if(crc(iview).eq.0.or.crc(iview).eq.2) then !OK
83    *----------- ALARMS
84               if(
85         $          fl1(iview).ne.0.or.
86         $          fl2(iview).ne.0.or.
87         $          fl3(iview).ne.0.or.
88         $          fl4(iview).ne.0.or.
89         $          fl5(iview).ne.0.or.
90         $          fl6(iview).ne.0.or.
91         $          fc(iview).ne.0.or.
92         $          DATAlength(iview).eq.0.or.
93         $          .false.)ALARMS=.true.
94             endif
95                    
96   2525    continue   2525    continue
97        enddo                     !end loop on views        enddo                     !end loop on views
98                
99   2222 continue   2222 continue
100    
101        close (lun_pkt)        if(npkt.eq.nviews)YODAflag=0
102          if(YODAflag.eq.0.and.(ALARMS.eqv..false.))good0=1
103    
104        return        return
105        end        end
106    
107  *     **********************************************  *     **********************************************************
108    *     *                                                        *
109    *     *                                                        *
110    *     *                                                        *
111    *     *                                                        *
112    *     *                                                        *
113    *     **********************************************************
114    
115  c      subroutine trk_calib_pkt(runerror,ffd_pkt)        subroutine trkcalibpkt(YODAflag,buffer,length_buffer,curpos
116        subroutine trkcalibpkt(runerror,event_file_name)       $     )
117    
118        include '../commonyoda/commontracker.f'        include '../common/commontracker.f'
119        include '../commonyoda/dataformat.f'        include '../common/common_readraw.f'
120        include '../commonyoda/trk_calib_parameters.f'        include '../common/trk_calib_parameters.f'
121            
122        integer ndummy        logical ALARMs
       data ndummy/1000/  
         
123        integer runerror          !readevent error flag        integer runerror          !readevent error flag
124        integer ffd_pkt           !pkt file descriptor        integer*1 crctemp
                                 !(file temporaneo)      
       character*60 event_file_name !nome file  
   
       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  
125    
126    *     -------------------
127    *     initializations
128    *     ---------------------------------------------------
129    *     the general flag YODAflag contains information
130    *     about the integrity of the DSP packets.
131    *    
132    *     If some packets are missing or the crc check fails,
133    *     YODAflag is asserted
134    *     ---------------------------------------------------
135          YODAflag = 1              !bad by default
136          call initcalib
137          ALARMS=.false.
138          npkt=0                    !#good DSP packets
139          startcrc=0  
140          stopcrc=0
141          crctemp=0        
142    *     -------------------
143    
144    *     ===================================
145          if(length_buffer.gt.MAXBUFFLEN)then
146    c         print*,'trkeventpkt: buffer() size must be at least '
147    c     $        ,length_buffer,' !!!!'
148             goto 2222
149          endif
150    *     ===================================
151                
152        do iview=1,ndummy         !loop on views (DSP pkt)        do iview=1,nplanes        !loop on views (DSP pkt)
153           call searchtrkheader(runerror,ffd_pkt)           call searchtrkheader(runerror,buffer,length_buffer,curpos,
154  c         if(runerror.eq.-1) goto 24       $        startcrc)
155           if(runerror.eq.-1) goto 2222  
156           if(runerror.eq.1) then                             if(runerror.eq.1.or.runerror.eq.-1) then                  
             print*,' '  
             print*,'readraw: END OF CPU PACKET '  
             print*,'______________________________________ '  
157              goto 2222           !end loop on views (DSP pkt)              goto 2222           !end loop on views (DSP pkt)
158           endif           endif
159    
160           if(checkheader.ne.3) then           if(checkheader.ne.3) then
161              print*,'>>>> ERROR <<<< (trkcalibpkt)'              print*,'>>>> ERROR <<<< (trkcalibpkt)'
162              print*,'>>>> CPU packet type ',!pkt_type,              print*,'>>>> CPU packet type ',!pkt_type,
# Line 127  c         if(runerror.eq.-1) goto 24 Line 171  c         if(runerror.eq.-1) goto 24
171              goto 2424           !next view (==> search another DSP header)              goto 2424           !next view (==> search another DSP header)
172           endif                               endif                    
173                    
174           call unpackcalibration(runerror,ffd_pkt)           call unpackcalibration(runerror,buffer,length_buffer,curpos,
175  c         if(runerror.eq.-1) goto 24       $        startcrc,stopcrc,crctemp)
176           if(runerror.eq.-1) goto 2222           if(runerror.eq.-1.or.runerror.eq.1)then
177  c         if(runerror.eq.1) goto 23              goto 2222           !end
          if(runerror.eq.1) goto 2222  
                     
           
          print*,'Calibration packet ==> ',iview  
           
          print*,'---- Calibration packet ',iview,' ----'  
          print*,'  DSP number       ',DSPnumber_cal  
          print*,'  DAQ mode         ',DAQmode_cal  
          print*,'  calibration run  ',calibrationnumber  
          print*,'  n. event used    ',nused_event  
          print*,'  <PED> ladder 1   ',ped_1  
          print*,'  <PED> ladder 2   ',ped_2  
          print*,'  <PED> ladder 3   ',ped_3  
          print*,'  <SIG> ladder 1   ',sig_1  
          print*,'  <SIG> ladder 2   ',sig_2  
          print*,'  <SIG> ladder 3   ',sig_3  
          print*,'  n.BAD ladder 1   ',nbad_1  
          print*,'  n.BAD ladder 2   ',nbad_2        
          print*,'  n.BAD ladder 3   ',nbad_3  
          print*,'  error flag       ',ff  
          if(nused_event.ne.0.or.ff.ne.0)then  
             print*,'*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*'  
             print*,'*     !!! CALIBRATION FAILURE !!!     *'  
             print*,'*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*'  
178           endif           endif
179                                    
180    
181             npkt = npkt + 1
182             call fillview_cal(iview) !
183    *--------CRC check
184             if(  crc_hcal(iview).eq.0.and.
185         $        crc_cal(iview,1).eq.0.and.
186         $        crc_cal(iview,2).eq.0.and.
187         $        crc_cal(iview,3).eq.0.and.
188         $        .true.)then
189    *----------- ALARMS
190                if(  ncalib_event(iview).ne.0.or.
191         $           cal_flag(iview).ne.0.or.
192         $           .false.)ALARMS=.true.
193             endif        
194    
          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  
195   2424    continue   2424    continue
196        enddo                     ! end loop on views (calibration pkt)        enddo                     ! end loop on views (calibration pkt)
197    
198   2222 continue   2222 continue
199    
200        close (lun_pkt)        if(npkt.eq.nplanes)YODAflag=0
201          if(YODAflag.eq.0.and.(ALARMS.eqv..false.))good0=1
202    
203        return        return
204        end        end
205    
206  ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***  *     **********************************************************
207  *  *     *                                                        *
208  *  *     *                                                        *
209  *  *     *                                                        *
210  *  *     *                                                        *
211  *  *     *                                                        *
212  *  *     **********************************************************
 *  
 *  
 ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***  
213    
214        subroutine searchtrkheader(runerror,ffd)        subroutine searchtrkheader(runerror,buffer,length_buffer,
215         $     curpos,startcrc)
216  C.............................................................  C.............................................................
217  C     Search for a valid tracker DSP header (=>one view)  C     Search for a valid tracker DSP header (=>one view)
218  C     and return the type of header  C     and return the type of header
219  C.............................................................  C.............................................................
220    
221        include '../commonyoda/commontracker.f'        include '../common/commontracker.f'
222        include '../commonyoda/dataformat.f'        include '../common/common_readraw.f'
223    
       integer ffd               !input file descriptor  
224        integer runerror          !readevent error flag        integer runerror          !readevent error flag
225    
226  c--------------------------------------------------  c--------------------------------------------------
# Line 224  c     N.B.13 bit packing is done for eac Line 228  c     N.B.13 bit packing is done for eac
228  C     so each DSP 13 bit  C     so each DSP 13 bit
229  c     first word starts at the beginnig of a 16 bit word  c     first word starts at the beginnig of a 16 bit word
230  c--------------------------------------------------  c--------------------------------------------------
231    
232   9100 continue   9100 continue
233        runerror=0                !error flag initialization        runerror=0                !error flag initialization
234        checkheader=0        checkheader=0
# Line 232  c--------------------------------------- Line 237  c---------------------------------------
237  c     looks for a DSP header beginning  c     looks for a DSP header beginning
238  C     (a word beginning with 1110)  C     (a word beginning with 1110)
239  c--------------------------------------------------  c--------------------------------------------------
       call findstart(runerror,ffd)  
240                
241        if(runerror.eq.1) goto 200        call findstart(runerror,buffer,length_buffer,curpos)
242        if(runerror.eq.-1)then              
243           runerror=1             !in this case I dont want the        if(runerror.eq.1) goto 200 !end
244                                  !the program to crash        if(runerror.eq.-1)goto 200 !end
          goto 200  
       endif  
245  c--------------------------------------------------  c--------------------------------------------------
246  c     the first word could be a DSP header first word:  c     the first word could be a DSP header first word:
247  C     reads 13 8-bit words and  C     reads 13 8-bit words and
248  c     writes them in 16 13-bit words to check for all  c     writes them in 16 13-bit words to check for all
249  C     DSP header features  C     DSP header features
250  c--------------------------------------------------  c--------------------------------------------------
251        runerror=0          
252                call hunpacker(header,runerror,buffer,length_buffer,curpos,
253        call hunpacker(header,runerror,ffd)       $     startcrc)
254                      
255        if(runerror.eq.1) goto 200        if(runerror.eq.1) goto 200 !end
256  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  
257  c--------------------------------------------------  c--------------------------------------------------
258  c     extracts and controls header:  c     extracts and controls header:
259  c--------------------------------------------------  c--------------------------------------------------
# Line 264  C     last header word must be: Line 261  C     last header word must be:
261  c     |0001|1100|0000|0000| for acquisition  c     |0001|1100|0000|0000| for acquisition
262  c     |0001|1111|1111|1111| for calibration  c     |0001|1111|1111|1111| for calibration
263  c--------------------------------------------------  c--------------------------------------------------
264        if(iand(header(16),z'ffff').eq.z'1c00') then !last header        if(iand(header(16),z'ffff').eq.z'1c00') then
265           checkheader=2          ! event           checkheader=2          ! event packet
266        elseif(iand(header(16),z'ffff').eq.z'1fff') then !last header        elseif(iand(header(16),z'ffff').eq.z'1fff') then
267           checkheader=3          ! calibration packet           checkheader=3          ! calibration packet
268        else        else
269           checkheader=1          ! not a valid DSP header           checkheader=1          ! not a valid DSP header
# Line 291  c     then this is not a DSP header (or Line 288  c     then this is not a DSP header (or
288  c     noise lurks around) so go a word ahead and  c     noise lurks around) so go a word ahead and
289  c     try again  c     try again
290  c--------------------------------------------------  c--------------------------------------------------
291        if(checkheader.eq.1) then        if(checkheader.eq.1) then  
292           call skipbyte(ffd)           curpos=curpos-(13*2)+1 !goes back 13 words, then half 16 bit word ahead
293           goto 9100           goto 9100
294        endif        endif
295          
296   200  continue   200  continue
297        end        end
298    
299  *.............................................................        *     **********************************************************
300    *     *                                                        *
301    *     *                                                        *
302    *     *                                                        *
303    *     *                                                        *
304    *     *                                                        *
305    *     **********************************************************
306    
307  *.............................................................              subroutine unpackcalibration(runerror,buffer,length_buffer,curpos,
308         $     startcrc,stopcrc,crctemp)
309    
       subroutine unpackcalibration(runerror,ffd)  
310  *.............................................................  *.............................................................
311  *     decode calibration data  *     decode calibration data
312  *     header + data(PED SIG BAD) + trailer  *     header + data(PED SIG BAD) + trailer
313  *............................................................  *............................................................
314        include '../commonyoda/commontracker.f'        include '../common/commontracker.f'
315        include '../commonyoda/dataformat.f'        include '../common/common_readraw.f'
316    
317        integer ffd               !input file descriptor        integer*1 crctemp
318          integer*1 crc_trail
319    
320        integer runerror          !readevent error flag        integer runerror          !readevent error flag
 c     buffer temporanei  
321        integer*2 templ(nstrips_ladder)        integer*2 templ(nstrips_ladder)
322        real*4 tempf(nstrips_ladder)        real*4 tempf(nstrips_ladder)
323                
324    
325    
326   12   format(z4)   12   format(z4)
327    
328  *-----------------------------------------------------------  *-----------------------------------------------------------
# Line 331  c     buffer temporanei Line 336  c     buffer temporanei
336        DSPnumber_cal = iand(header(1),z'000f')        DSPnumber_cal = iand(header(1),z'000f')
337        dataword = ior(ishft(iand(header(2),z'03ff')        dataword = ior(ishft(iand(header(2),z'03ff')
338       $     ,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'))  
339        calibrationnumber = iand(header(4),z'03ff')        calibrationnumber = iand(header(4),z'03ff')
340        nused_event = iand(header(5),z'03ff')        nused_event = iand(header(5),z'03ff')
341        ped_1 = iand(header(6),z'03ff')        ped_1 = iand(header(6),z'03ff')
# Line 349  c     $     ,z'03ff'),10),iand(header(5) Line 352  c     $     ,z'03ff'),10),iand(header(5)
352        nbad_3 = iand(header(14),z'03ff')        nbad_3 = iand(header(14),z'03ff')
353        ff = ishft(iand(header(15),z'0300'),-8)        ff = ishft(iand(header(15),z'0300'),-8)
354        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  
355  c-----------------------------------------------------------  c-----------------------------------------------------------
356  c     the checksum is a 8-bit word calculated as the  c     the checksum is a 8-bit word calculated as the
357  c     XOR of the 16-bit data words,  c     XOR of the 16-bit data words,
358  c     hence the XOR between the two halfs  c     hence the XOR between the two halfs
359  C----------------------------------------------------------  C----------------------------------------------------------
       do il=1,3                 !loop on ladders  
360    
361           call readped(tempf,runerror,ffd)        runerror=0
362    c$$$      
363    c$$$      print*,'-----------------------------------'
364    c$$$      print*,'unpackcalibration: readtrailer  --- ',
365    c$$$*     $     trailer,runerror,buffer,length_buffer,curpos,
366    c$$$     $     startcrc,stopcrc,crctemp  
367    c$$$      print*,'-----------------------------------'
368          call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
369         $     startcrc,stopcrc,crctemp)
370          
371          crc_trail=iand(trailer(3),z'00ff')
372          
373    c$$$      print *,'@@@@@@@@@@@@@ ',crctemp,crc_trail
374    
375          if (crctemp.eq.crc_trail)then
376             crc_hcalib=0
377          else
378             crc_hcalib=1
379          endif
380          
381          do il=1,3                 !loop on ladders
382             startcrc=curpos
383             call readped(tempf,runerror,buffer,length_buffer,curpos)
384           do is=1,nstrips_ladder           do is=1,nstrips_ladder
385              iss=is+nstrips_ladder*(il-1)              iss=is+nstrips_ladder*(il-1)
386              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)  
   
387           enddo           enddo
388            
389           call readsig(tempf,runerror,ffd)           call readsig(tempf,runerror,buffer,length_buffer,curpos)
390           do is=1,nstrips_ladder           do is=1,nstrips_ladder
391              iss=is+nstrips_ladder*(il-1)              iss=is+nstrips_ladder*(il-1)
392              DSPsig_o(DSPnumber_cal,iss)=tempf(is)              DSPsig_o(DSPnumber_cal,iss)=tempf(is)
 c            print*,DSPsig_o(DSPnumber,iss)  
393           enddo           enddo
394            
395           call readbad(templ,runerror,ffd)           call readbad(templ,runerror,buffer,length_buffer,curpos)
396           do is=1,nstrips_ladder           do is=1,nstrips_ladder
397              iss=is+nstrips_ladder*(il-1)              iss=is+nstrips_ladder*(il-1)
398              DSPbad_o(DSPnumber_cal,iss)=templ(is)              DSPbad_o(DSPnumber_cal,iss)=templ(is)
 c            print*,il,is,iss,DSPbad_o(DSPnumber,iss)  
399           enddo           enddo
400            
 C//// CAPIRE PERCHE` NON C'E` LA PAROLA DI FINE LADDER \\\\  
 c         call readeol(word,runerror,ffd)  
401   11      format(i1,'   ',z4)   11      format(i1,'   ',z4)
402  c         write(*,11)il,word          
403           call readtrailer(trailer,runerror,ffd)           call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
404  c$$$         do i=1,3       $        startcrc,stopcrc,crctemp)
 c$$$            write(*,12)trailer(i)  
 c$$$         enddo  
405    
406  c     print*,'fine ladder' !???           crc_trail=iand(trailer(3),z'00ff')
407                    
408             if (crctemp.eq.crc_trail)then
409               crc_calib(il)=0
410             else
411               crc_calib(il)=1
412             endif
413              
414        enddo                     !end loop on ladders        enddo                     !end loop on ladders
415                
416        return        return
417        end        end
 *.............................................................        
418    
419    *     **********************************************************
420    *     *                                                        *
421    *     *                                                        *
422    *     *                                                        *
423    *     *                                                        *
424    *     *                                                        *
425    *     **********************************************************
426    
427          subroutine unpackdata(runerror,buffer,length_buffer,curpos,
428         $     startcrc,stopcrc,crctemp)
429    
       subroutine unpackdata(runerror,ffd)  
430  *.............................................................  *.............................................................
431  *     decode event data  *     decode event data
432  *     header + data + trailer  *     header + data + trailer
433  *............................................................  *............................................................
       include '../commonyoda/commontracker.f'  
       include '../commonyoda/dataformat.f'  
       include '../commonyoda/level0.f'  
434    
435        integer ffd               !input file descriptor        include '../common/commontracker.f'
436        integer runerror          !readevent error flag        include '../common/common_readraw.f'
437        integer l_tra        include '../common/level0.f'
438    
439          integer*1 crctemp
440          integer*1 crcdat
441    
442          integer runerror          !readevent error flag
443    c      integer l_tra
444    
445          integer bid1_dat,bid2_dat,bid3_dat,bid4_dat,bid5_dat,bid6_dat
446         $     ,bid7_dat,bid_dat_sum
447          
448          
449   12   format(z4)   12   format(z4)
450    
451  *-----------------------------------------------------------  *-----------------------------------------------------------
# Line 426  c     print*,'fine ladder' !??? Line 455  c     print*,'fine ladder' !???
455        DAQmode_dat = ishft(iand(header(1),z'03f0'),-4)        DAQmode_dat = ishft(iand(header(1),z'03f0'),-4)
456        DSPnumber_dat = iand(header(1),z'000f')        DSPnumber_dat = iand(header(1),z'000f')
457  C     ------------------------------------------------------  C     ------------------------------------------------------
458  c     words 2 and 3 give tshe number of transmitted 16-bit  c     words 2 and 3 give the number of transmitted 16-bit
459  c     words ( 13 header words + data )  c     words ( 13 header words + data )
460  c     NB: data are packed from 13-bit to 16-bit words,  c     NB: data are packed from 13-bit to 16-bit words,
461  c     so the stream is complited with zeros in order to have  c     so the stream is complited with zeros in order to have
462  c     a number of bits multiple of 16  c     a number of bits multiple of 16
463    C     ------------------------------------------------------
464        l_tra = ior(ishft(iand(header(2),z'03ff')        l_tra = ior(ishft(iand(header(2),z'03ff')
465       $     ,10),iand(header(3),z'03ff'))       $     ,10),iand(header(3),z'03ff'))
466        l_tra=l_tra-13                    l_tra=l_tra-13            
# Line 448  C     ---------------------------------- Line 478  C     ----------------------------------
478        signcluster_dat(3) = iand(header(12),z'03ff')        signcluster_dat(3) = iand(header(12),z'03ff')
479        fc_dat = ishft(iand(header(13),z'0300'),-8)        fc_dat = ishft(iand(header(13),z'0300'),-8)
480        compressiontime_dat = iand(header(13),z'00ff')        compressiontime_dat = iand(header(13),z'00ff')
481        fl5_dat = ishft(iand(header(14),z'0300'),-8)  c      fl5_dat = ishft(iand(header(14),z'0300'),-8)
482        fl4_dat = ishft(iand(header(14),z'0300'),-6)  c      fl4_dat = ishft(iand(header(14),z'0300'),-6)
483        fl3_dat = ishft(iand(header(14),z'0300'),-4)  c      fl3_dat = ishft(iand(header(14),z'0300'),-4)
484        fl2_dat = ishft(iand(header(14),z'0300'),-2)  c      fl2_dat = ishft(iand(header(14),z'0300'),-2)
485        fl1_dat = iand(header(14),z'0300')  c      fl1_dat = iand(header(14),z'0300')
486        fl6_dat = ishft(iand(header(15),z'0300'),-8)  c      fl6_dat = ishft(iand(header(15),z'0300'),-8)
487          fl5_dat = iand(ishft(header(14),-8),z'0003')
488          fl4_dat = iand(ishft(header(14),-6),z'0003')
489          fl3_dat = iand(ishft(header(14),-4),z'0003')
490          fl2_dat = iand(ishft(header(14),-2),z'0003')
491          fl1_dat = iand(header(14),z'0003')
492          fl6_dat = iand(ishft(header(15),-8),z'0003')
493        checksum_dat = iand(header(15),z'00ff')        checksum_dat = iand(header(15),z'00ff')
494    
495  c-----------------------------------------------------------  c-----------------------------------------------------------
496  c     the cheacksum is a 8-bit word calculated as the  c     the cheacksum is a 8-bit word calculated as the
497  c     XOR of the 16-bit data words,  c     XOR of the 16-bit data words,
498  c     hence the XOR between the two halfs  c     hence the XOR between the two halfs
499  C----------------------------------------------------------  C----------------------------------------------------------
500        runerror=0        runerror=0
501        call dunpacker(l_tra,b_tra,runerror,ffd)        nqualcosa=0
502    c      if(l_tra.eq.0)then
503          if(l_tra.le.0)then
504             goto 18                !empty buffer
505          endif
506          
507          if(l_tra.gt.MAXBUFFLEN .or.(curpos+l_tra-1).ge.MAXBUFFLEN )then
508    c         print*,'unpackdata: '
509    c     $        ,'tracker buffer length l_tra ',l_tra
510    c     $        ,' exceeds tracker buffer dimensions '
511    c         print*,'(packet corrupted)'
512    cc         runerror=1
513             runerror=2
514             goto 50
515          endif
516          call dunpacker(l_tra,b_tra,runerror,buffer,length_buffer,curpos)
517          if(runerror.eq.1.or.runerror.eq.-1) then
518             goto 50                !go to end
519          endif
520    
521        nqualcosa = (real(l_tra))/13*16        nqualcosa = (real(l_tra))/13*16
522        xx = b_tra(nqualcosa)        xx = b_tra(nqualcosa)
523        if (xx.eq.0) nqualcosa=nqualcosa -1        if (xx.eq.0) nqualcosa=nqualcosa -1
524        datalength_dat= nqualcosa        
525  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  
   
   
   
526   11   format(i1,'   ',z4)   11   format(i1,'   ',z4)
527  c     write(*,11)il,word      
528        call readtrailer(trailer,runerror,ffd)        call readtrailer(trailer,runerror,buffer,length_buffer,curpos,
529  c$$$      do i=1,3       $     startcrc,stopcrc,crctemp)
 c$$$         write(*,12)trailer(i)  
 c$$$      enddo  
530                
531  ***************************************************************        ***************************************************************      
532  *                      TRAILER                                *  *                      TRAILER                                *
# Line 497  c$$$      enddo Line 544  c$$$      enddo
544        alarm_dat=ishft(iand(trailer(2),z'0300'),-8)          alarm_dat=ishft(iand(trailer(2),z'0300'),-8)  
545        aswr_dat=ior(ishft(iand(trailer(2),z'00ff'),8)        aswr_dat=ior(ishft(iand(trailer(2),z'00ff'),8)
546       $      ,ishft(iand(trailer(3),z'ff00'),-8))       $      ,ishft(iand(trailer(3),z'ff00'),-8))
547        crc_dat=iand(trailer(3),z'00ff')        crcdat=iand(trailer(3),z'00ff')
   
       bid_dat_sum = (bid1_dat + bid2_dat + bid3_dat + bid4_dat +  
      &     bid5_dat + bid6_dat + bid7_dat)  
548    
549        bid_dat = bid_dat_sum/7  c$$$      print*,'######################',crcdat,crctemp
550    
       if (bid_dat.ne.1.and.bid_dat.ne.2) then  
       write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
       write (*,*) 'unpack_data: TRAILER PACKET CORRUPTED'  
       write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
       endif  
       if (mod(bid_dat_sum,7).ne.0) then  
          bid_dat = 0  
          write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
          write (*,*) 'unpack_data: TRAILER PACKET CORRUPTED'  
          write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
       endif  
         
       if (alarm_dat.eq.3) then  
          write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
          write(*,*) 'unpack_data: AQUISITION ALARM'  
          write(*,*) '*** *** *** *** *** *** *** *** *** ***'          
551    
552          if(crcdat.eq.crctemp)then
553             crc_dat=0
554          else
555             crc_dat=1
556        endif        endif
         
          if (alarm_dat.ne.3.and.alarm_dat.ne.0) then  
          write(*,*) '*** *** *** *** *** *** *** *** *** ***'  
          write(*,*) 'unpack_data: TRAILER PACKET CORRUPTED'  
          write(*,*) '*** *** *** *** *** *** *** *** *** ***'          
557    
558        endif        bid_dat_sum = (bid1_dat + bid2_dat + bid3_dat + bid4_dat +
559         &     bid5_dat + bid6_dat + bid7_dat)
560    
561          bid_dat = bid_dat_sum/7
562                
563        return   50   return
564        end        end
565    
566    *     **********************************************************
567    *     *                                                        *
568    *     *                                                        *
569    *     *                                                        *
570    *     *                                                        *
571    *     *                                                        *
572    *     **********************************************************
573    
 *.............................................................................  
574        subroutine initlevel0        subroutine initlevel0
         
        include '../commonyoda/level0.f'  
575    
576          include '../common/commontracker.f'
577          include '../common/level0.f'
578    
579          good0=0
580          TOTDATAlength = 0
581    
582        do i=1, nviews        do i=1, nviews
583                    
# Line 570  c$$$      enddo Line 608  c$$$      enddo
608           bid(i) = 1           bid(i) = 1
609           alarm(i)= 0           alarm(i)= 0
610           aswr(i) = 0           aswr(i) = 0
611             crc(i)=0
612    
613        enddo        enddo
614    
       TOTDATAlength = 0  
       good0=.true.  
615    
616        return        return
617        end        end
618    
619    *     **********************************************************
620    *     *                                                        *
621    *     *                                                        *
622    *     *                                                        *
623    *     *                                                        *
624    *     *                                                        *
625    *     **********************************************************
626    
 *     *** *** *** *** *** *** *** *** ***  
 *  
 *  
 *  
 *  
 *  
 *  
 *     *** *** *** *** *** *** *** *** ***  
627        subroutine fillview(i)        subroutine fillview(i)
628  c     -----------------------------------------------------  c     -----------------------------------------------------
629  c     fill variables related to view i  c     fill variables related to view i
# Line 594  c     which will be stored in the level0 Line 631  c     which will be stored in the level0
631  c     at the end of loop on views  c     at the end of loop on views
632  c     ----------------------------------------------------  c     ----------------------------------------------------
633    
634        include '../commonyoda/commontracker.f'        include '../common/commontracker.f'
635        include '../commonyoda/level0.f'        include '../common/level0.f'
636        include '../commonyoda/dataformat.f'        include '../common/common_readraw.f'
637    
638    
639        DAQmode(i) = DAQmode_dat        DAQmode(i) = DAQmode_dat
640        DSPnumber(i) =  DSPnumber_dat        DSPnumber(i) =  DSPnumber_dat
# Line 620  c     ---------------------------------- Line 658  c     ----------------------------------
658        fl6(i) = fl6_dat        fl6(i) = fl6_dat
659        checksum(i) = checksum_dat        checksum(i) = checksum_dat
660        DATAlength(i) = datalength_dat        DATAlength(i) = datalength_dat
661          crc(i) = crc_dat
662    
663  c    -----------------------------------------------------------------------  c    -----------------------------------------------------------------------
664  c     filling TRAILER variables  c     filling TRAILER variables
# Line 631  c     ---------------------------------- Line 670  c     ----------------------------------
670        alarm(i)= alarm_dat        alarm(i)= alarm_dat
671        aswr(i) = aswr_dat        aswr(i) = aswr_dat
672    
       print*,'*-*-*-*-*-*-TRAILER-*-*-*-*-*-*'  
       print*,'*  PNUM   (periferal num) ',pnum_dat  
       print*,'*  CMDNUM (command)       ',cmdnum_dat  
       print*,'*  BID    (board id)      ',bid_dat  
       print*,'*  ALARM                  ',alarm_dat  
       print*,'*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'  
   
673        do idat=1,datalength_dat          do idat=1,datalength_dat  
674           id =  TOTDATAlength + idat           id =  TOTDATAlength + idat
675           datatracker(id) = b_tra(idat)           datatracker(id) = b_tra(idat)
# Line 647  c     ---------------------------------- Line 679  c     ----------------------------------
679        return        return
680        end        end
681    
682    *     **********************************************************
683    *     *                                                        *
684    *     *                                                        *
685    *     *                                                        *
686    *     *                                                        *
687    *     *                                                        *
688    *     **********************************************************
689    
690          subroutine fillview_cal(i)
691    c     -----------------------------------------------------
692    c     fill variables related to view i
693    c     which will be stored in the calibration nt-ple
694    c     at the end of loop on views
695    c     ----------------------------------------------------
696    
697          include '../common/commontracker.f'
698          include '../common/trk_calib_parameters.f'
699          include '../common/common_readraw.f'
700    
701          DAQmode(i)     = DAQmode_cal
702          DSPnumber(i)   = DSPnumber_cal
703          calibnumber(i) = calibrationnumber
704          ncalib_event(i)= nused_event
705          ped_l1(i)      = ped_1
706          ped_l2(i)      = ped_2
707          ped_l3(i)      = ped_3
708          sig_l1(i)      = sig_1
709          sig_l2(i)      = sig_2
710          sig_l3(i)      = sig_3
711          nbad_l1(i)     = nbad_1
712          nbad_l2(i)     = nbad_2
713          nbad_l3(i)     = nbad_3
714          cal_flag(i)    = ff
715    
716          do is=1,nstrips_view
717             DSPbad_par(i,is) = DSPbad_o(DSPnumber_cal,is)
718             DSPped_par(i,is) = DSPped_o(DSPnumber_cal,is)
719             DSPsig_par(i,is) = DSPsig_o(DSPnumber_cal,is)
720          enddo
721    
722          crc_hcal(i)    = crc_hcalib      
723          crc_cal(i,1)   = crc_calib(1)
724          crc_cal(i,2)   = crc_calib(2)
725          crc_cal(i,3)   = crc_calib(3)
726          
727          return
728          end
729    
730    *     **********************************************************
731    *     *                                                        *
732    *     *                                                        *
733    *     *                                                        *
734    *     *                                                        *
735    *     *                                                        *
736    *     **********************************************************
737    
738          subroutine initcalib
739          include '../common/commontracker.f'
740          include '../common/trk_calib_parameters.f'
741    
742          good0=0
743    
744          do i=1,nplanes
745    
746             DAQmode(i)     = 0
747             DSPnumber(i)   = 0
748             calibnumber(i) = 0
749             ncalib_event(i)= 0
750             ped_l1(i)      = 0
751             ped_l2(i)      = 0
752             ped_l3(i)      = 0
753             sig_l1(i)      = 0
754             sig_l2(i)      = 0
755             sig_l3(i)      = 0
756             nbad_l1(i)     = 0
757             nbad_l2(i)     = 0
758             nbad_l3(i)     = 0
759             cal_flag(i)    = 0
760            
761             do is=1,nstrips_view
762                DSPbad_par(i,is) = 0
763                DSPped_par(i,is) = 0
764                DSPsig_par(i,is) = 0
765             enddo
766             crc_hcal(i)    = 0
767             crc_cal(i,1)   = 0
768             crc_cal(i,2)   = 0
769             crc_cal(i,3)   = 0
770          enddo
771    
772          return
773          end

Legend:
Removed from v.1.1.1.1  
changed lines
  Added in v.6.6

  ViewVC Help
Powered by ViewVC 1.1.23