source: LMDZ6/trunk/libf/dyn3d/gcm.F90 @ 3981

Last change on this file since 3981 was 3579, checked in by Laurent Fairhead, 5 years ago

Make aquaplanets run again (on jean-zay)
EM & MP

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