/[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

trunk/libf/dyn3d/advtrac_m.f90 revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC trunk/libf/dyn3d/iniadvtrac.f90 revision 38 by guez, Thu Jan 6 17:52:19 2011 UTC
# Line 1  Line 1 
1  module advtrac_m  module iniadvtrac_m
2    
3    ! From advtrac.h, v 1.1.1.1 2004/05/19 12:53:06    ! From advtrac.h, v 1.1.1.1 2004/05/19 12:53:06
4    
# Line 18  module advtrac_m Line 18  module advtrac_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 26  contains Line 26  contains
26      ! Modification spéciale traceur F. Forget 05/94      ! Modification spéciale traceur F. Forget 05/94
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        ! Pour Van-Leer plus vapeur d'eau saturée : iadv(1)=4
30        ! Pour Van-Leer : iadv=10
31    
32      integer, intent(out):: nq      use nr_util, only: assert
33    
34      ! Variables local to the procedure:      ! Variables local to the procedure:
35    
# Line 36  contains Line 38  contains
38      character(len=2) txtp(9)      character(len=2) txtp(9)
39      character(len=13) str1, str2      character(len=13) str1, str2
40    
41      integer iq, iiq, iiiq, ierr, ii      integer iq, iiq, iiiq, ierr, ii, nq_local
42    
43      data txtp/'x', 'y', 'z', 'xx', 'xy', 'xz', 'yy', 'yz', 'zz'/      data txtp/'x', 'y', 'z', 'xx', 'xy', 'xz', 'yy', 'yz', 'zz'/
44    
# Line 91  contains Line 93  contains
93         endif         endif
94         tnom(iq)=str1         tnom(iq)=str1
95         tname(iq)=tnom(iq)         tname(iq)=tnom(iq)
96         str2=tnom(iq)         str2=tnom(iq)
97         ttext(iq) = trim(str2) // descrq(iadv(iq))         ttext(iq) = trim(str2) // descrq(iadv(iq))
98      end do      end do
99    
# Line 101  contains Line 103  contains
103           iostat=ierr)           iostat=ierr)
104      if (ierr == 0) then      if (ierr == 0) then
105         print *, 'Ouverture de "traceur.def" ok'         print *, 'Ouverture de "traceur.def" ok'
106         read(unit=90, fmt=*) nq         read(unit=90, fmt=*) nq_local
107         print *, 'nombre de traceurs ', nq         print *, 'nombre de traceurs ', nq_local
108         if (nq > nqmx) then         call assert(nq_local == nqmx, "iniadvtrac nq_local")
           print *, 'nombre de traceurs trop important'  
           print *, 'verifier traceur.def'  
           stop  
        endif  
109    
110         do iq=1, nq         do iq=1, nqmx
111            read(90, 999) hadv(iq), vadv(iq), tnom(iq)            read(90, 999) hadv(iq), vadv(iq), tnom(iq)
112         end do         end do
113         close(90)           close(90)  
114         PRINT *, 'lecture de traceur.def :'           PRINT *, 'lecture de traceur.def :'  
115         do iq=1, nq         do iq=1, nqmx
116            write(*, *) hadv(iq), vadv(iq), tnom(iq)            write(*, *) hadv(iq), vadv(iq), tnom(iq)
117         end do         end do
118      else      else
119         print *, 'problème ouverture traceur.def'         print *, 'Problème à l''ouverture de "traceur.def"'
120         print *, 'ATTENTION on prend des valeurs par défaut'         print *, 'Attention : on prend des valeurs par défaut.'
121         nq = 4         call assert(nqmx == 4, "iniadvtrac nqmx")
122         hadv(1) = 14         hadv(1) = 14
123         vadv(1) = 14         vadv(1) = 14
124         tnom(1) = 'H2Ov'         tnom(1) = 'H2Ov'
# Line 135  contains Line 133  contains
133         tnom(4) = 'PB'         tnom(4) = 'PB'
134      ENDIF      ENDIF
135      PRINT *, 'Valeur de traceur.def :'      PRINT *, 'Valeur de traceur.def :'
136      do iq=1, nq      do iq=1, nqmx
137         write(*, *) hadv(iq), vadv(iq), tnom(iq)         write(*, *) hadv(iq), vadv(iq), tnom(iq)
138      end do      end do
139    
# Line 143  contains Line 141  contains
141      ! détemine le nom long :      ! détemine le nom long :
142      iiq=0      iiq=0
143      ii=0      ii=0
144      do iq=1, nq      do iq=1, nqmx
145         iiq=iiq+1         iiq=iiq+1
146         if (hadv(iq) /= vadv(iq)) then         if (hadv(iq) /= vadv(iq)) then
147            if (hadv(iq) == 10.and.vadv(iq) == 16) then            if (hadv(iq) == 10.and.vadv(iq) == 16) then
# Line 214  contains Line 212  contains
212    
213    END subroutine iniadvtrac    END subroutine iniadvtrac
214    
215  end module advtrac_m  end module iniadvtrac_m

Legend:
Removed from v.3  
changed lines
  Added in v.38

  ViewVC Help
Powered by ViewVC 1.1.21