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

Diff of /trunk/Sources/dyn3d/Guide/guide.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/dyn3d/guide.f90 revision 44 by guez, Wed Apr 13 12:29:18 2011 UTC trunk/dyn3d/guide.f revision 90 by guez, Wed Mar 12 21:16:36 2014 UTC
# Line 13  CONTAINS Line 13  CONTAINS
13    
14      ! Author: F.Hourdin      ! Author: F.Hourdin
15    
16      USE comconst, ONLY : cpp, daysec, dtvr, kappa      USE comconst, ONLY: cpp, daysec, dtvr, kappa
17      USE comgeom, ONLY : aire, rlatu, rlonv      USE comgeom, ONLY: aire, rlatu, rlonv
18      USE comvert, ONLY : ap, bp, preff, presnivs      USE conf_gcm_m, ONLY: day_step, iperiod
     USE conf_gcm_m, ONLY : day_step, iperiod  
19      use conf_guide_m, only: conf_guide, guide_u, guide_v, guide_t, guide_q, &      use conf_guide_m, only: conf_guide, guide_u, guide_v, guide_t, guide_q, &
20           guide_p, ncep, ini_anal, tau_min_u, tau_max_u, tau_min_v, tau_max_v, &           ncep, ini_anal, tau_min_u, tau_max_u, tau_min_v, tau_max_v, &
21           tau_min_t, tau_max_t, tau_min_q, tau_max_q, tau_min_p, tau_max_p, &           tau_min_t, tau_max_t, tau_min_q, tau_max_q, tau_min_p, tau_max_p, &
22           online           online
23      USE dimens_m, ONLY : jjm, llm      USE dimens_m, ONLY: iim, jjm, llm
24      USE exner_hyb_m, ONLY : exner_hyb      USE disvert_m, ONLY: ap, bp, preff, presnivs
25      USE inigrads_m, ONLY : inigrads      USE exner_hyb_m, ONLY: exner_hyb
26        USE inigrads_m, ONLY: inigrads
27        use massdair_m, only: massdair
28      use netcdf, only: nf90_nowrite, nf90_open, nf90_close, nf90_inq_dimid, &      use netcdf, only: nf90_nowrite, nf90_open, nf90_close, nf90_inq_dimid, &
29           nf90_inquire_dimension           nf90_inquire_dimension
30      use nr_util, only: pi      use nr_util, only: pi
31      USE paramet_m, ONLY : iip1, ip1jm, ip1jmp1, jjp1, llmp1      USE paramet_m, ONLY: iip1, ip1jm, ip1jmp1, jjp1, llmp1
32      USE q_sat_m, ONLY : q_sat      USE q_sat_m, ONLY: q_sat
33      USE serre, ONLY : clat, clon      use read_reanalyse_m, only: read_reanalyse
34        USE serre, ONLY: clat, clon
35      use tau2alpha_m, only: tau2alpha, dxdys      use tau2alpha_m, only: tau2alpha, dxdys
36    
37        INTEGER, INTENT(IN):: itau
38    
39      ! variables dynamiques      ! variables dynamiques
40      REAL vcov(ip1jm, llm), ucov(ip1jmp1, llm) ! vents covariants      REAL ucov(ip1jmp1, llm), vcov(ip1jm, llm) ! vents covariants
41      REAL, intent(inout):: teta(ip1jmp1, llm) ! temperature potentielle      REAL, intent(inout):: teta(iim + 1, jjm + 1, llm) ! température potentielle
42      REAL q(ip1jmp1, llm) ! temperature potentielle      REAL q(iim + 1, jjm + 1, llm)
43      REAL ps(ip1jmp1) ! pression au sol      REAL, intent(out):: masse(ip1jmp1, llm) ! masse d'air
44      REAL masse(ip1jmp1, llm) ! masse d'air      REAL, intent(in):: ps(:, :) ! (iim + 1, jjm + 1) pression au sol
45    
46        ! Local:
47    
48      ! variables dynamiques pour les reanalyses.      ! variables dynamiques pour les reanalyses.
49      REAL, save:: ucovrea1(ip1jmp1, llm), vcovrea1(ip1jm, llm) !vts cov reas      REAL, save:: ucovrea1(ip1jmp1, llm), vcovrea1(ip1jm, llm) !vts cov reas
50      REAL, save:: tetarea1(ip1jmp1, llm) ! temp pot reales      REAL, save:: tetarea1(iim + 1, jjm + 1, llm) ! temp pot reales
51      REAL, save:: qrea1(ip1jmp1, llm) ! temp pot reales      REAL, save:: qrea1(iim + 1, jjm + 1, llm) ! temp pot reales
     REAL, save:: psrea1(ip1jmp1) ! ps  
52      REAL, save:: ucovrea2(ip1jmp1, llm), vcovrea2(ip1jm, llm) !vts cov reas      REAL, save:: ucovrea2(ip1jmp1, llm), vcovrea2(ip1jm, llm) !vts cov reas
53      REAL, save:: tetarea2(ip1jmp1, llm) ! temp pot reales      REAL, save:: tetarea2(iim + 1, jjm + 1, llm) ! temp pot reales
54      REAL, save:: qrea2(ip1jmp1, llm) ! temp pot reales      REAL, save:: qrea2(iim + 1, jjm + 1, llm) ! temp pot reales
55      REAL, save:: masserea2(ip1jmp1, llm) ! masse      REAL, save:: masserea2(ip1jmp1, llm) ! masse
     REAL, save:: psrea2(ip1jmp1) ! ps  
56    
57      REAL, save:: alpha_q(ip1jmp1)      REAL, save:: alpha_q(iim + 1, jjm + 1)
58      REAL, save:: alpha_t(ip1jmp1), alpha_p(ip1jmp1)      REAL, save:: alpha_t(iim + 1, jjm + 1), alpha_p(ip1jmp1)
59      REAL, save:: alpha_u(ip1jmp1), alpha_v(ip1jm)      REAL, save:: alpha_u(ip1jmp1), alpha_v(ip1jm)
60      REAL dday_step, toto, reste      REAL dday_step, toto, reste
61      real, save:: itau_test      real, save:: itau_test
62      INTEGER, save:: step_rea, count_no_rea      INTEGER, save:: step_rea, count_no_rea
63    
64      INTEGER ilon, ilat      INTEGER ilon, ilat
65      REAL factt, ztau(ip1jmp1)      REAL factt, ztau(iim + 1, jjm + 1)
66    
67      INTEGER, INTENT(IN):: itau      INTEGER ij, i, j, l
68      INTEGER ij, l      INTEGER ncidpl, status
     INTEGER ncidpl, varidpl, status  
69      INTEGER rcod, rid      INTEGER rcod, rid
70      REAL ditau, tau, a      REAL ditau, tau, a
71      INTEGER, SAVE:: nlev      INTEGER, SAVE:: nlev
72    
73      ! TEST SUR QSAT      ! TEST SUR QSAT
74      REAL p(ip1jmp1, llmp1), pk(ip1jmp1, llm), pks(ip1jmp1)      REAL p(iim + 1, jjm + 1, llmp1)
75      REAL pkf(ip1jmp1, llm)      real pk(iim + 1, jjm + 1, llm), pks(iim + 1, jjm + 1)
76      REAL pres(ip1jmp1, llm)      REAL pres(iim + 1, jjm + 1, llm)
77    
78      REAL qsat(ip1jmp1, llm)      REAL qsat(iim + 1, jjm + 1, llm)
79      REAL unskap      REAL unskap
80      REAL tnat(ip1jmp1, llm)      REAL tnat(iim + 1, jjm + 1, llm)
81    
82      LOGICAL:: first = .TRUE.      LOGICAL:: first = .TRUE.
83      CHARACTER(len=10) file      CHARACTER(len=10) file
# Line 87  CONTAINS Line 90  CONTAINS
90    
91      ! calcul de l'humidite saturante      ! calcul de l'humidite saturante
92    
93      forall (l = 1: llm + 1) p(:, l) = ap(l) + bp(l) * ps      forall (l = 1: llm + 1) p(:, :, l) = ap(l) + bp(l) * ps
94      CALL massdair(p, masse)      CALL massdair(p, masse)
95      CALL exner_hyb(ps, p, pks, pk, pkf)      CALL exner_hyb(ps, p, pks, pk)
96      tnat(:, :) = pk(:, :)*teta(:, :)/cpp      tnat = pk * teta / cpp
97      unskap = 1./kappa      unskap = 1. / kappa
98      pres(:, :) = preff*(pk(:, :)/cpp)**unskap      pres = preff * (pk / cpp)**unskap
99      qsat = q_sat(tnat, pres)      qsat = q_sat(tnat, pres)
100    
101      ! initialisations pour la lecture des reanalyses.      ! initialisations pour la lecture des reanalyses.
# Line 100  CONTAINS Line 103  CONTAINS
103      ! alpha=1 signifie pas d'injection      ! alpha=1 signifie pas d'injection
104      ! alpha=0 signifie injection totale      ! alpha=0 signifie injection totale
105    
106      IF (online==-1) THEN      IF (online== - 1) THEN
107         RETURN         RETURN
108      END IF      END IF
109    
110      IF (first) THEN      IF (first) THEN
111         CALL conf_guide         CALL conf_guide
112         file = 'guide'         file = 'guide'
113         CALL inigrads(igrads, rlonv, 180./pi, -180., 180., rlatu, -90., 90., &         CALL inigrads(igrads, rlonv, 180. / pi, -180., 180., rlatu, -90., 90., &
114              180./pi, presnivs, 1., dtgrads, file, 'dyn_zon ')              180. / pi, presnivs, 1., dtgrads, file, 'dyn_zon ')
115         PRINT *, '1: en-ligne, 0: hors-ligne (x=x_rea), -1: climat (x=x_gcm)'         PRINT *, '1: en-ligne, 0: hors-ligne (x=x_rea), -1: climat (x=x_gcm)'
116         IF (online==-1) RETURN         IF (online== - 1) RETURN
117    
118         IF (online==1) THEN         IF (online==1) THEN
119            ! Constantes de temps de rappel en jour            ! Constantes de temps de rappel en jour
# Line 120  CONTAINS Line 123  CONTAINS
123            ! coordonnees du centre du zoom            ! coordonnees du centre du zoom
124            CALL coordij(clon, clat, ilon, ilat)            CALL coordij(clon, clat, ilon, ilat)
125            ! aire de la maille au centre du zoom            ! aire de la maille au centre du zoom
126            aire_min = aire(ilon+(ilat-1)*iip1)            aire_min = aire(ilon+(ilat - 1) * iip1)
127            ! aire maximale de la maille            ! aire maximale de la maille
128            aire_max = 0.            aire_max = 0.
129            DO ij = 1, ip1jmp1            DO ij = 1, ip1jmp1
130               aire_max = max(aire_max, aire(ij))               aire_max = max(aire_max, aire(ij))
131            END DO            END DO
132            ! factt = pas de temps en fraction de jour            ! factt = pas de temps en fraction de jour
133            factt = dtvr*iperiod/daysec            factt = dtvr * iperiod / daysec
134    
135            CALL tau2alpha(3, iip1, jjm, factt, tau_min_v, tau_max_v, alpha_v)            CALL tau2alpha(3, iip1, jjm, factt, tau_min_v, tau_max_v, alpha_v)
136            CALL tau2alpha(2, iip1, jjp1, factt, tau_min_u, tau_max_u, alpha_u)            CALL tau2alpha(2, iip1, jjp1, factt, tau_min_u, tau_max_u, alpha_u)
# Line 156  CONTAINS Line 159  CONTAINS
159         ! itau_test montre si l'importation a deja ete faite au rang itau         ! itau_test montre si l'importation a deja ete faite au rang itau
160         ! lecture d'un fichier netcdf pour determiner le nombre de niveaux         ! lecture d'un fichier netcdf pour determiner le nombre de niveaux
161         if (guide_u) then         if (guide_u) then
162            if (ncidpl.eq.-99) rcod=nf90_open('u.nc',Nf90_NOWRITe,ncidpl)            if (ncidpl.eq. - 99) rcod=nf90_open('u.nc',Nf90_NOWRITe,ncidpl)
163         endif         endif
164    
165         if (guide_v) then         if (guide_v) then
166            if (ncidpl.eq.-99) rcod=nf90_open('v.nc',nf90_nowrite,ncidpl)            if (ncidpl.eq. - 99) rcod=nf90_open('v.nc',nf90_nowrite,ncidpl)
167         endif         endif
168    
169         if (guide_T) then         if (guide_T) then
170            if (ncidpl.eq.-99) rcod=nf90_open('T.nc',nf90_nowrite,ncidpl)            if (ncidpl.eq. - 99) rcod=nf90_open('T.nc',nf90_nowrite,ncidpl)
171         endif         endif
172    
173         if (guide_Q) then         if (guide_Q) then
174            if (ncidpl.eq.-99) rcod=nf90_open('hur.nc',nf90_nowrite, ncidpl)            if (ncidpl.eq. - 99) rcod=nf90_open('hur.nc',nf90_nowrite, ncidpl)
175         endif         endif
176    
177         IF (ncep) THEN         IF (ncep) THEN
# Line 181  CONTAINS Line 184  CONTAINS
184         rcod = nf90_close(ncidpl)         rcod = nf90_close(ncidpl)
185         ! Lecture du premier etat des reanalyses.         ! Lecture du premier etat des reanalyses.
186         CALL read_reanalyse(1, ps, ucovrea2, vcovrea2, tetarea2, qrea2, &         CALL read_reanalyse(1, ps, ucovrea2, vcovrea2, tetarea2, qrea2, &
187              masserea2, psrea2, 1, nlev)              masserea2, nlev)
188         qrea2(:, :) = max(qrea2(:, :), 0.1)         qrea2 = max(qrea2, 0.1)
189    
190         ! Debut de l'integration temporelle:         ! Debut de l'integration temporelle:
191      END IF ! first      END IF ! first
# Line 193  CONTAINS Line 196  CONTAINS
196      dday_step = real(day_step)      dday_step = real(day_step)
197      WRITE (*, *) 'ditau, dday_step'      WRITE (*, *) 'ditau, dday_step'
198      WRITE (*, *) ditau, dday_step      WRITE (*, *) ditau, dday_step
199      toto = 4*ditau/dday_step      toto = 4 * ditau / dday_step
200      reste = toto - aint(toto)      reste = toto - aint(toto)
201    
202      IF (reste==0.) THEN      IF (reste==0.) THEN
# Line 201  CONTAINS Line 204  CONTAINS
204            WRITE (*, *) 'deuxieme passage de advreel a itau=', itau            WRITE (*, *) 'deuxieme passage de advreel a itau=', itau
205            STOP            STOP
206         ELSE         ELSE
207            vcovrea1(:, :) = vcovrea2(:, :)            vcovrea1 = vcovrea2
208            ucovrea1(:, :) = ucovrea2(:, :)            ucovrea1 = ucovrea2
209            tetarea1(:, :) = tetarea2(:, :)            tetarea1 = tetarea2
210            qrea1(:, :) = qrea2(:, :)            qrea1 = qrea2
211    
212            PRINT *, 'LECTURE REANALYSES, pas ', step_rea, 'apres ', &            PRINT *, 'LECTURE REANALYSES, pas ', step_rea, 'apres ', &
213                 count_no_rea, ' non lectures'                 count_no_rea, ' non lectures'
214            step_rea = step_rea + 1            step_rea = step_rea + 1
215            itau_test = itau            itau_test = itau
216            CALL read_reanalyse(step_rea, ps, ucovrea2, vcovrea2, tetarea2, &            CALL read_reanalyse(step_rea, ps, ucovrea2, vcovrea2, tetarea2, &
217                 qrea2, masserea2, psrea2, 1, nlev)                 qrea2, masserea2, nlev)
218            qrea2(:, :) = max(qrea2(:, :), 0.1)            qrea2 = max(qrea2, 0.1)
219            factt = dtvr*iperiod/daysec            factt = dtvr * iperiod / daysec
220            ztau(:) = factt/max(alpha_t(:), 1.E-10)            ztau = factt / max(alpha_t, 1E-10)
221            CALL wrgrads(igrads, 1, aire, 'aire ', 'aire ')            CALL wrgrads(igrads, 1, aire, 'aire ', 'aire ')
222            CALL wrgrads(igrads, 1, dxdys, 'dxdy ', 'dxdy ')            CALL wrgrads(igrads, 1, dxdys, 'dxdy ', 'dxdy ')
223            CALL wrgrads(igrads, 1, alpha_u, 'au ', 'au ')            CALL wrgrads(igrads, 1, alpha_u, 'au ', 'au ')
# Line 235  CONTAINS Line 238  CONTAINS
238      END IF      END IF
239    
240      ! Guidage      ! Guidage
241      ! x_gcm = a * x_gcm + (1-a) * x_reanalyses      ! x_gcm = a * x_gcm + (1 - a) * x_reanalyses
242    
243      IF (ini_anal) PRINT *, 'ATTENTION !!! ON PART DU GUIDAGE'      IF (ini_anal) PRINT *, 'ATTENTION !!! ON PART DU GUIDAGE'
244    
245      ditau = real(itau)      ditau = real(itau)
246      dday_step = real(day_step)      dday_step = real(day_step)
247    
248      tau = 4*ditau/dday_step      tau = 4 * ditau / dday_step
249      tau = tau - aint(tau)      tau = tau - aint(tau)
250    
251      ! ucov      ! ucov
252      IF (guide_u) THEN      IF (guide_u) THEN
253         DO l = 1, llm         DO l = 1, llm
254            DO ij = 1, ip1jmp1            DO ij = 1, ip1jmp1
255               a = (1.-tau)*ucovrea1(ij, l) + tau*ucovrea2(ij, l)               a = (1. - tau) * ucovrea1(ij, l) + tau * ucovrea2(ij, l)
256               ucov(ij, l) = (1.-alpha_u(ij))*ucov(ij, l) + alpha_u(ij)*a               ucov(ij, l) = (1. - alpha_u(ij)) * ucov(ij, l) + alpha_u(ij) * a
257               IF (first .AND. ini_anal) ucov(ij, l) = a               IF (first .AND. ini_anal) ucov(ij, l) = a
258            END DO            END DO
259         END DO         END DO
# Line 258  CONTAINS Line 261  CONTAINS
261    
262      IF (guide_t) THEN      IF (guide_t) THEN
263         DO l = 1, llm         DO l = 1, llm
264            DO ij = 1, ip1jmp1            do j = 1, jjm + 1
265               a = (1.-tau)*tetarea1(ij, l) + tau*tetarea2(ij, l)               DO i = 1, iim + 1
266               teta(ij, l) = (1.-alpha_t(ij))*teta(ij, l) + alpha_t(ij)*a                  a = (1. - tau) * tetarea1(i, j, l) + tau * tetarea2(i, j, l)
267               IF (first .AND. ini_anal) teta(ij, l) = a                  teta(i, j, l) = (1. - alpha_t(i, j)) * teta(i, j, l) &
268            END DO                       + alpha_t(i, j) * a
269                    IF (first .AND. ini_anal) teta(i, j, l) = a
270                 END DO
271              end do
272         END DO         END DO
273      END IF      END IF
274    
     ! P  
     IF (guide_p) THEN  
        DO ij = 1, ip1jmp1  
           a = (1.-tau)*psrea1(ij) + tau*psrea2(ij)  
           ps(ij) = (1.-alpha_p(ij))*ps(ij) + alpha_p(ij)*a  
           IF (first .AND. ini_anal) ps(ij) = a  
        END DO  
        forall (l = 1: llm + 1) p(:, l) = ap(l) + bp(l) * ps  
        CALL massdair(p, masse)  
     END IF  
   
     ! q  
275      IF (guide_q) THEN      IF (guide_q) THEN
276         DO l = 1, llm         DO l = 1, llm
277            DO ij = 1, ip1jmp1            do j = 1, jjm + 1
278               a = (1.-tau)*qrea1(ij, l) + tau*qrea2(ij, l)               DO i = 1, iim + 1
279               ! hum relative en % -> hum specif                  a = (1. - tau) * qrea1(i, j, l) + tau * qrea2(i, j, l)
280               a = qsat(ij, l)*a*0.01                  ! hum relative en % -> hum specif
281               q(ij, l) = (1.-alpha_q(ij))*q(ij, l) + alpha_q(ij)*a                  a = qsat(i, j, l) * a * 0.01
282               IF (first .AND. ini_anal) q(ij, l) = a                  q(i, j, l) = (1. - alpha_q(i, j)) * q(i, j, l) &
283            END DO                       + alpha_q(i, j) * a
284                    IF (first .AND. ini_anal) q(i, j, l) = a
285                 END DO
286              end do
287         END DO         END DO
288      END IF      END IF
289    
# Line 294  CONTAINS Line 291  CONTAINS
291      IF (guide_v) THEN      IF (guide_v) THEN
292         DO l = 1, llm         DO l = 1, llm
293            DO ij = 1, ip1jm            DO ij = 1, ip1jm
294               a = (1.-tau)*vcovrea1(ij, l) + tau*vcovrea2(ij, l)               a = (1. - tau) * vcovrea1(ij, l) + tau * vcovrea2(ij, l)
295               vcov(ij, l) = (1.-alpha_v(ij))*vcov(ij, l) + alpha_v(ij)*a               vcov(ij, l) = (1. - alpha_v(ij)) * vcov(ij, l) + alpha_v(ij) * a
296               IF (first .AND. ini_anal) vcov(ij, l) = a               IF (first .AND. ini_anal) vcov(ij, l) = a
297            END DO            END DO
298            IF (first .AND. ini_anal) vcov(ij, l) = a            IF (first .AND. ini_anal) vcov(ij, l) = a

Legend:
Removed from v.44  
changed lines
  Added in v.90

  ViewVC Help
Powered by ViewVC 1.1.21