source: LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F @ 2600

Last change on this file since 2600 was 2600, checked in by Ehouarn Millour, 8 years ago

Cleanup in the dynamics: turn comvert.h into module comvert_mod.F90
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 56.4 KB
Line 
1!
2! $Id: leapfrog_p.F 2600 2016-07-23 05:45:38Z emillour $
3!
4c
5c
6
7      SUBROUTINE leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,time_0)
8
9      use exner_hyb_m, only: exner_hyb
10      use exner_milieu_m, only: exner_milieu
11      use exner_hyb_p_m, only: exner_hyb_p
12      use exner_milieu_p_m, only: exner_milieu_p
13       USE misc_mod
14       USE parallel_lmdz
15       USE times
16       USE mod_hallo
17       USE Bands
18       USE Write_Field
19       USE Write_Field_p
20       USE vampir
21       USE timer_filtre, ONLY : print_filtre_timer
22       USE infotrac, ONLY: nqtot
23       USE guide_p_mod, ONLY : guide_main
24       USE getparam
25       USE control_mod, ONLY: nday, day_step, planet_type, offline,
26     &                       iconser, iphysiq, iperiod, dissip_period,
27     &                       iecri, ip_ebil_dyn, ok_dynzon, ok_dyn_ins,
28     &                       periodav, ok_dyn_ave, output_grads_dyn,
29     &                       iapp_tracvl
30       USE comvert_mod, ONLY: ap,bp,pressure_exner,presnivs
31       USE comconst_mod, ONLY: cpp, dtvr, ihf, dtphys, pi, jmp1
32      IMPLICIT NONE
33
34c      ......   Version  du 10/01/98    ..........
35
36c             avec  coordonnees  verticales hybrides
37c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
38
39c=======================================================================
40c
41c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
42c   -------
43c
44c   Objet:
45c   ------
46c
47c   GCM LMD nouvelle grille
48c
49c=======================================================================
50c
51c  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
52c      et possibilite d'appeler une fonction f(y)  a derivee tangente
53c      hyperbolique a la  place de la fonction a derivee sinusoidale.
54
55c  ... Possibilite de choisir le shema pour l'advection de
56c        q  , en modifiant iadv dans traceur.def  (10/02) .
57c
58c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
59c      Pour Van-Leer iadv=10
60c
61c-----------------------------------------------------------------------
62c   Declarations:
63c   -------------
64
65#include "dimensions.h"
66#include "paramet.h"
67#include "comdissnew.h"
68#include "comgeom.h"
69#include "logic.h"
70#include "temps.h"
71#include "ener.h"
72#include "description.h"
73!#include "com_io_dyn.h"
74#include "iniprint.h"
75#include "academic.h"
76     
77      REAL,INTENT(IN) :: time_0 ! not used
78
79c   dynamical variables:
80      REAL,INTENT(INOUT) :: ucov(ip1jmp1,llm)    ! zonal covariant wind
81      REAL,INTENT(INOUT) :: vcov(ip1jm,llm)      ! meridional covariant wind
82      REAL,INTENT(INOUT) :: teta(ip1jmp1,llm)    ! potential temperature
83      REAL,INTENT(INOUT) :: ps(ip1jmp1)          ! surface pressure (Pa)
84      REAL,INTENT(INOUT) :: masse(ip1jmp1,llm)   ! air mass
85      REAL,INTENT(INOUT) :: phis(ip1jmp1)        ! geopotentiat at the surface
86      REAL,INTENT(INOUT) :: q(ip1jmp1,llm,nqtot) ! advected tracers
87
88      REAL,SAVE :: p (ip1jmp1,llmp1  )       ! interlayer pressure
89      REAL,SAVE :: pks(ip1jmp1)              ! exner at the surface
90      REAL,SAVE :: pk(ip1jmp1,llm)           ! exner at mid-layer
91      REAL,SAVE :: pkf(ip1jmp1,llm)          ! filtered exner at mid-layer
92      REAL,SAVE :: phi(ip1jmp1,llm)          ! geopotential
93      REAL,SAVE :: w(ip1jmp1,llm)            ! vertical velocity
94
95      real zqmin,zqmax
96
97c variables dynamiques intermediaire pour le transport
98      REAL,SAVE :: pbaru(ip1jmp1,llm),pbarv(ip1jm,llm) !flux de masse
99
100c   variables dynamiques au pas -1
101      REAL,SAVE :: vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
102      REAL,SAVE :: tetam1(ip1jmp1,llm),psm1(ip1jmp1)
103      REAL,SAVE :: massem1(ip1jmp1,llm)
104
105c   tendances dynamiques
106      REAL,SAVE :: dv(ip1jm,llm),du(ip1jmp1,llm)
107      REAL,SAVE :: dteta(ip1jmp1,llm),dp(ip1jmp1)
108      REAL,DIMENSION(:,:,:), ALLOCATABLE, SAVE :: dq
109
110c   tendances de la dissipation
111      REAL,SAVE :: dvdis(ip1jm,llm),dudis(ip1jmp1,llm)
112      REAL,SAVE :: dtetadis(ip1jmp1,llm)
113
114c   tendances physiques
115      REAL,SAVE :: dvfi(ip1jm,llm),dufi(ip1jmp1,llm)
116      REAL,SAVE :: dtetafi(ip1jmp1,llm)
117      REAL,SAVE :: dpfi(ip1jmp1)
118      REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: dqfi
119
120c   variables pour le fichier histoire
121      REAL dtav      ! intervalle de temps elementaire
122
123      REAL tppn(iim),tpps(iim),tpn,tps
124c
125      INTEGER itau,itaufinp1,iav
126!      INTEGER  iday ! jour julien
127      REAL       time
128
129      REAL  SSUM
130!      REAL,SAVE :: finvmaold(ip1jmp1,llm)
131
132cym      LOGICAL  lafin
133      LOGICAL :: lafin
134      INTEGER ij,iq,l
135      INTEGER ik
136
137      real time_step, t_wrt, t_ops
138
139! jD_cur: jour julien courant
140! jH_cur: heure julienne courante
141      REAL :: jD_cur, jH_cur
142      INTEGER :: an, mois, jour
143      REAL :: secondes
144
145      logical :: physic
146      LOGICAL first,callinigrads
147
148      data callinigrads/.true./
149      character*10 string10
150
151      REAL,SAVE :: flxw(ip1jmp1,llm) ! flux de masse verticale
152
153c+jld variables test conservation energie
154      REAL,SAVE :: ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
155C     Tendance de la temp. potentiel d (theta)/ d t due a la
156C     tansformation d'energie cinetique en energie thermique
157C     cree par la dissipation
158      REAL,SAVE :: dtetaecdt(ip1jmp1,llm)
159      REAL,SAVE :: vcont(ip1jm,llm),ucont(ip1jmp1,llm)
160      REAL,SAVE :: vnat(ip1jm,llm),unat(ip1jmp1,llm)
161      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
162      CHARACTER*15 ztit
163!      INTEGER   ip_ebil_dyn  ! PRINT level for energy conserv. diag.
164!      SAVE      ip_ebil_dyn
165!      DATA      ip_ebil_dyn/0/
166c-jld
167
168      character*80 dynhist_file, dynhistave_file
169      character(len=*),parameter :: modname="leapfrog"
170      character*80 abort_message
171
172
173      logical,PARAMETER :: dissip_conservative=.TRUE.
174 
175      INTEGER testita
176      PARAMETER (testita = 9)
177
178      logical , parameter :: flag_verif = .false.
179     
180c declaration liees au parallelisme
181      INTEGER :: ierr
182      LOGICAL :: FirstCaldyn
183      LOGICAL :: FirstPhysic
184      INTEGER :: ijb,ije,j,i
185      type(Request) :: TestRequest
186      type(Request) :: Request_Dissip
187      type(Request) :: Request_physic
188      REAL,SAVE :: dvfi_tmp(iip1,llm),dufi_tmp(iip1,llm)
189      REAL,SAVE :: dtetafi_tmp(iip1,llm)
190      REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: dqfi_tmp
191      REAL,SAVE :: dpfi_tmp(iip1)
192
193      INTEGER :: true_itau
194      INTEGER :: iapptrac
195      INTEGER :: AdjustCount
196!      INTEGER :: var_time
197      LOGICAL :: ok_start_timer=.FALSE.
198      LOGICAL, SAVE :: firstcall=.TRUE.
199
200c$OMP MASTER
201      ItCount=0
202c$OMP END MASTER     
203      true_itau=0
204      FirstCaldyn=.TRUE.
205      FirstPhysic=.TRUE.
206      iapptrac=0
207      AdjustCount = 0
208      lafin=.false.
209     
210      if (nday>=0) then
211         itaufin   = nday*day_step
212      else
213         itaufin   = -nday
214      endif
215
216      itaufinp1 = itaufin +1
217
218      itau = 0
219      physic=.true.
220      if (iflag_phys==0.or.iflag_phys==2) physic=.false.
221!      iday = day_ini+itau/day_step
222!      time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
223!         IF(time.GT.1.) THEN
224!          time = time-1.
225!          iday = iday+1
226!         ENDIF
227
228c Allocate variables depending on dynamic variable nqtot
229c$OMP MASTER
230         IF (firstcall) THEN
231            firstcall=.FALSE.
232            ALLOCATE(dq(ip1jmp1,llm,nqtot))
233            ALLOCATE(dqfi(ip1jmp1,llm,nqtot))
234            ALLOCATE(dqfi_tmp(iip1,llm,nqtot))
235         END IF
236c$OMP END MASTER     
237c$OMP BARRIER
238
239c-----------------------------------------------------------------------
240c   On initialise la pression et la fonction d'Exner :
241c   --------------------------------------------------
242
243c$OMP MASTER
244      dq(:,:,:)=0.
245      CALL pression ( ip1jmp1, ap, bp, ps, p       )
246      if (pressure_exner) then
247        CALL exner_hyb( ip1jmp1, ps, p, pks, pk, pkf )
248      else
249        CALL exner_milieu( ip1jmp1, ps, p, pks, pk, pkf )
250      endif
251c$OMP END MASTER
252c-----------------------------------------------------------------------
253c   Debut de l'integration temporelle:
254c   ----------------------------------
255c et du parallelisme !!
256
257   1  CONTINUE ! Matsuno Forward step begins here
258
259c   date: (NB: date remains unchanged for Backward step)
260c   -----
261
262      jD_cur = jD_ref + day_ini - day_ref +                             &
263     &          (itau+1)/day_step
264      jH_cur = jH_ref + start_time +                                    &
265     &         mod(itau+1,day_step)/float(day_step)
266      if (jH_cur > 1.0 ) then
267        jD_cur = jD_cur +1.
268        jH_cur = jH_cur -1.
269      endif
270
271
272#ifdef CPP_IOIPSL
273      if (ok_guide) then
274!$OMP MASTER
275        call guide_main(itau,ucov,vcov,teta,q,masse,ps)
276!$OMP END MASTER
277!$OMP BARRIER
278      endif
279#endif
280
281c
282c     IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
283c       CALL  test_period ( ucov,vcov,teta,q,p,phis )
284c       PRINT *,' ----   Test_period apres continue   OK ! -----', itau
285c     ENDIF
286c
287cym      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
288cym      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
289cym      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
290cym      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
291cym      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
292
293       if (FirstCaldyn) then
294c$OMP MASTER
295         ucovm1=ucov
296         vcovm1=vcov
297         tetam1= teta
298         massem1= masse
299         psm1= ps
300
301! Ehouarn: finvmaold is actually not used       
302!         finvmaold = masse
303!         CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
304c$OMP END MASTER
305c$OMP BARRIER
306       else
307! Save fields obtained at previous time step as '...m1'
308         ijb=ij_begin
309         ije=ij_end
310
311c$OMP MASTER           
312         psm1     (ijb:ije) = ps    (ijb:ije)
313c$OMP END MASTER
314
315c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)         
316         DO l=1,llm     
317           ije=ij_end
318           ucovm1   (ijb:ije,l) = ucov  (ijb:ije,l)
319           tetam1   (ijb:ije,l) = teta  (ijb:ije,l)
320           massem1  (ijb:ije,l) = masse (ijb:ije,l)
321!           finvmaold(ijb:ije,l)=masse(ijb:ije,l)
322                 
323           if (pole_sud) ije=ij_end-iip1
324           vcovm1(ijb:ije,l) = vcov  (ijb:ije,l)
325       
326
327         ENDDO
328c$OMP ENDDO 
329
330! Ehouarn: finvmaold not used
331!          CALL filtreg_p ( finvmaold ,jj_begin,jj_end,jjp1,
332!     .                    llm, -2,2, .TRUE., 1 )
333
334       endif ! of if (FirstCaldyn)
335       
336      forward = .TRUE.
337      leapf   = .FALSE.
338      dt      =  dtvr
339
340c   ...    P.Le Van .26/04/94  ....
341
342cym      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
343cym      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
344
345cym  ne sert a rien
346cym      call minmax(ijp1llm,q(:,:,3),zqmin,zqmax)
347
348   2  CONTINUE ! Matsuno backward or leapfrog step begins here
349
350c$OMP MASTER
351      ItCount=ItCount+1
352      if (MOD(ItCount,1)==1) then
353        debug=.true.
354      else
355        debug=.false.
356      endif
357c$OMP END MASTER
358c-----------------------------------------------------------------------
359
360c   date: (NB: only leapfrog step requires recomputing date)
361c   -----
362
363      IF (leapf) THEN
364        jD_cur = jD_ref + day_ini - day_ref +
365     &            (itau+1)/day_step
366        jH_cur = jH_ref + start_time +
367     &           mod(itau+1,day_step)/float(day_step)
368        if (jH_cur > 1.0 ) then
369          jD_cur = jD_cur +1.
370          jH_cur = jH_cur -1.
371        endif
372      ENDIF
373
374c   gestion des appels de la physique et des dissipations:
375c   ------------------------------------------------------
376c
377c   ...    P.Le Van  ( 6/02/95 )  ....
378
379      apphys = .FALSE.
380      statcl = .FALSE.
381      conser = .FALSE.
382      apdiss = .FALSE.
383
384      IF( purmats ) THEN
385      ! Purely Matsuno time stepping
386         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
387         IF( MOD(itau,dissip_period ).EQ.0.AND..NOT.forward )
388     s        apdiss = .TRUE.
389         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
390     s          .and. physic                        ) apphys = .TRUE.
391      ELSE
392      ! Leapfrog/Matsuno time stepping
393         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
394         IF( MOD(itau+1,dissip_period).EQ.0 .AND. .NOT. forward )
395     s        apdiss = .TRUE.
396         IF( MOD(itau+1,iphysiq).EQ.0.AND.physic) apphys=.TRUE.
397      END IF
398
399! Ehouarn: for Shallow Water case (ie: 1 vertical layer),
400!          supress dissipation step
401      if (llm.eq.1) then
402        apdiss=.false.
403      endif
404
405cym    ---> Pour le moment     
406cym      apphys = .FALSE.
407      statcl = .FALSE.
408      conser = .FALSE. ! ie: no output of control variables to stdout in //
409     
410      if (firstCaldyn) then
411c$OMP MASTER
412          call SetDistrib(jj_Nb_Caldyn)
413c$OMP END MASTER
414c$OMP BARRIER
415          firstCaldyn=.FALSE.
416cym          call InitTime
417c$OMP MASTER
418          call Init_timer
419c$OMP END MASTER
420      endif
421
422c$OMP MASTER     
423      IF (ok_start_timer) THEN
424        CALL InitTime
425        ok_start_timer=.FALSE.
426      ENDIF     
427c$OMP END MASTER     
428     
429      if (Adjust) then
430c$OMP MASTER
431        AdjustCount=AdjustCount+1
432        if (iapptrac==iapp_tracvl .and. (forward. OR . leapf)
433     &         .and. itau/iphysiq>2 .and. Adjustcount>30) then
434           AdjustCount=0
435           call allgather_timer_average
436
437        if (prt_level > 9) then
438       
439        print *,'*********************************'
440        print *,'******    TIMER CALDYN     ******'
441        do i=0,mpi_size-1
442          print *,'proc',i,' :   Nb Bandes  :',jj_nb_caldyn(i),
443     &            '  : temps moyen :',
444     &             timer_average(jj_nb_caldyn(i),timer_caldyn,i),
445     &            '+-',timer_delta(jj_nb_caldyn(i),timer_caldyn,i)
446        enddo
447     
448        print *,'*********************************'
449        print *,'******    TIMER VANLEER    ******'
450        do i=0,mpi_size-1
451          print *,'proc',i,' :   Nb Bandes  :',jj_nb_vanleer(i),
452     &            '  : temps moyen :',
453     &             timer_average(jj_nb_vanleer(i),timer_vanleer,i),
454     &            '+-',timer_delta(jj_nb_vanleer(i),timer_vanleer,i)
455        enddo
456     
457        print *,'*********************************'
458        print *,'******    TIMER DISSIP    ******'
459        do i=0,mpi_size-1
460          print *,'proc',i,' :   Nb Bandes  :',jj_nb_dissip(i),
461     &            '  : temps moyen :',
462     &             timer_average(jj_nb_dissip(i),timer_dissip,i),
463     &             '+-',timer_delta(jj_nb_dissip(i),timer_dissip,i)
464        enddo
465       
466        if (mpi_rank==0) call WriteBands
467       
468       endif
469       
470         call AdjustBands_caldyn
471         if (mpi_rank==0) call WriteBands
472         
473         call Register_SwapFieldHallo(ucov,ucov,ip1jmp1,llm,
474     &                                jj_Nb_caldyn,0,0,TestRequest)
475         call Register_SwapFieldHallo(ucovm1,ucovm1,ip1jmp1,llm,
476     &                                jj_Nb_caldyn,0,0,TestRequest)
477         call Register_SwapFieldHallo(vcov,vcov,ip1jm,llm,
478     &                                jj_Nb_caldyn,0,0,TestRequest)
479         call Register_SwapFieldHallo(vcovm1,vcovm1,ip1jm,llm,
480     &                                jj_Nb_caldyn,0,0,TestRequest)
481         call Register_SwapFieldHallo(teta,teta,ip1jmp1,llm,
482     &                                jj_Nb_caldyn,0,0,TestRequest)
483         call Register_SwapFieldHallo(tetam1,tetam1,ip1jmp1,llm,
484     &                                jj_Nb_caldyn,0,0,TestRequest)
485         call Register_SwapFieldHallo(masse,masse,ip1jmp1,llm,
486     &                                jj_Nb_caldyn,0,0,TestRequest)
487         call Register_SwapFieldHallo(massem1,massem1,ip1jmp1,llm,
488     &                                jj_Nb_caldyn,0,0,TestRequest)
489         call Register_SwapFieldHallo(ps,ps,ip1jmp1,1,
490     &                                jj_Nb_caldyn,0,0,TestRequest)
491         call Register_SwapFieldHallo(psm1,psm1,ip1jmp1,1,
492     &                                jj_Nb_caldyn,0,0,TestRequest)
493         call Register_SwapFieldHallo(pkf,pkf,ip1jmp1,llm,
494     &                                jj_Nb_caldyn,0,0,TestRequest)
495         call Register_SwapFieldHallo(pk,pk,ip1jmp1,llm,
496     &                                jj_Nb_caldyn,0,0,TestRequest)
497         call Register_SwapFieldHallo(pks,pks,ip1jmp1,1,
498     &                                jj_Nb_caldyn,0,0,TestRequest)
499         call Register_SwapFieldHallo(phis,phis,ip1jmp1,1,
500     &                                jj_Nb_caldyn,0,0,TestRequest)
501         call Register_SwapFieldHallo(phi,phi,ip1jmp1,llm,
502     &                                jj_Nb_caldyn,0,0,TestRequest)
503!         call Register_SwapFieldHallo(finvmaold,finvmaold,ip1jmp1,llm,
504!     &                                jj_Nb_caldyn,0,0,TestRequest)
505 
506        do j=1,nqtot
507         call Register_SwapFieldHallo(q(1,1,j),q(1,1,j),ip1jmp1,llm,
508     &                                jj_nb_caldyn,0,0,TestRequest)
509        enddo
510
511         call SetDistrib(jj_nb_caldyn)
512         call SendRequest(TestRequest)
513         call WaitRequest(TestRequest)
514         
515        call AdjustBands_dissip
516        call AdjustBands_physic
517
518      endif
519c$OMP END MASTER 
520      endif       
521     
522     
523     
524c-----------------------------------------------------------------------
525c   calcul des tendances dynamiques:
526c   --------------------------------
527c$OMP BARRIER
528c$OMP MASTER
529       call VTb(VThallo)
530c$OMP END MASTER
531
532       call Register_Hallo(ucov,ip1jmp1,llm,1,1,1,1,TestRequest)
533       call Register_Hallo(vcov,ip1jm,llm,1,1,1,1,TestRequest)
534       call Register_Hallo(teta,ip1jmp1,llm,1,1,1,1,TestRequest)
535       call Register_Hallo(ps,ip1jmp1,1,1,2,2,1,TestRequest)
536       call Register_Hallo(pkf,ip1jmp1,llm,1,1,1,1,TestRequest)
537       call Register_Hallo(pk,ip1jmp1,llm,1,1,1,1,TestRequest)
538       call Register_Hallo(pks,ip1jmp1,1,1,1,1,1,TestRequest)
539       call Register_Hallo(p,ip1jmp1,llmp1,1,1,1,1,TestRequest)
540       
541c       do j=1,nqtot
542c         call Register_Hallo(q(1,1,j),ip1jmp1,llm,1,1,1,1,
543c     *                       TestRequest)
544c        enddo
545
546       call SendRequest(TestRequest)
547c$OMP BARRIER
548       call WaitRequest(TestRequest)
549
550c$OMP MASTER
551       call VTe(VThallo)
552c$OMP END MASTER
553c$OMP BARRIER
554     
555      if (debug) then       
556!$OMP BARRIER
557!$OMP MASTER
558        call WriteField_p('ucov',reshape(ucov,(/iip1,jmp1,llm/)))
559        call WriteField_p('vcov',reshape(vcov,(/iip1,jjm,llm/)))
560        call WriteField_p('teta',reshape(teta,(/iip1,jmp1,llm/)))
561        call WriteField_p('ps',reshape(ps,(/iip1,jmp1/)))
562        call WriteField_p('masse',reshape(masse,(/iip1,jmp1,llm/)))
563        call WriteField_p('pk',reshape(pk,(/iip1,jmp1,llm/)))
564        call WriteField_p('pks',reshape(pks,(/iip1,jmp1/)))
565        call WriteField_p('pkf',reshape(pkf,(/iip1,jmp1,llm/)))
566        call WriteField_p('phis',reshape(phis,(/iip1,jmp1/)))
567        do j=1,nqtot
568          call WriteField_p('q'//trim(int2str(j)),
569     .                reshape(q(:,:,j),(/iip1,jmp1,llm/)))
570        enddo
571!$OMP END MASTER       
572c$OMP BARRIER
573      endif
574
575     
576      True_itau=True_itau+1
577
578c$OMP MASTER
579      IF (prt_level>9) THEN
580        WRITE(lunout,*)"leapfrog_p: Iteration No",True_itau
581      ENDIF
582
583
584      call start_timer(timer_caldyn)
585
586      ! compute geopotential phi()
587      CALL geopot_p  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
588
589     
590      call VTb(VTcaldyn)
591c$OMP END MASTER
592!      var_time=time+iday-day_ini
593
594c$OMP BARRIER
595!      CALL FTRACE_REGION_BEGIN("caldyn")
596      time = jD_cur + jH_cur
597      CALL caldyn_p
598     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
599     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time )
600
601!      CALL FTRACE_REGION_END("caldyn")
602
603c$OMP MASTER
604      call VTe(VTcaldyn)
605c$OMP END MASTER     
606
607cc$OMP BARRIER
608cc$OMP MASTER
609!      call WriteField_p('du',reshape(du,(/iip1,jmp1,llm/)))
610!      call WriteField_p('dv',reshape(dv,(/iip1,jjm,llm/)))
611!      call WriteField_p('dteta',reshape(dteta,(/iip1,jmp1,llm/)))
612!      call WriteField_p('dp',reshape(dp,(/iip1,jmp1/)))
613!      call WriteField_p('w',reshape(w,(/iip1,jmp1,llm/)))
614!      call WriteField_p('pbaru',reshape(pbaru,(/iip1,jmp1,llm/)))
615!      call WriteField_p('pbarv',reshape(pbarv,(/iip1,jjm,llm/)))
616!      call WriteField_p('p',reshape(p,(/iip1,jmp1,llmp1/)))
617!      call WriteField_p('masse',reshape(masse,(/iip1,jmp1,llm/)))
618!      call WriteField_p('pk',reshape(pk,(/iip1,jmp1,llm/)))
619cc$OMP END MASTER
620
621c-----------------------------------------------------------------------
622c   calcul des tendances advection des traceurs (dont l'humidite)
623c   -------------------------------------------------------------
624
625      IF( forward. OR . leapf )  THEN
626! Ehouarn: NB: fields sent to advtrac are those at the beginning of the time step
627         CALL caladvtrac_p(q,pbaru,pbarv,
628     *        p, masse, dq,  teta,
629     .        flxw,pk, iapptrac)
630
631C        Stokage du flux de masse pour traceurs OFF-LINE
632         IF (offline .AND. .NOT. adjust) THEN
633            CALL fluxstokenc_p(pbaru,pbarv,masse,teta,phi,phis,
634     .           dtvr, itau)
635         ENDIF
636
637      ENDIF ! of IF( forward. OR . leapf )
638
639c-----------------------------------------------------------------------
640c   integrations dynamique et traceurs:
641c   ----------------------------------
642
643c$OMP MASTER
644       call VTb(VTintegre)
645c$OMP END MASTER
646c      call WriteField_p('ucovm1',reshape(ucovm1,(/iip1,jmp1,llm/)))
647c      call WriteField_p('vcovm1',reshape(vcovm1,(/iip1,jjm,llm/)))
648c      call WriteField_p('tetam1',reshape(tetam1,(/iip1,jmp1,llm/)))
649c      call WriteField_p('psm1',reshape(psm1,(/iip1,jmp1/)))
650c      call WriteField_p('ucov',reshape(ucov,(/iip1,jmp1,llm/)))
651c      call WriteField_p('vcov',reshape(vcov,(/iip1,jjm,llm/)))
652c      call WriteField_p('teta',reshape(teta,(/iip1,jmp1,llm/)))
653c      call WriteField_p('ps',reshape(ps,(/iip1,jmp1/)))
654cc$OMP PARALLEL DEFAULT(SHARED)
655c$OMP BARRIER
656!       CALL FTRACE_REGION_BEGIN("integrd")
657
658       CALL integrd_p ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
659     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis )
660!     $              finvmaold                                    )
661
662!       CALL FTRACE_REGION_END("integrd")
663c$OMP BARRIER
664cc$OMP MASTER
665c      call WriteField_p('ucovm1',reshape(ucovm1,(/iip1,jmp1,llm/)))
666c      call WriteField_p('vcovm1',reshape(vcovm1,(/iip1,jjm,llm/)))
667c      call WriteField_p('tetam1',reshape(tetam1,(/iip1,jmp1,llm/)))
668c      call WriteField_p('psm1',reshape(psm1,(/iip1,jmp1/)))
669c      call WriteField_p('ucov',reshape(ucov,(/iip1,jmp1,llm/)))
670c      call WriteField_p('vcov',reshape(vcov,(/iip1,jjm,llm/)))
671c      call WriteField_p('teta',reshape(teta,(/iip1,jmp1,llm/)))
672c      call WriteField_p('dteta',reshape(dteta,(/iip1,jmp1,llm/)))
673c
674c      call WriteField_p('ps',reshape(ps,(/iip1,jmp1/)))
675c      do j=1,nqtot
676c        call WriteField_p('q'//trim(int2str(j)),
677c     .                reshape(q(:,:,j),(/iip1,jmp1,llm/)))
678c        call WriteField_p('dq'//trim(int2str(j)),
679c     .                reshape(dq(:,:,j),(/iip1,jmp1,llm/)))
680c      enddo
681cc$OMP END MASTER
682
683
684c$OMP MASTER
685       call VTe(VTintegre)
686c$OMP END MASTER
687c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
688c
689c-----------------------------------------------------------------------
690c   calcul des tendances physiques:
691c   -------------------------------
692c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
693c
694       IF( purmats )  THEN
695          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
696       ELSE
697          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
698       ENDIF
699
700cc$OMP END PARALLEL
701
702c
703c
704       IF( apphys )  THEN
705c
706c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
707c
708cc$OMP PARALLEL DEFAULT(SHARED)
709cc$OMP+         PRIVATE(rdaym_ini,rdayvrai,ijb,ije)
710
711c$OMP MASTER
712         call suspend_timer(timer_caldyn)
713
714        if (prt_level >= 10) then
715         write(lunout,*)
716     &   'leapfrog_p: Entree dans la physique : Iteration No ',true_itau
717        endif
718c$OMP END MASTER
719
720         CALL pression_p (  ip1jmp1, ap, bp, ps,  p      )
721
722c$OMP BARRIER
723         if (pressure_exner) then
724           CALL exner_hyb_p(  ip1jmp1, ps, p,pks, pk, pkf )
725         else
726           CALL exner_milieu_p( ip1jmp1, ps, p, pks, pk, pkf )
727         endif
728c$OMP BARRIER
729! Appel a geopot ajoute le 2014/05/08 pour garantir la convergence numerique
730! avec dyn3dmem
731      CALL geopot_p  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
732
733           jD_cur = jD_ref + day_ini - day_ref
734     $        + (itau+1)/day_step
735
736           IF (planet_type .eq."generic") THEN
737              ! AS: we make jD_cur to be pday
738              jD_cur = int(day_ini + itau/day_step)
739           ENDIF
740
741           jH_cur = jH_ref + start_time +                                &
742     &              mod(itau+1,day_step)/float(day_step)
743!         call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes)
744           if (jH_cur > 1.0 ) then
745             jD_cur = jD_cur +1.
746             jH_cur = jH_cur -1.
747           endif
748
749c rajout debug
750c       lafin = .true.
751
752
753c   Inbterface avec les routines de phylmd (phymars ... )
754c   -----------------------------------------------------
755
756c+jld
757
758c  Diagnostique de conservation de l'energie : initialisation
759      IF (ip_ebil_dyn.ge.1 ) THEN
760          ztit='bil dyn'
761! Ehouarn: be careful, diagedyn is Earth-specific!
762           IF (planet_type.eq."earth") THEN
763            CALL diagedyn(ztit,2,1,1,dtphys
764     &    , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
765           ENDIF
766      ENDIF
767c-jld
768c$OMP BARRIER
769c$OMP MASTER
770        call VTb(VThallo)
771c$OMP END MASTER
772
773        call SetTag(Request_physic,800)
774       
775        call Register_SwapFieldHallo(ucov,ucov,ip1jmp1,llm,
776     *                               jj_Nb_physic,2,2,Request_physic)
777       
778        call Register_SwapFieldHallo(vcov,vcov,ip1jm,llm,
779     *                               jj_Nb_physic,2,2,Request_physic)
780       
781        call Register_SwapFieldHallo(teta,teta,ip1jmp1,llm,
782     *                               jj_Nb_physic,2,2,Request_physic)
783       
784        call Register_SwapFieldHallo(masse,masse,ip1jmp1,llm,
785     *                               jj_Nb_physic,1,2,Request_physic)
786
787        call Register_SwapFieldHallo(ps,ps,ip1jmp1,1,
788     *                               jj_Nb_physic,2,2,Request_physic)
789
790        call Register_SwapFieldHallo(p,p,ip1jmp1,llmp1,
791     *                               jj_Nb_physic,2,2,Request_physic)
792       
793        call Register_SwapFieldHallo(pk,pk,ip1jmp1,llm,
794     *                               jj_Nb_physic,2,2,Request_physic)
795       
796        call Register_SwapFieldHallo(phis,phis,ip1jmp1,1,
797     *                               jj_Nb_physic,2,2,Request_physic)
798       
799        call Register_SwapFieldHallo(phi,phi,ip1jmp1,llm,
800     *                               jj_Nb_physic,2,2,Request_physic)
801       
802        call Register_SwapFieldHallo(w,w,ip1jmp1,llm,
803     *                               jj_Nb_physic,2,2,Request_physic)
804       
805c        call SetDistrib(jj_nb_vanleer)
806        do j=1,nqtot
807 
808          call Register_SwapFieldHallo(q(1,1,j),q(1,1,j),ip1jmp1,llm,
809     *                               jj_Nb_physic,2,2,Request_physic)
810        enddo
811
812        call Register_SwapFieldHallo(flxw,flxw,ip1jmp1,llm,
813     *                               jj_Nb_physic,2,2,Request_physic)
814       
815        call SendRequest(Request_Physic)
816c$OMP BARRIER
817        call WaitRequest(Request_Physic)       
818
819c$OMP BARRIER
820c$OMP MASTER
821        call SetDistrib(jj_nb_Physic)
822        call VTe(VThallo)
823       
824        call VTb(VTphysiq)
825c$OMP END MASTER
826c$OMP BARRIER
827
828cc$OMP MASTER       
829c      call WriteField_p('ucovfi',reshape(ucov,(/iip1,jmp1,llm/)))
830c      call WriteField_p('vcovfi',reshape(vcov,(/iip1,jjm,llm/)))
831c      call WriteField_p('tetafi',reshape(teta,(/iip1,jmp1,llm/)))
832c      call WriteField_p('pfi',reshape(p,(/iip1,jmp1,llmp1/)))
833c      call WriteField_p('pkfi',reshape(pk,(/iip1,jmp1,llm/)))
834cc$OMP END MASTER
835cc$OMP BARRIER
836!        CALL FTRACE_REGION_BEGIN("calfis")
837#ifdef CPP_PHYS
838        CALL calfis_p(lafin ,jD_cur, jH_cur,
839     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
840     $               du,dv,dteta,dq,
841     $               flxw, dufi,dvfi,dtetafi,dqfi,dpfi  )
842#endif
843!        CALL FTRACE_REGION_END("calfis")
844        ijb=ij_begin
845        ije=ij_end 
846        if ( .not. pole_nord) then
847c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
848          DO l=1,llm
849          dufi_tmp(1:iip1,l)   = dufi(ijb:ijb+iim,l)
850          dvfi_tmp(1:iip1,l)   = dvfi(ijb:ijb+iim,l) 
851          dtetafi_tmp(1:iip1,l)= dtetafi(ijb:ijb+iim,l) 
852          dqfi_tmp(1:iip1,l,:) = dqfi(ijb:ijb+iim,l,:) 
853          ENDDO
854c$OMP END DO NOWAIT
855
856c$OMP MASTER
857          dpfi_tmp(1:iip1)     = dpfi(ijb:ijb+iim) 
858c$OMP END MASTER
859        endif ! of if ( .not. pole_nord)
860
861c$OMP BARRIER
862c$OMP MASTER
863        call SetDistrib(jj_nb_Physic_bis)
864
865        call VTb(VThallo)
866c$OMP END MASTER
867c$OMP BARRIER
868 
869        call Register_Hallo(dufi,ip1jmp1,llm,
870     *                      1,0,0,1,Request_physic)
871       
872        call Register_Hallo(dvfi,ip1jm,llm,
873     *                      1,0,0,1,Request_physic)
874       
875        call Register_Hallo(dtetafi,ip1jmp1,llm,
876     *                      1,0,0,1,Request_physic)
877
878        call Register_Hallo(dpfi,ip1jmp1,1,
879     *                      1,0,0,1,Request_physic)
880
881        do j=1,nqtot
882          call Register_Hallo(dqfi(1,1,j),ip1jmp1,llm,
883     *                        1,0,0,1,Request_physic)
884        enddo
885       
886        call SendRequest(Request_Physic)
887c$OMP BARRIER
888        call WaitRequest(Request_Physic)
889             
890c$OMP BARRIER
891c$OMP MASTER
892        call VTe(VThallo)
893 
894        call SetDistrib(jj_nb_Physic)
895c$OMP END MASTER
896c$OMP BARRIER       
897                ijb=ij_begin
898        if (.not. pole_nord) then
899       
900c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
901          DO l=1,llm
902            dufi(ijb:ijb+iim,l) = dufi(ijb:ijb+iim,l)+dufi_tmp(1:iip1,l)
903            dvfi(ijb:ijb+iim,l) = dvfi(ijb:ijb+iim,l)+dvfi_tmp(1:iip1,l)
904            dtetafi(ijb:ijb+iim,l) = dtetafi(ijb:ijb+iim,l)
905     &                              +dtetafi_tmp(1:iip1,l)
906            dqfi(ijb:ijb+iim,l,:) = dqfi(ijb:ijb+iim,l,:)
907     &                              + dqfi_tmp(1:iip1,l,:)
908          ENDDO
909c$OMP END DO NOWAIT
910
911c$OMP MASTER
912          dpfi(ijb:ijb+iim)   = dpfi(ijb:ijb+iim)+ dpfi_tmp(1:iip1)
913c$OMP END MASTER
914         
915        endif ! of if (.not. pole_nord)
916c$OMP BARRIER
917cc$OMP MASTER       
918c      call WriteField_p('dufi',reshape(dufi,(/iip1,jmp1,llm/)))
919c      call WriteField_p('dvfi',reshape(dvfi,(/iip1,jjm,llm/)))
920c      call WriteField_p('dtetafi',reshape(dtetafi,(/iip1,jmp1,llm/)))
921c      call WriteField_p('dpfi',reshape(dpfi,(/iip1,jmp1/)))
922cc$OMP END MASTER
923c     
924c      do j=1,nqtot
925c        call WriteField_p('dqfi'//trim(int2str(j)),
926c     .                reshape(dqfi(:,:,j),(/iip1,jmp1,llm/)))
927c      enddo
928
929c      ajout des tendances physiques:
930c      ------------------------------
931          CALL addfi_p( dtphys, leapf, forward   ,
932     $                  ucov, vcov, teta , q   ,ps ,
933     $                 dufi, dvfi, dtetafi , dqfi ,dpfi  )
934          ! since addfi updates ps(), also update p(), masse() and pk()
935          CALL pression_p(ip1jmp1,ap,bp,ps,p)
936c$OMP BARRIER
937          CALL massdair_p(p,masse)
938c$OMP BARRIER
939          if (pressure_exner) then
940            CALL exner_hyb_p(ip1jmp1,ps,p,pks,pk,pkf)
941          else
942            CALL exner_milieu_p(ip1jmp1,ps,p,pks,pk,pkf)
943          endif
944c$OMP BARRIER
945         
946         IF (ok_strato) THEN
947           CALL top_bound_p(vcov,ucov,teta,masse,dtphys)
948         ENDIF
949       
950c$OMP BARRIER
951c$OMP MASTER
952        call VTe(VTphysiq)
953
954        call VTb(VThallo)
955c$OMP END MASTER
956
957        call SetTag(Request_physic,800)
958        call Register_SwapField(ucov,ucov,ip1jmp1,llm,
959     *                               jj_Nb_caldyn,Request_physic)
960       
961        call Register_SwapField(vcov,vcov,ip1jm,llm,
962     *                               jj_Nb_caldyn,Request_physic)
963       
964        call Register_SwapField(teta,teta,ip1jmp1,llm,
965     *                               jj_Nb_caldyn,Request_physic)
966       
967        call Register_SwapField(masse,masse,ip1jmp1,llm,
968     *                               jj_Nb_caldyn,Request_physic)
969
970        call Register_SwapField(ps,ps,ip1jmp1,1,
971     *                               jj_Nb_caldyn,Request_physic)
972
973        call Register_SwapField(p,p,ip1jmp1,llmp1,
974     *                               jj_Nb_caldyn,Request_physic)
975       
976        call Register_SwapField(pk,pk,ip1jmp1,llm,
977     *                               jj_Nb_caldyn,Request_physic)
978       
979        call Register_SwapField(phis,phis,ip1jmp1,1,
980     *                               jj_Nb_caldyn,Request_physic)
981       
982        call Register_SwapField(phi,phi,ip1jmp1,llm,
983     *                               jj_Nb_caldyn,Request_physic)
984       
985        call Register_SwapField(w,w,ip1jmp1,llm,
986     *                               jj_Nb_caldyn,Request_physic)
987
988        do j=1,nqtot
989       
990          call Register_SwapField(q(1,1,j),q(1,1,j),ip1jmp1,llm,
991     *                               jj_Nb_caldyn,Request_physic)
992       
993        enddo
994
995        call SendRequest(Request_Physic)
996c$OMP BARRIER
997        call WaitRequest(Request_Physic)     
998
999c$OMP BARRIER
1000c$OMP MASTER
1001       call VTe(VThallo)
1002       call SetDistrib(jj_Nb_caldyn)
1003c$OMP END MASTER
1004c$OMP BARRIER
1005c
1006c  Diagnostique de conservation de l'energie : difference
1007      IF (ip_ebil_dyn.ge.1 ) THEN
1008          ztit='bil phys'
1009          CALL diagedyn(ztit,2,1,1,dtphys
1010     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
1011      ENDIF
1012
1013cc$OMP MASTER     
1014c      if (debug) then
1015c       call WriteField_p('ucovfi',reshape(ucov,(/iip1,jmp1,llm/)))
1016c       call WriteField_p('vcovfi',reshape(vcov,(/iip1,jjm,llm/)))
1017c       call WriteField_p('tetafi',reshape(teta,(/iip1,jmp1,llm/)))
1018c      endif
1019cc$OMP END MASTER
1020
1021
1022c-jld
1023c$OMP MASTER
1024         call resume_timer(timer_caldyn)
1025         if (FirstPhysic) then
1026           ok_start_timer=.TRUE.
1027           FirstPhysic=.false.
1028         endif
1029c$OMP END MASTER
1030       ENDIF ! of IF( apphys )
1031
1032      IF(iflag_phys.EQ.2) THEN ! "Newtonian" case
1033!   Academic case : Simple friction and Newtonan relaxation
1034!   -------------------------------------------------------
1035c$OMP MASTER
1036         if (FirstPhysic) then
1037           ok_start_timer=.TRUE.
1038           FirstPhysic=.false.
1039         endif
1040c$OMP END MASTER
1041
1042       ijb=ij_begin
1043       ije=ij_end
1044!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
1045       do l=1,llm
1046        teta(ijb:ije,l)=teta(ijb:ije,l)-dtvr*
1047     &         (teta(ijb:ije,l)-tetarappel(ijb:ije,l))*
1048     &                  (knewt_g+knewt_t(l)*clat4(ijb:ije))
1049       enddo ! of do l=1,llm
1050!$OMP END DO
1051
1052!$OMP MASTER
1053       if (planet_type.eq."giant") then
1054         ! add an intrinsic heat flux at the base of the atmosphere
1055         teta(ijb:ije,1) = teta(ijb:ije,1)
1056     &        + dtvr * aire(ijb:ije) * ihf / cpp / masse(ijb:ije,1)
1057       endif
1058!$OMP END MASTER
1059!$OMP BARRIER
1060
1061       call Register_Hallo(ucov,ip1jmp1,llm,0,1,1,0,Request_Physic)
1062       call Register_Hallo(vcov,ip1jm,llm,1,1,1,1,Request_Physic)
1063       call SendRequest(Request_Physic)
1064c$OMP BARRIER
1065       call WaitRequest(Request_Physic)     
1066c$OMP BARRIER
1067       call friction_p(ucov,vcov,dtvr)
1068!$OMP BARRIER
1069
1070        ! Sponge layer (if any)
1071        IF (ok_strato) THEN
1072          CALL top_bound_p(vcov,ucov,teta,masse,dtvr)
1073!$OMP BARRIER
1074        ENDIF ! of IF (ok_strato)
1075      ENDIF ! of IF(iflag_phys.EQ.2)
1076
1077
1078        CALL pression_p ( ip1jmp1, ap, bp, ps, p                  )
1079c$OMP BARRIER
1080        if (pressure_exner) then
1081          CALL exner_hyb_p( ip1jmp1, ps, p, pks, pk, pkf )
1082        else
1083          CALL exner_milieu_p( ip1jmp1, ps, p, pks, pk, pkf )
1084        endif
1085c$OMP BARRIER
1086        CALL massdair_p(p,masse)
1087c$OMP BARRIER
1088
1089cc$OMP END PARALLEL
1090
1091c-----------------------------------------------------------------------
1092c   dissipation horizontale et verticale  des petites echelles:
1093c   ----------------------------------------------------------
1094
1095      IF(apdiss) THEN
1096cc$OMP  PARALLEL DEFAULT(SHARED)
1097cc$OMP+          PRIVATE(ijb,ije,tppn,tpn,tpps,tps)
1098c$OMP MASTER
1099        call suspend_timer(timer_caldyn)
1100       
1101c       print*,'Entree dans la dissipation : Iteration No ',true_itau
1102c   calcul de l'energie cinetique avant dissipation
1103c       print *,'Passage dans la dissipation'
1104
1105        call VTb(VThallo)
1106c$OMP END MASTER
1107
1108c$OMP BARRIER
1109
1110        call Register_SwapFieldHallo(ucov,ucov,ip1jmp1,llm,
1111     *                          jj_Nb_dissip,1,1,Request_dissip)
1112
1113        call Register_SwapFieldHallo(vcov,vcov,ip1jm,llm,
1114     *                          jj_Nb_dissip,1,1,Request_dissip)
1115
1116        call Register_SwapField(teta,teta,ip1jmp1,llm,
1117     *                          jj_Nb_dissip,Request_dissip)
1118
1119        call Register_SwapField(p,p,ip1jmp1,llmp1,
1120     *                          jj_Nb_dissip,Request_dissip)
1121
1122        call Register_SwapField(pk,pk,ip1jmp1,llm,
1123     *                          jj_Nb_dissip,Request_dissip)
1124
1125        call SendRequest(Request_dissip)       
1126c$OMP BARRIER
1127        call WaitRequest(Request_dissip)       
1128
1129c$OMP BARRIER
1130c$OMP MASTER
1131        call SetDistrib(jj_Nb_dissip)
1132        call VTe(VThallo)
1133        call VTb(VTdissipation)
1134        call start_timer(timer_dissip)
1135c$OMP END MASTER
1136c$OMP BARRIER
1137
1138        call covcont_p(llm,ucov,vcov,ucont,vcont)
1139        call enercin_p(vcov,ucov,vcont,ucont,ecin0)
1140
1141c   dissipation
1142
1143!        CALL FTRACE_REGION_BEGIN("dissip")
1144        CALL dissip_p(vcov,ucov,teta,p,dvdis,dudis,dtetadis)
1145!        CALL FTRACE_REGION_END("dissip")
1146         
1147        ijb=ij_begin
1148        ije=ij_end
1149c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)       
1150        DO l=1,llm
1151          ucov(ijb:ije,l)=ucov(ijb:ije,l)+dudis(ijb:ije,l)
1152        ENDDO
1153c$OMP END DO NOWAIT       
1154        if (pole_sud) ije=ije-iip1
1155c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)       
1156        DO l=1,llm
1157          vcov(ijb:ije,l)=vcov(ijb:ije,l)+dvdis(ijb:ije,l)
1158        ENDDO
1159c$OMP END DO NOWAIT       
1160
1161c       teta=teta+dtetadis
1162
1163
1164c------------------------------------------------------------------------
1165        if (dissip_conservative) then
1166C       On rajoute la tendance due a la transform. Ec -> E therm. cree
1167C       lors de la dissipation
1168c$OMP BARRIER
1169c$OMP MASTER
1170            call suspend_timer(timer_dissip)
1171            call VTb(VThallo)
1172c$OMP END MASTER
1173            call Register_Hallo(ucov,ip1jmp1,llm,1,1,1,1,Request_Dissip)
1174            call Register_Hallo(vcov,ip1jm,llm,1,1,1,1,Request_Dissip)
1175            call SendRequest(Request_Dissip)
1176c$OMP BARRIER
1177            call WaitRequest(Request_Dissip)
1178c$OMP MASTER
1179            call VTe(VThallo)
1180            call resume_timer(timer_dissip)
1181c$OMP END MASTER
1182c$OMP BARRIER           
1183            call covcont_p(llm,ucov,vcov,ucont,vcont)
1184            call enercin_p(vcov,ucov,vcont,ucont,ecin)
1185           
1186            ijb=ij_begin
1187            ije=ij_end
1188c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)           
1189            do l=1,llm
1190              do ij=ijb,ije
1191                dtetaecdt(ij,l)= (ecin0(ij,l)-ecin(ij,l))/ pk(ij,l)
1192                dtetadis(ij,l)=dtetadis(ij,l)+dtetaecdt(ij,l)
1193              enddo
1194            enddo
1195c$OMP END DO NOWAIT           
1196       endif ! of if (dissip_conservative)
1197
1198       ijb=ij_begin
1199       ije=ij_end
1200c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)           
1201         do l=1,llm
1202           do ij=ijb,ije
1203              teta(ij,l)=teta(ij,l)+dtetadis(ij,l)
1204           enddo
1205         enddo
1206c$OMP END DO NOWAIT         
1207c------------------------------------------------------------------------
1208
1209
1210c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
1211c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
1212c
1213
1214        ijb=ij_begin
1215        ije=ij_end
1216         
1217        if (pole_nord) then
1218c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
1219          DO l  =  1, llm
1220            DO ij =  1,iim
1221             tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
1222            ENDDO
1223             tpn  = SSUM(iim,tppn,1)/apoln
1224
1225            DO ij = 1, iip1
1226             teta(  ij    ,l) = tpn
1227            ENDDO
1228          ENDDO
1229c$OMP END DO NOWAIT
1230
1231         if (1 == 0) then
1232!!! Ehouarn: lines here 1) kill 1+1=2 in the dynamics
1233!!!                     2) should probably not be here anyway
1234!!! but are kept for those who would want to revert to previous behaviour
1235c$OMP MASTER               
1236          DO ij =  1,iim
1237            tppn(ij)  = aire(  ij    ) * ps (  ij    )
1238          ENDDO
1239            tpn  = SSUM(iim,tppn,1)/apoln
1240 
1241          DO ij = 1, iip1
1242            ps(  ij    ) = tpn
1243          ENDDO
1244c$OMP END MASTER
1245         endif ! of if (1 == 0)
1246        endif ! of of (pole_nord)
1247       
1248        if (pole_sud) then
1249c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
1250          DO l  =  1, llm
1251            DO ij =  1,iim
1252             tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
1253            ENDDO
1254             tps  = SSUM(iim,tpps,1)/apols
1255
1256            DO ij = 1, iip1
1257             teta(ij+ip1jm,l) = tps
1258            ENDDO
1259          ENDDO
1260c$OMP END DO NOWAIT
1261
1262         if (1 == 0) then
1263!!! Ehouarn: lines here 1) kill 1+1=2 in the dynamics
1264!!!                     2) should probably not be here anyway
1265!!! but are kept for those who would want to revert to previous behaviour
1266c$OMP MASTER               
1267          DO ij =  1,iim
1268            tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
1269          ENDDO
1270            tps  = SSUM(iim,tpps,1)/apols
1271 
1272          DO ij = 1, iip1
1273            ps(ij+ip1jm) = tps
1274          ENDDO
1275c$OMP END MASTER
1276         endif ! of if (1 == 0)
1277        endif ! of if (pole_sud)
1278
1279
1280c$OMP BARRIER
1281c$OMP MASTER
1282        call VTe(VTdissipation)
1283
1284        call stop_timer(timer_dissip)
1285       
1286        call VTb(VThallo)
1287c$OMP END MASTER
1288        call Register_SwapField(ucov,ucov,ip1jmp1,llm,
1289     *                          jj_Nb_caldyn,Request_dissip)
1290
1291        call Register_SwapField(vcov,vcov,ip1jm,llm,
1292     *                          jj_Nb_caldyn,Request_dissip)
1293
1294        call Register_SwapField(teta,teta,ip1jmp1,llm,
1295     *                          jj_Nb_caldyn,Request_dissip)
1296
1297        call Register_SwapField(p,p,ip1jmp1,llmp1,
1298     *                          jj_Nb_caldyn,Request_dissip)
1299
1300        call Register_SwapField(pk,pk,ip1jmp1,llm,
1301     *                          jj_Nb_caldyn,Request_dissip)
1302
1303        call SendRequest(Request_dissip)       
1304c$OMP BARRIER
1305        call WaitRequest(Request_dissip)       
1306
1307c$OMP BARRIER
1308c$OMP MASTER
1309        call SetDistrib(jj_Nb_caldyn)
1310        call VTe(VThallo)
1311        call resume_timer(timer_caldyn)
1312c        print *,'fin dissipation'
1313c$OMP END MASTER
1314c$OMP BARRIER
1315      END IF ! of IF(apdiss)
1316
1317cc$OMP END PARALLEL
1318
1319c ajout debug
1320c              IF( lafin ) then 
1321c                abort_message = 'Simulation finished'
1322c                call abort_gcm(modname,abort_message,0)
1323c              ENDIF
1324       
1325c   ********************************************************************
1326c   ********************************************************************
1327c   .... fin de l'integration dynamique  et physique pour le pas itau ..
1328c   ********************************************************************
1329c   ********************************************************************
1330
1331c   preparation du pas d'integration suivant  ......
1332cym      call WriteField('ucov',reshape(ucov,(/iip1,jmp1,llm/)))
1333cym      call WriteField('vcov',reshape(vcov,(/iip1,jjm,llm/)))
1334c$OMP MASTER     
1335      call stop_timer(timer_caldyn)
1336c$OMP END MASTER
1337      IF (itau==itaumax) then
1338c$OMP MASTER
1339            call allgather_timer_average
1340
1341      if (mpi_rank==0) then
1342       
1343        print *,'*********************************'
1344        print *,'******    TIMER CALDYN     ******'
1345        do i=0,mpi_size-1
1346          print *,'proc',i,' :   Nb Bandes  :',jj_nb_caldyn(i),
1347     &            '  : temps moyen :',
1348     &             timer_average(jj_nb_caldyn(i),timer_caldyn,i)
1349        enddo
1350     
1351        print *,'*********************************'
1352        print *,'******    TIMER VANLEER    ******'
1353        do i=0,mpi_size-1
1354          print *,'proc',i,' :   Nb Bandes  :',jj_nb_vanleer(i),
1355     &            '  : temps moyen :',
1356     &             timer_average(jj_nb_vanleer(i),timer_vanleer,i)
1357        enddo
1358     
1359        print *,'*********************************'
1360        print *,'******    TIMER DISSIP    ******'
1361        do i=0,mpi_size-1
1362          print *,'proc',i,' :   Nb Bandes  :',jj_nb_dissip(i),
1363     &            '  : temps moyen :',
1364     &             timer_average(jj_nb_dissip(i),timer_dissip,i)
1365        enddo
1366       
1367        print *,'*********************************'
1368        print *,'******    TIMER PHYSIC    ******'
1369        do i=0,mpi_size-1
1370          print *,'proc',i,' :   Nb Bandes  :',jj_nb_physic(i),
1371     &            '  : temps moyen :',
1372     &             timer_average(jj_nb_physic(i),timer_physic,i)
1373        enddo
1374       
1375      endif 
1376     
1377      print *,'Taille du Buffer MPI (REAL*8)',MaxBufferSize
1378      print *,'Taille du Buffer MPI utilise (REAL*8)',MaxBufferSize_Used
1379      print *, 'Temps total ecoule sur la parallelisation :',DiffTime()
1380      print *, 'Temps CPU ecoule sur la parallelisation :',DiffCpuTime()
1381      CALL print_filtre_timer
1382      call fin_getparam
1383        call finalize_parallel
1384c$OMP END MASTER
1385c$OMP BARRIER
1386        RETURN
1387      ENDIF ! of IF (itau==itaumax)
1388     
1389      IF ( .NOT.purmats ) THEN
1390c       ........................................................
1391c       ..............  schema matsuno + leapfrog  ..............
1392c       ........................................................
1393
1394            IF(forward. OR. leapf) THEN
1395              itau= itau + 1
1396!              iday= day_ini+itau/day_step
1397!              time= REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
1398!                IF(time.GT.1.) THEN
1399!                  time = time-1.
1400!                  iday = iday+1
1401!                ENDIF
1402            ENDIF
1403
1404
1405            IF( itau. EQ. itaufinp1 ) then
1406
1407              if (flag_verif) then
1408                write(79,*) 'ucov',ucov
1409                write(80,*) 'vcov',vcov
1410                write(81,*) 'teta',teta
1411                write(82,*) 'ps',ps
1412                write(83,*) 'q',q
1413                WRITE(85,*) 'q1 = ',q(:,:,1)
1414                WRITE(86,*) 'q3 = ',q(:,:,3)
1415              endif
1416 
1417
1418c$OMP MASTER
1419              call fin_getparam
1420c$OMP END MASTER
1421#ifdef INCA
1422                 call finalize_inca
1423#endif
1424c$OMP MASTER
1425               call finalize_parallel
1426c$OMP END MASTER
1427              abort_message = 'Simulation finished'
1428              call abort_gcm(modname,abort_message,0)
1429              RETURN
1430            ENDIF
1431c-----------------------------------------------------------------------
1432c   ecriture du fichier histoire moyenne:
1433c   -------------------------------------
1434
1435            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
1436c$OMP BARRIER
1437               IF(itau.EQ.itaufin) THEN
1438                  iav=1
1439               ELSE
1440                  iav=0
1441               ENDIF
1442#ifdef CPP_IOIPSL
1443             IF (ok_dynzon) THEN
1444              CALL bilan_dyn_p(2,dtvr*iperiod,dtvr*day_step*periodav,
1445     ,             ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
1446              ENDIF !ok_dynzon
1447#endif
1448               IF (ok_dyn_ave) THEN
1449!$OMP MASTER
1450#ifdef CPP_IOIPSL
1451! Ehouarn: Gather fields and make master send to output
1452                call Gather_Field(vcov,ip1jm,llm,0)
1453                call Gather_Field(ucov,ip1jmp1,llm,0)
1454                call Gather_Field(teta,ip1jmp1,llm,0)
1455                call Gather_Field(pk,ip1jmp1,llm,0)
1456                call Gather_Field(phi,ip1jmp1,llm,0)
1457                do iq=1,nqtot
1458                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
1459                enddo
1460                call Gather_Field(masse,ip1jmp1,llm,0)
1461                call Gather_Field(ps,ip1jmp1,1,0)
1462                call Gather_Field(phis,ip1jmp1,1,0)
1463                if (mpi_rank==0) then
1464                 CALL writedynav(itau,vcov,
1465     &                 ucov,teta,pk,phi,q,masse,ps,phis)
1466                endif
1467#endif
1468!$OMP END MASTER
1469               ENDIF ! of IF (ok_dyn_ave)
1470            ENDIF ! of IF((MOD(itau,iperiod).EQ.0).OR.(itau.EQ.itaufin))
1471
1472c-----------------------------------------------------------------------
1473c   ecriture de la bande histoire:
1474c   ------------------------------
1475
1476            IF( MOD(itau,iecri).EQ.0) THEN
1477             ! Ehouarn: output only during LF or Backward Matsuno
1478             if (leapf.or.(.not.leapf.and.(.not.forward))) then
1479c$OMP BARRIER
1480c$OMP MASTER
1481              CALL geopot_p(ip1jmp1,teta,pk,pks,phis,phi)
1482       
1483cym        unat=0.
1484       
1485              ijb=ij_begin
1486              ije=ij_end
1487       
1488              if (pole_nord) then
1489                ijb=ij_begin+iip1
1490                unat(1:iip1,:)=0.
1491              endif
1492       
1493              if (pole_sud) then
1494                ije=ij_end-iip1
1495                unat(ij_end-iip1+1:ij_end,:)=0.
1496              endif
1497           
1498              do l=1,llm
1499                unat(ijb:ije,l)=ucov(ijb:ije,l)/cu(ijb:ije)
1500              enddo
1501
1502              ijb=ij_begin
1503              ije=ij_end
1504              if (pole_sud) ije=ij_end-iip1
1505       
1506              do l=1,llm
1507                vnat(ijb:ije,l)=vcov(ijb:ije,l)/cv(ijb:ije)
1508              enddo
1509       
1510#ifdef CPP_IOIPSL
1511              if (ok_dyn_ins) then
1512! Ehouarn: Gather fields and make master write to output
1513                call Gather_Field(vcov,ip1jm,llm,0)
1514                call Gather_Field(ucov,ip1jmp1,llm,0)
1515                call Gather_Field(teta,ip1jmp1,llm,0)
1516                call Gather_Field(phi,ip1jmp1,llm,0)
1517                do iq=1,nqtot
1518                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
1519                enddo
1520                call Gather_Field(masse,ip1jmp1,llm,0)
1521                call Gather_Field(ps,ip1jmp1,1,0)
1522                call Gather_Field(phis,ip1jmp1,1,0)
1523                if (mpi_rank==0) then
1524                 CALL writehist(itau,vcov,ucov,teta,phi,q,masse,ps,phis)
1525                endif
1526!              CALL writehist_p(histid,histvid, itau,vcov,
1527!     &                         ucov,teta,phi,q,masse,ps,phis)
1528! or use writefield_p
1529!      call WriteField_p('ucov',reshape(ucov,(/iip1,jmp1,llm/)))
1530!      call WriteField_p('vcov',reshape(vcov,(/iip1,jjm,llm/)))
1531!      call WriteField_p('teta',reshape(teta,(/iip1,jmp1,llm/)))
1532!      call WriteField_p('ps',reshape(ps,(/iip1,jmp1/)))
1533              endif ! of if (ok_dyn_ins)
1534#endif
1535! For some Grads outputs of fields
1536              if (output_grads_dyn) then
1537! Ehouarn: hope this works the way I think it does:
1538                  call Gather_Field(unat,ip1jmp1,llm,0)
1539                  call Gather_Field(vnat,ip1jm,llm,0)
1540                  call Gather_Field(teta,ip1jmp1,llm,0)
1541                  call Gather_Field(ps,ip1jmp1,1,0)
1542                  do iq=1,nqtot
1543                    call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
1544                  enddo
1545                  if (mpi_rank==0) then
1546#include "write_grads_dyn.h"
1547                  endif
1548              endif ! of if (output_grads_dyn)
1549c$OMP END MASTER
1550             endif ! of if (leapf.or.(.not.leapf.and.(.not.forward)))
1551            ENDIF ! of IF(MOD(itau,iecri).EQ.0)
1552
1553            IF(itau.EQ.itaufin) THEN
1554
1555c$OMP BARRIER
1556c$OMP MASTER
1557
1558!              if (planet_type.eq."earth") then
1559! Write an Earth-format restart file
1560                CALL dynredem1_p("restart.nc",0.0,
1561     &                           vcov,ucov,teta,q,masse,ps)
1562!              endif ! of if (planet_type.eq."earth")
1563
1564!              CLOSE(99)
1565c$OMP END MASTER
1566            ENDIF ! of IF (itau.EQ.itaufin)
1567
1568c-----------------------------------------------------------------------
1569c   gestion de l'integration temporelle:
1570c   ------------------------------------
1571
1572            IF( MOD(itau,iperiod).EQ.0 )    THEN
1573                    GO TO 1
1574            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
1575
1576                   IF( forward )  THEN
1577c      fin du pas forward et debut du pas backward
1578
1579                      forward = .FALSE.
1580                        leapf = .FALSE.
1581                           GO TO 2
1582
1583                   ELSE
1584c      fin du pas backward et debut du premier pas leapfrog
1585
1586                        leapf =  .TRUE.
1587                        dt  =  2.*dtvr
1588                        GO TO 2
1589                   END IF
1590            ELSE
1591
1592c      ......   pas leapfrog  .....
1593
1594                 leapf = .TRUE.
1595                 dt  = 2.*dtvr
1596                 GO TO 2
1597            END IF ! of IF (MOD(itau,iperiod).EQ.0)
1598                   !    ELSEIF (MOD(itau-1,iperiod).EQ.0)
1599
1600
1601      ELSE ! of IF (.not.purmats)
1602
1603c       ........................................................
1604c       ..............       schema  matsuno        ...............
1605c       ........................................................
1606            IF( forward )  THEN
1607
1608             itau =  itau + 1
1609!             iday = day_ini+itau/day_step
1610!             time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
1611!
1612!                  IF(time.GT.1.) THEN
1613!                   time = time-1.
1614!                   iday = iday+1
1615!                  ENDIF
1616
1617               forward =  .FALSE.
1618               IF( itau. EQ. itaufinp1 ) then 
1619c$OMP MASTER
1620                 call fin_getparam
1621                 call finalize_parallel
1622c$OMP END MASTER
1623                 abort_message = 'Simulation finished'
1624                 call abort_gcm(modname,abort_message,0)
1625                 RETURN
1626               ENDIF
1627               GO TO 2
1628
1629            ELSE ! of IF(forward) i.e. backward step
1630
1631              IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
1632               IF(itau.EQ.itaufin) THEN
1633                  iav=1
1634               ELSE
1635                  iav=0
1636               ENDIF
1637#ifdef CPP_IOIPSL
1638               IF (ok_dynzon) THEN
1639               CALL bilan_dyn_p(2,dtvr*iperiod,dtvr*day_step*periodav,
1640     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
1641               END IF !ok_dynzon
1642#endif
1643               IF (ok_dyn_ave) THEN
1644!$OMP MASTER
1645#ifdef CPP_IOIPSL
1646! Ehouarn: Gather fields and make master send to output
1647                call Gather_Field(vcov,ip1jm,llm,0)
1648                call Gather_Field(ucov,ip1jmp1,llm,0)
1649                call Gather_Field(teta,ip1jmp1,llm,0)
1650                call Gather_Field(pk,ip1jmp1,llm,0)
1651                call Gather_Field(phi,ip1jmp1,llm,0)
1652                do iq=1,nqtot
1653                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
1654                enddo
1655                call Gather_Field(masse,ip1jmp1,llm,0)
1656                call Gather_Field(ps,ip1jmp1,1,0)
1657                call Gather_Field(phis,ip1jmp1,1,0)
1658                if (mpi_rank==0) then
1659                 CALL writedynav(itau,vcov,
1660     &                 ucov,teta,pk,phi,q,masse,ps,phis)
1661                endif
1662#endif
1663!$OMP END MASTER
1664               ENDIF ! of IF (ok_dyn_ave)
1665
1666              ENDIF ! of IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin)
1667
1668
1669               IF(MOD(itau,iecri         ).EQ.0) THEN
1670c              IF(MOD(itau,iecri*day_step).EQ.0) THEN
1671c$OMP BARRIER
1672c$OMP MASTER
1673                CALL geopot_p(ip1jmp1,teta,pk,pks,phis,phi)
1674
1675cym        unat=0.
1676                ijb=ij_begin
1677                ije=ij_end
1678       
1679                if (pole_nord) then
1680                  ijb=ij_begin+iip1
1681                  unat(1:iip1,:)=0.
1682                endif
1683       
1684                if (pole_sud) then
1685                  ije=ij_end-iip1
1686                  unat(ij_end-iip1+1:ij_end,:)=0.
1687                endif
1688           
1689                do l=1,llm
1690                  unat(ijb:ije,l)=ucov(ijb:ije,l)/cu(ijb:ije)
1691                enddo
1692
1693                ijb=ij_begin
1694                ije=ij_end
1695                if (pole_sud) ije=ij_end-iip1
1696       
1697                do l=1,llm
1698                  vnat(ijb:ije,l)=vcov(ijb:ije,l)/cv(ijb:ije)
1699                enddo
1700
1701#ifdef CPP_IOIPSL
1702              if (ok_dyn_ins) then
1703! Ehouarn: Gather fields and make master send to output
1704                call Gather_Field(vcov,ip1jm,llm,0)
1705                call Gather_Field(ucov,ip1jmp1,llm,0)
1706                call Gather_Field(teta,ip1jmp1,llm,0)
1707                call Gather_Field(phi,ip1jmp1,llm,0)
1708                do iq=1,nqtot
1709                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
1710                enddo
1711                call Gather_Field(masse,ip1jmp1,llm,0)
1712                call Gather_Field(ps,ip1jmp1,1,0)
1713                call Gather_Field(phis,ip1jmp1,1,0)
1714                if (mpi_rank==0) then
1715                 CALL writehist(itau,vcov,ucov,teta,phi,q,masse,ps,phis)
1716                endif
1717!                CALL writehist_p(histid, histvid, itau,vcov ,
1718!     &                           ucov,teta,phi,q,masse,ps,phis)
1719              endif ! of if (ok_dyn_ins)
1720#endif
1721! For some Grads output (but does it work?)
1722                if (output_grads_dyn) then
1723                  call Gather_Field(unat,ip1jmp1,llm,0)
1724                  call Gather_Field(vnat,ip1jm,llm,0)
1725                  call Gather_Field(teta,ip1jmp1,llm,0)
1726                  call Gather_Field(ps,ip1jmp1,1,0)
1727                  do iq=1,nqtot
1728                    call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
1729                  enddo
1730c     
1731                  if (mpi_rank==0) then
1732#include "write_grads_dyn.h"
1733                  endif
1734                endif ! of if (output_grads_dyn)
1735
1736c$OMP END MASTER
1737              ENDIF ! of IF(MOD(itau,iecri).EQ.0)
1738
1739              IF(itau.EQ.itaufin) THEN
1740!                if (planet_type.eq."earth") then
1741c$OMP MASTER
1742                   CALL dynredem1_p("restart.nc",0.0,
1743     .                               vcov,ucov,teta,q,masse,ps)
1744c$OMP END MASTER
1745!                endif ! of if (planet_type.eq."earth")
1746              ENDIF ! of IF(itau.EQ.itaufin)
1747
1748              forward = .TRUE.
1749              GO TO  1
1750
1751            ENDIF ! of IF (forward)
1752
1753      END IF ! of IF(.not.purmats)
1754c$OMP MASTER
1755      call fin_getparam
1756      call finalize_parallel
1757c$OMP END MASTER
1758      RETURN
1759      END
Note: See TracBrowser for help on using the repository browser.