/[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 3 by guez, Wed Feb 27 13:16:39 2008 UTC revision 5 by guez, Mon Mar 3 16:32:04 2008 UTC
# 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):: nq      integer, intent(out), optional:: nq
31    
32      ! Variables local to the procedure:      ! Variables local to the procedure:
33    
# Line 36  contains Line 36  contains
36      character(len=2) txtp(9)      character(len=2) txtp(9)
37      character(len=13) str1, str2      character(len=13) str1, str2
38    
39      integer iq, iiq, iiiq, ierr, ii      integer iq, iiq, iiiq, ierr, ii, nq_local
40    
41      data txtp/'x', 'y', 'z', 'xx', 'xy', 'xz', 'yy', 'yz', 'zz'/      data txtp/'x', 'y', 'z', 'xx', 'xy', 'xz', 'yy', 'yz', 'zz'/
42    
# Line 101  contains Line 101  contains
101           iostat=ierr)           iostat=ierr)
102      if (ierr == 0) then      if (ierr == 0) then
103         print *, 'Ouverture de "traceur.def" ok'         print *, 'Ouverture de "traceur.def" ok'
104         read(unit=90, fmt=*) nq         read(unit=90, fmt=*) nq_local
105         print *, 'nombre de traceurs ', nq         print *, 'nombre de traceurs ', nq_local
106         if (nq > nqmx) then         if (nq_local > nqmx) then
107            print *, 'nombre de traceurs trop important'            print *, 'nombre de traceurs trop important'
108            print *, 'verifier traceur.def'            print *, 'verifier traceur.def'
109            stop            stop
110         endif         endif
111    
112         do iq=1, nq         do iq=1, nq_local
113            read(90, 999) hadv(iq), vadv(iq), tnom(iq)            read(90, 999) hadv(iq), vadv(iq), tnom(iq)
114         end do         end do
115         close(90)           close(90)  
116         PRINT *, 'lecture de traceur.def :'           PRINT *, 'lecture de traceur.def :'  
117         do iq=1, nq         do iq=1, nq_local
118            write(*, *) hadv(iq), vadv(iq), tnom(iq)            write(*, *) hadv(iq), vadv(iq), tnom(iq)
119         end do         end do
120      else      else
121         print *, 'problème ouverture traceur.def'         print *, 'Problème à l''ouverture de "traceur.def"'
122         print *, 'ATTENTION on prend des valeurs par défaut'         print *, 'Attention : on prend des valeurs par défaut.'
123         nq = 4         nq_local = 4
124         hadv(1) = 14         hadv(1) = 14
125         vadv(1) = 14         vadv(1) = 14
126         tnom(1) = 'H2Ov'         tnom(1) = 'H2Ov'
# Line 135  contains Line 135  contains
135         tnom(4) = 'PB'         tnom(4) = 'PB'
136      ENDIF      ENDIF
137      PRINT *, 'Valeur de traceur.def :'      PRINT *, 'Valeur de traceur.def :'
138      do iq=1, nq      do iq=1, nq_local
139         write(*, *) hadv(iq), vadv(iq), tnom(iq)         write(*, *) hadv(iq), vadv(iq), tnom(iq)
140      end do      end do
141    
# Line 143  contains Line 143  contains
143      ! détemine le nom long :      ! détemine le nom long :
144      iiq=0      iiq=0
145      ii=0      ii=0
146      do iq=1, nq      do iq=1, nq_local
147         iiq=iiq+1         iiq=iiq+1
148         if (hadv(iq) /= vadv(iq)) then         if (hadv(iq) /= vadv(iq)) then
149            if (hadv(iq) == 10.and.vadv(iq) == 16) then            if (hadv(iq) == 10.and.vadv(iq) == 16) then
# Line 209  contains Line 209  contains
209            niadv(iiq)=iq            niadv(iiq)=iq
210         endif         endif
211      end do      end do
212        if (present(nq)) nq = nq_local
213    
214  999 format (i2, 1x, i2, 1x, a8)  999 format (i2, 1x, i2, 1x, a8)
215    

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

  ViewVC Help
Powered by ViewVC 1.1.21