source: LMDZ6/branches/Amaury_dev/libf/dyn3d/gcm.F90 @ 5116

Last change on this file since 5116 was 5116, checked in by abarral, 4 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

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