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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 62 - (show annotations)
Thu Jul 26 14:37:37 2012 UTC (11 years, 9 months ago) by guez
File size: 4012 byte(s)
Changed handling of compiler in compilation system.

Removed the prefix letters "y", "p", "t" or "z" in some names of variables.

Replaced calls to NetCDF by calls to NetCDF95.

Extracted "ioget_calendar" procedures from "calendar.f90" into a
separate file.

Extracted to a separate file, "mathop2.f90", procedures that were not
part of the generic interface "mathop" in "mathop.f90".

Removed computation of "dq" in "bilan_dyn", which was not used.

In "iniadvtrac", removed schemes 20 Slopes and 30 Prather. Was not
compatible with declarations of array sizes.

In "clcdrag", "ustarhb", "vdif_kcay", "yamada4" and "coefkz", changed
the size of some arrays from "klon" to "knon".

Removed possible call to "conema3" in "physiq".

Removed unused argument "cd" in "yamada".

1 module iniadvtrac_m
2
3 ! From advtrac.h, version 1.1.1.1 2004/05/19 12:53:06
4
5 ! iq = 1 pour l'eau vapeur
6 ! iq = 2 pour l'eau liquide
7 ! Et éventuellement iq = 3, nqmx pour les autres traceurs
8
9 use dimens_m, only: nqmx
10
11 implicit none
12
13 private nqmx
14
15 INTEGER iadv(nqmx) ! indice schéma d'advection pour l'eau et les traceurs
16 ! 11 means schema Van-Leer pour hadv et version PPM (Monotone) pour vadv
17
18 integer, parameter:: allowed_adv(10) = (/0, 1, 2, 10, 12, 13, 14, 16, 17, 18/)
19 ! Allowed values for hadv and vadv:
20 ! 1: schema transport type "humidite specifique LMD"
21 ! 2: schema amont
22 ! 10: schema Van-leer (retenu pour l'eau vapeur et liquide)
23 ! 12: schema Frederic Hourdin I
24 ! 13: schema Frederic Hourdin II
25 ! 14: schema Van-leer + humidite specifique
26 ! 16: schema PPM Monotone(Collela & Woodward 1984)
27 ! 17: schema PPM Semi Monotone (overshoots autorisés)
28 ! 18: schema PPM Positif Defini (overshoots undershoots autorisés)
29 ! Pour Van-Leer plus vapeur d'eau saturée : iadv(1)=4
30
31 INTEGER hadv(nqmx) ! indice schéma transport horizontal
32 INTEGER vadv(nqmx) ! indice schéma transport vertical
33 INTEGER niadv(nqmx) ! équivalent dynamique / physique
34 character(len=8) tnom(nqmx) ! nom court du traceur
35 character(len=10) tname(nqmx) ! nom du traceur pour restart
36 character(len=13) ttext(nqmx) ! nom long du traceur pour sorties
37
38 contains
39
40 subroutine iniadvtrac
41
42 ! From dyn3d/iniadvtrac.F, version 1.3 2005/04/13 08:58:34
43
44 ! Authors : P. Le Van, L. Fairhead, F. Hourdin, F. Codron,
45 ! F. Forget, M.-A. Filiberti
46
47 use nr_util, only: assert
48 use jumble, only: new_unit
49
50 ! Variables local to the procedure:
51
52 character(len=3) descrq(18)
53
54 integer iq, iostat, nq_local, unit
55
56 !-----------------------------------------------------------------------
57
58 print *, "Call sequence information: iniadvtrac"
59
60 ! Initializations:
61 descrq(10)='VL1'
62 descrq(11)='VLP'
63 descrq(12)='FH1'
64 descrq(13)='FH2'
65 descrq(14)='VLH'
66 descrq(16)='PPM'
67 descrq(17)='PPS'
68 descrq(18)='PPP'
69
70 ! Choix du schéma pour l'advection dans fichier "traceur.def"
71 call new_unit(unit)
72 open(unit, file='traceur.def', status='old', action="read", &
73 position="rewind", iostat=iostat)
74 if (iostat == 0) then
75 print *, 'Ouverture de "traceur.def" ok'
76 read(unit, fmt=*) nq_local
77 print *, 'nombre de traceurs ', nq_local
78 call assert(nq_local == nqmx, "iniadvtrac nq_local")
79
80 do iq=1, nqmx
81 read(unit, fmt=*) hadv(iq), vadv(iq), tnom(iq)
82 if (.not. any(hadv(iq) == allowed_adv) &
83 .or. .not. any(vadv(iq) == allowed_adv)) then
84 print *, "bad number for advection scheme"
85 stop 1
86 end if
87 end do
88 close(unit)
89 else
90 print *, 'Problème à l''ouverture de "traceur.def"'
91 print *, 'Attention : on prend des valeurs par défaut.'
92 call assert(nqmx == 4, "iniadvtrac nqmx")
93 hadv(1) = 14
94 vadv(1) = 14
95 tnom(1) = 'H2Ov'
96 hadv(2) = 10
97 vadv(2) = 10
98 tnom(2) = 'H2Ol'
99 hadv(3) = 10
100 vadv(3) = 10
101 tnom(3) = 'RN'
102 hadv(4) = 10
103 vadv(4) = 10
104 tnom(4) = 'PB'
105 do iq = 1, nqmx
106 print *, hadv(iq), vadv(iq), tnom(iq)
107 end do
108 ENDIF
109
110 tname = tnom
111
112 ! À partir du nom court du traceur et du schéma d'advection, on
113 ! détermine le nom long :
114 do iq=1, nqmx
115 if (hadv(iq) /= vadv(iq)) then
116 if (hadv(iq) == 10 .and. vadv(iq) == 16) then
117 iadv(iq)=11
118 else
119 print *, "Bad combination for hozizontal and vertical schemes."
120 stop 1
121 endif
122 else
123 iadv(iq)=hadv(iq)
124 endif
125
126 IF (iadv(iq) == 0) THEN
127 ttext(iq) = tnom(iq)
128 ELSE
129 ttext(iq)=trim(tnom(iq)) // descrq(iadv(iq))
130 endif
131 end do
132
133 forall (iq = 1: nqmx) niadv(iq)=iq
134
135 END subroutine iniadvtrac
136
137 end module iniadvtrac_m

  ViewVC Help
Powered by ViewVC 1.1.21