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

Last change on this file since 5127 was 5118, checked in by abarral, 3 months ago

Replace iniprint.h by lmdz_iniprint.f90
(lint) along the way

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