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

Last change on this file since 5090 was 5090, checked in by abarral, 2 months ago

Move lmdz_netcdf_format.F90 -> lmdz_cppkeys_wrapper.F90 to handle other CPP keys
Replace all (except wrapper) use of CPP_PHYS by fortran logical

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