/[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.1.1.1 - (hide annotations) (download) (vendor branch)
Tue Jul 6 12:20:23 2004 UTC (20 years, 5 months ago) by kusanagi
Changes since 1.1: +0 -0 lines

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

  ViewVC Help
Powered by ViewVC 1.1.23