source: trunk/LMDZ.GENERIC/libf/dyn3d/gcm.F @ 995

Last change on this file since 995 was 993, checked in by emillour, 12 years ago

Generic GCM:

  • Some more cleanup in dynamics:
    • Moved "start2archive" (and auxilliary routines) to phystd
    • removed unused (obsolete) testharm.F , para_netcdf.h , readhead_NC.F , angtot.h from dyn3d
    • removed obsolete addit.F (and change corresponding lines in gcm)
    • remove unused "description.h" (and many places where it was "included")

EM

File size: 18.7 KB
Line 
1      PROGRAM gcm
2
3      IMPLICIT NONE
4
5c      ......   Version  du 10/01/98    ..........
6
7c             avec  coordonnees  verticales hybrides
8c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
9
10c=======================================================================
11c
12c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
13c   -------
14c
15c   Objet:
16c   ------
17c
18c   GCM LMD nouvelle grille
19c
20c=======================================================================
21c
22c  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
23c      et possibilite d'appeler une fonction f(y)  a derivee tangente
24c      hyperbolique a la  place de la fonction a derivee sinusoidale.
25
26c  ... Possibilite de choisir le shema de Van-leer pour l'advection de
27c        q  , en faisant iadv = 3  dans   traceur  (29/04/97) .
28c
29c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
30c
31c-----------------------------------------------------------------------
32c   Declarations:
33c   -------------
34
35#include "dimensions.h"
36#include "paramet.h"
37#include "comconst.h"
38#include "comdissnew.h"
39#include "comvert.h"
40#include "comgeom.h"
41#include "logic.h"
42#include "temps.h"
43#include "control.h"
44#include "ener.h"
45#include "netcdf.inc"
46#include "serre.h"
47#include "tracstoke.h"
48#include "sponge.h"
49#include"advtrac.h"
50
51      INTEGER*4  iday ! jour julien
52      REAL       time ! Heure de la journee en fraction d''1 jour
53      REAL zdtvr
54
55c   variables dynamiques
56      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
57      real, dimension(ip1jmp1,llm) :: teta   ! temperature potentielle
58      REAL q(ip1jmp1,llm,nqmx)               ! champs advectes
59      REAL ps(ip1jmp1)                       ! pression  au sol
60      REAL pext(ip1jmp1)                     ! pression  extensive
61      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
62      REAL pks(ip1jmp1)                      ! exner au  sol
63      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
64      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
65      REAL masse(ip1jmp1,llm)                ! masse d''air
66      REAL phis(ip1jmp1)                     ! geopotentiel au sol
67      REAL phi(ip1jmp1,llm)                  ! geopotentiel
68      REAL w(ip1jmp1,llm)                    ! vitesse verticale
69
70c variables dynamiques intermediaire pour le transport
71      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm) !flux de masse
72
73c   variables dynamiques au pas -1
74      REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
75
76      REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1)
77      REAL massem1(ip1jmp1,llm)
78
79c   tendances dynamiques
80      REAL dv(ip1jm,llm),du(ip1jmp1,llm)
81      REAL dteta(ip1jmp1,llm),dq(ip1jmp1,llm,nqmx),dp(ip1jmp1)
82
83c   tendances de la dissipation
84      REAL dvdis(ip1jm,llm),dudis(ip1jmp1,llm)
85      REAL dhdis(ip1jmp1,llm)
86
87c   tendances physiques
88      REAL dvfi(ip1jm,llm),dufi(ip1jmp1,llm)
89      REAL dhfi(ip1jmp1,llm),dqfi(ip1jmp1,llm,nqmx),dpfi(ip1jmp1)
90
91c   variables pour le fichier histoire
92      REAL dtav      ! intervalle de temps elementaire
93
94      REAL tppn(iim),tpps(iim),tpn,tps
95c
96!      INTEGER iadv(nqmx) ! indice schema de transport pour le traceur iq
97
98      INTEGER itau,itaufinp1,iav
99
100
101      EXTERNAL caldyn, traceur
102      EXTERNAL dissip,geopot,iniconst,inifilr
103      EXTERNAL integrd,SCOPY
104      EXTERNAL inigeom
105      EXTERNAL exner_hyb
106      EXTERNAL defrun_new, test_period
107      REAL  SSUM
108      REAL time_0 , finvmaold(ip1jmp1,llm)
109
110      LOGICAL lafin
111      INTEGER ij,iq,l,ierr,numvanle,iapp_tracvl
112
113      REAL rdayvrai,rdaym_ini,rday_ecri
114!      LOGICAL first
115      REAL beta(ip1jmp1,llm)
116
117      LOGICAL offline  ! Controle du stockage ds "fluxmass"
118      PARAMETER (offline=.false.)
119
120      character*20 modname
121      character*80 abort_message
122
123      LOGICAL tracer
124          data tracer/.true./
125      INTEGER nq
126
127C Calendrier
128      LOGICAL true_calendar
129      PARAMETER (true_calendar = .false.)
130
131! flag to set/remove calls to groupeun
132      logical callgroupeun
133      parameter (callgroupeun = .false.)
134
135!     added by RDW for tests without dynamics
136      logical calldyn
137      parameter (calldyn = .true.)
138
139!     added by RW for test
140!      real pmean,airetot
141
142!     added by FF for dissipation / energy conservation tests
143      logical dissip_conservative
144      parameter (dissip_conservative = .false.)
145      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
146!     d (theta)/ d t (pot. temperature) due to the creation
147!     of thermal energy by dissipation
148      REAL dtetaecdt(ip1jmp1,llm)
149      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
150      REAL vnat(ip1jm,llm),unat(ip1jmp1,llm)
151
152
153c-----------------------------------------------------------------------
154c   Initialisations:
155c   ----------------
156
157      modname = 'gcm'
158      lafin    = .FALSE.
159
160c-----------------------------------------------------------------------
161c  Initialize tracers using iniadvtrac (Ehouarn, oct 2008)
162      CALL iniadvtrac(nq,numvanle)
163
164
165      CALL dynetat0("start.nc",nqmx,vcov,ucov,
166     .              teta,q,masse,ps,phis, time_0)
167
168      CALL defrun_new( 99, .TRUE. )
169
170c  on recalcule eventuellement le pas de temps
171
172      IF(MOD(day_step,iperiod).NE.0)
173     * STOP'Il faut choisir un nb de pas par jour multiple de iperiod'
174
175      IF(MOD(day_step,iphysiq).NE.0)
176     * STOP'Il faut choisir un nb de pas par jour multiple de iphysiq'
177
178      zdtvr    = daysec/FLOAT(day_step)
179
180        IF(dtvr.NE.zdtvr) THEN
181         PRINT*,'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
182        ENDIF
183
184c  nombre d'etats dans les fichiers demarrage et histoire
185
186      dtvr = zdtvr
187      CALL iniconst
188      CALL inigeom
189      CALL inifilr
190
191c
192c   ......    P.Le Van    ( modif  le 29/04/97 )   ......... 
193c
194
195      CALL inidissip ( lstardis, nitergdiv, nitergrot, niterh   ,
196     *                tetagdiv, tetagrot , tetatemp              )
197c
198
199      CALL pression ( ip1jmp1, ap, bp, ps, p       )
200
201      call dump2d(iip1,jjp1,ps,'PRESSION SURFACE')
202      CALL exner_hyb( ip1jmp1, ps, p,beta, pks, pk, pkf )
203
204
205c  numero de stockage pour les fichiers de redemarrage:
206
207c-----------------------------------------------------------------------
208c   temps de depart et de fin:
209c   --------------------------
210
211      itau = 0
212      iday = day_ini+itau/day_step
213      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
214
215
216         IF(time.GT.1.) THEN
217          time = time-1.
218          iday = iday+1
219         ENDIF
220      itaufin   = nday*day_step
221c ********************************
222c      itaufin = 120   ! temporaire !!
223c ********************************
224      itaufinp1 = itaufin +1
225
226      day_end = day_ini + nday
227      PRINT 300, itau,itaufin,day_ini,day_end
228 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
229     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
230
231      CALL dynredem0("restart.nc",day_end,anne_ini,phis,nqmx)
232
233      ecripar = .TRUE.
234
235      dtav = iperiod*dtvr/daysec
236
237
238c   Quelques initialisations pour les traceurs
239      call initial0(ijp1llm*nqmx,dq)
240c     istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
241c     istphy=istdyn/iphysiq
242
243      write(*,*) "gcm: callgroupeun set to:",callgroupeun
244c-----------------------------------------------------------------------
245c   Debut de l'integration temporelle:
246c   ----------------------------------
247
248   1  CONTINUE
249c
250      IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
251        CALL test_period ( ucov,vcov,teta,q,p,phis )
252        PRINT *,' ----   Test_period apres continue   OK ! -----', itau
253      ENDIF
254
255      if (callgroupeun) then
256        call groupeun(jjp1,llm,ucov,.true.)
257        call groupeun(jjm,llm,vcov,.true.)
258        call groupeun(jjp1,llm,teta,.true.)
259        call groupeun(jjp1,llm,masse,.true.)
260        call groupeun(jjp1,1,ps,.false.)
261      endif
262
263      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
264      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
265      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
266      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
267      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
268
269      forward = .TRUE.
270      leapf   = .FALSE.
271      dt      =  dtvr
272
273c   ...    P.Le Van .26/04/94  ....
274
275      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
276      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
277
278
279   2  CONTINUE
280
281c-----------------------------------------------------------------------
282
283c   date:
284c   -----
285
286!      write(*,*) 'GCM: itau=',itau
287
288c   gestion des appels de la physique et des dissipations:
289c   ------------------------------------------------------
290c
291c   ...    P.Le Van  ( 6/02/95 )  ....
292
293      apphys = .FALSE.
294      statcl = .FALSE.
295      conser = .FALSE.
296      apdiss = .FALSE.
297
298      IF( purmats ) THEN
299         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
300         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
301         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
302     $                              .AND.   physic    ) apphys = .TRUE.
303      ELSE
304         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
305         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
306         IF( MOD(itau+1,iphysiq).EQ.0. AND. physic    ) apphys = .TRUE.
307      END IF
308
309c-----------------------------------------------------------------------
310c   calcul des tendances dynamiques:
311c   --------------------------------
312
313      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
314
315      if(calldyn)then
316         CALL caldyn
317     $        ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
318     $        phi,conser,du,dv,dteta,dp,w,pbaru,pbarv,time+iday-day_ini)
319      endif
320
321c-----------------------------------------------------------------------
322c   calcul des tendances advection des traceurs (dont l'humidite)
323c   -------------------------------------------------------------
324
325
326
327      if (tracer) then
328       IF( forward. OR . leapf )  THEN
329
330        DO iq = 1, nqmx
331c
332         IF ( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
333            CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
334
335         ELSE IF( iq.EQ. nqmx )   THEN
336c
337            iapp_tracvl = 5
338c
339cccc     iapp_tracvl est la frequence en pas du groupement des flux
340cccc      de masse pour  Van-Leer dans la routine  tracvl  .
341c
342
343            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
344     *                      p, masse, dq,  iadv(1), teta, pk     )
345
346c
347c                   ...  Modif  F.Codron  ....
348c
349         ENDIF
350c
351        ENDDO
352C
353c        IF (offline) THEN
354C maf stokage du flux de masse pour traceurs OFF-LINE
355
356c           CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
357c    .   time_step, itau)
358
359c        ENDIF
360c
361      ENDIF
362          END IF   ! tracer
363
364
365c-----------------------------------------------------------------------
366c   integrations dynamique et traceurs:
367c   ----------------------------------
368
369          if(calldyn)then
370             CALL integrd(2,vcovm1,ucovm1,tetam1,psm1,massem1,
371     $            dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis,
372     $            finvmaold)
373          else
374             print*,'Currently no dynamics in this GCM...'
375          endif
376
377
378
379
380
381c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
382c
383c-----------------------------------------------------------------------
384c   calcul des tendances physiques:
385c   -------------------------------
386c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
387c
388       IF( purmats )  THEN
389          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
390       ELSE
391          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
392       ENDIF
393c
394c
395       IF( apphys )  THEN
396c
397c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
398c
399
400         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
401         CALL exner_hyb(  ip1jmp1, ps, p,beta,pks, pk, pkf )
402
403           rdaym_ini  = itau * dtvr / daysec
404           rdayvrai   = rdaym_ini  + day_ini
405
406           IF ( ecritphy.LT.1. )  THEN
407             rday_ecri = rdaym_ini
408           ELSE
409             rday_ecri = INT(rdaym_ini)+INT(day_ini)
410           ENDIF
411c
412
413
414
415        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
416     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
417     $     du,dv,dteta,dq,w, dufi,dvfi,dhfi,dqfi,dpfi,tracer)
418
419
420c      ajout des tendances physiques:
421c      ------------------------------
422!        if(1.eq.2)then
423          CALL addfi( nqmx, dtphys, leapf, forward   ,
424     $                  ucov, vcov, teta , q   ,ps , masse,
425     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
426!       else
427!          print*,'Currently no physics in this GCM...'
428!       endif
429c
430       ENDIF
431
432       CALL pression ( ip1jmp1, ap, bp, ps, p                  )
433
434       CALL exner_hyb( ip1jmp1, ps, p,beta, pks, pk, pkf )
435c   ----------------------------------------------------------
436
437c
438c
439c   dissipation horizontale et verticale  des petites echelles:
440c   ----------------------------------------------------------
441
442      IF(apdiss) THEN
443
444c        Sponge layer
445c        ~~~~~~~~~~~~
446         DO ij=1, ip1jmp1
447            pext(ij)=ps(ij)*aire(ij)
448         ENDDO
449         IF (callsponge) THEN
450            CALL sponge(ucov,vcov,teta,pext,dtdiss,mode_sponge)
451         ENDIF
452
453c        Dissipation horizontale
454c        ~~~~~~~~~~~~~~~~~~~~~~~
455
456
457         if(dissip_conservative) then
458!     calculate kinetic energy before dissipation
459            call covcont(llm,ucov,vcov,ucont,vcont)
460            call enercin(vcov,ucov,vcont,ucont,ecin0)
461         end if
462
463         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
464
465         ucov(:,:)=ucov(:,:)+dudis(:,:)
466         vcov(:,:)=vcov(:,:)+dvdis(:,:)
467
468
469         if (dissip_conservative) then
470C           On rajoute la tendance due a la transform. Ec -> E therm. cree
471C           lors de la dissipation
472            call covcont(llm,ucov,vcov,ucont,vcont)
473            call enercin(vcov,ucov,vcont,ucont,ecin)
474            dtetaecdt(:,:) = (ecin0(:,:)-ecin(:,:))/ pk(:,:)
475            dhdis(:,:)     = dhdis(:,:) + dtetaecdt(:,:)
476         endif
477
478         teta(:,:)=teta(:,:)+dhdis(:,:)
479
480
481c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
482c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
483c
484
485        DO l  =  1, llm
486          DO ij =  1,iim
487           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
488           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
489          ENDDO
490
491           tpn  = SSUM(iim,tppn,1)/apoln
492           tps  = SSUM(iim,tpps,1)/apols
493
494          DO ij = 1, iip1
495           teta(  ij    ,l) = tpn
496           teta(ij+ip1jm,l) = tps
497          ENDDO
498        ENDDO
499
500        DO ij =  1,iim
501          tppn(ij)  = aire(  ij    ) * ps (  ij    )
502          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
503        ENDDO
504          tpn  = SSUM(iim,tppn,1)/apoln
505
506          tps  = SSUM(iim,tpps,1)/apols
507
508        DO ij = 1, iip1
509          ps(  ij    ) = tpn
510          ps(ij+ip1jm) = tps
511        ENDDO
512
513
514
515
516
517
518
519      END IF
520       
521c   ********************************************************************
522c   ********************************************************************
523c   .... fin de l'integration dynamique  et physique pour le pas itau ..
524c   ********************************************************************
525c   ********************************************************************
526
527c   preparation du pas d'integration suivant  ......
528
529      IF ( .NOT.purmats ) THEN
530c       ........................................................
531c       ..............  schema matsuno + leapfrog  ..............
532c       ........................................................
533
534            IF(forward. OR. leapf) THEN
535              itau= itau + 1
536              iday= day_ini+itau/day_step
537              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
538                IF(time.GT.1.) THEN
539                  time = time-1.
540                  iday = iday+1
541                ENDIF
542            ENDIF
543
544
545            IF( itau. EQ. itaufinp1 ) then 
546              abort_message = 'Simulation finished'
547              call abort_gcm(modname,abort_message,0)
548            ENDIF
549c-----------------------------------------------------------------------
550c   ecriture du fichier histoire moyenne:
551c   -------------------------------------
552
553c           IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
554c              IF(itau.EQ.itaufin) THEN
555c                 iav=1
556c              ELSE
557c                 iav=0
558c              ENDIF
559c              CALL writedynav(histaveid, nqmx, itau,vcov ,
560c    ,                          ucov,teta,pk,phi,q,masse,ps,phis)
561c           ENDIF
562
563c-----------------------------------------------------------------------
564
565
566            IF(itau.EQ.itaufin) THEN
567
568
569       PRINT *,' Appel test_period avant redem ', itau
570       CALL test_period ( ucov,vcov,teta,q,p,phis )
571       CALL dynredem1("restart.nc",0.0,
572     .                     vcov,ucov,teta,q,nqmx,masse,ps)
573
574              CLOSE(99)
575            ENDIF
576
577c-----------------------------------------------------------------------
578c   gestion de l'integration temporelle:
579c   ------------------------------------
580
581            IF( MOD(itau,iperiod).EQ.0 )    THEN
582                    GO TO 1
583            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
584
585                   IF( forward )  THEN
586c      fin du pas forward et debut du pas backward
587
588                      forward = .FALSE.
589                        leapf = .FALSE.
590                           GO TO 2
591
592                   ELSE
593c      fin du pas backward et debut du premier pas leapfrog
594
595                        leapf =  .TRUE.
596                        dt  =  2.*dtvr
597                        GO TO 2
598                   END IF
599            ELSE
600
601c      ......   pas leapfrog  .....
602
603                 leapf = .TRUE.
604                 dt  = 2.*dtvr
605                 GO TO 2
606            END IF
607
608      ELSE
609
610c       ........................................................
611c       ..............       schema  matsuno        ...............
612c       ........................................................
613            IF( forward )  THEN
614
615             itau =  itau + 1
616             iday = day_ini+itau/day_step
617             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
618
619                  IF(time.GT.1.) THEN
620                   time = time-1.
621                   iday = iday+1
622                  ENDIF
623
624               forward =  .FALSE.
625               IF( itau. EQ. itaufinp1 ) then 
626                 abort_message = 'Simulation finished'
627                 call abort_gcm(modname,abort_message,0)
628               ENDIF
629               GO TO 2
630
631            ELSE
632
633            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
634               IF(itau.EQ.itaufin) THEN
635                  iav=1
636               ELSE
637                  iav=0
638               ENDIF
639c              CALL writedynav(histaveid, nqmx, itau,vcov ,
640c    ,                          ucov,teta,pk,phi,q,masse,ps,phis)
641
642            ENDIF
643
644
645                 IF(itau.EQ.itaufin)
646     . CALL dynredem1("restart.nc",0.0,
647     .                     vcov,ucov,teta,q,nqmx,masse,ps)
648
649                 forward = .TRUE.
650                 GO TO  1
651
652
653            ENDIF
654
655      END IF
656
657      STOP
658      END
Note: See TracBrowser for help on using the repository browser.