source: LMDZ.3.3/branches/rel-LF/libf/dyn3d/gcm.F @ 516

Last change on this file since 516 was 516, checked in by lmdzadmin, 20 years ago

Deplacement de commentaires pour raisons d'optimisation
LF

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 24.6 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      print*,'***WARNING***: Pour des rasions d optimisations'
366      print*,'***WARNING***: iapp_tracvl = iperiod'
367      print*,'***WARNING***: Appel vanleer avec 2 traceurs'
368      print*,'               et non nqmx'
369
370c-----------------------------------------------------------------------
371c   Debut de l'integration temporelle:
372c   ----------------------------------
373
374
375   1  CONTINUE
376
377
378
379      if (ok_nudge) then
380        call nudge(itau,ucov,vcov,teta,masse,ps)
381      endif
382c
383c     IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
384        CALL  test_period ( ucov,vcov,teta,q,p,phis )
385c        PRINT *,' ----   Test_period apres continue   OK ! -----', itau
386c     ENDIF
387c
388      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
389      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
390      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
391      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
392      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
393
394      forward = .TRUE.
395      leapf   = .FALSE.
396      dt      =  dtvr
397
398c   ...    P.Le Van .26/04/94  ....
399
400      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
401      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
402
403
404   2  CONTINUE
405
406c-----------------------------------------------------------------------
407
408c   date:
409c   -----
410
411
412c   gestion des appels de la physique et des dissipations:
413c   ------------------------------------------------------
414c
415c   ...    P.Le Van  ( 6/02/95 )  ....
416
417      apphys = .FALSE.
418      statcl = .FALSE.
419      conser = .FALSE.
420      apdiss = .FALSE.
421
422      IF( purmats ) THEN
423         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
424         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
425         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
426     $                              .AND.   physic    ) apphys = .TRUE.
427      ELSE
428         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
429         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
430         IF( MOD(itau+1,iphysiq).EQ.0. AND. physic    ) apphys = .TRUE.
431      END IF
432
433c-----------------------------------------------------------------------
434c   calcul des tendances dynamiques:
435c   --------------------------------
436
437      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
438c
439c
440      CALL caldyn
441     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
442     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
443
444c-----------------------------------------------------------------------
445c   calcul des tendances advection des traceurs (dont l'humidite)
446c   -------------------------------------------------------------
447
448      IF( forward. OR . leapf )  THEN
449c
450        DO 15  iq = 1, nqmx
451c
452         IF( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
453           CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
454
455         ELSE IF( iq.EQ. nqmx )   THEN
456c
457c           iapp_tracvl = 5
458            iapp_tracvl = iperiod
459c
460cccc     iapp_tracvl est la frequence en pas du groupement des flux
461cccc      de masse pour  Van-Leer dans la routine  tracvl  .
462c
463c            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
464            CALL vanleer(numvanle,iapp_tracvl,2,q,pbaru,pbarv,
465     *                      p, masse, dq,  iadv(1), teta, pk     )
466c
467c                   ...  Modif  F.Codron  ....
468c
469         ENDIF
470c
471 15     CONTINUE
472C
473         IF (offline) THEN
474Cmaf stokage du flux de masse pour traceurs OFF-LINE
475
476            CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
477     .   time_step, itau)
478
479
480         ENDIF
481c
482      ENDIF
483
484
485c-----------------------------------------------------------------------
486c   integrations dynamique et traceurs:
487c   ----------------------------------
488
489
490       CALL integrd ( iadv, 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
491     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
492     $              finvmaold                                    )
493
494
495c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
496c
497c-----------------------------------------------------------------------
498c   calcul des tendances physiques:
499c   -------------------------------
500c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
501c
502       IF( purmats )  THEN
503          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
504       ELSE
505          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
506       ENDIF
507c
508c
509       IF( apphys )  THEN
510c
511c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
512c
513
514         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
515         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
516
517           rdaym_ini  = itau * dtvr / daysec
518           rdayvrai   = rdaym_ini  + day_ini
519
520           IF ( ecritphy.LT.1. )  THEN
521             rday_ecri = rdaym_ini
522           ELSE
523             rday_ecri = NINT( rdayvrai )
524           ENDIF
525c
526
527c rajout debug
528c       lafin = .true.
529c+jld
530      IF (ip_ebil_dyn.ge.1 ) THEN
531          ztit='bil dyn'
532          CALL diagedyn(ztit,2,1,1,dtphys
533     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
534     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
535      ENDIF
536c-jld
537        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
538     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
539     $     du,dv,dteta,dq,w,clesphy0, dufi,dvfi,dhfi,dqfi,dpfi  )
540
541c      ajout des tendances physiques:
542c      ------------------------------
543          CALL addfi( nqmx, dtphys, leapf, forward   ,
544     $                  ucov, vcov, teta , q   ,ps ,
545     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
546c
547c+jld
548      IF (ip_ebil_dyn.ge.1 ) THEN
549          ztit='bil phys'
550          CALL diagedyn(ztit,2,1,1,dtphys
551     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
552     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
553      ENDIF
554c-jld
555       ENDIF
556
557        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
558        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
559
560c-----------------------------------------------------------------------
561c
562c
563c   dissipation horizontale et verticale  des petites echelles:
564c   ----------------------------------------------------------
565
566      IF(apdiss) THEN
567c+jld
568      IF (ip_ebil_dyn.ge.2 ) THEN
569          ztit='avant dissip'
570          CALL diagedyn(ztit,2,2,2,dtvr
571     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
572     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
573      ENDIF
574        CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
575        CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin0  )
576c-jld
577
578         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
579
580         CALL addit( ijp1llm,ucov ,dudis,ucov )
581         CALL addit( ijmllm ,vcov ,dvdis,vcov )
582c+jld
583        CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
584        CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin  )
585C
586C       On rajoute la tendance due a la transform. Ec -> E therm. cree
587C       lors de la dissipation
588        DO l  =  1, llm
589          DO    ij     = 1, ip1jmp1
590            dhecdt(ij,l)= (ecin0(ij,l)-ecin(ij,l))/ pk(ij,l)
591            dhdis(ij,l) = dhdis(ij,l) + dhecdt(ij,l)
592          ENDDO
593        ENDDO
594c-jld
595         CALL addit( ijp1llm,teta ,dhdis,teta )
596c+jld
597c
598         IF (ip_ebil_dyn.ge.2 ) THEN
599             ztit='apres dissip'
600             CALL diagedyn(ztit,2,2,2,dtdiss
601     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
602     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
603         ENDIF
604c-jld
605
606c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
607c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
608c
609
610        DO l  =  1, llm
611          DO ij =  1,iim
612           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
613           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
614          ENDDO
615           tpn  = SSUM(iim,tppn,1)/apoln
616           tps  = SSUM(iim,tpps,1)/apols
617
618          DO ij = 1, iip1
619           teta(  ij    ,l) = tpn
620           teta(ij+ip1jm,l) = tps
621          ENDDO
622        ENDDO
623
624        DO ij =  1,iim
625          tppn(ij)  = aire(  ij    ) * ps (  ij    )
626          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
627        ENDDO
628          tpn  = SSUM(iim,tppn,1)/apoln
629          tps  = SSUM(iim,tpps,1)/apols
630
631        DO ij = 1, iip1
632          ps(  ij    ) = tpn
633          ps(ij+ip1jm) = tps
634        ENDDO
635
636
637      END IF
638
639c ajout debug
640c              IF( lafin ) then 
641c                abort_message = 'Simulation finished'
642c                call abort_gcm(modname,abort_message,0)
643c              ENDIF
644       
645c   ********************************************************************
646c   ********************************************************************
647c   .... fin de l'integration dynamique  et physique pour le pas itau ..
648c   ********************************************************************
649c   ********************************************************************
650
651c   preparation du pas d'integration suivant  ......
652
653      IF ( .NOT.purmats ) THEN
654c       ........................................................
655c       ..............  schema matsuno + leapfrog  ..............
656c       ........................................................
657
658            IF(forward. OR. leapf) THEN
659              itau= itau + 1
660              iday= day_ini+itau/day_step
661              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
662                IF(time.GT.1.) THEN
663                  time = time-1.
664                  iday = iday+1
665                ENDIF
666            ENDIF
667
668
669            IF( itau. EQ. itaufinp1 ) then 
670
671
672              abort_message = 'Simulation finished'
673              call abort_gcm(modname,abort_message,0)
674            ENDIF
675c-----------------------------------------------------------------------
676c   ecriture du fichier histoire moyenne:
677c   -------------------------------------
678
679            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
680               IF(itau.EQ.itaufin) THEN
681                  iav=1
682               ELSE
683                  iav=0
684               ENDIF
685               CALL writedynav(histaveid, nqmx, itau,vcov ,
686     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
687cccIM cf. FH
688               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
689     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
690
691            ENDIF
692
693c-----------------------------------------------------------------------
694c   ecriture de la bande histoire:
695c   ------------------------------
696
697            IF( MOD(itau,iecri*day_step).EQ.0) THEN
698
699               nbetat = nbetatdem
700       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
701c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
702c     ,                          ucov,teta,phi,q,masse,ps,phis)
703
704
705            ENDIF
706
707            IF(itau.EQ.itaufin) THEN
708
709
710       PRINT *,' Appel test_period avant redem ', itau
711       CALL  test_period ( ucov,vcov,teta,q,p,phis )
712       CALL dynredem1("restart.nc",0.0,
713     .                     vcov,ucov,teta,q,nqmx,masse,ps)
714
715              CLOSE(99)
716            ENDIF
717
718c-----------------------------------------------------------------------
719c   gestion de l'integration temporelle:
720c   ------------------------------------
721
722            IF( MOD(itau,iperiod).EQ.0 )    THEN
723                    GO TO 1
724            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
725
726                   IF( forward )  THEN
727c      fin du pas forward et debut du pas backward
728
729                      forward = .FALSE.
730                        leapf = .FALSE.
731                           GO TO 2
732
733                   ELSE
734c      fin du pas backward et debut du premier pas leapfrog
735
736                        leapf =  .TRUE.
737                        dt  =  2.*dtvr
738                        GO TO 2
739                   END IF
740            ELSE
741
742c      ......   pas leapfrog  .....
743
744                 leapf = .TRUE.
745                 dt  = 2.*dtvr
746                 GO TO 2
747            END IF
748
749      ELSE
750
751c       ........................................................
752c       ..............       schema  matsuno        ...............
753c       ........................................................
754            IF( forward )  THEN
755
756             itau =  itau + 1
757             iday = day_ini+itau/day_step
758             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
759
760                  IF(time.GT.1.) THEN
761                   time = time-1.
762                   iday = iday+1
763                  ENDIF
764
765               forward =  .FALSE.
766               IF( itau. EQ. itaufinp1 ) then 
767                 abort_message = 'Simulation finished'
768                 call abort_gcm(modname,abort_message,0)
769               ENDIF
770               GO TO 2
771
772            ELSE
773
774            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
775               IF(itau.EQ.itaufin) THEN
776                  iav=1
777               ELSE
778                  iav=0
779               ENDIF
780               CALL writedynav(histaveid, nqmx, itau,vcov ,
781     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
782cccIM cf. FH
783               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
784     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
785
786            ENDIF
787
788               IF(MOD(itau,iecri*day_step).EQ.0) THEN
789                  nbetat = nbetatdem
790       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
791c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
792c     ,                          ucov,teta,phi,q,masse,ps,phis)
793               ENDIF
794
795                 IF(itau.EQ.itaufin)
796     . CALL dynredem1("restart.nc",0.0,
797     .                     vcov,ucov,teta,q,nqmx,masse,ps)
798
799                 forward = .TRUE.
800                 GO TO  1
801
802            ENDIF
803
804      END IF
805
806 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
807     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
808
809      STOP
810      END
Note: See TracBrowser for help on using the repository browser.