source: LMDZ4/branches/LMDZ4V5.0-dev/libf/dyn3d/gcm.F @ 1357

Last change on this file since 1357 was 1357, checked in by Ehouarn Millour, 14 years ago

Some cleanup and fixing the possibility to output fields in the dynamics, on the dynamical grids.

CLEANUPS:

  • arch-PW6_VARGAS.fcm : add potentially benefic compiling options
  • removed obsolete "control.h" in dyn3d/dyn3dpar (module control_mod.F90 is used instead)

OUTPUTS in the dynamics (3 sets of files, one for each grid: scalar, u, v):

  • removed "com_io_dyn.h" common; use module "com_io_dyn_mod.F90" instead
  • updated "initdynav.F","inithist.F","writehist.F" and "writedynav.F" in bibio: which field will be written is hard coded there.
  • flags "ok_dyn_ins" and "ok_dyn_ave" (loaded via conf_gcm.F) trigger output of fields in the dynamics: if ok_dyn_ins is true, then files "dyn_hist.nc", "dyn_histu.nc" and "dyn_histv.nc" are written (the frequency of the outputs is given by 'iecri' in run.def; values are written every 'iecri' dynamical step). if ok_dyn_ave is true then files "dyn_hist_ave.nc", "dyn_histu_ave.nc" and "dyn_histv_ave.nc" are written (the rate at which averages and made/written, in days, is given by 'periodav' in run.def).

EM

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 15.8 KB
RevLine 
[1279]1!
2! $Id: gcm.F 1357 2010-04-14 14:03:19Z emillour $
3!
[524]4c
5c
6      PROGRAM gcm
7
8#ifdef CPP_IOIPSL
9      USE IOIPSL
[1146]10#else
11! if not using IOIPSL, we still need to use (a local version of) getin
12      USE ioipsl_getincom
[524]13#endif
[956]14
[1146]15      USE filtreg_mod
16      USE infotrac
[1299]17      USE control_mod
[1146]18
[956]19!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
20! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
21! A nettoyer. On ne veut qu'une ou deux routines d'interface
22! dynamique -> physique pour l'initialisation
[1146]23! Ehouarn: for now these only apply to Earth:
24#ifdef CPP_EARTH
[762]25      USE dimphy
26      USE comgeomphy
[863]27      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
[956]28#endif
29!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
30
[524]31      IMPLICIT NONE
32
33c      ......   Version  du 10/01/98    ..........
34
35c             avec  coordonnees  verticales hybrides
36c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
37
38c=======================================================================
39c
40c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
41c   -------
42c
43c   Objet:
44c   ------
45c
46c   GCM LMD nouvelle grille
47c
48c=======================================================================
49c
50c  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
51c      et possibilite d'appeler une fonction f(y)  a derivee tangente
52c      hyperbolique a la  place de la fonction a derivee sinusoidale.
53c  ... Possibilite de choisir le schema pour l'advection de
54c        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
55c
56c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
57c      Pour Van-Leer iadv=10
58c
59c-----------------------------------------------------------------------
60c   Declarations:
61c   -------------
62
63#include "dimensions.h"
64#include "paramet.h"
65#include "comconst.h"
66#include "comdissnew.h"
67#include "comvert.h"
68#include "comgeom.h"
69#include "logic.h"
70#include "temps.h"
[1299]71!!!!!!!!!!!#include "control.h"
[524]72#include "ener.h"
73#include "description.h"
74#include "serre.h"
[1357]75!#include "com_io_dyn.h"
[524]76#include "iniprint.h"
[541]77#include "tracstoke.h"
[1357]78#ifdef INCA
79! Only INCA needs these informations (from the Earth's physics)
[1316]80#include "indicesol.h"
[1357]81#endif
[524]82      INTEGER         longcles
83      PARAMETER     ( longcles = 20 )
84      REAL  clesphy0( longcles )
85      SAVE  clesphy0
86
87
88
89      REAL zdtvr
90      INTEGER nbetatmoy, nbetatdem,nbetat
91
92c   variables dynamiques
93      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
94      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
[1146]95      REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
[524]96      REAL ps(ip1jmp1)                       ! pression  au sol
97      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
98      REAL pks(ip1jmp1)                      ! exner au  sol
99      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
100      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
101      REAL masse(ip1jmp1,llm)                ! masse d'air
102      REAL phis(ip1jmp1)                     ! geopotentiel au sol
103      REAL phi(ip1jmp1,llm)                  ! geopotentiel
104      REAL w(ip1jmp1,llm)                    ! vitesse verticale
105
106c variables dynamiques intermediaire pour le transport
107
108c   variables pour le fichier histoire
109      REAL dtav      ! intervalle de temps elementaire
110
111      REAL time_0
112
113      LOGICAL lafin
114      INTEGER ij,iq,l,i,j
115
116
117      real time_step, t_wrt, t_ops
118
119      LOGICAL first
120
121      LOGICAL call_iniphys
122      data call_iniphys/.true./
123
124      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm)
125c+jld variables test conservation energie
[962]126c      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
[524]127C     Tendance de la temp. potentiel d (theta)/ d t due a la
128C     tansformation d'energie cinetique en energie thermique
129C     cree par la dissipation
130      REAL dhecdt(ip1jmp1,llm)
[962]131c      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
132c      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
133      CHARACTER (len=15) :: ztit
[524]134c-jld
135
136
[962]137      character (len=80) :: dynhist_file, dynhistave_file
138      character (len=20) :: modname
139      character (len=80) :: abort_message
[1279]140! locales pour gestion du temps
141      INTEGER :: an, mois, jour
142      REAL :: heure
[524]143
144
145c-----------------------------------------------------------------------
146c    variables pour l'initialisation de la physique :
147c    ------------------------------------------------
[1146]148      INTEGER ngridmx
[524]149      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
150      REAL zcufi(ngridmx),zcvfi(ngridmx)
151      REAL latfi(ngridmx),lonfi(ngridmx)
152      REAL airefi(ngridmx)
153      SAVE latfi, lonfi, airefi
154
155c-----------------------------------------------------------------------
156c   Initialisations:
157c   ----------------
158
159      abort_message = 'last timestep reached'
160      modname = 'gcm'
161      descript = 'Run GCM LMDZ'
162      lafin    = .FALSE.
163      dynhist_file = 'dyn_hist.nc'
164      dynhistave_file = 'dyn_hist_ave.nc'
165
[762]166
167
[524]168c----------------------------------------------------------------------
169c  lecture des fichiers gcm.def ou run.def
170c  ---------------------------------------
171c
[1146]172! Ehouarn: dump possibility of using defrun
173!#ifdef CPP_IOIPSL
[524]174      CALL conf_gcm( 99, .TRUE. , clesphy0 )
[1146]175!#else
176!      CALL defrun( 99, .TRUE. , clesphy0 )
177!#endif
[762]178
[956]179!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
180! FH 2008/05/02
181! A nettoyer. On ne veut qu'une ou deux routines d'interface
182! dynamique -> physique pour l'initialisation
[1146]183! Ehouarn : temporarily (?) keep this only for Earth
184      if (planet_type.eq."earth") then
185#ifdef CPP_EARTH
186      CALL Init_Phys_lmdz(iim,jjp1,llm,1,(jjm-1)*iim+2)
[762]187      call InitComgeomphy
[956]188#endif
[1146]189      endif
[956]190!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1279]191c-----------------------------------------------------------------------
192c   Choix du calendrier
193c   -------------------
[762]194
[1279]195c      calend = 'earth_365d'
196
197#ifdef CPP_IOIPSL
198      if (calend == 'earth_360d') then
199        call ioconf_calendar('360d')
200        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
201      else if (calend == 'earth_365d') then
202        call ioconf_calendar('noleap')
203        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
204      else if (calend == 'earth_366d') then
205        call ioconf_calendar('gregorian')
206        write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
207      else
208        abort_message = 'Mauvais choix de calendrier'
209        call abort_gcm(modname,abort_message,1)
210      endif
211#endif
212c-----------------------------------------------------------------------
213
[960]214      IF (config_inca /= 'none') THEN
[762]215#ifdef INCA
[1316]216      call init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday,
217     $        nbsrf, is_oce,is_sic,is_ter,is_lic)
[863]218      call init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
[762]219#endif
[960]220      END IF
[524]221c
222c
[762]223c------------------------------------
224c   Initialisation partie parallele
225c------------------------------------
226
227c
228c
[524]229c-----------------------------------------------------------------------
230c   Initialisation des traceurs
231c   ---------------------------
[1146]232c  Choix du nombre de traceurs et du schema pour l'advection
233c  dans fichier traceur.def, par default ou via INCA
234      call infotrac_init
[524]235
[1146]236c Allocation de la tableau q : champs advectes   
237      allocate(q(ip1jmp1,llm,nqtot))
238
[524]239c-----------------------------------------------------------------------
240c   Lecture de l'etat initial :
241c   ---------------------------
242
243c  lecture du fichier start.nc
244      if (read_start) then
[1146]245      ! we still need to run iniacademic to initialize some
246      ! constants & fields, if we run the 'newtonian' case:
247        if (iflag_phys.eq.2) then
248          CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
249        endif
250!#ifdef CPP_IOIPSL
251        if (planet_type.eq."earth") then
252#ifdef CPP_EARTH
253! Load an Earth-format start file
254         CALL dynetat0("start.nc",vcov,ucov,
[524]255     .              teta,q,masse,ps,phis, time_0)
[1146]256#endif
257        endif ! of if (planet_type.eq."earth")
[524]258c       write(73,*) 'ucov',ucov
259c       write(74,*) 'vcov',vcov
260c       write(75,*) 'teta',teta
261c       write(76,*) 'ps',ps
262c       write(77,*) 'q',q
263
[1146]264      endif ! of if (read_start)
[524]265
[960]266      IF (config_inca /= 'none') THEN
[762]267#ifdef INCA
[960]268         call init_inca_dim(klon,llm,iim,jjm,
269     $        rlonu,rlatu,rlonv,rlatv)
[762]270#endif
[960]271      END IF
[524]272
273
274c le cas echeant, creation d un etat initial
275      IF (prt_level > 9) WRITE(lunout,*)
[1146]276     .              'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
[524]277      if (.not.read_start) then
[1146]278         CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
[524]279      endif
280
281
282c-----------------------------------------------------------------------
283c   Lecture des parametres de controle pour la simulation :
284c   -------------------------------------------------------
285c  on recalcule eventuellement le pas de temps
286
287      IF(MOD(day_step,iperiod).NE.0) THEN
288        abort_message =
289     .  'Il faut choisir un nb de pas par jour multiple de iperiod'
290        call abort_gcm(modname,abort_message,1)
291      ENDIF
292
293      IF(MOD(day_step,iphysiq).NE.0) THEN
294        abort_message =
295     * 'Il faut choisir un nb de pas par jour multiple de iphysiq'
296        call abort_gcm(modname,abort_message,1)
297      ENDIF
298
[1299]299      zdtvr    = daysec/REAL(day_step)
[524]300        IF(dtvr.NE.zdtvr) THEN
301         WRITE(lunout,*)
302     .    'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
303        ENDIF
304
305C
306C on remet le calendrier à zero si demande
307c
[1333]308      IF (raz_date == 1) THEN
309        annee_ref = anneeref
310        day_ref = dayref
311        day_ini = dayref
312        itau_dyn = 0
313        itau_phy = 0
314        time_0 = 0.
[524]315        write(lunout,*)
[1333]316     .   'GCM: On reinitialise a la date lue dans gcm.def'
317      ELSE IF (annee_ref .ne. anneeref .or. day_ref .ne. dayref) THEN
318        write(lunout,*)
[1146]319     .  'GCM: Attention les dates initiales lues dans le fichier'
[524]320        write(lunout,*)
321     .  ' restart ne correspondent pas a celles lues dans '
322        write(lunout,*)' gcm.def'
[1357]323        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
324        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
325        write(lunout,*)' Pas de remise a zero'
[1333]326      ENDIF
[1279]327
[1357]328c      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
329c        write(lunout,*)
330c     .  'GCM: Attention les dates initiales lues dans le fichier'
331c        write(lunout,*)
332c     .  ' restart ne correspondent pas a celles lues dans '
333c        write(lunout,*)' gcm.def'
334c        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
335c        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
336c        if (raz_date .ne. 1) then
337c          write(lunout,*)
338c     .    'GCM: On garde les dates du fichier restart'
339c        else
340c          annee_ref = anneeref
341c          day_ref = dayref
342c          day_ini = dayref
343c          itau_dyn = 0
344c          itau_phy = 0
345c          time_0 = 0.
346c          write(lunout,*)
347c     .   'GCM: On reinitialise a la date lue dans gcm.def'
348c        endif
349c      ELSE
350c        raz_date = 0
351c      endif
[1333]352
[1147]353#ifdef CPP_IOIPSL
[1279]354      mois = 1
355      heure = 0.
356      call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
357      jH_ref = jD_ref - int(jD_ref)
358      jD_ref = int(jD_ref)
359
360      call ioconf_startdate(INT(jD_ref), jH_ref)
361
362      write(lunout,*)'DEBUG'
363      write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
364      write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
365      call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure)
366      write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
367      write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
368#else
369! Ehouarn: we still need to define JD_ref and JH_ref
370! and since we don't know how many days there are in a year
371! we set JD_ref to 0 (this should be improved ...)
372      jD_ref=0
373      jH_ref=0
[1147]374#endif
[524]375
376c  nombre d'etats dans les fichiers demarrage et histoire
377      nbetatdem = nday / iecri
378      nbetatmoy = nday / periodav + 1
379
380c-----------------------------------------------------------------------
381c   Initialisation des constantes dynamiques :
382c   ------------------------------------------
383      dtvr = zdtvr
384      CALL iniconst
385
386c-----------------------------------------------------------------------
387c   Initialisation de la geometrie :
388c   --------------------------------
389      CALL inigeom
390
391c-----------------------------------------------------------------------
392c   Initialisation du filtre :
393c   --------------------------
394      CALL inifilr
395c
396c-----------------------------------------------------------------------
397c   Initialisation de la dissipation :
398c   ----------------------------------
399
400      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
401     *                tetagdiv, tetagrot , tetatemp              )
402
403c-----------------------------------------------------------------------
404c   Initialisation de la physique :
405c   -------------------------------
[1146]406
407      IF (call_iniphys.and.(iflag_phys.eq.1)) THEN
[524]408         latfi(1)=rlatu(1)
409         lonfi(1)=0.
410         zcufi(1) = cu(1)
411         zcvfi(1) = cv(1)
412         DO j=2,jjm
413            DO i=1,iim
414               latfi((j-2)*iim+1+i)= rlatu(j)
415               lonfi((j-2)*iim+1+i)= rlonv(i)
416               zcufi((j-2)*iim+1+i) = cu((j-1)*iip1+i)
417               zcvfi((j-2)*iim+1+i) = cv((j-1)*iip1+i)
418            ENDDO
419         ENDDO
420         latfi(ngridmx)= rlatu(jjp1)
421         lonfi(ngridmx)= 0.
422         zcufi(ngridmx) = cu(ip1jm+1)
423         zcvfi(ngridmx) = cv(ip1jm-iim)
424         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
425         WRITE(lunout,*)
[1146]426     .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
427! Earth:
428         if (planet_type.eq."earth") then
429#ifdef CPP_EARTH
[1320]430         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys ,
[524]431     ,                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp     )
[1146]432#endif
433         endif ! of if (planet_type.eq."earth")
[524]434         call_iniphys=.false.
[1146]435      ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1))
436!#endif
[524]437
438c  numero de stockage pour les fichiers de redemarrage:
439
440c-----------------------------------------------------------------------
441c   Initialisation des I/O :
442c   ------------------------
443
444
445      day_end = day_ini + nday
446      WRITE(lunout,300)day_ini,day_end
[1146]447 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
[524]448
[1279]449#ifdef CPP_IOIPSL
450      call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
451      write (lunout,301)jour, mois, an
452      call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
453      write (lunout,302)jour, mois, an
454 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
455 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
456#endif
457
[1146]458      if (planet_type.eq."earth") then
[1279]459        CALL dynredem0("restart.nc", day_end, phis)
[1146]460      endif
[524]461
462      ecripar = .TRUE.
463
[1146]464#ifdef CPP_IOIPSL
[524]465      time_step = zdtvr
[1357]466      if (ok_dyn_ins) then
467        ! initialize output file for instantaneous outputs
468        ! t_ops = iecri * daysec ! do operations every t_ops
469        t_ops =((1.0*iecri)/day_step) * daysec 
470        t_wrt = daysec ! iecri * daysec ! write output every t_wrt
471        CALL inithist(day_ref,annee_ref,time_step,
472     &              t_ops,t_wrt)
473      endif
[524]474
[1357]475      IF (ok_dyn_ave) THEN
476        ! initialize output file for averaged outputs
477        t_ops = iperiod * time_step ! do operations every t_ops
478        t_wrt = periodav * daysec   ! write output every t_wrt
479        CALL initdynav(day_ref,annee_ref,time_step,
480     &       t_ops,t_wrt)
481      END IF
[524]482      dtav = iperiod*dtvr/daysec
483#endif
[1146]484! #endif of #ifdef CPP_IOIPSL
[524]485
[541]486c  Choix des frequences de stokage pour le offline
487c      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
488c      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
489      istdyn=day_step/4     ! stockage toutes les 6h=1jour/12
490      istphy=istdyn/iphysiq     
491
492
[524]493c
494c-----------------------------------------------------------------------
495c   Integration temporelle du modele :
496c   ----------------------------------
497
498c       write(78,*) 'ucov',ucov
499c       write(78,*) 'vcov',vcov
500c       write(78,*) 'teta',teta
501c       write(78,*) 'ps',ps
502c       write(78,*) 'q',q
503
504
[1146]505      CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
[550]506     .              time_0)
[524]507
508      END
509
Note: See TracBrowser for help on using the repository browser.