source: LMDZ.3.3/tags/IPSL-CM4_LJ29_OPT/libf/dyn3d/gcm.F @ 497

Last change on this file since 497 was 497, checked in by (none), 20 years ago

This commit was manufactured by cvs2svn to create tag
'IPSL-CM4_LJ29_OPT'.

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 24.5 KB
Line 
1
2      PROGRAM gcm
3
4      USE IOIPSL
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:  P. Le Van /L. Fairhead/F.Hourdin
16c   -------
17c
18c   Objet:
19c   ------
20c
21c   GCM LMD nouvelle grille
22c
23c=======================================================================
24c
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 = 3  dans   traceur  (29/04/97) .
31c
32c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
33c
34c-----------------------------------------------------------------------
35c   Declarations:
36c   -------------
37
38#include "dimensions.h"
39#include "paramet.h"
40#include "comconst.h"
41#include "comdissnew.h"
42#include "comvert.h"
43#include "comgeom.h"
44#include "logic.h"
45#include "temps.h"
46#include "control.h"
47#include "ener.h"
48#include "netcdf.inc"
49#include "description.h"
50#include "serre.h"
51#include "tracstoke.h"
52
53
54      INTEGER         longcles
55      PARAMETER     ( longcles = 20 )
56      REAL  clesphy0( longcles )
57      SAVE  clesphy0
58
59      INTEGER*4  iday ! jour julien
60      REAL       time ! Heure de la journee en fraction d'1 jour
61      REAL zdtvr
62      INTEGER nbetatmoy, nbetatdem,nbetat
63
64c   variables dynamiques
65      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
66      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
67      REAL q(ip1jmp1,llm,nqmx)               ! champs advectes
68      REAL ps(ip1jmp1)                       ! pression  au sol
69      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
70      REAL pks(ip1jmp1)                      ! exner au  sol
71      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
72      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
73      REAL masse(ip1jmp1,llm)                ! masse d'air
74      REAL phis(ip1jmp1)                     ! geopotentiel au sol
75      REAL phi(ip1jmp1,llm)                  ! geopotentiel
76      REAL w(ip1jmp1,llm)                    ! vitesse verticale
77
78c variables dynamiques intermediaire pour le transport
79      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm) !flux de masse
80
81c   variables dynamiques au pas -1
82      REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
83      REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1)
84      REAL massem1(ip1jmp1,llm)
85
86c   tendances dynamiques
87      REAL dv(ip1jm,llm),du(ip1jmp1,llm)
88      REAL dteta(ip1jmp1,llm),dq(ip1jmp1,llm,nqmx),dp(ip1jmp1)
89
90c   tendances de la dissipation
91      REAL dvdis(ip1jm,llm),dudis(ip1jmp1,llm)
92      REAL dhdis(ip1jmp1,llm)
93
94c   tendances physiques
95      REAL dvfi(ip1jm,llm),dufi(ip1jmp1,llm)
96      REAL dhfi(ip1jmp1,llm),dqfi(ip1jmp1,llm,nqmx),dpfi(ip1jmp1)
97
98c   variables pour le fichier histoire
99      REAL dtav      ! intervalle de temps elementaire
100
101      REAL tppn(iim),tpps(iim),tpn,tps
102c
103      INTEGER iadv(nqmx) ! indice schema de transport pour le traceur iq
104
105      INTEGER itau,itaufinp1,iav
106
107      EXTERNAL caldyn, traceur
108      EXTERNAL dissip,geopot,iniconst,inifilr
109      EXTERNAL integrd,SCOPY
110      EXTERNAL iniav,writeav,writehist
111      EXTERNAL inigeom
112      EXTERNAL exner_hyb,addit
113      EXTERNAL defrun_new, test_period
114      REAL  SSUM
115      REAL time_0 , finvmaold(ip1jmp1,llm)
116
117      LOGICAL lafin
118      INTEGER ij,iq,l,numvanle,iapp_tracvl
119
120
121      INTEGER fluxid, fluxvid,fluxdid
122      integer histid, histvid, histaveid
123      real time_step, t_wrt, t_ops
124
125      REAL rdayvrai,rdaym_ini,rday_ecri
126      LOGICAL first
127      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm)
128c+jld variables test conservation energie
129      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
130C     Tendance de la temp. potentiel d (theta)/ d t due a la
131C     tansformation d'energie cinetique en energie thermique
132C     cree par la dissipation
133      REAL dhecdt(ip1jmp1,llm)
134      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
135      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
136      CHARACTER*15 ztit
137      INTEGER   ip_ebil_dyn  ! PRINT level for energy conserv. diag.
138      SAVE      ip_ebil_dyn
139      DATA      ip_ebil_dyn/0/
140c-jld
141
142      LOGICAL offline  ! Controle du stockage ds "fluxmass"
143      PARAMETER (offline=.false.)
144
145      character*80 dynhist_file, dynhistave_file
146      character*20 modname
147      character*80 abort_message
148
149C Calendrier
150      LOGICAL true_calendar
151      PARAMETER (true_calendar = .false.)
152C Run nudge
153      LOGICAL ok_nudge
154      PARAMETER (ok_nudge = .false.)
155c
156
157c-----------------------------------------------------------------------
158c   Initialisations:
159c   ----------------
160
161      abort_message = 'last timestep reached'
162      modname = 'gcm'
163      descript = 'Run GCM LMDZ'
164      lafin    = .FALSE.
165      dynhist_file = 'dyn_hist.nc'
166      dynhistave_file = 'dyn_hist_ave.nc'
167
168      if (true_calendar) then
169        call ioconf_calendar('gregorian')
170      else
171        call ioconf_calendar('360d')
172      endif
173c-----------------------------------------------------------------------
174c
175c  ....  Choix  des shemas d'advection pour l'eau et les traceurs  ...
176c  ...................................................................
177c
178c     iadv = 1    shema  transport type "humidite specifique LMD" 
179c     iadv = 2    shema   amont
180c     iadv = 3    shema  Van-leer
181c     iadv = 4    schema  Van-leer + humidite specifique
182c                        Modif F.Codron
183c
184c     dans le tableau q(ij,l,iq) , iq = 1  pour l'eau vapeur
185c                                , iq = 2  pour l'eau liquide
186c         et eventuellement      , iq = 3, nqmx pour les autres traceurs
187c
188      DO iq = 1, nqmx
189       iadv( iq ) = 3
190      ENDDO
191c
192c     iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
193      iadv( 1 ) = 4
194c
195       IF( iadv(1).EQ.1 ) PRINT *,' Choix du shema humidite specifique'
196     * ,' pour la vapeur d''eau'
197       IF( iadv(1).EQ.2 ) PRINT *,' Choix du shema  amont',' pour la'
198     * ,' vapeur d''eau '
199       IF( iadv(1).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour'
200     * ,'la vapeur d''eau'
201       IF( iadv(1).EQ.4 ) PRINT *,' Choix du shema  Van-Leer + humidite'
202     * ,' specifique pour la vapeur d''eau'
203c
204       IF( iadv(1).LE.0.OR.iadv(1).GT.4 )   THEN
205        PRINT *,' Erreur dans le choix de iadv (1).Corriger et repasser
206     * ,  car  iadv(1) = ', iadv(1)
207         CALL ABORT
208       ENDIF
209
210      DO  iq = 2, nqmx
211       IF( iadv(iq).EQ.1 ) PRINT *,' Choix du shema humidite specifique'
212     * ,' pour le traceur no ', iq
213       IF( iadv(iq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour le'
214     * ,' traceur no ', iq
215       IF( iadv(iq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour'
216     * ,'le traceur no ', iq
217
218       IF( iadv(iq).EQ.4 )  THEN
219         PRINT *,' Le shema  Van-Leer + humidite specifique ',
220     * ' est  uniquement pour la vapeur d eau .'
221         PRINT *,' Corriger iadv( ',iq, ')  et repasser ! '
222         CALL ABORT
223       ENDIF
224
225       IF( iadv(iq).LE.0.OR.iadv(iq).GT.4 )   THEN
226       PRINT *,' Erreur dans le  choix de  iadv . Corriger et repasser
227     * . '
228         CALL ABORT
229       ENDIF
230      ENDDO
231c
232      first = .TRUE.
233      numvanle = nqmx + 1
234      DO  iq = 1, nqmx
235        IF((iadv(iq).EQ.3.OR.iadv(iq).EQ.4).AND.first ) THEN
236          numvanle = iq
237          first    = .FALSE.
238        ENDIF
239      ENDDO
240c
241      DO  iq = 1, nqmx
242      IF( (iadv(iq).NE.3.AND.iadv(iq).NE.4).AND.iq.GT.numvanle )  THEN
243          PRINT *,' Il y a discontinuite dans le choix du shema de ',
244     *    'Van-leer pour les traceurs . Corriger et repasser . '
245           CALL ABORT
246      ENDIF
247        IF( iadv(iq).LT.1.OR.iadv(iq).GT.4 )    THEN
248          PRINT *,' Le choix de  iadv  est errone pour le traceur ',
249     *    iq
250         STOP
251        ENDIF
252      ENDDO
253c
254
255      CALL dynetat0("start.nc",nqmx,vcov,ucov,
256     .              teta,q,masse,ps,phis, time_0)
257
258
259c     OPEN( 99,file ='run.def',status='old',form='formatted')
260c      CALL defrun_new( 99, .TRUE. , clesphy0 )
261      CALL conf_gcm( 99, .TRUE. , clesphy0 )
262c     CLOSE(99)
263
264c  on recalcule eventuellement le pas de temps
265
266      IF(MOD(day_step,iperiod).NE.0)
267     * STOP'Il faut choisir un nb de pas par jour multiple de iperiod'
268
269      IF(MOD(day_step,iphysiq).NE.0)
270     * STOP'Il faut choisir un nb de pas par jour multiple de iphysiq'
271
272      zdtvr    = daysec/FLOAT(day_step)
273        IF(dtvr.NE.zdtvr) THEN
274         PRINT*,'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
275        ENDIF
276C
277C on remet le calendrier à zero
278c
279      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
280        write(*,*)' Attention les dates initiales lues dans le fichier'
281        write(*,*)' restart ne correspondent pas a celles lues dans '
282        write(*,*)' gcm.def'
283        if (raz_date .ne. 1) then
284          write(*,*)' On garde les dates du fichier restart'
285        else
286          annee_ref = anneeref
287          day_ref = dayref
288          day_ini = dayref
289          itau_dyn = 0
290          itau_phy = 0
291          time_0 = 0.
292          write(*,*)' On reinitialise a la date lue dans gcm.def'
293        endif
294      ELSE
295        raz_date = 0
296      endif
297
298c  nombre d'etats dans les fichiers demarrage et histoire
299      nbetatdem = nday / iecri
300      nbetatmoy = nday / periodav + 1
301
302      dtvr = zdtvr
303      CALL iniconst
304      CALL inigeom
305
306      CALL inifilr
307c
308c   ......    P.Le Van    ( modif  le 29/04/97 )   ......... 
309c
310      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
311     *                tetagdiv, tetagrot , tetatemp              )
312c+jld
313C     initialisation constantes thermo utilisees dans diagedyn
314      IF (ip_ebil_dyn.ge.1 ) THEN
315        CALL suphec
316      ENDIF
317c-jld
318c
319
320      CALL pression ( ip1jmp1, ap, bp, ps, p       )
321      CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
322c
323
324c  numero de stockage pour les fichiers de redemarrage:
325
326c-----------------------------------------------------------------------
327c   temps de depart et de fin:
328c   --------------------------
329
330      itau = 0
331      iday = day_ini+itau/day_step
332      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
333         IF(time.GT.1.) THEN
334          time = time-1.
335          iday = iday+1
336         ENDIF
337      itaufin   = nday*day_step
338      itaufinp1 = itaufin +1
339
340      day_end = day_ini + nday
341      PRINT 300, itau,itaufin,day_ini,day_end
342
343      CALL dynredem0("restart.nc", day_end, phis, nqmx)
344
345      ecripar = .TRUE.
346
347      time_step = zdtvr
348      t_ops = iecri * daysec
349      t_wrt = iecri * daysec
350C      CALL inithist(dynhist_file,day_ref,annee_ref,time_step,
351c     .              t_ops, t_wrt, nqmx, histid, histvid)
352
353      t_ops = iperiod * time_step
354      t_wrt = periodav * daysec
355      CALL initdynav(dynhistave_file,day_ref,annee_ref,time_step,
356     .              t_ops, t_wrt, nqmx, histaveid)
357
358      dtav = iperiod*dtvr/daysec
359
360
361c   Quelques initialisations pour les traceurs
362      call initial0(ijp1llm*nqmx,dq)
363      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
364      istphy=istdyn/iphysiq
365
366c-----------------------------------------------------------------------
367c   Debut de l'integration temporelle:
368c   ----------------------------------
369
370
371   1  CONTINUE
372
373
374
375      if (ok_nudge) then
376        call nudge(itau,ucov,vcov,teta,masse,ps)
377      endif
378c
379c     IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
380        CALL  test_period ( ucov,vcov,teta,q,p,phis )
381c        PRINT *,' ----   Test_period apres continue   OK ! -----', itau
382c     ENDIF
383c
384      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
385      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
386      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
387      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
388      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
389
390      forward = .TRUE.
391      leapf   = .FALSE.
392      dt      =  dtvr
393
394c   ...    P.Le Van .26/04/94  ....
395
396      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
397      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
398
399
400   2  CONTINUE
401
402c-----------------------------------------------------------------------
403
404c   date:
405c   -----
406
407
408c   gestion des appels de la physique et des dissipations:
409c   ------------------------------------------------------
410c
411c   ...    P.Le Van  ( 6/02/95 )  ....
412
413      apphys = .FALSE.
414      statcl = .FALSE.
415      conser = .FALSE.
416      apdiss = .FALSE.
417
418      IF( purmats ) THEN
419         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
420         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
421         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
422     $                              .AND.   physic    ) apphys = .TRUE.
423      ELSE
424         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
425         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
426         IF( MOD(itau+1,iphysiq).EQ.0. AND. physic    ) apphys = .TRUE.
427      END IF
428
429c-----------------------------------------------------------------------
430c   calcul des tendances dynamiques:
431c   --------------------------------
432
433      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
434c
435c
436      CALL caldyn
437     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
438     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
439
440c-----------------------------------------------------------------------
441c   calcul des tendances advection des traceurs (dont l'humidite)
442c   -------------------------------------------------------------
443
444      IF( forward. OR . leapf )  THEN
445c
446        DO 15  iq = 1, nqmx
447c
448         IF( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
449           CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
450
451         ELSE IF( iq.EQ. nqmx )   THEN
452c
453c           iapp_tracvl = 5
454            iapp_tracvl = iperiod
455            print*,'***WARNING***: iapp_tracvl = iperiod'
456c
457cccc     iapp_tracvl est la frequence en pas du groupement des flux
458cccc      de masse pour  Van-Leer dans la routine  tracvl  .
459c
460c            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
461            CALL vanleer(numvanle,iapp_tracvl,2,q,pbaru,pbarv,
462     *                      p, masse, dq,  iadv(1), teta, pk     )
463c
464            print*,'***WARNING***: Appel vanleer avec 2 traceurs'
465            print*,'               et non nqmx'
466c                   ...  Modif  F.Codron  ....
467c
468         ENDIF
469c
470 15     CONTINUE
471C
472         IF (offline) THEN
473Cmaf stokage du flux de masse pour traceurs OFF-LINE
474
475            CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
476     .   time_step, itau)
477
478
479         ENDIF
480c
481      ENDIF
482
483
484c-----------------------------------------------------------------------
485c   integrations dynamique et traceurs:
486c   ----------------------------------
487
488
489       CALL integrd ( iadv, 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
490     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
491     $              finvmaold                                    )
492
493
494c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
495c
496c-----------------------------------------------------------------------
497c   calcul des tendances physiques:
498c   -------------------------------
499c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
500c
501       IF( purmats )  THEN
502          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
503       ELSE
504          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
505       ENDIF
506c
507c
508       IF( apphys )  THEN
509c
510c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
511c
512
513         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
514         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
515
516           rdaym_ini  = itau * dtvr / daysec
517           rdayvrai   = rdaym_ini  + day_ini
518
519           IF ( ecritphy.LT.1. )  THEN
520             rday_ecri = rdaym_ini
521           ELSE
522             rday_ecri = NINT( rdayvrai )
523           ENDIF
524c
525
526c rajout debug
527c       lafin = .true.
528c+jld
529      IF (ip_ebil_dyn.ge.1 ) THEN
530          ztit='bil dyn'
531          CALL diagedyn(ztit,2,1,1,dtphys
532     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
533     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
534      ENDIF
535c-jld
536        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
537     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
538     $     du,dv,dteta,dq,w,clesphy0, dufi,dvfi,dhfi,dqfi,dpfi  )
539
540c      ajout des tendances physiques:
541c      ------------------------------
542          CALL addfi( nqmx, dtphys, leapf, forward   ,
543     $                  ucov, vcov, teta , q   ,ps ,
544     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
545c
546c+jld
547      IF (ip_ebil_dyn.ge.1 ) THEN
548          ztit='bil phys'
549          CALL diagedyn(ztit,2,1,1,dtphys
550     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
551     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
552      ENDIF
553c-jld
554       ENDIF
555
556        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
557        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
558
559c-----------------------------------------------------------------------
560c
561c
562c   dissipation horizontale et verticale  des petites echelles:
563c   ----------------------------------------------------------
564
565      IF(apdiss) THEN
566c+jld
567      IF (ip_ebil_dyn.ge.2 ) THEN
568          ztit='avant dissip'
569          CALL diagedyn(ztit,2,2,2,dtvr
570     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
571     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
572      ENDIF
573        CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
574        CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin0  )
575c-jld
576
577         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
578
579         CALL addit( ijp1llm,ucov ,dudis,ucov )
580         CALL addit( ijmllm ,vcov ,dvdis,vcov )
581c+jld
582        CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
583        CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin  )
584C
585C       On rajoute la tendance due a la transform. Ec -> E therm. cree
586C       lors de la dissipation
587        DO l  =  1, llm
588          DO    ij     = 1, ip1jmp1
589            dhecdt(ij,l)= (ecin0(ij,l)-ecin(ij,l))/ pk(ij,l)
590            dhdis(ij,l) = dhdis(ij,l) + dhecdt(ij,l)
591          ENDDO
592        ENDDO
593c-jld
594         CALL addit( ijp1llm,teta ,dhdis,teta )
595c+jld
596c
597         IF (ip_ebil_dyn.ge.2 ) THEN
598             ztit='apres dissip'
599             CALL diagedyn(ztit,2,2,2,dtdiss
600     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
601     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
602         ENDIF
603c-jld
604
605c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
606c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
607c
608
609        DO l  =  1, llm
610          DO ij =  1,iim
611           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
612           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
613          ENDDO
614           tpn  = SSUM(iim,tppn,1)/apoln
615           tps  = SSUM(iim,tpps,1)/apols
616
617          DO ij = 1, iip1
618           teta(  ij    ,l) = tpn
619           teta(ij+ip1jm,l) = tps
620          ENDDO
621        ENDDO
622
623        DO ij =  1,iim
624          tppn(ij)  = aire(  ij    ) * ps (  ij    )
625          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
626        ENDDO
627          tpn  = SSUM(iim,tppn,1)/apoln
628          tps  = SSUM(iim,tpps,1)/apols
629
630        DO ij = 1, iip1
631          ps(  ij    ) = tpn
632          ps(ij+ip1jm) = tps
633        ENDDO
634
635
636      END IF
637
638c ajout debug
639c              IF( lafin ) then 
640c                abort_message = 'Simulation finished'
641c                call abort_gcm(modname,abort_message,0)
642c              ENDIF
643       
644c   ********************************************************************
645c   ********************************************************************
646c   .... fin de l'integration dynamique  et physique pour le pas itau ..
647c   ********************************************************************
648c   ********************************************************************
649
650c   preparation du pas d'integration suivant  ......
651
652      IF ( .NOT.purmats ) THEN
653c       ........................................................
654c       ..............  schema matsuno + leapfrog  ..............
655c       ........................................................
656
657            IF(forward. OR. leapf) THEN
658              itau= itau + 1
659              iday= day_ini+itau/day_step
660              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
661                IF(time.GT.1.) THEN
662                  time = time-1.
663                  iday = iday+1
664                ENDIF
665            ENDIF
666
667
668            IF( itau. EQ. itaufinp1 ) then 
669
670
671              abort_message = 'Simulation finished'
672              call abort_gcm(modname,abort_message,0)
673            ENDIF
674c-----------------------------------------------------------------------
675c   ecriture du fichier histoire moyenne:
676c   -------------------------------------
677
678            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
679               IF(itau.EQ.itaufin) THEN
680                  iav=1
681               ELSE
682                  iav=0
683               ENDIF
684               CALL writedynav(histaveid, nqmx, itau,vcov ,
685     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
686cccIM cf. FH
687               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
688     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
689
690            ENDIF
691
692c-----------------------------------------------------------------------
693c   ecriture de la bande histoire:
694c   ------------------------------
695
696            IF( MOD(itau,iecri*day_step).EQ.0) THEN
697
698               nbetat = nbetatdem
699       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
700c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
701c     ,                          ucov,teta,phi,q,masse,ps,phis)
702
703
704            ENDIF
705
706            IF(itau.EQ.itaufin) THEN
707
708
709       PRINT *,' Appel test_period avant redem ', itau
710       CALL  test_period ( ucov,vcov,teta,q,p,phis )
711       CALL dynredem1("restart.nc",0.0,
712     .                     vcov,ucov,teta,q,nqmx,masse,ps)
713
714              CLOSE(99)
715            ENDIF
716
717c-----------------------------------------------------------------------
718c   gestion de l'integration temporelle:
719c   ------------------------------------
720
721            IF( MOD(itau,iperiod).EQ.0 )    THEN
722                    GO TO 1
723            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
724
725                   IF( forward )  THEN
726c      fin du pas forward et debut du pas backward
727
728                      forward = .FALSE.
729                        leapf = .FALSE.
730                           GO TO 2
731
732                   ELSE
733c      fin du pas backward et debut du premier pas leapfrog
734
735                        leapf =  .TRUE.
736                        dt  =  2.*dtvr
737                        GO TO 2
738                   END IF
739            ELSE
740
741c      ......   pas leapfrog  .....
742
743                 leapf = .TRUE.
744                 dt  = 2.*dtvr
745                 GO TO 2
746            END IF
747
748      ELSE
749
750c       ........................................................
751c       ..............       schema  matsuno        ...............
752c       ........................................................
753            IF( forward )  THEN
754
755             itau =  itau + 1
756             iday = day_ini+itau/day_step
757             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
758
759                  IF(time.GT.1.) THEN
760                   time = time-1.
761                   iday = iday+1
762                  ENDIF
763
764               forward =  .FALSE.
765               IF( itau. EQ. itaufinp1 ) then 
766                 abort_message = 'Simulation finished'
767                 call abort_gcm(modname,abort_message,0)
768               ENDIF
769               GO TO 2
770
771            ELSE
772
773            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
774               IF(itau.EQ.itaufin) THEN
775                  iav=1
776               ELSE
777                  iav=0
778               ENDIF
779               CALL writedynav(histaveid, nqmx, itau,vcov ,
780     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
781cccIM cf. FH
782               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
783     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
784
785            ENDIF
786
787               IF(MOD(itau,iecri*day_step).EQ.0) THEN
788                  nbetat = nbetatdem
789       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
790c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
791c     ,                          ucov,teta,phi,q,masse,ps,phis)
792               ENDIF
793
794                 IF(itau.EQ.itaufin)
795     . CALL dynredem1("restart.nc",0.0,
796     .                     vcov,ucov,teta,q,nqmx,masse,ps)
797
798                 forward = .TRUE.
799                 GO TO  1
800
801            ENDIF
802
803      END IF
804
805 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
806     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
807
808      STOP
809      END
Note: See TracBrowser for help on using the repository browser.