source: LMDZ4/branches/pre_V3/libf/dyn3dpar/guide_p.F @ 1387

Last change on this file since 1387 was 630, checked in by Laurent Fairhead, 19 years ago

Import d'une version parallele de la dynamique YM
LF

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