/[lmdze]/trunk/dyn3d/dynetat0.f
ViewVC logotype

Contents of /trunk/dyn3d/dynetat0.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 259 - (show annotations)
Tue Mar 6 16:19:52 2018 UTC (6 years, 2 months ago) by guez
File size: 7099 byte(s)
Try to clarify the logic. Remove module ener. Move variables from
module ener to module dynetat0_m, where they are defined in program
gcm. In sortvarc, I do not see how ptot0 could be 0, discard this possibility.

Remove dummy argument resetvarc of procedure sortvarc. The difference
is that sortvarc is called by caldyn or caldyn0 so just do different
processing in caldyn and caldyn0 instead of inside sortvarc.

No need for variables ang, etot, ptot, rmsdpdt, rmsv, stot, ztot to be
at module level in module sortvarc_m, downgrade them to arguments of
sortvarc. Instead of modyfying the meaning of ang, etot, ptot,
rmsdpdt, rmsv, stot, ztot from absolute quantities to variations of
these quantities, print the ratio in caldyn.

1 module dynetat0_m
2
3 use dimens_m, only: iim, jjm
4
5 IMPLICIT NONE
6
7 private iim, jjm
8
9 INTEGER day_ini
10 ! day number at the beginning of the run, based at value 1 on
11 ! January 1st of annee_ref
12
13 integer:: day_ref = 1 ! jour de l'ann\'ee de l'\'etat initial
14 ! (= 350 si 20 d\'ecembre par exemple)
15
16 integer:: annee_ref = 1998 ! Annee de l'etat initial (avec 4 chiffres)
17
18 REAL clon ! longitude of the center of the zoom, in rad
19 real clat ! latitude of the center of the zoom, in rad
20
21 real grossismx, grossismy
22 ! facteurs de grossissement du zoom, selon la longitude et la latitude
23 ! = 2 si 2 fois, = 3 si 3 fois, etc.
24
25 real dzoomx, dzoomy
26 ! extensions en longitude et latitude de la zone du zoom (fractions
27 ! de la zone totale)
28
29 real taux, tauy
30 ! raideur de la transition de l'int\'erieur \`a l'ext\'erieur du zoom
31
32 real rlatu(jjm + 1)
33 ! latitudes of points of the "scalar" and "u" grid, in rad
34
35 real rlatv(jjm)
36 ! latitudes of points of the "v" grid, in rad, in decreasing order
37
38 real rlonu(iim + 1) ! longitudes of points of the "u" grid, in rad
39
40 real rlonv(iim + 1)
41 ! longitudes of points of the "scalar" and "v" grid, in rad
42
43 real xprimu(iim + 1), xprimv(iim + 1)
44 ! 2 pi / iim * (derivative of the longitudinal zoom function)(rlon[uv])
45
46 REAL xprimm025(iim + 1), xprimp025(iim + 1)
47 REAL rlatu1(jjm), rlatu2(jjm), yprimu1(jjm), yprimu2(jjm)
48 REAL ang0, etot0, ptot0, ztot0, stot0
49
50 save
51
52 contains
53
54 SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis)
55
56 ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30
57 ! Authors: P. Le Van, L. Fairhead
58 ! This procedure reads the initial state of the atmosphere.
59
60 use comconst, only: dtvr
61 use conf_gcm_m, only: raz_date
62 use dimens_m, only: iim, jjm, llm, nqmx
63 use disvert_m, only: pa
64 use iniadvtrac_m, only: tname
65 use netcdf, only: NF90_NOWRITE, NF90_NOERR
66 use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, &
67 NF95_Gw_VAR
68 use nr_util, only: assert
69 use temps, only: itau_dyn
70 use unit_nml_m, only: unit_nml
71
72 REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)
73 REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
74 REAL, intent(out):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
75 REAL, intent(out):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
76 REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
77 REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa
78 REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
79
80 ! Local variables:
81 INTEGER iq
82 REAL, allocatable:: tab_cntrl(:) ! tableau des param\`etres du run
83 INTEGER ierr, ncid, varid
84
85 namelist /dynetat0_nml/ day_ref, annee_ref
86
87 !-----------------------------------------------------------------------
88
89 print *, "Call sequence information: dynetat0"
90
91 call assert((/size(ucov, 1), size(vcov, 1), size(masse, 1), size(ps, 1), &
92 size(phis, 1), size(q, 1), size(teta, 1)/) == iim + 1, "dynetat0 iim")
93 call assert((/size(ucov, 2), size(vcov, 2) + 1, size(masse, 2), &
94 size(ps, 2), size(phis, 2), size(q, 2), size(teta, 2)/) == jjm + 1, &
95 "dynetat0 jjm")
96 call assert((/size(vcov, 3), size(ucov, 3), size(teta, 3), size(q, 3), &
97 size(masse, 3)/) == llm, "dynetat0 llm")
98 call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")
99
100 ! Fichier \'etat initial :
101 call nf95_open("start.nc", NF90_NOWRITE, ncid)
102
103 call nf95_inq_varid(ncid, "controle", varid)
104 call NF95_Gw_VAR(ncid, varid, tab_cntrl)
105
106 call assert(int(tab_cntrl(1)) == iim, "dynetat0 tab_cntrl iim")
107 call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")
108 call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")
109
110 IF (dtvr /= tab_cntrl(12)) THEN
111 print *, 'Warning: the time steps from day_step and "start.nc" ' // &
112 'are different.'
113 print *, 'dtvr from day_step: ', dtvr
114 print *, 'dtvr from "start.nc": ', tab_cntrl(12)
115 print *, 'Using the value from day_step.'
116 ENDIF
117
118 etot0 = tab_cntrl(13)
119 ptot0 = tab_cntrl(14)
120 ztot0 = tab_cntrl(15)
121 stot0 = tab_cntrl(16)
122 ang0 = tab_cntrl(17)
123 pa = tab_cntrl(18)
124
125 clon = tab_cntrl(20)
126 clat = tab_cntrl(21)
127 grossismx = tab_cntrl(22)
128 grossismy = tab_cntrl(23)
129 dzoomx = tab_cntrl(25)
130 dzoomy = tab_cntrl(26)
131 taux = tab_cntrl(28)
132 tauy = tab_cntrl(29)
133
134 print *, "Enter namelist 'dynetat0_nml'."
135 read(unit=*, nml=dynetat0_nml)
136 write(unit_nml, nml=dynetat0_nml)
137
138 if (raz_date) then
139 print *, 'Resetting the date, using the namelist.'
140 day_ini = day_ref
141 itau_dyn = 0
142 else
143 day_ref = tab_cntrl(4)
144 annee_ref = tab_cntrl(5)
145 itau_dyn = tab_cntrl(31)
146 day_ini = tab_cntrl(30)
147 end if
148
149 print *, "day_ini = ", day_ini
150
151 call NF95_INQ_VARID (ncid, "rlonu", varid)
152 call NF95_GET_VAR(ncid, varid, rlonu)
153
154 call NF95_INQ_VARID (ncid, "rlatu", varid)
155 call NF95_GET_VAR(ncid, varid, rlatu)
156
157 call NF95_INQ_VARID (ncid, "rlonv", varid)
158 call NF95_GET_VAR(ncid, varid, rlonv)
159
160 call NF95_INQ_VARID (ncid, "rlatv", varid)
161 call NF95_GET_VAR(ncid, varid, rlatv)
162
163 CALL nf95_inq_varid(ncid, 'xprimu', varid)
164 CALL nf95_get_var(ncid, varid, xprimu)
165
166 CALL nf95_inq_varid(ncid, 'xprimv', varid)
167 CALL nf95_get_var(ncid, varid, xprimv)
168
169 CALL nf95_inq_varid(ncid, 'xprimm025', varid)
170 CALL nf95_get_var(ncid, varid, xprimm025)
171
172 CALL nf95_inq_varid(ncid, 'xprimp025', varid)
173 CALL nf95_get_var(ncid, varid, xprimp025)
174
175 call NF95_INQ_VARID (ncid, "rlatu1", varid)
176 call NF95_GET_VAR(ncid, varid, rlatu1)
177
178 call NF95_INQ_VARID (ncid, "rlatu2", varid)
179 call NF95_GET_VAR(ncid, varid, rlatu2)
180
181 CALL nf95_inq_varid(ncid, 'yprimu1', varid)
182 CALL nf95_get_var(ncid, varid, yprimu1)
183
184 CALL nf95_inq_varid(ncid, 'yprimu2', varid)
185 CALL nf95_get_var(ncid, varid, yprimu2)
186
187 call NF95_INQ_VARID (ncid, "phis", varid)
188 call NF95_GET_VAR(ncid, varid, phis)
189
190 call NF95_INQ_VARID (ncid, "ucov", varid)
191 call NF95_GET_VAR(ncid, varid, ucov)
192
193 call NF95_INQ_VARID (ncid, "vcov", varid)
194 call NF95_GET_VAR(ncid, varid, vcov)
195
196 call NF95_INQ_VARID (ncid, "teta", varid)
197 call NF95_GET_VAR(ncid, varid, teta)
198
199 DO iq = 1, nqmx
200 call NF95_INQ_VARID(ncid, tname(iq), varid, ierr)
201 IF (ierr == NF90_NOERR) THEN
202 call NF95_GET_VAR(ncid, varid, q(:, :, :, iq))
203 ELSE
204 PRINT *, 'dynetat0: "' // tname(iq) // '" not found, ' // &
205 "setting it to zero..."
206 q(:, :, :, iq) = 0.
207 ENDIF
208 ENDDO
209
210 call NF95_INQ_VARID (ncid, "masse", varid)
211 call NF95_GET_VAR(ncid, varid, masse)
212
213 call NF95_INQ_VARID (ncid, "ps", varid)
214 call NF95_GET_VAR(ncid, varid, ps)
215 ! Check that there is a single value at each pole:
216 call assert(ps(1, 1) == ps(2:, 1), "dynetat0 ps north pole")
217 call assert(ps(1, jjm + 1) == ps(2:, jjm + 1), "dynetat0 ps south pole")
218
219 call NF95_CLOSE(ncid)
220
221 END SUBROUTINE dynetat0
222
223 end module dynetat0_m

  ViewVC Help
Powered by ViewVC 1.1.21