source: trunk/SOURCES/tracer_mod.f90 @ 111

Last change on this file since 111 was 54, checked in by aquiquet, 8 years ago

Tracers back in the code / use notracer unchanged

File size: 18.4 KB
Line 
1!> module appele par le main (step) qui calcule les traceurs
2!!  @todo depuis tracer_mod, decider e() en local ou global
3!!  @todo attention l'appel au module climat est en dur
4!!    et peut poser des pb si different du module choix.
5
6!--------------------------------------------------------------
7! Position des forages dans la grille grisli.
8! Groenland grille GreeneemXX
9!
10! Ordre GMT :
11! mapproject  -Js-39/90/71/1:50000000 -Fk -R/-150/50/50/85 -C
12!
13! NEEM : -50.9E 77.5N  -> -281.129 / -1334.05
14!  5km:  ineem=143 /jneem=437
15!  15km: ineem=48 / jneem=146
16!  45km: ineem=16 / jneem=49
17!
18! GRIP : -37.633333E 72.583333N -> 45.4707 / -1905.94
19!  5km:  igrip=208 /jgrip=323
20!  15km: igrip=70 / jgrip=108 ! grosso modo
21!  45km: igrip=24 / jgrip=36  ! grosso modo
22!
23!--------------------------------------------------------------
24
25
26
27module tracer_mod
28
29  use module3d_phy
30  use tracer_vars             ! module de declaration de variables pour les traceurs
31!cdc  use climat_perturb_mois_mod ! on en a besoin, notamment pour NFT
32! afq, new version of tracer, does not require climat_perturb
33 
34  implicit none
35
36! variables de travail
37  integer :: i_ij, i_jj, ip, jp, im, jm, km      ! indice dans les matrices des traceurs
38  real    :: v_xij, v_yij, v_zij                 ! vitesses 'cumulees'
39
40! pour chaque point de grille on recherche ou etait la particule au pas de temps precedent
41! Tout ce qui est mentionne traceur est lie aux proprietes de ce point
42
43  real    :: x_tra                               ! position x du traceur 
44  real    :: y_tra                               ! position y du traceur
45  real    :: e_tra                               ! position verticale du traceur
46
47! ecart entre la position du traceur et le point de grille grisli le plus proche
48  real    :: fx                                  ! ecart en x
49  real    :: fy                                  ! ecart en y
50  real    :: fz                                  ! ecart vertical ? (z ou sigma ?)
51
52  integer :: deltracer   ! pas de temps du traceur ?  -> dans la version d'origine tracer est appele tous les dtt
53  integer :: time_tra    ! temps traceur
54
55
56!===============================================================
57
58 
59contains
60
61subroutine init_tracer
62
63! formats pour les ecritures dans 42
64428 format(A)
65
66  real :: lambdab  ! fusion basale 'artificielle' pour age des couches
67  real :: agemax   ! age maximum de la glace (pour init_tracer)
68
69  integer :: pert_type ! 0 we give tpert/coeft/rappact,1 we give acc_pert only / afq
70  character(len=200) :: filforc    ! nom du fichier forcage
71  character(len=200) :: filin      ! variable intermediaire
72  character(len=8) :: control      ! label to check clim. forc. file (filin) is usable
73  integer ::  err                  ! pour l'allocation des tableaux
74  real :: bidon                    ! to skip sealevel change in fileforc
75 
76  integer :: kk   ! indice vertical pour definition de E, mais on veut conserver la valeur de k
77!  real,dimension(nz) :: E   ! vertical coordinate in ice, scaled to H zeta
78
79  ! on lit les parametres par namelist dorenavant
80  namelist/tracer/file_tr_dat,file_tr_out,file_tr_dep,lambdab,agemax,coefT_tra,rappact_tra,filforc,pert_type 
81
82
83if (itracebug.eq.1) write(num_tracebug,*)'init_tracer dans tracer_mod'
84
85! itracer pour les ecritures et lectures recovery
86 itracer = 1
87
88! profondeur reduite
89  E(1)=0.
90  E(NZ)=1.
91  do KK=1,NZ
92     if ((KK.ne.1).and.(KK.ne.NZ)) E(KK)=(KK-1.)/(NZ-1.)
93  end do
94
95
96if (itracebug.eq.1) write(num_tracebug,*)'init_tracer dans tracer_mod'
97
98  time_tra = floor(time) 
99
100  deltracer = dtt           ! sorte de pas de temps du tracer -  multiple de dtt !
101
102
103  rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
104  read(num_param,tracer)
105  print*
106  print*
107  print*, 'tracer .dat file: ', file_tr_dat
108  print*, 'tracer .out file: ', file_tr_out
109  print*, 'tracer dep. file: ', file_tr_dep
110
111
112  write(num_rep_42,428)'!___________________________________________________________' 
113  write(num_rep_42,428) '&tracer                                    ! module tracer_mod'
114  write(num_rep_42,'(A,A)')   'tracer .dat file : ', file_tr_dat
115  write(num_rep_42,'(A,A)')   'tracer .out file : ', file_tr_out
116  write(num_rep_42,'(A,A)')   'tracer dep. file : ', file_tr_dep
117  write(num_rep_42,'(A,A)')   'lambdab : ', lambdab
118  write(num_rep_42,'(A,A)')   'agemax : ', agemax
119  write(num_rep_42,'(A,A)')   'coefT_tra : ', coefT_tra
120  write(num_rep_42,'(A,A)')   'rappact_tra : ', rappact_tra
121  write(num_rep_42,'(A,A)')   'fileforc : ', filforc
122  write(num_rep_42,'(A,A)')   'pert_type : ', pert_type
123  write(num_rep_42,*)'/'                     
124  write(num_rep_42,428) 'declaration des repertoires *traceurs*'
125  write(num_rep_42,*)
126
127! on appelle la soubroutine qui lit le fichier .dat des traceurs
128! ce fichier contient les dates de sorties des traceurs
129  call read_tr_dat ! intervalles d'output
130
131  nij = nx * ny
132
133! initialize "previous" tracer arrays as if all ice at start
134! time was created instantaneously and in-place
135
136! attention pourquoi ne pas utiliser xcc et ycc ?
137!!$  do i=1,nx
138!!$     xgrid(i) = (i- (nx+1)/2. ) * dx
139!!$  end do
140!!$  do j=1,ny
141!!$     ygrid(j) = (j - (ny+1)/2.) * dy
142!!$  end do
143
144! notre grille a nous
145  do i=1,nx
146     xgrid(i)=xmin*1000+(i-1)*dx
147  end do
148  do j=1,ny
149     ygrid(j)=ymin*1000+(j-1)*dy
150  end do
151 
152! initialisation des abscisses et ordonnees a la valeur en surface
153! initialisation de l'age
154  do j=2,ny-1
155     i_jj = j-1
156     ydepk(:,:,i_jj) = ygrid(j) 
157     do i=2,nx-1
158        i_ij = i-1
159        xdepk(:,i_ij,i_jj) = xgrid(i)
160
161! todo0710
162! remplacer par une formule logarithmique
163! 10**-4 m/an fusion basale (ou valeur de lambda a la base)
164! + agemax 1 million d'annees
165
166!!$        if (h(i,j)>10.) then
167!!$           do k=1,4
168!!$              tdepk(k,i_ij,i_jj) = - min(3500., h(i,j)) *real((k-1)**2)
169!!$           end do
170!!$           do k=5,nz
171!!$              tdepk(k,i_ij,i_jj) = - min(3500., h(i,j)) *real((k-1)*3)
172!!$           end do
173!!$           do k=12,nz
174!!$              tdepk(k,i_ij,i_jj) = tdepk(k,i_ij,i_jj) * (real(11) + real((k-7)**3)/125. )/12.
175!!$           end do
176!!$        else
177!!$           tdepk(:,i_ij,i_jj) = 0.
178!!$        end if
179!!$     end do
180!!$  end do
181!!$
182!!$   
183!!$! a enlever eventuellement si on utilise le log
184!!$  do j=1,ny-2
185!!$     do i=1,nx-2
186!!$        if (((tdepk(20,i,j)-tdepk(21,i,j))<1000.)) then
187!!$           if ((h(i,j)>100.))  then
188!!$              tdepk(21,i,j)=tdepk(20,i,j)-10*h(i,j)
189!!$           else
190!!$              tdepk(21,i,j)=tdepk(20,i,j)- 1000.
191!!$           end if
192!!$        end if
193!!$     end do
194!!$  end do
195!!$   
196        do k=1,nz
197           if(acc(i,j).gt.lambdab) then
198              tdepk(k,i_ij,i_jj)=H(i,j)*log(    &
199                   1-E(k)*(1-lambdab/ACC(i,j)))/(ACC(i,j)-lambdab)
200           else
201              tdepk(k,i_ij,i_jj)=0.
202           end if
203        end do
204
205     end do
206  end do
207
208  where (tdepk(:,:,:).ge.agemax)
209     tdepk(:,:,:)=agemax
210  end where
211  tdepk(:,:,:) = tdepk(:,:,:) + tbegin
212
213
214  ! afq marion dufresne:
215  ! to build accucumul, we read all what is in climat_perturb here now
216  ! meaning: nft, tpert, tdate
217  ! OR if pert_type = 1 we read nft, acc_pert, tdate
218  ! acc_pert should be the ratio acc_palaeo / acc_present
219 
220    filin=trim(dirforcage)//trim(filforc)
221
222    open(num_forc,file=filin,status='old')
223
224    read(num_forc,*) control,nft_tra
225
226    ! Determination of file size (line nb), allocation of perturbation array
227    if (control.ne.'nb_lines') then
228       write(6,*) filin,'indiquer le nb de ligne en debut de fichier:'
229       write(6,*) 'le nb de lignes et le label de control nb_lines'
230       stop
231    endif
232    if (.not.allocated(tdate_tra)) then
233       allocate(tdate_tra(nft_tra),stat=err)
234       if (err/=0) then
235          print *,"erreur a l'allocation du tableau Tdate",err
236          stop 4
237       end if
238    end if
239    if (.not.allocated(tpert_tra)) then
240       allocate(tpert_tra(nft_tra),stat=err)
241       if (err/=0) then
242          print *,"erreur a l'allocation du tableau Tpert",err
243          stop 4
244       end if
245    end if
246
247    do i=1,nft_tra
248       read(num_forc,*) tdate_tra(i),bidon,tpert_tra(i)
249    end do
250    close(num_forc)
251
252 
253 2009 format(21(f12.1))
254   
255   ! prepares accu-cumul variable for accu-interp
256
257  ! note aurel neem : ATTENTION ! dans version NL ->
258  ! chaque indice d'accucumul vaut 100 ans.
259  ! 0 pour le present, 10 pour 1000 ans
260   allocate(accucumul(0:nft_tra-1)); accucumul = 0.0
261   ! watch out its size !!!
262   ! note: tpert(1) = tpert at -422700yr
263   ! nl 12/08/02: attention au param de l'exp(): doit etre coherent avec le
264   ! forcage climatique: ici, change de 0.062 a 0.100
265   ! attention a ce que nft <=> present, sinon mon indexage est fourré
266   ! a la rigueur je pourrais modifier le fichier d'interpolation pour
267   ! l'adapter a tdate
268   accucumul(nft_tra-1) =  0.
269
270   ! todo0710 : marge d'amelioration en tenant compte des accum de depot ?
271
272   if (type_accum.eq.0) then   !Tpert is given, needs to be converted in accumulation ratio
273      tpert_tra(:)=tpert_tra(:)*coefT_tra
274      do k=2,nft_tra
275         accucumul(nft_tra-k) = accucumul(nft_tra-k+1) + (exp(rappact_tra  * tpert_tra(k) ))
276      end do
277   else if (type_accum.eq.1) then ! accum ration is given, nothing to do
278      do k=2,nft_tra
279         accucumul(nft_tra-k) = accucumul(nft_tra-k+1) + tpert_tra(k)
280      end do
281   else
282      write (*,*) "Problem in tracer, do you provide tpert or accpert???"
283      STOP
284   end if
285   time_max_accu = tdate_tra(1)
286   uxsave(:,:,:) = 0.0
287   uysave(:,:,:) = 0.0
288   uzrsave(:,:,:) = 0.0
289   xdep(:,:,:)=xdepk(:,:,:)
290   ydep(:,:,:)=ydepk(:,:,:)
291   tdep(:,:,:)=tdepk(:,:,:)
292   freezeon(:,:) = 0.     ! variable added on 19/03/03
293
294   print*, 'tbegin, tend : ',tbegin, tend
295
296end subroutine init_tracer
297
298
299subroutine tracer
300
301  real,dimension(nz) :: E   ! vertical coordinate in ice, scaled to H zeta
302
303  E(1)=0.
304  E(NZ)=1.
305  do K=1,NZ
306     if ((K.ne.1).and.(K.ne.NZ)) E(K)=(K-1.)/(NZ-1.)
307  end do
308
309  If (Itracebug.Eq.1) Write(num_tracebug,*)' Entree Dans Routine tracer at time=',Time
310
311   time_tra = floor(time) 
312      !! start of main task
313      ! main calculation loop omits the outer buffer cells.  update here.
314
315  !===== accucumulative velocities
316 
317     uxsave(:,:,:) = uxsave(:,:,:) + ux(:,:,:)*real(dtt)  ! todo0710 mettre les tableaux
318     uysave(:,:,:) = uysave(:,:,:) + uy(:,:,:)*real(dtt)  ! attention uxsave position en maille staggered
319                                     ! ATTENTION, il faudrait deltra pas dtt, SIGNE ?
320     do j=1,ny
321        do i=1,nx
322           ! added on 16/12/03: somehow worked before too
323           if (h(i,j)>1.5) &
324             uzrsave(i,j,:) = uzrsave(i,j,:) + uzr(i,j,:) *real(dtt) / h(i,j)
325        end do
326     end do
327
328!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
329
330! recalcul de accucumul d'après les valeurs courantes pour
331!reconstruire accucumul de façon interactive. utile pour une calotte
332! qui varie beaucoup en géométrie.
333
334!if (mod(time_tra,100)==0) then
335!       update accu, rewriting on top of the older value
336!       i=-time_tra/100
337!       accucumul(i) = accucumul(i+1) + acc(105,49)/ 0.0295
338!end if
339
340  if (mod(time_tra,deltracer)==0) then
341     
342     !============ east and west boundaries
343     do j=2,ny-1
344        i_jj = j-1
345        xdep(:,1,i_jj) = xgrid(2)
346        xdep(:,nx-2,i_jj) = xgrid(nx-1)
347        ydep(:,1,i_jj) = ygrid(j)
348        ydep(:,nx-2,i_jj) = ygrid(j)
349!        tdep(:,1,i_jj) = time_
350!        tdep(:,nx-2,i_jj) = time_
351        tdep(:,1,i_jj) = time   
352        tdep(:,nx-2,i_jj) = time
353     end do
354      !=========== north and south boundaries
355     do i=2,nx-1
356        i_ij = i-1
357        xdep(:,i_ij,1) = xgrid(i)
358        xdep(:,i_ij,ny-2) = xgrid(i)
359        ydep(:,i_ij,1) = ygrid(2)
360        ydep(:,i_ij,ny-2) = ygrid(ny-1)
361!       tdep(:,i_ij,1) =  time_
362!       tdep(:,i_ij,ny-2) =  time_
363        tdep(:,i_ij,1) =  time   
364        tdep(:,i_ij,ny-2) =  time
365     end do
366
367     
368      !============= inside grid: now watch out: (i,j) dyn-grid <=> (i_ij, i_jj) tracer-grid
369      do j=3,ny-2
370        do i=3,nx-2
371          i_ij = i-1
372          i_jj = j-1
373
374! nl 11/03/04
375          if (h(i,j)<=1.5) then
376            xdep(:,i_ij,i_jj) = xgrid(i)
377            ydep(:,i_ij,i_jj) = ygrid(j)
378            tdep(:,i_ij,i_jj) =  time 
379            cycle
380          end if
381          freezeon(i_ij,i_jj) = max(0.0, freezeon(i_ij,i_jj)-bmelt(i,j) )
382         
383          ip = i+1
384          jp = j+1
385          do k=1,nz
386            v_xij       = (uxsave(i,j,k)+uxsave(ip,j,k)) / real(2)
387            v_yij       = (uysave(i,j,k)+uysave(i,jp,k)) / real(2)
388            v_zij       = uzrsave(i,j,k)
389
390            x_tra       = xgrid(i) - v_xij      !* real(deltracer)
391            y_tra       = ygrid(j) - v_yij      !* real(deltracer)
392            e_tra       = e(k) - v_zij          !* real(deltracer)
393
394            if ((k==nz).and.(bmelt(i,j)<-1.e-4)) then   ! bottom freezeon
395               xdep(k,i_ij,i_jj) = xgrid(i)
396               ydep(k,i_ij,i_jj) = ygrid(j)
397               if (h(i,j)>100.) then
398                 tdep(k,i_ij,i_jj) =  tdepk(k,i_ij,i_jj) - &
399                        min( abs( (tdepk(k-1,i_ij,i_jj)-tdepk(k,i_ij,i_jj)) *  &
400                          bmelt(i,j)  / ( ( e(k)-e(k-1) )*h(i,j) ) ), 2.) * deltracer
401                  ! this added 26/03/04 so that not more 2.*deltracer new years of refreezing
402               else
403                 tdep(k,i_ij,i_jj) =  tdepk(k,i_ij,i_jj)
404                 
405               end if 
406                !fix:    need to track where freeze-on happens
407                ! *1.001        proven to be dumb
408!               if((tdep(k,i_ij,i_jj)<=time_  -  1500000.) .or. (tdep(k,i_ij,i_jj)>=tend+1.0)) then
409               if((tdep(k,i_ij,i_jj)<=time  -  1500000.) .or. (tdep(k,i_ij,i_jj)>=tend+1.0)) then
410                  print *,"tdep(",k,",",i_ij,",",i_jj,") range error at time=",time_tra
411                   print *,"tdep(k,i_ij,i_jj) =",tdep(k,i_ij,i_jj), v_xij, v_yij, v_zij
412                   print *, bmelt(i,j), s(i,j), h(i,j), e_tra, tdepk(k,i_ij,i_jj), tdepk(k,i,j)
413                   print *, flot(im,jm), flot(im+1,jm), flot(im+1,jm+1), flot(im,jm+1)
414                   if (k>1) tdep(k,i_ij,i_jj) = tdepk(k-1,i_ij,i_jj) - real(h(i,j)*(k-1)**2/30.)
415                   print *, tdep(k,i_ij,i_jj)
416                end if
417
418             else if (k==1 .and. bm(i,j)>0.0) then        !! surface mass balance
419              xdep(k,i_ij,i_jj) = xgrid(i)
420              ydep(k,i_ij,i_jj) = ygrid(j)
421              tdep(k,i_ij,i_jj) =  time 
422            else if ( e_tra < e(1) ) then               !! rapid thickening by
423              xdep(k,i_ij,i_jj) = xgrid(i)                              !! surface accumulation
424              ydep(k,i_ij,i_jj) = ygrid(j)
425              tdep(k,i_ij,i_jj) =  time   
426           else
427                call celltest(time_tra,i,j,k,v_xij, v_yij, v_zij, x_tra, y_tra, e_tra, &
428                                im,jm,km,fx,fy,fz)
429                !! convert seach results from (i,j) grid to (i_ij,i_jj) tracer grid
430                !print*,'i,j,k avt interp',i,j,k
431
432                call interpolate(i_ij, i_jj, k, im-1, jm-1, km, fx,fy,fz, e_tra, nft_tra) 
433
434                if((tdep(k,i_ij,i_jj)<=time  -  1500000.) .or. (tdep(k,i_ij,i_jj)> time   )) then
435                   print *,"tdep(",k,",",i_ij,",",i_jj,") range error at time=",time_tra
436                   print *,"tdep(k,i_ij,i_jj) =",tdep(k,i_ij,i_jj), v_xij, v_yij, v_zij
437                   print *, bmelt(i,j), s(i,j), h(i,j), e_tra, tdepk(k,i_ij,i_jj), tdepk(k,i,j)
438                   print *, flot(im,jm), flot(im+1,jm), flot(im+1,jm+1), flot(im,jm+1) 
439                   if (k>1) tdep(k,i_ij,i_jj) = tdepk(k-1,i_ij,i_jj) - real(h(i,j)*(k-1)**2/30.)
440                   print *, tdep(k,i_ij,i_jj) 
441                end if
442
443            end if
444
445          end do
446        end do
447      end do
448
449      xdepk(:,:,:) = xdep(:,:,:)
450      ydepk(:,:,:) = ydep(:,:,:)
451      tdepk(:,:,:) = tdep(:,:,:)
452      uxsave = 0.00
453      uysave = 0.00
454      uzrsave = 0.00
455
456   end if !========== if deltracer
457
458   if (abs(time-tend)<19) then   
459      open(505,file="freezeonmap.out",status="replace")
460      print*,"save freezeon file"
461      write(505,  * ) freezeon
462      close(505)
463      print *, tdep(:,70,70)
464   end if
465
466! aurel neem -> je me cree une version formatte "out" pour les sorties
467! on traite d'abord les 4 coins
468xdep_out(1,1,:)=xdep(:,1,1)
469xdep_out(nx,1,:)=xdep(:,nx-2,1)
470xdep_out(nx,ny,:)=xdep(:,nx-2,ny-2)
471xdep_out(1,ny,:)=xdep(:,1,ny-2)
472ydep_out(1,1,:)=ydep(:,1,1)
473ydep_out(nx,1,:)=ydep(:,nx-2,1)
474ydep_out(nx,ny,:)=ydep(:,nx-2,ny-2)
475ydep_out(1,ny,:)=ydep(:,1,ny-2)
476tdep_out(1,1,:)=tdep(:,1,1)
477tdep_out(nx,1,:)=tdep(:,nx-2,1)
478tdep_out(nx,ny,:)=tdep(:,nx-2,ny-2)
479tdep_out(1,ny,:)=tdep(:,1,ny-2)
480! puis les bords Ouest et Est
481do i=2,nx-1
482   xdep_out(i,1,:)=xdep(:,i-1,1)
483   xdep_out(i,ny,:)=xdep(:,i-1,ny-2)
484   ydep_out(i,1,:)=ydep(:,i-1,1)
485   ydep_out(i,ny,:)=ydep(:,i-1,ny-2)
486   tdep_out(i,1,:)=tdep(:,i-1,1)
487   tdep_out(i,ny,:)=tdep(:,i-1,ny-2)
488end do
489! et les bords Sud et Nord
490do j=2,ny-1
491   xdep_out(1,j,:)=xdep(:,1,j-1)
492   xdep_out(nx,j,:)=xdep(:,nx-2,j-1)
493   ydep_out(1,j,:)=ydep(:,1,j-1)
494   ydep_out(nx,j,:)=ydep(:,nx-2,j-1)
495   tdep_out(1,j,:)=tdep(:,1,j-1)
496   tdep_out(nx,j,:)=tdep(:,nx-2,j-1)
497end do
498! et enfin on complete l'interieur
499do k=1,nz
500   do j=2,ny-1
501      do i=2,nx-1
502         xdep_out(i,j,k)=xdep(k,i-1,j-1)
503         ydep_out(i,j,k)=ydep(k,i-1,j-1)
504         tdep_out(i,j,k)=tdep(k,i-1,j-1)
505      end do
506   end do
507end do
508
509end subroutine tracer
510
511!=============================================================================
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526!========================================================================
527!========================================================================
528subroutine get_date_time(yr, mon, iday, hr, minu, sec)
529
530  implicit none
531  integer, intent(out) :: yr, mon, iday, hr, minu, sec
532
533  integer, dimension(8) :: values
534  character :: date*8, chtime*10, zone*5
535     
536  call date_and_time(date, chtime, zone, values)
537     
538  yr   = values(1)
539  mon  = values(2)
540  iday = values(3)
541  hr   = values(5)
542  minu  = values(6)
543  sec  = values(7)
544
545end subroutine get_date_time
546
547!========================================================================
548subroutine read_tr_dat
549!      use global_param
550  use tracer_vars
551  implicit none
552
553! lit le fichier tracer.dat du coup.
554  integer :: ioerr
555  character(len=60) :: line
556
557  open(unit=unit_tr_dat, file=file_tr_dat)
558 
559  read(unit=unit_tr_dat, fmt=*) delttrout
560  print*,delttrout
56111 format(i8)
562  nspectimes = 0
563  read(unit=unit_tr_dat, fmt="(a)",iostat=ioerr) line
564  if(ioerr/=0 .or. line(1:13)/="special times") return
565
566  do
567     nspectimes = nspectimes+1
568     read(unit=line, fmt=*,iostat=ioerr) trout(nspectimes)
569     if(ioerr/=0) then
570        nspectimes=nspectimes-1
571        exit
572     end if
573  end do
574
575  close(unit=unit_tr_dat)
576 
577end subroutine read_tr_dat
578
579   
580end module tracer_mod
Note: See TracBrowser for help on using the repository browser.