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

Contents of /trunk/dyn3d/dynetat0.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 154 - (show annotations)
Tue Jul 7 17:49:23 2015 UTC (8 years, 10 months ago) by guez
Original Path: trunk/Sources/dyn3d/dynetat0.f
File size: 7171 byte(s)
Removed argument dtphys of physiq. Use it directly from comconst in
physiq instead.

Donwgraded variables eignfnu, eignfnv of module inifgn_m to dummy
arguments of SUBROUTINE inifgn. They were not used elsewhere than in
the calling procedure inifilr. Renamed argument dv of inifgn to eignval_v.

Made alboc and alboc_cd independent of the size of arguments. Now we
can call them only at indices knindex in interfsurf_hq, where we need
them. Fixed a bug in alboc_cd: rmu0 was modified, and the
corresponding actual argument in interfsurf_hq is an intent(in)
argument of interfsurf_hq.

Variables of size knon instead of klon in interfsur_lim and interfsurf_hq.

Removed argument alb_new of interfsurf_hq because it was the same than
alblw. Simplified test on cycle_diurne, following LMDZ.

Moved tests on nbapp_rad from physiq to read_clesphys2. No need for
separate counter itaprad, we can use itap. Define lmt_pas and radpas
from integer input parameters instead of real-type computed values.

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 ! xprim[uv] = 2 pi / iim * (derivative of the longitudinal zoom
45 ! function)(rlon[uv])
46
47 REAL xprimm025(iim + 1), xprimp025(iim + 1)
48 REAL rlatu1(jjm), rlatu2(jjm), yprimu1(jjm), yprimu2(jjm)
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 ener, only: etot0, ang0, ptot0, stot0, ztot0
65 use iniadvtrac_m, only: tname
66 use netcdf, only: NF90_NOWRITE, NF90_NOERR
67 use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, &
68 NF95_Gw_VAR
69 use nr_util, only: assert
70 use temps, only: itau_dyn
71 use unit_nml_m, only: unit_nml
72
73 REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)
74 REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
75 REAL, intent(out):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
76 REAL, intent(out):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
77 REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
78 REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa
79 REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
80
81 ! Local variables:
82 INTEGER iq
83 REAL, pointer:: tab_cntrl(:) ! tableau des param\`etres du run
84 INTEGER ierr, ncid, varid
85
86 namelist /dynetat0_nml/ day_ref, annee_ref
87
88 !-----------------------------------------------------------------------
89
90 print *, "Call sequence information: dynetat0"
91
92 call assert((/size(ucov, 1), size(vcov, 1), size(masse, 1), size(ps, 1), &
93 size(phis, 1), size(q, 1), size(teta, 1)/) == iim + 1, "dynetat0 iim")
94 call assert((/size(ucov, 2), size(vcov, 2) + 1, size(masse, 2), &
95 size(ps, 2), size(phis, 2), size(q, 2), size(teta, 2)/) == jjm + 1, &
96 "dynetat0 jjm")
97 call assert((/size(vcov, 3), size(ucov, 3), size(teta, 3), size(q, 3), &
98 size(masse, 3)/) == llm, "dynetat0 llm")
99 call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")
100
101 ! Fichier \'etat initial :
102 call nf95_open("start.nc", NF90_NOWRITE, ncid)
103
104 call nf95_inq_varid(ncid, "controle", varid)
105 call NF95_Gw_VAR(ncid, varid, tab_cntrl)
106
107 call assert(int(tab_cntrl(1)) == iim, "dynetat0 tab_cntrl iim")
108 call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")
109 call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")
110
111 IF (dtvr /= tab_cntrl(12)) THEN
112 print *, 'Warning: the time steps from day_step and "start.nc" ' // &
113 'are different.'
114 print *, 'dtvr from day_step: ', dtvr
115 print *, 'dtvr from "start.nc": ', tab_cntrl(12)
116 print *, 'Using the value from day_step.'
117 ENDIF
118
119 etot0 = tab_cntrl(13)
120 ptot0 = tab_cntrl(14)
121 ztot0 = tab_cntrl(15)
122 stot0 = tab_cntrl(16)
123 ang0 = tab_cntrl(17)
124 pa = tab_cntrl(18)
125
126 clon = tab_cntrl(20)
127 clat = tab_cntrl(21)
128 grossismx = tab_cntrl(22)
129 grossismy = tab_cntrl(23)
130 dzoomx = tab_cntrl(25)
131 dzoomy = tab_cntrl(26)
132 taux = tab_cntrl(28)
133 tauy = tab_cntrl(29)
134
135 print *, "Enter namelist 'dynetat0_nml'."
136 read(unit=*, nml=dynetat0_nml)
137 write(unit_nml, nml=dynetat0_nml)
138
139 if (raz_date) then
140 print *, 'Resetting the date, using the namelist.'
141 day_ini = day_ref
142 itau_dyn = 0
143 else
144 day_ref = tab_cntrl(4)
145 annee_ref = tab_cntrl(5)
146 itau_dyn = tab_cntrl(31)
147 day_ini = tab_cntrl(30)
148 end if
149
150 print *, "day_ini = ", day_ini
151
152 deallocate(tab_cntrl) ! pointer
153
154 call NF95_INQ_VARID (ncid, "rlonu", varid)
155 call NF95_GET_VAR(ncid, varid, rlonu)
156
157 call NF95_INQ_VARID (ncid, "rlatu", varid)
158 call NF95_GET_VAR(ncid, varid, rlatu)
159
160 call NF95_INQ_VARID (ncid, "rlonv", varid)
161 call NF95_GET_VAR(ncid, varid, rlonv)
162
163 call NF95_INQ_VARID (ncid, "rlatv", varid)
164 call NF95_GET_VAR(ncid, varid, rlatv)
165
166 CALL nf95_inq_varid(ncid, 'xprimu', varid)
167 CALL nf95_get_var(ncid, varid, xprimu)
168
169 CALL nf95_inq_varid(ncid, 'xprimv', varid)
170 CALL nf95_get_var(ncid, varid, xprimv)
171
172 CALL nf95_inq_varid(ncid, 'xprimm025', varid)
173 CALL nf95_get_var(ncid, varid, xprimm025)
174
175 CALL nf95_inq_varid(ncid, 'xprimp025', varid)
176 CALL nf95_get_var(ncid, varid, xprimp025)
177
178 call NF95_INQ_VARID (ncid, "rlatu1", varid)
179 call NF95_GET_VAR(ncid, varid, rlatu1)
180
181 call NF95_INQ_VARID (ncid, "rlatu2", varid)
182 call NF95_GET_VAR(ncid, varid, rlatu2)
183
184 CALL nf95_inq_varid(ncid, 'yprimu1', varid)
185 CALL nf95_get_var(ncid, varid, yprimu1)
186
187 CALL nf95_inq_varid(ncid, 'yprimu2', varid)
188 CALL nf95_get_var(ncid, varid, yprimu2)
189
190 call NF95_INQ_VARID (ncid, "phisinit", varid)
191 call NF95_GET_VAR(ncid, varid, phis)
192
193 call NF95_INQ_VARID (ncid, "ucov", varid)
194 call NF95_GET_VAR(ncid, varid, ucov)
195
196 call NF95_INQ_VARID (ncid, "vcov", varid)
197 call NF95_GET_VAR(ncid, varid, vcov)
198
199 call NF95_INQ_VARID (ncid, "teta", varid)
200 call NF95_GET_VAR(ncid, varid, teta)
201
202 DO iq = 1, nqmx
203 call NF95_INQ_VARID(ncid, tname(iq), varid, ierr)
204 IF (ierr /= NF90_NOERR) THEN
205 PRINT *, 'dynetat0: "' // tname(iq) // '" not found, ' // &
206 "setting it to zero..."
207 q(:, :, :, iq) = 0.
208 ELSE
209 call NF95_GET_VAR(ncid, varid, q(:, :, :, iq))
210 ENDIF
211 ENDDO
212
213 call NF95_INQ_VARID (ncid, "masse", varid)
214 call NF95_GET_VAR(ncid, varid, masse)
215
216 call NF95_INQ_VARID (ncid, "ps", varid)
217 call NF95_GET_VAR(ncid, varid, ps)
218 ! Check that there is a single value at each pole:
219 call assert(ps(1, 1) == ps(2:, 1), "dynetat0 ps north pole")
220 call assert(ps(1, jjm + 1) == ps(2:, jjm + 1), "dynetat0 ps south pole")
221
222 call NF95_CLOSE(ncid)
223
224 END SUBROUTINE dynetat0
225
226 end module dynetat0_m

  ViewVC Help
Powered by ViewVC 1.1.21