/[lmdze]/trunk/libf/dyn3d/iniadvtrac.f90
ViewVC logotype

Diff of /trunk/libf/dyn3d/iniadvtrac.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 18 by guez, Thu Aug 7 12:29:13 2008 UTC revision 23 by guez, Mon Dec 14 15:25:16 2009 UTC
# Line 18  module iniadvtrac_m Line 18  module iniadvtrac_m
18    
19  contains  contains
20    
21    subroutine iniadvtrac(nq)    subroutine iniadvtrac
22    
23      ! From dyn3d/iniadvtrac.F, version 1.3 2005/04/13 08:58:34      ! From dyn3d/iniadvtrac.F, version 1.3 2005/04/13 08:58:34
24    
# Line 27  contains Line 27  contains
27      ! Modification M.-A. Filiberti 02/02 lecture de "traceur.def"      ! Modification M.-A. Filiberti 02/02 lecture de "traceur.def"
28      ! Modification de l'intégration de "q" (26/04/94)      ! Modification de l'intégration de "q" (26/04/94)
29    
30      integer, intent(out), optional:: nq      use numer_rec, only: assert
31    
32      ! Variables local to the procedure:      ! Variables local to the procedure:
33    
# Line 103  contains Line 103  contains
103         print *, 'Ouverture de "traceur.def" ok'         print *, 'Ouverture de "traceur.def" ok'
104         read(unit=90, fmt=*) nq_local         read(unit=90, fmt=*) nq_local
105         print *, 'nombre de traceurs ', nq_local         print *, 'nombre de traceurs ', nq_local
106         if (nq_local > nqmx) then         call assert(nq_local == nqmx, "iniadvtrac nq_local")
           print *, 'nombre de traceurs trop important'  
           print *, 'verifier traceur.def'  
           stop 1  
        endif  
107    
108         do iq=1, nq_local         do iq=1, nqmx
109            read(90, 999) hadv(iq), vadv(iq), tnom(iq)            read(90, 999) hadv(iq), vadv(iq), tnom(iq)
110         end do         end do
111         close(90)           close(90)  
112         PRINT *, 'lecture de traceur.def :'           PRINT *, 'lecture de traceur.def :'  
113         do iq=1, nq_local         do iq=1, nqmx
114            write(*, *) hadv(iq), vadv(iq), tnom(iq)            write(*, *) hadv(iq), vadv(iq), tnom(iq)
115         end do         end do
116      else      else
117         print *, 'Problème à l''ouverture de "traceur.def"'         print *, 'Problème à l''ouverture de "traceur.def"'
118         print *, 'Attention : on prend des valeurs par défaut.'         print *, 'Attention : on prend des valeurs par défaut.'
119         nq_local = 4         call assert(nqmx == 4, "iniadvtrac nqmx")
120         hadv(1) = 14         hadv(1) = 14
121         vadv(1) = 14         vadv(1) = 14
122         tnom(1) = 'H2Ov'         tnom(1) = 'H2Ov'
# Line 135  contains Line 131  contains
131         tnom(4) = 'PB'         tnom(4) = 'PB'
132      ENDIF      ENDIF
133      PRINT *, 'Valeur de traceur.def :'      PRINT *, 'Valeur de traceur.def :'
134      do iq=1, nq_local      do iq=1, nqmx
135         write(*, *) hadv(iq), vadv(iq), tnom(iq)         write(*, *) hadv(iq), vadv(iq), tnom(iq)
136      end do      end do
137    
# Line 143  contains Line 139  contains
139      ! détemine le nom long :      ! détemine le nom long :
140      iiq=0      iiq=0
141      ii=0      ii=0
142      do iq=1, nq_local      do iq=1, nqmx
143         iiq=iiq+1         iiq=iiq+1
144         if (hadv(iq) /= vadv(iq)) then         if (hadv(iq) /= vadv(iq)) then
145            if (hadv(iq) == 10.and.vadv(iq) == 16) then            if (hadv(iq) == 10.and.vadv(iq) == 16) then
# Line 209  contains Line 205  contains
205            niadv(iiq)=iq            niadv(iiq)=iq
206         endif         endif
207      end do      end do
     if (present(nq)) nq = nq_local  
208    
209  999 format (i2, 1x, i2, 1x, a8)  999 format (i2, 1x, i2, 1x, a8)
210    

Legend:
Removed from v.18  
changed lines
  Added in v.23

  ViewVC Help
Powered by ViewVC 1.1.21