source: LMDZ4/trunk/libf/dyn3d/guide.F @ 1042

Last change on this file since 1042 was 1042, checked in by lmdzadmin, 16 years ago

Par defaut, pas de sorties grads
FH/IM

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 15.6 KB
Line 
1!
2! $Header$
3!
4      subroutine guide(itau,ucov,vcov,teta,q,masse,ps)
5
6      IMPLICIT NONE
7
8c      ......   Version  du 10/01/98    ..........
9
10c             avec  coordonnees  verticales hybrides
11c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
12
13c=======================================================================
14c
15c   Auteur:  F.Hourdin
16c   -------
17c
18c   Objet:
19c   ------
20c
21c   GCM LMD nouvelle grille
22c
23c=======================================================================
24
25c   ...  Dans inigeom , nouveaux calculs pour les elongations  cu , cv
26c        et possibilite d'appeler une fonction f(y)  a derivee tangente
27c        hyperbolique a la  place de la fonction a derivee sinusoidale.         
28
29c   ...  Possibilite de choisir le shema de Van-leer pour l'advection de
30c         q  , en faisant iadv = 10  dans   traceur  (29/04/97) .
31c
32c-----------------------------------------------------------------------
33c   Declarations:
34c   -------------
35
36#include "dimensions.h"
37#include "paramet.h"
38#include "comconst.h"
39#include "comdissnew.h"
40#include "comvert.h"
41#include "comgeom.h"
42#include "logic.h"
43#include "temps.h"
44#include "control.h"
45#include "ener.h"
46#include "netcdf.inc"
47#include "description.h"
48#include "serre.h"
49#include "tracstoke.h"
50#include "guide.h"
51
52
53c   variables dynamiques
54      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
55      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
56      REAL q(ip1jmp1,llm)                 ! temperature potentielle
57      REAL ps(ip1jmp1)                       ! pression  au sol
58      REAL masse(ip1jmp1,llm)                ! masse d'air
59
60c   common passe pour des sorties
61      real dxdys(iip1,jjp1),dxdyu(iip1,jjp1),dxdyv(iip1,jjm)
62      common/comdxdy/dxdys,dxdyu,dxdyv
63
64c   variables dynamiques pour les reanalyses.
65      REAL ucovrea1(ip1jmp1,llm),vcovrea1(ip1jm,llm) !vts cov reas
66      REAL tetarea1(ip1jmp1,llm)             ! temp pot  reales
67      REAL qrea1(ip1jmp1,llm)             ! temp pot  reales
68      REAL masserea1(ip1jmp1,llm)             ! masse
69      REAL psrea1(ip1jmp1)             ! ps
70      REAL ucovrea2(ip1jmp1,llm),vcovrea2(ip1jm,llm) !vts cov reas
71      REAL tetarea2(ip1jmp1,llm)             ! temp pot  reales
72      REAL qrea2(ip1jmp1,llm)             ! temp pot  reales
73      REAL masserea2(ip1jmp1,llm)             ! masse
74      REAL psrea2(ip1jmp1)             ! ps
75      real latmin
76
77      real alpha_q(ip1jmp1)
78      real alpha_T(ip1jmp1),alpha_P(ip1jmp1)
79      real alpha_u(ip1jmp1),alpha_v(ip1jm)
80      real dday_step,toto,reste,itau_test
81      INTEGER step_rea,count_no_rea
82
83cIM 180305   real aire_min,aire_max
84      integer ilon,ilat
85      real factt,ztau(ip1jmp1)
86
87      INTEGER itau,ij,l,i,j
88      integer ncidpl,varidpl,nlev,status
89      integer rcod,rid
90      real ditau,tau,a
91      save nlev
92
93c  TEST SUR QSAT
94      real p(ip1jmp1,llmp1),pk(ip1jmp1,llm),pks(ip1jmp1)
95      real pkf(ip1jmp1,llm)
96      real pres(ip1jmp1,llm)
97      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm)
98
99      real qsat(ip1jmp1,llm)
100      real unskap
101      real tnat(ip1jmp1,llm)
102ccccccccccccccccc
103
104
105      LOGICAL first
106      save first
107      data first/.true./
108
109      save ucovrea1,vcovrea1,tetarea1,masserea1,psrea1,qrea1
110      save ucovrea2,vcovrea2,tetarea2,masserea2,psrea2,qrea2
111
112      save alpha_T,alpha_q,alpha_u,alpha_v,alpha_P,itau_test
113      save step_rea,count_no_rea
114
115#define gradsfile
116#undef gradsfile
117
118#ifdef gradsfile
119      character*10 file
120      integer igrads
121      real dtgrads
122      save igrads,dtgrads
123      data igrads,dtgrads/2,100./
124#endif
125C-----------------------------------------------------------------------
126c calcul de l'humidite saturante
127C-----------------------------------------------------------------------
128c     print*,'OK0'
129      CALL pression( ip1jmp1, ap, bp, ps, p )
130      call massdair(p,masse)
131c     print*,'OK1'
132      CALL exner_hyb(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf)
133c     print*,'OK2'
134      tnat(:,:)=pk(:,:)*teta(:,:)/cpp
135c     print*,'OK3'
136      unskap   = 1./ kappa
137      pres(:,:)=preff*(pk(:,:)/cpp)**unskap
138c     print*,'OK4'
139      call q_sat(iip1*jjp1*llm,tnat,pres,qsat)
140
141C-----------------------------------------------------------------------
142
143c-----------------------------------------------------------------------
144c   initialisations pour la lecture des reanalyses.
145c    alpha determine la part des injections de donnees a chaque etape
146c    alpha=1 signifie pas d'injection
147c    alpha=0 signifie injection totale
148c-----------------------------------------------------------------------
149
150c     print*,'ONLINE=',online
151      if(online.eq.-1) then
152          return
153      endif
154
155      if (first) then
156
157         print*,'initialisation du guide '
158         call conf_guide
159         print*,'apres conf_guide'
160
161
162#ifdef gradsfile
163         file='guide'
164         call inigrads(igrads,iip1
165     s  ,rlonv,180./pi,-180.,180.,jjp1,rlatu,-90.,90.,180./pi
166     s  ,llm,presnivs,1.
167     s  ,dtgrads,file,'dyn_zon ')
168#endif
169
170         print*
171     s   ,'1: en-ligne, 0: hors-ligne (x=x_rea), -1: climat (x=x_gcm)'
172
173         if(online.eq.-1) return
174         if (online.eq.1) then
175
176cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
177c  Constantes de temps de rappel en jour
178c  0.1 c'est en gros 2h30.
179c  1e10  est une constante infinie donc en gros pas de guidage
180cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
181c   coordonnees du centre du zoom
182           call coordij(clon,clat,ilon,ilat)
183c   aire de la maille au centre du zoom
184           aire_min=aire(ilon+(ilat-1)*iip1)
185c   aire maximale de la maille
186           aire_max=0.
187           do ij=1,ip1jmp1
188              aire_max=max(aire_max,aire(ij))
189           enddo
190C  factt = pas de temps en fraction de jour
191           factt=dtvr*iperiod/daysec
192
193c     subroutine tau2alpha(type,im,jm,factt,taumin,taumax,alpha)
194           call tau2alpha(3,iip1,jjm ,factt,tau_min_v,tau_max_v,alpha_v)
195           call tau2alpha(2,iip1,jjp1,factt,tau_min_u,tau_max_u,alpha_u)
196           call tau2alpha(1,iip1,jjp1,factt,tau_min_T,tau_max_T,alpha_T)
197           call tau2alpha(1,iip1,jjp1,factt,tau_min_P,tau_max_P,alpha_P)
198           call tau2alpha(1,iip1,jjp1,factt,tau_min_q,tau_max_q,alpha_q)
199
200           call dump2d(iip1,jjp1,aire,'AIRE MAILLe ')
201           call dump2d(iip1,jjp1,alpha_u,'COEFF U   ')
202           call dump2d(iip1,jjp1,alpha_T,'COEFF T   ')
203
204cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
205c   Cas ou on force exactement par les variables analysees
206         else
207            alpha_T=0.
208            alpha_u=0.
209            alpha_v=0.
210            alpha_P=0.
211c           physic=.false.
212         endif
213
214         itau_test=1001
215         step_rea=1
216         count_no_rea=0
217         ncidpl=-99
218
219c    itau_test    montre si l'importation a deja ete faite au rang itau
220c lecture d'un fichier netcdf pour determiner le nombre de niveaux
221         if (guide_u) then
222           if (ncidpl.eq.-99) ncidpl=NCOPN('u.nc',NCNOWRIT,rcod)
223         endif
224c
225         if (guide_v) then
226           if (ncidpl.eq.-99) ncidpl=NCOPN('v.nc',NCNOWRIT,rcod)
227         endif
228c
229         if (guide_T) then
230           if (ncidpl.eq.-99) ncidpl=NCOPN('T.nc',NCNOWRIT,rcod)
231         endif
232c
233         if (guide_Q) then
234           if (ncidpl.eq.-99) ncidpl=NCOPN('hur.nc',NCNOWRIT,rcod)
235         endif
236c
237         if (ncep) then
238          status=NF_INQ_DIMID(ncidpl,'LEVEL',rid)
239         else
240          status=NF_INQ_DIMID(ncidpl,'PRESSURE',rid)
241         endif
242          status=NF_INQ_DIMLEN(ncidpl,rid,nlev)
243         print *,'nlev', nlev
244          call ncclos(ncidpl,rcod)
245c   Lecture du premier etat des reanalyses.
246         call read_reanalyse(1,ps
247     s   ,ucovrea2,vcovrea2,tetarea2,qrea2,masserea2,psrea2,1,nlev)
248         qrea2(:,:)=max(qrea2(:,:),0.1)
249
250
251c-----------------------------------------------------------------------
252c   Debut de l'integration temporelle:
253c   ----------------------------------
254
255      endif ! first
256c
257C-----------------------------------------------------------------------
258C----- IMPORTATION DES VENTS,PRESSION ET TEMPERATURE REELS:
259C-----------------------------------------------------------------------
260
261      ditau=real(itau)
262      DDAY_step=real(day_step)
263      write(*,*)'ditau,dday_step'
264      write(*,*)ditau,dday_step
265      toto=4*ditau/dday_step
266      reste=toto-aint(toto)
267c     write(*,*)'toto,reste',toto,reste
268
269      if (reste.eq.0.) then
270        if (itau_test.eq.itau) then
271          write(*,*)'deuxieme passage de advreel a itau=',itau
272          stop
273        else
274        vcovrea1(:,:)=vcovrea2(:,:)
275        ucovrea1(:,:)=ucovrea2(:,:)
276        tetarea1(:,:)=tetarea2(:,:)
277        qrea1(:,:)=qrea2(:,:)
278
279          print*,'LECTURE REANALYSES, pas ',step_rea
280     s         ,'apres ',count_no_rea,' non lectures'
281           step_rea=step_rea+1
282           itau_test=itau
283           call read_reanalyse(step_rea,ps
284     s     ,ucovrea2,vcovrea2,tetarea2,qrea2,masserea2,psrea2,1,nlev)
285         qrea2(:,:)=max(qrea2(:,:),0.1)
286      factt=dtvr*iperiod/daysec
287      ztau(:)=factt/max(alpha_T(:),1.e-10)
288#ifdef gradsfile
289      call wrgrads(igrads,1,aire   ,'aire      ','aire      ' )
290      call wrgrads(igrads,1,dxdys  ,'dxdy      ','dxdy      ' )
291      call wrgrads(igrads,1,alpha_u,'au        ','au        ' )
292      call wrgrads(igrads,1,alpha_T,'at        ','at        ' )
293      call wrgrads(igrads,1,ztau,'taut      ','taut      ' )
294      call wrgrads(igrads,llm,ucov,'u         ','u         ' )
295      call wrgrads(igrads,llm,ucovrea2,'ua        ','ua        ' )
296      call wrgrads(igrads,llm,teta,'T         ','T         ' )
297      call wrgrads(igrads,llm,tetarea2,'Ta        ','Ta        ' )
298      call wrgrads(igrads,llm,qrea2,'Qa        ','Qa        ' )
299      call wrgrads(igrads,llm,q,'Q         ','Q         ' )
300
301      call wrgrads(igrads,llm,qsat,'QSAT      ','QSAT      ' )
302#endif
303        endif
304      else
305        count_no_rea=count_no_rea+1
306      endif
307 
308C-----------------------------------------------------------------------
309c   Guidage
310c    x_gcm = a * x_gcm + (1-a) * x_reanalyses
311C-----------------------------------------------------------------------
312
313       if(ini_anal) print*,'ATTENTION !!! ON PART DU GUIDAGE'
314
315      ditau=real(itau)
316      dday_step=real(day_step)
317
318
319      tau=4*ditau/dday_step
320      tau=tau-aint(tau)
321
322c  ucov
323      if (guide_u) then
324         do l=1,llm
325            do ij=1,ip1jmp1
326                a=(1.-tau)*ucovrea1(ij,l)+tau*ucovrea2(ij,l)
327                ucov(ij,l)=(1.-alpha_u(ij))*ucov(ij,l)+alpha_u(ij)*a
328                if (first.and.ini_anal) ucov(ij,l)=a
329            enddo
330         enddo
331      endif
332
333c  teta
334      if (guide_T) then
335         do l=1,llm
336            do ij=1,ip1jmp1
337                a=(1.-tau)*tetarea1(ij,l)+tau*tetarea2(ij,l)
338                teta(ij,l)=(1.-alpha_T(ij))*teta(ij,l)+alpha_T(ij)*a
339                if (first.and.ini_anal) teta(ij,l)=a
340            enddo
341         enddo
342      endif
343
344c  P
345      if (guide_P) then
346         do ij=1,ip1jmp1
347             a=(1.-tau)*psrea1(ij)+tau*psrea2(ij)
348             ps(ij)=(1.-alpha_P(ij))*ps(ij)+alpha_P(ij)*a
349             if (first.and.ini_anal) ps(ij)=a
350         enddo
351         CALL pression(ip1jmp1,ap,bp,ps,p)
352         CALL massdair(p,masse)
353      endif
354
355
356c  q
357      if (guide_Q) then
358         do l=1,llm
359            do ij=1,ip1jmp1
360                a=(1.-tau)*qrea1(ij,l)+tau*qrea2(ij,l)
361c   hum relative en % -> hum specif
362                a=qsat(ij,l)*a*0.01
363                q(ij,l)=(1.-alpha_Q(ij))*q(ij,l)+alpha_Q(ij)*a
364                if (first.and.ini_anal) q(ij,l)=a
365            enddo
366         enddo
367      endif
368
369c vcov
370      if (guide_v) then
371         do l=1,llm
372            do ij=1,ip1jm
373                a=(1.-tau)*vcovrea1(ij,l)+tau*vcovrea2(ij,l)
374                vcov(ij,l)=(1.-alpha_v(ij))*vcov(ij,l)+alpha_v(ij)*a
375                if (first.and.ini_anal) vcov(ij,l)=a
376            enddo
377         enddo
378      endif
379
380c     call dump2d(iip1,jjp1,tetarea1,'TETA REA 1     ')
381c     call dump2d(iip1,jjp1,tetarea2,'TETA REA 2     ')
382c     call dump2d(iip1,jjp1,teta,'TETA           ')
383
384         first=.false.
385
386      return
387      end
388
389c=======================================================================
390      subroutine tau2alpha(type,pim,pjm,factt,taumin,taumax,alpha)
391c=======================================================================
392
393      implicit none
394
395#include "dimensions.h"
396#include "paramet.h"
397#include "comconst.h"
398#include "comgeom2.h"
399#include "guide.h"
400#include "serre.h"
401
402c   arguments :
403      integer type
404      integer pim,pjm
405      real factt,taumin,taumax,dxdymin,dxdymax
406      real dxdy_,alpha(pim,pjm)
407      real dxdy_min,dxdy_max
408
409c  local :
410      real alphamin,alphamax,gamma,xi
411      save gamma
412      integer i,j,ilon,ilat
413
414      logical first
415      save first
416      data first/.true./
417
418      real cus(iip1,jjp1),cvs(iip1,jjp1)
419      real cuv(iip1,jjm),cvu(iip1,jjp1)
420      real zdx(iip1,jjp1),zdy(iip1,jjp1)
421
422      real zlat
423      real dxdys(iip1,jjp1),dxdyu(iip1,jjp1),dxdyv(iip1,jjm)
424      common/comdxdy/dxdys,dxdyu,dxdyv
425
426      if (first) then
427         do j=2,jjm
428            do i=2,iip1
429               zdx(i,j)=0.5*(cu(i-1,j)+cu(i,j))/cos(rlatu(j))
430            enddo
431            zdx(1,j)=zdx(iip1,j)
432         enddo
433         do j=2,jjm
434            do i=1,iip1
435               zdy(i,j)=0.5*(cv(i,j-1)+cv(i,j))
436            enddo
437         enddo
438         do i=1,iip1
439            zdx(i,1)=zdx(i,2)
440            zdx(i,jjp1)=zdx(i,jjm)
441            zdy(i,1)=zdy(i,2)
442            zdy(i,jjp1)=zdy(i,jjm)
443         enddo
444         do j=1,jjp1
445            do i=1,iip1
446               dxdys(i,j)=sqrt(zdx(i,j)*zdx(i,j)+zdy(i,j)*zdy(i,j))
447            enddo
448         enddo
449         do j=1,jjp1
450            do i=1,iim
451               dxdyu(i,j)=0.5*(dxdys(i,j)+dxdys(i+1,j))
452            enddo
453            dxdyu(iip1,j)=dxdyu(1,j)
454         enddo
455         do j=1,jjm
456            do i=1,iip1
457               dxdyv(i,j)=0.5*(dxdys(i,j)+dxdys(i,j+1))
458            enddo
459         enddo
460
461         call dump2d(iip1,jjp1,dxdys,'DX2DY2 SCAL  ')
462         call dump2d(iip1,jjp1,dxdyu,'DX2DY2 U     ')
463         call dump2d(iip1,jjp1,dxdyv,'DX2DY2 v     ')
464
465c   coordonnees du centre du zoom
466           call coordij(clon,clat,ilon,ilat)
467c   aire de la maille au centre du zoom
468           dxdy_min=dxdys(ilon,ilat)
469c   dxdy maximale de la maille
470           dxdy_max=0.
471           do j=1,jjp1
472              do i=1,iip1
473                 dxdy_max=max(dxdy_max,dxdys(i,j))
474              enddo
475           enddo
476
477         if (abs(grossismx-1.).lt.0.1.or.abs(grossismy-1.).lt.0.1) then
478             print*,'ATTENTION modele peu zoome'
479             print*,'ATTENTION on prend une constante de guidage cste'
480             gamma=0.
481         else
482            gamma=(dxdy_max-2.*dxdy_min)/(dxdy_max-dxdy_min)
483            print*,'gamma=',gamma
484            if (gamma.lt.1.e-5) then
485              print*,'gamma =',gamma,'<1e-5'
486              stop
487            endif
488            print*,'gamma=',gamma
489            gamma=log(0.5)/log(gamma)
490         endif
491      endif
492
493      alphamin=factt/taumax
494      alphamax=factt/taumin
495
496      do j=1,pjm
497         do i=1,pim
498            if (type.eq.1) then
499               dxdy_=dxdys(i,j)
500               zlat=rlatu(j)*180./pi
501            elseif (type.eq.2) then
502               dxdy_=dxdyu(i,j)
503               zlat=rlatu(j)*180./pi
504            elseif (type.eq.3) then
505               dxdy_=dxdyv(i,j)
506               zlat=rlatv(j)*180./pi
507            endif
508         if (abs(grossismx-1.).lt.0.1.or.abs(grossismy-1.).lt.0.1) then
509c  pour une grille reguliere, xi=xxx**0=1 -> alpha=alphamin
510             alpha(i,j)=alphamin
511         else
512            xi=((dxdy_max-dxdy_)/(dxdy_max-dxdy_min))**gamma
513            xi=min(xi,1.)
514            if(lat_min_guide.le.zlat .and. zlat.le.lat_max_guide) then
515               alpha(i,j)=xi*alphamin+(1.-xi)*alphamax
516            else
517               alpha(i,j)=0.
518            endif
519         endif
520         enddo
521      enddo
522
523
524      return
525      end
Note: See TracBrowser for help on using the repository browser.