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

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

  ViewVC Help
Powered by ViewVC 1.1.23