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

Annotation of /trunk/dyn3d/dynetat0.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 154 - (hide 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 guez 3 module dynetat0_m
2    
3 guez 139 use dimens_m, only: iim, jjm
4    
5 guez 3 IMPLICIT NONE
6    
7 guez 139 private iim, jjm
8    
9 guez 129 INTEGER day_ini
10 guez 130 ! day number at the beginning of the run, based at value 1 on
11     ! January 1st of annee_ref
12 guez 25
13 guez 139 integer:: day_ref = 1 ! jour de l'ann\'ee de l'\'etat initial
14     ! (= 350 si 20 d\'ecembre par exemple)
15 guez 129
16     integer:: annee_ref = 1998 ! Annee de l'etat initial (avec 4 chiffres)
17    
18 guez 139 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 guez 151 ! raideur de la transition de l'int\'erieur \`a l'ext\'erieur du zoom
31 guez 139
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 guez 154 ! xprim[uv] = 2 pi / iim * (derivative of the longitudinal zoom
45     ! function)(rlon[uv])
46 guez 139
47     REAL xprimm025(iim + 1), xprimp025(iim + 1)
48     REAL rlatu1(jjm), rlatu2(jjm), yprimu1(jjm), yprimu2(jjm)
49    
50     save
51    
52 guez 3 contains
53    
54 guez 128 SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis)
55 guez 3
56 guez 38 ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30
57     ! Authors: P. Le Van, L. Fairhead
58 guez 39 ! This procedure reads the initial state of the atmosphere.
59 guez 3
60 guez 79 use comconst, only: dtvr
61 guez 129 use conf_gcm_m, only: raz_date
62 guez 38 use dimens_m, only: iim, jjm, llm, nqmx
63 guez 67 use disvert_m, only: pa
64 guez 3 use ener, only: etot0, ang0, ptot0, stot0, ztot0
65 guez 18 use iniadvtrac_m, only: tname
66 guez 67 use netcdf, only: NF90_NOWRITE, NF90_NOERR
67 guez 44 use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, &
68     NF95_Gw_VAR
69 guez 36 use nr_util, only: assert
70 guez 129 use temps, only: itau_dyn
71     use unit_nml_m, only: unit_nml
72 guez 3
73 guez 55 REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)
74     REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
75 guez 43 REAL, intent(out):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
76 guez 40 REAL, intent(out):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
77 guez 55 REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
78 guez 39 REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa
79     REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
80 guez 3
81 guez 44 ! Local variables:
82 guez 38 INTEGER iq
83 guez 139 REAL, pointer:: tab_cntrl(:) ! tableau des param\`etres du run
84 guez 38 INTEGER ierr, ncid, varid
85 guez 3
86 guez 129 namelist /dynetat0_nml/ day_ref, annee_ref
87    
88 guez 3 !-----------------------------------------------------------------------
89    
90     print *, "Call sequence information: dynetat0"
91    
92 guez 55 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 guez 40 call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")
100 guez 3
101 guez 139 ! Fichier \'etat initial :
102 guez 25 call nf95_open("start.nc", NF90_NOWRITE, ncid)
103 guez 3
104 guez 38 call nf95_inq_varid(ncid, "controle", varid)
105 guez 44 call NF95_Gw_VAR(ncid, varid, tab_cntrl)
106 guez 3
107 guez 79 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 guez 3
111 guez 79 IF (dtvr /= tab_cntrl(12)) THEN
112     print *, 'Warning: the time steps from day_step and "start.nc" ' // &
113 guez 129 'are different.'
114 guez 79 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 guez 38 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 guez 113
126 guez 38 clon = tab_cntrl(20)
127     clat = tab_cntrl(21)
128     grossismx = tab_cntrl(22)
129     grossismy = tab_cntrl(23)
130 guez 113 dzoomx = tab_cntrl(25)
131     dzoomy = tab_cntrl(26)
132     taux = tab_cntrl(28)
133     tauy = tab_cntrl(29)
134    
135 guez 129 print *, "Enter namelist 'dynetat0_nml'."
136     read(unit=*, nml=dynetat0_nml)
137     write(unit_nml, nml=dynetat0_nml)
138 guez 3
139 guez 129 if (raz_date) then
140 guez 139 print *, 'Resetting the date, using the namelist.'
141 guez 129 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 guez 38 call NF95_INQ_VARID (ncid, "rlonu", varid)
155     call NF95_GET_VAR(ncid, varid, rlonu)
156 guez 3
157 guez 38 call NF95_INQ_VARID (ncid, "rlatu", varid)
158     call NF95_GET_VAR(ncid, varid, rlatu)
159 guez 3
160 guez 38 call NF95_INQ_VARID (ncid, "rlonv", varid)
161     call NF95_GET_VAR(ncid, varid, rlonv)
162 guez 3
163 guez 38 call NF95_INQ_VARID (ncid, "rlatv", varid)
164     call NF95_GET_VAR(ncid, varid, rlatv)
165 guez 3
166 guez 139 CALL nf95_inq_varid(ncid, 'xprimu', varid)
167     CALL nf95_get_var(ncid, varid, xprimu)
168 guez 3
169 guez 139 CALL nf95_inq_varid(ncid, 'xprimv', varid)
170     CALL nf95_get_var(ncid, varid, xprimv)
171 guez 3
172 guez 139 CALL nf95_inq_varid(ncid, 'xprimm025', varid)
173     CALL nf95_get_var(ncid, varid, xprimm025)
174 guez 3
175 guez 139 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 guez 38 call NF95_INQ_VARID (ncid, "phisinit", varid)
191     call NF95_GET_VAR(ncid, varid, phis)
192 guez 3
193 guez 38 call NF95_INQ_VARID (ncid, "ucov", varid)
194 guez 55 call NF95_GET_VAR(ncid, varid, ucov)
195 guez 3
196 guez 38 call NF95_INQ_VARID (ncid, "vcov", varid)
197 guez 55 call NF95_GET_VAR(ncid, varid, vcov)
198 guez 3
199 guez 38 call NF95_INQ_VARID (ncid, "teta", varid)
200 guez 43 call NF95_GET_VAR(ncid, varid, teta)
201 guez 3
202     DO iq = 1, nqmx
203 guez 38 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 guez 40 q(:, :, :, iq) = 0.
208 guez 3 ELSE
209 guez 40 call NF95_GET_VAR(ncid, varid, q(:, :, :, iq))
210 guez 3 ENDIF
211     ENDDO
212    
213 guez 38 call NF95_INQ_VARID (ncid, "masse", varid)
214 guez 55 call NF95_GET_VAR(ncid, varid, masse)
215 guez 3
216 guez 38 call NF95_INQ_VARID (ncid, "ps", varid)
217 guez 39 call NF95_GET_VAR(ncid, varid, ps)
218 guez 85 ! 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 guez 3
222 guez 25 call NF95_CLOSE(ncid)
223 guez 3
224     END SUBROUTINE dynetat0
225    
226     end module dynetat0_m

  ViewVC Help
Powered by ViewVC 1.1.21