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

Contents of /trunk/dyn3d/dynetat0.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 113 - (show annotations)
Thu Sep 18 19:56:46 2014 UTC (9 years, 7 months ago) by guez
File size: 5279 byte(s)
Moved the call to read_serre out of conf_gcm so that it can be called
only in the program ce0l, not in gcm. In gcm, variables of module
serre are read from start file. Added reading of dzoomx, dzoomy, taux,
tauy from start file, in dynetat0. Those variables were written by
dynredem0 but not read.

Removed possibility fxyhypb = false, because the geometric part of the
program is such a mess. Could then remove variables transx, transy,
alphax, alphay, pxo, pyo of module serre.

Bug fix in tau2alpha: missing save attributes. The first call to
tau2alpha needs to compute dxdyu and dxdyv regardless of value of
argument type, because they will be needed for subsequent calls to
tau2alpha with various values of argument type.

1 module dynetat0_m
2
3 IMPLICIT NONE
4
5 INTEGER day_ini
6
7 contains
8
9 SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis, time_0)
10
11 ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30
12 ! Authors: P. Le Van, L. Fairhead
13 ! This procedure reads the initial state of the atmosphere.
14
15 use comconst, only: dtvr
16 use comgeom, only: rlonu, rlatu, rlonv, rlatv, cu_2d, cv_2d, aire_2d
17 use dimens_m, only: iim, jjm, llm, nqmx
18 use disvert_m, only: pa
19 use ener, only: etot0, ang0, ptot0, stot0, ztot0
20 use iniadvtrac_m, only: tname
21 use netcdf, only: NF90_NOWRITE, NF90_NOERR
22 use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, &
23 NF95_Gw_VAR
24 use nr_util, only: assert
25 use serre, only: clon, clat, grossismy, grossismx, dzoomx, dzoomy, taux, &
26 tauy
27 use temps, only: day_ref, itau_dyn, annee_ref
28
29 REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm)
30 REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
31 REAL, intent(out):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
32 REAL, intent(out):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
33 REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
34 REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa
35 REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
36 REAL, intent(out):: time_0
37
38 ! Local variables:
39 INTEGER iq
40 REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run
41 INTEGER ierr, ncid, varid
42
43 !-----------------------------------------------------------------------
44
45 print *, "Call sequence information: dynetat0"
46
47 call assert((/size(ucov, 1), size(vcov, 1), size(masse, 1), size(ps, 1), &
48 size(phis, 1), size(q, 1), size(teta, 1)/) == iim + 1, "dynetat0 iim")
49 call assert((/size(ucov, 2), size(vcov, 2) + 1, size(masse, 2), &
50 size(ps, 2), size(phis, 2), size(q, 2), size(teta, 2)/) == jjm + 1, &
51 "dynetat0 jjm")
52 call assert((/size(vcov, 3), size(ucov, 3), size(teta, 3), size(q, 3), &
53 size(masse, 3)/) == llm, "dynetat0 llm")
54 call assert(size(q, 4) == nqmx, "dynetat0 q nqmx")
55
56 ! Fichier état initial :
57 call nf95_open("start.nc", NF90_NOWRITE, ncid)
58
59 call nf95_inq_varid(ncid, "controle", varid)
60 call NF95_Gw_VAR(ncid, varid, tab_cntrl)
61
62 call assert(int(tab_cntrl(1)) == iim, "dynetat0 tab_cntrl iim")
63 call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm")
64 call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm")
65
66 day_ref = int(tab_cntrl(4))
67 annee_ref = int(tab_cntrl(5))
68
69 IF (dtvr /= tab_cntrl(12)) THEN
70 print *, 'Warning: the time steps from day_step and "start.nc" ' // &
71 'are different.'
72 print *, 'dtvr from day_step: ', dtvr
73 print *, 'dtvr from "start.nc": ', tab_cntrl(12)
74 print *, 'Using the value from day_step.'
75 ENDIF
76
77 etot0 = tab_cntrl(13)
78 ptot0 = tab_cntrl(14)
79 ztot0 = tab_cntrl(15)
80 stot0 = tab_cntrl(16)
81 ang0 = tab_cntrl(17)
82 pa = tab_cntrl(18)
83
84 clon = tab_cntrl(20)
85 clat = tab_cntrl(21)
86 grossismx = tab_cntrl(22)
87 grossismy = tab_cntrl(23)
88 dzoomx = tab_cntrl(25)
89 dzoomy = tab_cntrl(26)
90 taux = tab_cntrl(28)
91 tauy = tab_cntrl(29)
92
93 itau_dyn = tab_cntrl(31)
94
95 call NF95_INQ_VARID (ncid, "rlonu", varid)
96 call NF95_GET_VAR(ncid, varid, rlonu)
97
98 call NF95_INQ_VARID (ncid, "rlatu", varid)
99 call NF95_GET_VAR(ncid, varid, rlatu)
100
101 call NF95_INQ_VARID (ncid, "rlonv", varid)
102 call NF95_GET_VAR(ncid, varid, rlonv)
103
104 call NF95_INQ_VARID (ncid, "rlatv", varid)
105 call NF95_GET_VAR(ncid, varid, rlatv)
106
107 call NF95_INQ_VARID (ncid, "cu", varid)
108 call NF95_GET_VAR(ncid, varid, cu_2d)
109
110 call NF95_INQ_VARID (ncid, "cv", varid)
111 call NF95_GET_VAR(ncid, varid, cv_2d)
112
113 call NF95_INQ_VARID (ncid, "aire", varid)
114 call NF95_GET_VAR(ncid, varid, aire_2d)
115
116 call NF95_INQ_VARID (ncid, "phisinit", varid)
117 call NF95_GET_VAR(ncid, varid, phis)
118
119 call NF95_INQ_VARID (ncid, "temps", varid)
120 call NF95_GET_VAR(ncid, varid, time_0)
121
122 day_ini = tab_cntrl(30) + INT(time_0)
123 time_0 = time_0 - INT(time_0)
124 ! {0 <= time0 < 1}
125
126 deallocate(tab_cntrl) ! pointer
127
128 call NF95_INQ_VARID (ncid, "ucov", varid)
129 call NF95_GET_VAR(ncid, varid, ucov)
130
131 call NF95_INQ_VARID (ncid, "vcov", varid)
132 call NF95_GET_VAR(ncid, varid, vcov)
133
134 call NF95_INQ_VARID (ncid, "teta", varid)
135 call NF95_GET_VAR(ncid, varid, teta)
136
137 DO iq = 1, nqmx
138 call NF95_INQ_VARID(ncid, tname(iq), varid, ierr)
139 IF (ierr /= NF90_NOERR) THEN
140 PRINT *, 'dynetat0: "' // tname(iq) // '" not found, ' // &
141 "setting it to zero..."
142 q(:, :, :, iq) = 0.
143 ELSE
144 call NF95_GET_VAR(ncid, varid, q(:, :, :, iq))
145 ENDIF
146 ENDDO
147
148 call NF95_INQ_VARID (ncid, "masse", varid)
149 call NF95_GET_VAR(ncid, varid, masse)
150
151 call NF95_INQ_VARID (ncid, "ps", varid)
152 call NF95_GET_VAR(ncid, varid, ps)
153 ! Check that there is a single value at each pole:
154 call assert(ps(1, 1) == ps(2:, 1), "dynetat0 ps north pole")
155 call assert(ps(1, jjm + 1) == ps(2:, jjm + 1), "dynetat0 ps south pole")
156
157 call NF95_CLOSE(ncid)
158
159 END SUBROUTINE dynetat0
160
161 end module dynetat0_m

  ViewVC Help
Powered by ViewVC 1.1.21