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

Legend:
Removed from v.2.0  
changed lines
  Added in v.6.3

  ViewVC Help
Powered by ViewVC 1.1.23