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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 108 - (hide annotations)
Tue Sep 16 14:00:41 2014 UTC (9 years, 8 months ago) by guez
Original Path: trunk/dyn3d/Read_reanalyse/read_reanalyse.f
File size: 4412 byte(s)
Imported writefield from LMDZ. Close at the end of gcm the files which
were created by writefiled (not done in LMDZ).

Removed procedures for the output of Grads files. Removed calls to
dump2d. In guide, replaced calls to wrgrads by calls to writefield.

In vlspltqs, removed redundant programming of saturation
pressure. Call foeew from module FCTTRE instead.

Bug fix in interpre: size of w exceeding size of correponding actual
argument wg in advtrac.

In leapfrog, call guide until the end of the run, instead of six hours
before the end.

Bug fix in readsulfate_preind: type of arguments.

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

  ViewVC Help
Powered by ViewVC 1.1.21