source: LMDZ6/branches/Amaury_dev/libf/dyn3d/gcm.f90 @ 5214

Last change on this file since 5214 was 5195, checked in by abarral, 7 days ago

Correct r5192, some lmdz_description cases were missing

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