/[lmdze]/trunk/dyn3d/infotrac_init.f90
ViewVC logotype

Diff of /trunk/dyn3d/infotrac_init.f90

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

trunk/Sources/dyn3d/iniadvtrac.f revision 178 by guez, Fri Mar 11 18:47:26 2016 UTC trunk/dyn3d/infotrac_init.f revision 321 by guez, Tue Dec 11 22:48:09 2018 UTC
# Line 1  Line 1 
1  module iniadvtrac_m  module infotrac_init_m
2    
3    ! From advtrac.h, version 1.1.1.1 2004/05/19 12:53:06    ! From advtrac.h, version 1.1.1.1 2004/05/19 12:53:06
4    
# Line 6  module iniadvtrac_m Line 6  module iniadvtrac_m
6    ! iq = 2 pour l'eau liquide    ! iq = 2 pour l'eau liquide
7    ! et \'eventuellement iq = 3, ..., nqmx pour les autres traceurs    ! et \'eventuellement iq = 3, ..., nqmx pour les autres traceurs
8    
9    use dimens_m, only: nqmx    use dimensions, only: nqmx
10    
11    implicit none    implicit none
12    
13    private nqmx    private nqmx
14    
15    INTEGER iadv(nqmx) ! indice du sch\'ema d'advection pour l'eau et les traceurs    INTEGER, protected:: iadv(nqmx)
16      ! indice du sch\'ema d'advection pour l'eau et les traceurs
17    
18    character(len=10) tname(nqmx)    character(len = 10), protected:: tname(nqmx)
19    ! nom du traceur pour fichiers restart et historiques    ! nom du traceur pour fichiers restart et historiques
20    
21    character(len=13) ttext(nqmx) ! nom long du traceur pour sorties    character(len = 13), protected:: ttext(nqmx)
22      ! nom long du traceur pour sorties
23    
24  contains  contains
25    
26    subroutine iniadvtrac    subroutine infotrac_init
27    
28      ! 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
29    
# Line 35  contains Line 37  contains
37      use jumble, only: new_unit      use jumble, only: new_unit
38    
39      ! Local:      ! Local:
40      character(len=3) descrq(0:14)      character(len = 3) descrq(0:14)
41      integer iq, iostat, nq_local, unit      integer iq, iostat, nq_local, unit
42    
43      integer, parameter:: allowed_adv(5) = (/0, 10, 12, 13, 14/)      integer, parameter:: allowed_adv(5) = (/0, 10, 12, 13, 14/)
# Line 47  contains Line 49  contains
49    
50      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
51    
52      print *, "Call sequence information: iniadvtrac"      print *, "Call sequence information: infotrac_init"
53    
54      ! Initializations:      ! Initializations:
55      descrq(0)=''      descrq(0) = ''
56      descrq(10)='VL1'      descrq(10) = 'VL1'
57      descrq(12)='FH1'      descrq(12) = 'FH1'
58      descrq(13)='FH2'      descrq(13) = 'FH2'
59      descrq(14)='VLH'      descrq(14) = 'VLH'
60    
61      ! Choix du sch\'ema pour l'advection dans fichier "traceur.def"      ! Choix du sch\'ema pour l'advection dans fichier "traceur.def"
62      call new_unit(unit)      call new_unit(unit)
63      open(unit, file='traceur.def', status='old', action="read", &      open(unit, file = 'traceur.def', status = 'old', action = "read", &
64           position="rewind", iostat=iostat)           position = "rewind", iostat = iostat)
65      if (iostat == 0) then      if (iostat == 0) then
66         print *, 'Ouverture de "traceur.def" ok'         print *, 'Ouverture de "traceur.def" ok'
67         read(unit, fmt=*) nq_local         read(unit, fmt = *) nq_local
68         print *, 'nombre de traceurs ', nq_local         print *, 'nombre de traceurs ', nq_local
69         call assert(nq_local == nqmx, "iniadvtrac nq_local")         call assert(nq_local == nqmx, "infotrac_init nq_local")
70    
71         do iq=1, nqmx         do iq = 1, nqmx
72            read(unit, fmt=*) iadv(iq), tname(iq)            read(unit, fmt = *) iadv(iq), tname(iq)
73            if (.not. any(iadv(iq) == allowed_adv)) then            if (.not. any(iadv(iq) == allowed_adv)) then
74               print *, "bad number for advection scheme"               print *, "bad number for advection scheme"
75               stop 1               stop 1
# Line 77  contains Line 79  contains
79      else      else
80         print *, 'Could not open "traceur.def".'         print *, 'Could not open "traceur.def".'
81         print *, 'Using default values.'         print *, 'Using default values.'
82         call assert(nqmx == 4, "iniadvtrac nqmx")         call assert(nqmx == 4, "infotrac_init nqmx")
83         iadv(:4) = (/14, 10, 10, 10/)         iadv(:4) = (/14, 10, 10, 10/)
84         tname(1) = 'H2Ov'         tname(1) = 'H2Ov'
85         tname(2) = 'H2Ol'         tname(2) = 'H2Ol'
# Line 91  contains Line 93  contains
93      ! \`A partir du nom court du traceur et du sch\'ema d'advection, on      ! \`A partir du nom court du traceur et du sch\'ema d'advection, on
94      ! d\'etermine le nom long :      ! d\'etermine le nom long :
95      do iq = 1, nqmx      do iq = 1, nqmx
96         ttext(iq)=trim(tname(iq)) // descrq(iadv(iq))         ttext(iq) = trim(tname(iq)) // descrq(iadv(iq))
97      end do      end do
98    
99    END subroutine iniadvtrac    END subroutine infotrac_init
100    
101  end module iniadvtrac_m  end module infotrac_init_m

Legend:
Removed from v.178  
changed lines
  Added in v.321

  ViewVC Help
Powered by ViewVC 1.1.21