/[lmdze]/trunk/dyn3d/Read_reanalyse/read_reanalyse.f
ViewVC logotype

Annotation of /trunk/dyn3d/Read_reanalyse/read_reanalyse.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 102 - (hide annotations)
Tue Jul 15 13:43:24 2014 UTC (9 years, 10 months ago) by guez
File size: 5265 byte(s)
Removed unused file "condsurf.f" (only useful for ocean slab).

day_step must be a multiple of 4 * iperiod if ok_guide.

Changed type of variable online of module conf_guide_m from integer to
logical. Value -1 was not useful, equivalent to not ok_guide.

Removed argument masse of procedure guide. masse is kept consistent
with ps throughout the run. masse need only be computed again just
after ps has been modified. In prodecure guide, replaced use of
remanent variable first by test on itau. Replaced test on variable
"test" by test on integer values.

In leapfrog, for the call to guide, replaced test on real values by
test on integer values.

Bug fix in tau2alpha: computation of dxdyv (following LMDZ revision 1040).

In procedure wrgrads, replaced badly chosen argument name "if" by i_f.

1 guez 88 module read_reanalyse_m
2 guez 37
3 guez 88 IMPLICIT NONE
4 guez 3
5 guez 88 contains
6 guez 20
7 guez 88 subroutine read_reanalyse(timestep, psi, u, v, t, q, masse, nlevnc)
8 guez 3
9 guez 88 ! From LMDZ4/libf/dyn3d/read_reanalyse.F, version 1.3, 2005/04/15 12:31:21
10 guez 3
11 guez 88 USE conf_guide_m, ONLY: guide_q, guide_t, guide_u, guide_v, ncep
12     USE dimens_m, ONLY: iim, jjm, llm
13 guez 102 use dump2d_m, only: dump2d
14 guez 88 USE netcdf, ONLY: nf90_get_var, nf90_inq_varid, nf90_nowrite, nf90_open
15     USE paramet_m, ONLY: iip1, jjp1
16     use reanalyse2nat_m, only: reanalyse2nat
17 guez 3
18 guez 88 integer timestep
19     real, intent(in):: psi(iip1, jjp1)
20     real u(iip1, jjp1, llm), v(iip1, jjm, llm)
21     real t(iip1, jjp1, llm), q(iip1, jjp1, llm)
22     real masse(iip1, jjp1, llm)
23     integer nlevnc
24 guez 3
25 guez 88 ! Local:
26 guez 3
27 guez 88 integer l
28     real pk(iip1, jjp1, llm)
29     integer, save:: ncidu, varidu, ncidv, varidv, ncidt, varidt
30     integer, save:: ncidpl
31     integer, save:: varidpl, ncidQ, varidQ
32     real unc(iip1, jjp1, nlevnc), vnc(iip1, jjm, nlevnc)
33     real tnc(iip1, jjp1, nlevnc)
34     real Qnc(iip1, jjp1, nlevnc)
35     real pl(nlevnc)
36     integer start(4), count(4), status
37     real rcode
38     logical:: first = .true.
39 guez 3
40 guez 88 ! -----------------------------------------------------------------
41 guez 3
42 guez 88 ! Initialisation de la lecture des fichiers
43 guez 3
44 guez 88 if (first) then
45     ncidpl=-99
46     print *, 'Intitialisation de read reanalsye'
47 guez 3
48 guez 88 ! Vent zonal
49     if (guide_u) then
50     rcode=nf90_open('u.nc', nf90_nowrite, ncidu)
51     rcode = nf90_inq_varid(ncidu, 'UWND', varidu)
52     print *, 'ncidu, varidu', ncidu, varidu
53     if (ncidpl.eq.-99) ncidpl=ncidu
54     endif
55 guez 3
56 guez 88 ! Vent meridien
57     if (guide_v) then
58     rcode=nf90_open('v.nc', nf90_nowrite, ncidv)
59     rcode = nf90_inq_varid(ncidv, 'VWND', varidv)
60     print *, 'ncidv, varidv', ncidv, varidv
61     if (ncidpl.eq.-99) ncidpl=ncidv
62     endif
63 guez 3
64 guez 88 ! Temperature
65     if (guide_T) then
66     rcode=nf90_open('T.nc', nf90_nowrite, ncidt)
67     rcode = nf90_inq_varid(ncidt, 'AIR', varidt)
68     print *, 'ncidt, varidt', ncidt, varidt
69     if (ncidpl.eq.-99) ncidpl=ncidt
70     endif
71 guez 3
72 guez 88 ! Humidite
73     if (guide_Q) then
74     rcode=nf90_open('hur.nc', nf90_nowrite, ncidQ)
75     rcode = nf90_inq_varid(ncidQ, 'RH', varidQ)
76     print *, 'ncidQ, varidQ', ncidQ, varidQ
77     if (ncidpl.eq.-99) ncidpl=ncidQ
78     endif
79 guez 3
80 guez 88 ! Coordonnee verticale
81     if (ncep) then
82     print *, 'Vous etes entrain de lire des donnees NCEP'
83     rcode = nf90_inq_varid(ncidpl, 'LEVEL', varidpl)
84     else
85     print *, 'Vous etes entrain de lire des donnees ECMWF'
86     rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
87     endif
88     print *, 'ncidu, varidpl', ncidu, varidpl
89     endif
90     print *, 'ok1'
91 guez 3
92 guez 88 ! Niveaux de pression
93     print *, 'WARNING!!! Il n y a pas de test de coherence'
94     print *, 'sur le nombre de niveaux verticaux dans le fichier nc'
95     status=NF90_GET_VAR(ncidpl, varidpl, pl)
96     ! passage en pascal
97     pl(:)=100.*pl(:)
98     if (first) then
99     do l=1, nlevnc
100     print *, 'PL(', l, ')=', pl(l)
101     enddo
102     endif
103 guez 3
104 guez 88 ! lecture des champs u, v, T
105 guez 3
106 guez 88 ! dimensions pour les champs scalaires et le vent zonal
107 guez 3
108 guez 88 start(1)=1
109     start(2)=1
110     start(3)=1
111     start(4)=timestep
112 guez 3
113 guez 88 count(1)=iip1
114     count(2)=jjp1
115     count(3)=nlevnc
116     count(4)=1
117 guez 3
118 guez 88 ! mise a zero des tableaux
119 guez 3
120 guez 88 unc(:, :, :)=0.
121     vnc(:, :, :)=0.
122     tnc(:, :, :)=0.
123     Qnc(:, :, :)=0.
124 guez 3
125 guez 88 ! Vent zonal
126 guez 3
127 guez 88 if (guide_u) then
128     print *, 'avant la lecture de UNCEP nd de niv:', nlevnc
129     status=NF90_GET_VAR(ncidu, varidu, unc, start, count)
130     print *, 'WARNING!!! Correction bidon pour palier a un '
131     print *, 'probleme dans la creation des fichiers nc'
132     call correctbid(iim, jjp1*nlevnc, unc)
133     call dump2d(iip1, jjp1, unc, 'UNC COUCHE 1 ')
134     endif
135 guez 3
136 guez 88 ! Temperature
137 guez 3
138 guez 88 print *, 'ncidt=', ncidt, 'varidt=', varidt, 'start=', start
139     print *, 'count=', count
140     if (guide_T) then
141     status=NF90_GET_VAR(ncidt, varidt, tnc, start, count)
142     call dump2d(iip1, jjp1, tnc, 'TNC COUCHE 1 AAA ')
143     call correctbid(iim, jjp1*nlevnc, tnc)
144     call dump2d(iip1, jjp1, tnc, 'TNC COUCHE 1 BBB ')
145     endif
146 guez 3
147 guez 88 ! Humidite
148 guez 3
149 guez 88 if (guide_Q) then
150     status=NF90_GET_VAR(ncidQ, varidQ, Qnc, start, count)
151     call correctbid(iim, jjp1*nlevnc, Qnc)
152     call dump2d(iip1, jjp1, Qnc, 'QNC COUCHE 1 ')
153     endif
154 guez 3
155 guez 88 count(2)=jjm
156     ! Vent meridien
157 guez 3
158 guez 88 if (guide_v) then
159     status=NF90_GET_VAR(ncidv, varidv, vnc, start, count)
160     call correctbid(iim, jjm*nlevnc, vnc)
161     call dump2d(iip1, jjm, vnc, 'VNC COUCHE 1 ')
162     endif
163 guez 3
164 guez 88 start(3)=timestep
165     start(4)=0
166     count(2)=jjp1
167     count(3)=1
168     count(4)=0
169 guez 3
170 guez 88 ! Interpolation verticale sur les niveaux modele
171 guez 3
172 guez 88 call reanalyse2nat(nlevnc, psi, unc, vnc, tnc, Qnc, pl, u, v, t, Q, &
173     masse, pk)
174 guez 3
175 guez 88 call dump2d(iip1, jjm, v, 'V COUCHE APRES ')
176 guez 3
177 guez 88 ! Passage aux variables du modele (vents covariants, temperature
178     ! potentielle et humidite specifique)
179 guez 3
180 guez 88 call nat2gcm(u, v, t, Q, pk, u, v, t, Q)
181     print *, 'TIMESTEP ', timestep
182     first=.false.
183 guez 3
184 guez 88 end subroutine read_reanalyse
185 guez 3
186 guez 88 end module read_reanalyse_m

  ViewVC Help
Powered by ViewVC 1.1.21