/[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 134 by guez, Wed Apr 29 15:47:56 2015 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    
5    ! iq = 1 pour l'eau vapeur    ! iq = 1 pour l'eau vapeur
6    ! iq = 2 pour l'eau liquide    ! iq = 2 pour l'eau liquide
7    ! et éventuellement 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éma d'advection pour l'eau et les traceurs    INTEGER, protected:: iadv(nqmx)
16    ! 11 means Van-Leer scheme for hadv et monotonous PPM for vadv    ! indice du sch\'ema d'advection pour l'eau et les traceurs
17    
18    integer, parameter:: allowed_adv(10) = (/0, 1, 2, 10, 12, 13, 14, 16, 17, 18/)    character(len = 10), protected:: tname(nqmx)
   ! Allowed values for hadv and vadv:  
   ! 1: schema transport type "humidite specifique LMD"  
   ! 2: schema amont  
   ! 10: schema Van-leer (retenu pour l'eau vapeur et liquide)  
   ! 12: schema Frederic Hourdin I  
   ! 13: schema Frederic Hourdin II  
   ! 14: schema Van-leer + humidite specifique  
   ! 16: schema PPM Monotone(Collela & Woodward 1984)  
   ! 17: schema PPM Semi Monotone (overshoots autorisés)  
   ! 18: schema PPM Positif Defini (overshoots undershoots autorisés)  
   ! Pour Van-Leer plus vapeur d'eau saturée : iadv(1)=4  
   
   INTEGER hadv(nqmx) ! indice schéma transport horizontal  
   INTEGER vadv(nqmx) ! indice schéma transport vertical  
   
   character(len=10) 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 46  contains Line 31  contains
31      ! F. Forget, M.-A. Filiberti      ! F. Forget, M.-A. Filiberti
32    
33      ! Initialisation des traceurs      ! Initialisation des traceurs
34      ! Choix du schéma pour l'advection dans le fichier "traceur.def"      ! Choix du sch\'ema pour l'advection dans le fichier "traceur.def"
35    
36      use nr_util, only: assert      use nr_util, only: assert
37      use jumble, only: new_unit      use jumble, only: new_unit
38    
39      ! Variables local to the procedure:      ! Local:
40        character(len = 3) descrq(0:14)
     character(len=3) descrq(18)  
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/)
44        ! Allowed values for iadv:
45        ! 10: schema Van-leer (retenu pour l'eau vapeur et liquide)
46        ! 12: schema Frederic Hourdin I
47        ! 13: schema Frederic Hourdin II
48        ! 14: schema Van-leer + humidite specifique
49    
50      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
51    
52      print *, "Call sequence information: iniadvtrac"      print *, "Call sequence information: infotrac_init"
53    
54      ! Initializations:      ! Initializations:
55      descrq(10)='VL1'      descrq(0) = ''
56      descrq(11)='VLP'      descrq(10) = 'VL1'
57      descrq(12)='FH1'      descrq(12) = 'FH1'
58      descrq(13)='FH2'      descrq(13) = 'FH2'
59      descrq(14)='VLH'      descrq(14) = 'VLH'
     descrq(16)='PPM'  
     descrq(17)='PPS'  
     descrq(18)='PPP'  
60    
61      ! Choix du schéma 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=*) hadv(iq), vadv(iq), tname(iq)            read(unit, fmt = *) iadv(iq), tname(iq)
73            if (.not. any(hadv(iq) == allowed_adv) &            if (.not. any(iadv(iq) == allowed_adv)) then
                .or. .not. any(vadv(iq) == allowed_adv)) then  
74               print *, "bad number for advection scheme"               print *, "bad number for advection scheme"
75               stop 1               stop 1
76            end if            end if
77         end do         end do
78         close(unit)         close(unit)
79      else      else
80         print *, 'Problème à l''ouverture de "traceur.def"'         print *, 'Could not open "traceur.def".'
81         print *, 'Attention : on prend des valeurs par défaut.'         print *, 'Using default values.'
82         call assert(nqmx == 4, "iniadvtrac nqmx")         call assert(nqmx == 4, "infotrac_init nqmx")
83         hadv(:4) = (/14, 10, 10, 10/)         iadv(:4) = (/14, 10, 10, 10/)
        vadv(:4) = hadv(:4)  
84         tname(1) = 'H2Ov'         tname(1) = 'H2Ov'
85         tname(2) = 'H2Ol'         tname(2) = 'H2Ol'
86         tname(3) = 'RN'         tname(3) = 'RN'
87         tname(4) = 'PB'         tname(4) = 'PB'
88         do iq = 1, nqmx         do iq = 1, nqmx
89            print *, hadv(iq), vadv(iq), tname(iq)            print *, iadv(iq), tname(iq)
90         end do         end do
91      ENDIF      ENDIF
92    
93      ! À partir du nom court du traceur et du schéma d'advection, on      ! \`A partir du nom court du traceur et du sch\'ema d'advection, on
94      ! détermine le nom long :      ! d\'etermine le nom long :
95      do iq = 1, nqmx      do iq = 1, nqmx
96         if (hadv(iq) /= vadv(iq)) then         ttext(iq) = trim(tname(iq)) // descrq(iadv(iq))
           if (hadv(iq) == 10 .and. vadv(iq) == 16) then  
              iadv(iq) = 11  
           else  
              print *, "Bad combination for hozizontal and vertical schemes."  
              stop 1  
           endif  
        else  
           iadv(iq) = hadv(iq)  
        endif  
   
        IF (iadv(iq) == 0) THEN  
           ttext(iq) = tname(iq)  
        ELSE  
           ttext(iq)=trim(tname(iq)) // descrq(iadv(iq))  
        endif  
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.134  
changed lines
  Added in v.321

  ViewVC Help
Powered by ViewVC 1.1.21