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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.3 - (hide annotations) (download)
Thu Aug 19 15:24:51 2004 UTC (21 years, 2 months ago) by kusanagi
Branch: MAIN
Changes since 1.2: +59 -59 lines
*** empty log message ***

1 kusanagi 1.1 subroutine trkeventpkt(runerror,event_file_name)
2    
3     include '../commonyoda/commontracker.f'
4     include '../commonyoda/dataformat.f'
5     c include '../commonyoda/trk_calib_parameters.f'
6     include '../commonyoda/level0.f'
7    
8    
9     integer ndummy
10     data ndummy/1000/
11 kusanagi 1.2 integer lun_pkt
12     parameter (lun_pkt=10)
13 kusanagi 1.1 integer runerror !readevent error flag
14     integer ffd_pkt !pkt file descriptor
15     !(file temporaneo)
16     character*60 event_file_name !nome file
17     c print*,' lun_pkt-----',int(lun_pkt);
18     open(unit=lun_pkt,
19     $ name=EVENT_FILE_NAME(1:lnblnk(EVENT_FILE_NAME)),
20     $ status='old',
21     $ form='unformatted'
22     $ )
23     ffd_pkt = FNum(lun_pkt) !reads unix file descriptor
24    
25    
26     call initlevel0
27    
28     TOTDATAlength = 0. !total length of data buffer
29     do iview=1,ndummy !loop on views
30     call searchtrkheader(runerror,ffd_pkt)
31     c if(runerror.eq.-1) goto 24
32     if(runerror.eq.-1) goto 2222
33     if(runerror.eq.1) then
34     print*,' '
35     print*,'readraw: END OF CPU PACKET '
36     print*,'______________________________________ '
37     c goto 9900 !end loop on files
38     c goto 8800 !end loop on views (DSP pkt)
39     goto 2222
40     endif
41    
42     if(checkheader.ne.2) then
43 kusanagi 1.3 c print*,'>>>> ERROR <<<< (trkeventpkt)'
44     c print*,'>>>> CPU packet type ',!pkt_type,
45     c $ ' does not match DSP type ',checkheader
46 kusanagi 1.1 c goto 9909 ! next event (==> search another CPU header)
47     DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)
48     DSPnumber_temp = iand(header(1),z'000f')
49 kusanagi 1.3 c print*,' -----------------------------------'
50     c $ ,iview
51     c print*,' DSP number-----',int(DSPnumber_temp)
52     c print*,' DAQ mode-------',int(DAQmode_temp)
53     c print*,' -----------------------------------'
54 kusanagi 1.1 goto 2525 !next view (==> search another DSP header)
55     endif
56    
57     call unpackdata(runerror,ffd_pkt)
58     c if(runerror.eq.-1) goto 24
59     if(runerror.eq.-1) goto 2222
60     c if(runerror.eq.1) goto 23
61     if(runerror.eq.1) goto 2222
62    
63 kusanagi 1.3 c print*,' '
64     c print*,' -----------------------------------',iview
65     c print*,' DSP number-----',DSPnumber_dat
66     c print*,' DAQ mode-------',DAQmode_dat
67     c print*,' event number ',eventn_dat
68 kusanagi 1.1
69     trk_DSP_ok(DSPnumber_dat)=1
70    
71     call fillview(iview)
72    
73     2525 continue
74     enddo !end loop on views
75    
76     2222 continue
77    
78     close (lun_pkt)
79     return
80     end
81    
82     * **********************************************
83    
84     c subroutine trk_calib_pkt(runerror,ffd_pkt)
85     subroutine trkcalibpkt(runerror,event_file_name)
86    
87     include '../commonyoda/commontracker.f'
88     include '../commonyoda/dataformat.f'
89     include '../commonyoda/trk_calib_parameters.f'
90    
91     integer ndummy
92     data ndummy/1000/
93    
94     integer runerror !readevent error flag
95     integer ffd_pkt !pkt file descriptor
96     !(file temporaneo)
97     character*60 event_file_name !nome file
98    
99     open(unit=lun_pkt,
100     $ name=EVENT_FILE_NAME(1:lnblnk(EVENT_FILE_NAME)),
101     $ status='old',
102     $ form='unformatted'
103     $ )
104     ffd_pkt = FNum(lun_pkt) !reads unix file descriptor
105    
106    
107     do iview=1,ndummy !loop on views (DSP pkt)
108     call searchtrkheader(runerror,ffd_pkt)
109     c if(runerror.eq.-1) goto 24
110     if(runerror.eq.-1) goto 2222
111     if(runerror.eq.1) then
112     print*,' '
113     print*,'readraw: END OF CPU PACKET '
114     print*,'______________________________________ '
115     goto 2222 !end loop on views (DSP pkt)
116     endif
117     if(checkheader.ne.3) then
118 kusanagi 1.3 c print*,'>>>> ERROR <<<< (trkcalibpkt)'
119     c print*,'>>>> CPU packet type ',!pkt_type,
120     c $ ' does not match DSP type ',checkheader
121 kusanagi 1.1 DAQmode_temp = ishft(iand(header(1),z'03f0'),-4)
122     DSPnumber_temp = iand(header(1),z'000f')
123 kusanagi 1.3 c print*,' -----------------------------------'
124     c $ ,iview
125     c print*,' DSP number-----',int(DSPnumber_temp)
126     c print*,' DAQ mode-------',int(DAQmode_temp)
127     c print*,' -----------------------------------'
128 kusanagi 1.1 goto 2424 !next view (==> search another DSP header)
129     endif
130    
131     call unpackcalibration(runerror,ffd_pkt)
132     c if(runerror.eq.-1) goto 24
133     if(runerror.eq.-1) goto 2222
134     c if(runerror.eq.1) goto 23
135     if(runerror.eq.1) goto 2222
136    
137    
138 kusanagi 1.3 c print*,'Calibration packet ==> ',iview
139 kusanagi 1.1
140 kusanagi 1.3 c print*,'---- Calibration packet ',iview,' ----'
141     c print*,' DSP number ',DSPnumber_cal
142     c print*,' DAQ mode ',DAQmode_cal
143     c print*,' calibration run ',calibrationnumber
144     c print*,' n. event used ',nused_event
145     c print*,' <PED> ladder 1 ',ped_1
146     c print*,' <PED> ladder 2 ',ped_2
147     c print*,' <PED> ladder 3 ',ped_3
148     c print*,' <SIG> ladder 1 ',sig_1
149     c print*,' <SIG> ladder 2 ',sig_2
150     c print*,' <SIG> ladder 3 ',sig_3
151     c print*,' n.BAD ladder 1 ',nbad_1
152     c print*,' n.BAD ladder 2 ',nbad_2
153     c print*,' n.BAD ladder 3 ',nbad_3
154     c print*,' error flag ',ff
155 kusanagi 1.1 if(nused_event.ne.0.or.ff.ne.0)then
156 kusanagi 1.3 c print*,'*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*'
157     c print*,'* !!! CALIBRATION FAILURE !!! *'
158     c print*,'*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*.*'
159 kusanagi 1.1 endif
160    
161    
162     DAQmode(iview)=DAQmode_cal
163     DSPnumber(iview)=DSPnumber_cal
164     calibnumber(iview)=calibrationnumber
165     ncalib_event(iview)=nused_event
166     ped_l1(iview)=ped_1
167     ped_l2(iview)=ped_2
168     ped_l3(iview)=ped_3
169     sig_l1(iview)=sig_1
170     sig_l2(iview)=sig_2
171     sig_l3(iview)=sig_3
172     nbad_l1(iview)=nbad_1
173     nbad_l2(iview)=nbad_2
174     nbad_l3(iview)=nbad_3
175     cal_flag(iview)=ff
176    
177     do is=1,nstrips_view
178     DSPbad_par(iview,is)=DSPbad_o(DSPnumber_cal,is)
179     DSPped_par(iview,is)=DSPped_o(DSPnumber_cal,is)
180     DSPsig_par(iview,is)=DSPsig_o(DSPnumber_cal,is)
181     enddo
182     c
183     trk_DSP_ok(DSPnumber_cal)=1
184     c----------------------------------------------------------
185     c NVIEWS calibration packets should have been found
186     c----------------------------------------------------------
187     c if(n_cal_pkt.eq.nviews)then
188     c found_cal_pkt = .true.
189     c n_cal_pkt = 0
190     c endif
191     2424 continue
192     enddo ! end loop on views (calibration pkt)
193     2222 continue
194    
195     close (lun_pkt)
196    
197     return
198     end
199    
200     ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***
201     *
202     *
203     *
204     *
205     *
206     *
207     *
208     *
209     ***...***...***...***...***...***...***...***...***...***...***...***...***...***...***...***
210    
211     subroutine searchtrkheader(runerror,ffd)
212     C.............................................................
213     C Search for a valid tracker DSP header (=>one view)
214     C and return the type of header
215     C.............................................................
216    
217     include '../commonyoda/commontracker.f'
218     include '../commonyoda/dataformat.f'
219    
220     integer ffd !input file descriptor
221     integer runerror !readevent error flag
222    
223     c--------------------------------------------------
224     c N.B.13 bit packing is done for each DSP header+datablock,
225     C so each DSP 13 bit
226     c first word starts at the beginnig of a 16 bit word
227     c--------------------------------------------------
228     9100 continue
229     runerror=0 !error flag initialization
230     checkheader=0
231    
232     c--------------------------------------------------
233     c looks for a DSP header beginning
234     C (a word beginning with 1110)
235     c--------------------------------------------------
236     call findstart(runerror,ffd)
237    
238     if(runerror.eq.1) goto 200
239     if(runerror.eq.-1)then
240     runerror=1 !in this case I dont want the
241     !the program to crash
242     goto 200
243     endif
244     c--------------------------------------------------
245     c the first word could be a DSP header first word:
246     C reads 13 8-bit words and
247     c writes them in 16 13-bit words to check for all
248     C DSP header features
249     c--------------------------------------------------
250     runerror=0
251    
252     call hunpacker(header,runerror,ffd)
253    
254     if(runerror.eq.1) goto 200
255     c if(runerror.eq.-1) goto 200
256     if(runerror.eq.-1)then
257     runerror=1 !in this case I dont want the
258     !the program to crash
259     goto 200
260     endif
261     c--------------------------------------------------
262     c extracts and controls header:
263     c--------------------------------------------------
264     C last header word must be:
265     c |0001|1100|0000|0000| for acquisition
266     c |0001|1111|1111|1111| for calibration
267     c--------------------------------------------------
268     if(iand(header(16),z'ffff').eq.z'1c00') then !last header
269     checkheader=2 ! event
270     elseif(iand(header(16),z'ffff').eq.z'1fff') then !last header
271     checkheader=3 ! calibration packet
272     else
273     checkheader=1 ! not a valid DSP header
274     endif
275     c--------------------------------------------------
276     c first header word must be:
277     c |0001|110x|xxxx|xxxx|
278     c--------------------------------------------------
279     if(iand(header(1),z'fe00').ne.z'1c00')
280     $ checkheader=1 !not a valid DSP header
281     c--------------------------------------------------
282     c intermediate header words must be:
283     c |0001|010x|xxxx|xxxx|
284     c--------------------------------------------------
285     do i=2,15
286     if(iand(header(i),z'fc00').ne.z'1400')
287     $ checkheader=1 !not a valid DSP header
288     enddo
289     c--------------------------------------------------
290     c if checkheader = 1
291     c then this is not a DSP header (or some
292     c noise lurks around) so go a word ahead and
293     c try again
294     c--------------------------------------------------
295     if(checkheader.eq.1) then
296     call skipbyte(ffd)
297     goto 9100
298     endif
299     200 continue
300     end
301    
302     *.............................................................
303    
304    
305     *.............................................................
306    
307     subroutine unpackcalibration(runerror,ffd)
308     *.............................................................
309     * decode calibration data
310     * header + data(PED SIG BAD) + trailer
311     *............................................................
312     include '../commonyoda/commontracker.f'
313     include '../commonyoda/dataformat.f'
314    
315     integer ffd !input file descriptor
316     integer runerror !readevent error flag
317     c buffer temporanei
318     integer*2 templ(nstrips_ladder)
319     real*4 tempf(nstrips_ladder)
320    
321    
322     12 format(z4)
323    
324     *-----------------------------------------------------------
325     * HEADER
326     * (N.B. during test 2003 the header of calibration packets
327     * was only partially filled)
328     *
329     * the following is the final calibration header
330     *-----------------------------------------------------------
331     DAQmode_cal = ishft(iand(header(1),z'03f0'),-4)
332     DSPnumber_cal = iand(header(1),z'000f')
333     dataword = ior(ishft(iand(header(2),z'03ff')
334     $ ,10),iand(header(3),z'03ff'))
335     c calibrationnumber = ior(ishft(iand(header(4)
336     c $ ,z'03ff'),10),iand(header(5),z'03ff'))
337     calibrationnumber = iand(header(4),z'03ff')
338     nused_event = iand(header(5),z'03ff')
339     ped_1 = iand(header(6),z'03ff')
340     ped_2 = iand(header(7),z'03ff')
341     ped_3 = iand(header(8),z'03ff')
342     ped_1 = ped_1 * 4
343     ped_2 = ped_2 * 4
344     ped_3 = ped_3 * 4
345     sig_1 = iand(header(9),z'03ff')
346     sig_2 = iand(header(10),z'03ff')
347     sig_3 = iand(header(11),z'03ff')
348     nbad_1 = iand(header(12),z'03ff')
349     nbad_2 = iand(header(13),z'03ff')
350     nbad_3 = iand(header(14),z'03ff')
351     ff = ishft(iand(header(15),z'0300'),-8)
352     checksum_cal = iand(header(15),z'00ff')
353    
354     runerror=0
355     call readtrailer(trailer,runerror,ffd)
356     c$$$ do i=1,3
357     c$$$ write(*,12)trailer(i)
358     c$$$ enddo
359     c-----------------------------------------------------------
360     c the checksum is a 8-bit word calculated as the
361     c XOR of the 16-bit data words,
362     c hence the XOR between the two halfs
363     C----------------------------------------------------------
364     do il=1,3 !loop on ladders
365    
366     call readped(tempf,runerror,ffd)
367     do is=1,nstrips_ladder
368     iss=is+nstrips_ladder*(il-1)
369     DSPped_o(DSPnumber_cal,iss)=tempf(is)
370     c print*,il,iss,DSPped_o(DSPnumber,iss)
371     c print *,DSPnumber_cal,iss,tempf(is)
372    
373     enddo
374    
375     call readsig(tempf,runerror,ffd)
376     do is=1,nstrips_ladder
377     iss=is+nstrips_ladder*(il-1)
378     DSPsig_o(DSPnumber_cal,iss)=tempf(is)
379     c print*,DSPsig_o(DSPnumber,iss)
380     enddo
381    
382     call readbad(templ,runerror,ffd)
383     do is=1,nstrips_ladder
384     iss=is+nstrips_ladder*(il-1)
385     DSPbad_o(DSPnumber_cal,iss)=templ(is)
386     c print*,il,is,iss,DSPbad_o(DSPnumber,iss)
387     enddo
388    
389     C//// CAPIRE PERCHE` NON C'E` LA PAROLA DI FINE LADDER \\\\
390     c call readeol(word,runerror,ffd)
391     11 format(i1,' ',z4)
392     c write(*,11)il,word
393     call readtrailer(trailer,runerror,ffd)
394     c$$$ do i=1,3
395     c$$$ write(*,12)trailer(i)
396     c$$$ enddo
397    
398     c print*,'fine ladder' !???
399    
400     enddo !end loop on ladders
401    
402     return
403     end
404     *.............................................................
405    
406    
407     subroutine unpackdata(runerror,ffd)
408     *.............................................................
409     * decode event data
410     * header + data + trailer
411     *............................................................
412     include '../commonyoda/commontracker.f'
413     include '../commonyoda/dataformat.f'
414     include '../commonyoda/level0.f'
415    
416     integer ffd !input file descriptor
417     integer runerror !readevent error flag
418     integer l_tra
419    
420    
421     12 format(z4)
422    
423     *-----------------------------------------------------------
424     * HEADER
425     *-----------------------------------------------------------
426    
427     DAQmode_dat = ishft(iand(header(1),z'03f0'),-4)
428     DSPnumber_dat = iand(header(1),z'000f')
429     C ------------------------------------------------------
430     c words 2 and 3 give tshe number of transmitted 16-bit
431     c words ( 13 header words + data )
432     c NB: data are packed from 13-bit to 16-bit words,
433     c so the stream is complited with zeros in order to have
434     c a number of bits multiple of 16
435     l_tra = ior(ishft(iand(header(2),z'03ff')
436     $ ,10),iand(header(3),z'03ff'))
437     l_tra=l_tra-13
438     C ------------------------------------------------------
439     eventn_dat = ior(ishft(iand(header(4),z'03ff')
440     $ ,10),iand(header(5),z'03ff'))
441     nclust_dat = ishft(iand(header(6),z'0380'),-7)
442     cutc_dat = ishft(iand(header(6),z'0070'),-4)
443     cutcl_dat = iand(header(6),z'000f')
444     addrcluster_dat(1) = iand(header(7),z'03ff')
445     signcluster_dat(1) = iand(header(8),z'03ff')
446     addrcluster_dat(2) = iand(header(9),z'03ff')
447     signcluster_dat(2) = iand(header(10),z'03ff')
448     addrcluster_dat(3) = iand(header(11),z'03ff')
449     signcluster_dat(3) = iand(header(12),z'03ff')
450     fc_dat = ishft(iand(header(13),z'0300'),-8)
451     compressiontime_dat = iand(header(13),z'00ff')
452     fl5_dat = ishft(iand(header(14),z'0300'),-8)
453     fl4_dat = ishft(iand(header(14),z'0300'),-6)
454     fl3_dat = ishft(iand(header(14),z'0300'),-4)
455     fl2_dat = ishft(iand(header(14),z'0300'),-2)
456     fl1_dat = iand(header(14),z'0300')
457     fl6_dat = ishft(iand(header(15),z'0300'),-8)
458     checksum_dat = iand(header(15),z'00ff')
459     c-----------------------------------------------------------
460     c the cheacksum is a 8-bit word calculated as the
461     c XOR of the 16-bit data words,
462     c hence the XOR between the two halfs
463     C----------------------------------------------------------
464     runerror=0
465     call dunpacker(l_tra,b_tra,runerror,ffd)
466     nqualcosa = (real(l_tra))/13*16
467     xx = b_tra(nqualcosa)
468     if (xx.eq.0) nqualcosa=nqualcosa -1
469     datalength_dat= nqualcosa
470     c$$$ TOTDATAlength = TOTDATAlength + datalength_dat
471     c$$$ do i=1,datalength_dat
472     c$$$ id = id + 1
473     c$$$ datatracker(id) = b_tra(i)
474     c$$$ enddo
475    
476    
477    
478     11 format(i1,' ',z4)
479     c write(*,11)il,word
480     call readtrailer(trailer,runerror,ffd)
481     c$$$ do i=1,3
482     c$$$ write(*,12)trailer(i)
483     c$$$ enddo
484    
485     ***************************************************************
486     * TRAILER *
487     ***************************************************************
488    
489     pnum_dat=ishft(iand(trailer(1),z'f000'),-12)
490     cmdnum_dat=ishft(iand(trailer(1),z'0f00'),-8)
491     bid1_dat=ishft(iand(trailer(1),z'00c0'),-6)
492     bid2_dat=ishft(iand(trailer(1),z'0030'),-4)
493     bid3_dat=ishft(iand(trailer(1),z'000c'),-2)
494     bid4_dat=iand(trailer(1),z'0003')
495     bid5_dat=ishft(iand(trailer(2),z'c000'),-14)
496     bid6_dat=ishft(iand(trailer(2),z'3000'),-12)
497     bid7_dat=ishft(iand(trailer(2),z'0c00'),-10)
498     alarm_dat=ishft(iand(trailer(2),z'0300'),-8)
499     aswr_dat=ior(ishft(iand(trailer(2),z'00ff'),8)
500     $ ,ishft(iand(trailer(3),z'ff00'),-8))
501     crc_dat=iand(trailer(3),z'00ff')
502    
503     bid_dat_sum = (bid1_dat + bid2_dat + bid3_dat + bid4_dat +
504     & bid5_dat + bid6_dat + bid7_dat)
505    
506     bid_dat = bid_dat_sum/7
507    
508     if (bid_dat.ne.1.and.bid_dat.ne.2) then
509 kusanagi 1.3 c write(*,*) '*** *** *** *** *** *** *** *** *** ***'
510     c write (*,*) 'unpack_data: TRAILER PACKET CORRUPTED'
511     c write(*,*) '*** *** *** *** *** *** *** *** *** ***'
512 kusanagi 1.1 endif
513     if (mod(bid_dat_sum,7).ne.0) then
514     bid_dat = 0
515 kusanagi 1.3 c write(*,*) '*** *** *** *** *** *** *** *** *** ***'
516     c write (*,*) 'unpack_data: TRAILER PACKET CORRUPTED'
517     c write(*,*) '*** *** *** *** *** *** *** *** *** ***'
518 kusanagi 1.1 endif
519    
520     if (alarm_dat.eq.3) then
521 kusanagi 1.3 c write(*,*) '*** *** *** *** *** *** *** *** *** ***'
522     c write(*,*) 'unpack_data: AQUISITION ALARM'
523     c write(*,*) '*** *** *** *** *** *** *** *** *** ***'
524 kusanagi 1.1
525     endif
526    
527     if (alarm_dat.ne.3.and.alarm_dat.ne.0) then
528 kusanagi 1.3 c write(*,*) '*** *** *** *** *** *** *** *** *** ***'
529     c write(*,*) 'unpack_data: TRAILER PACKET CORRUPTED'
530     c write(*,*) '*** *** *** *** *** *** *** *** *** ***'
531 kusanagi 1.1
532     endif
533    
534    
535     return
536     end
537    
538    
539     *.............................................................................
540     subroutine initlevel0
541    
542     include '../commonyoda/level0.f'
543    
544    
545     do i=1, nviews
546    
547     DAQmode(i) = 0
548     DSPnumber(i) = 0
549     eventn(i) = 0
550     nclust(i) = 0
551     cutc(i) = 0
552     cutcl(i) = 0
553     addrcluster(i,1) = 0
554     signcluster(i,1) = 0
555     addrcluster(i,2) = 0
556     signcluster(i,2) = 0
557     addrcluster(i,3) = 0
558     signcluster(i,3) = 0
559     fc(i) = 0
560     compressiontime(i) = 0
561     fl5(i) = 0
562     fl4(i) = 0
563     fl3(i) = 0
564     fl2(i) = 0
565     fl1(i) = 0
566     fl6(i) = 0
567     checksum(i) = 0
568     DATAlength(i) = 0
569     pnum(i)= 0
570     cmdnum(i)= 0
571     bid(i) = 1
572     alarm(i)= 0
573     aswr(i) = 0
574     enddo
575    
576     TOTDATAlength = 0
577     good0=.true.
578    
579     return
580     end
581    
582    
583     * *** *** *** *** *** *** *** *** ***
584     *
585     *
586     *
587     *
588     *
589     *
590     * *** *** *** *** *** *** *** *** ***
591     subroutine fillview(i)
592     c -----------------------------------------------------
593     c fill variables related to view i
594     c which will be stored in the level0 nt-ple
595     c at the end of loop on views
596     c ----------------------------------------------------
597    
598     include '../commonyoda/commontracker.f'
599     include '../commonyoda/level0.f'
600     include '../commonyoda/dataformat.f'
601    
602     DAQmode(i) = DAQmode_dat
603     DSPnumber(i) = DSPnumber_dat
604     eventn(i) = eventn_dat
605     nclust(i) = nclust_dat
606     cutc(i) = cutc_dat
607     cutcl(i) = cutcl_dat
608     addrcluster(i,1) = addrcluster_dat(1)
609     signcluster(i,1) = signcluster_dat(1)
610     addrcluster(i,2) = addrcluster_dat(2)
611     signcluster(i,2) = signcluster_dat(2)
612     addrcluster(i,3) = addrcluster_dat(3)
613     signcluster(i,3) = signcluster_dat(3)
614     fc(i) = fc_dat
615     compressiontime(i) = compressiontime_dat
616     fl5(i) = fl5_dat
617     fl4(i) = fl4_dat
618     fl3(i) = fl3_dat
619     fl2(i) = fl2_dat
620     fl1(i) = fl1_dat
621     fl6(i) = fl6_dat
622     checksum(i) = checksum_dat
623     DATAlength(i) = datalength_dat
624    
625     c -----------------------------------------------------------------------
626     c filling TRAILER variables
627     c ----------------------------------------------------------------------
628    
629     pnum(i)= pnum_dat
630     cmdnum(i)= cmdnum_dat
631     bid(i) = bid_dat
632     alarm(i)= alarm_dat
633     aswr(i) = aswr_dat
634    
635 kusanagi 1.3 c print*,'*-*-*-*-*-*-TRAILER-*-*-*-*-*-*'
636     c print*,'* PNUM (periferal num) ',pnum_dat
637     c print*,'* CMDNUM (command) ',cmdnum_dat
638     c print*,'* BID (board id) ',bid_dat
639     c print*,'* ALARM ',alarm_dat
640     c print*,'*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'
641 kusanagi 1.1
642     do idat=1,datalength_dat
643     id = TOTDATAlength + idat
644     datatracker(id) = b_tra(idat)
645     enddo
646     TOTDATAlength = TOTDATAlength + datalength_dat
647 kusanagi 1.3
648 kusanagi 1.1 return
649     end
650    

  ViewVC Help
Powered by ViewVC 1.1.23