source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/gcm.F90 @ 5098

Last change on this file since 5098 was 5090, checked in by abarral, 4 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:keywords set to Id
File size: 15.2 KB
Line 
1!
2! $Id: gcm.F90 5090 2024-07-20 16:08:57Z abarral $
3!
4
5PROGRAM gcm
6
7#ifdef CPP_IOIPSL
8  USE IOIPSL
9#endif
10
11  USE mod_const_mpi, ONLY: init_const_mpi
12  USE parallel_lmdz
13  USE infotrac, ONLY: nqtot, init_infotrac
14  USE mod_hallo
15  USE Bands
16  USE filtreg_mod
17  USE control_mod
18
19
20  USE iniphysiq_mod, ONLY: iniphysiq
21  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS
22
23  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
24  USE logic_mod ! all of it, because of copyin clause when calling leapfrog
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, &
27                       dt,hour_ini,itaufin
28  USE mod_xios_dyn3dmem, ONLY: xios_dyn3dmem_init
29
30  IMPLICIT NONE
31
32  !      ......   Version  du 10/01/98    ..........
33
34  !             avec  coordonnees  verticales hybrides
35  !   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
36
37  !=======================================================================
38  !
39  !   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
40  !   -------
41  !
42  !   Objet:
43  !   ------
44  !
45  !   GCM LMD nouvelle grille
46  !
47  !=======================================================================
48  !
49  !  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
50  !      et possibilite d'appeler une fonction f(y)  a derivee tangente
51  !      hyperbolique a la  place de la fonction a derivee sinusoidale.
52  !  ... Possibilite de choisir le schema pour l'advection de
53  !        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
54  !
55  !      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
56  !      Pour Van-Leer iadv=10
57  !
58  !-----------------------------------------------------------------------
59  !   Declarations:
60  !   -------------
61  include "dimensions.h"
62  include "paramet.h"
63  include "comdissnew.h"
64  include "comgeom.h"
65  include "description.h"
66  include "iniprint.h"
67  include "tracstoke.h"
68
69
70  REAL zdtvr
71
72  !   variables dynamiques
73  REAL,ALLOCATABLE,SAVE  :: vcov(:,:),ucov(:,:) ! vents covariants
74  REAL,ALLOCATABLE,SAVE  :: teta(:,:)     ! temperature potentielle
75  REAL, ALLOCATABLE,SAVE :: q(:,:,:)      ! champs advectes
76  REAL,ALLOCATABLE,SAVE  :: ps(:)         ! pression  au sol
77  !      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
78  REAL,ALLOCATABLE,SAVE  :: masse(:,:)    ! masse d'air
79  REAL,ALLOCATABLE,SAVE  :: phis(:)       ! geopotentiel au sol
80  !      REAL phi(ip1jmp1,llm)                  ! geopotentiel
81  !      REAL w(ip1jmp1,llm)                    ! vitesse verticale
82
83  ! variables dynamiques intermediaire pour le transport
84
85  !   variables pour le fichier histoire
86  REAL dtav      ! intervalle de temps elementaire
87
88  REAL time_0
89
90  LOGICAL lafin
91
92  real time_step, t_wrt, t_ops
93
94  !+jld variables test conservation energie
95  !      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
96  !     Tendance de la temp. potentiel d (theta)/ d t due a la
97  !     tansformation d'energie cinetique en energie thermique
98  !     cree par la dissipation
99  !      REAL dhecdt(ip1jmp1,llm)
100  !      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
101  !      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
102  !      CHARACTER (len=15) :: ztit
103  !-jld
104
105
106  character (len=80) :: dynhist_file, dynhistave_file
107  character (len=20) :: modname
108  character (len=80) :: abort_message
109  ! locales pour gestion du temps
110  INTEGER :: an, mois, jour
111  REAL :: heure
112  ! needed for xios interface
113  character (len=10) :: xios_cal_type
114  INTEGER :: anref, moisref, jourref
115  REAL :: heureref
116 
117
118
119  !-----------------------------------------------------------------------
120  !   Initialisations:
121  !   ----------------
122
123  abort_message = 'last timestep reached'
124  modname = 'gcm'
125  descript = 'Run GCM LMDZ'
126  lafin    = .FALSE.
127  dynhist_file = 'dyn_hist'
128  dynhistave_file = 'dyn_hist_ave'
129
130
131
132  !----------------------------------------------------------------------
133  !  lecture des fichiers gcm.def ou run.def
134  !  ---------------------------------------
135  !
136  CALL conf_gcm( 99, .TRUE. )
137  if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm", &
138       "iphysiq must be a multiple of iperiod", 1)
139  !
140  !
141  !------------------------------------
142  !   Initialisation partie parallele
143  !------------------------------------
144  CALL init_const_mpi
145
146  call init_parallel
147  call Read_Distrib
148
149!#ifdef CPP_PHYS
150!  CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
151  !#endif
152  !      CALL set_bands
153  !#ifdef CPP_PHYS
154!  CALL Init_interface_dyn_phys
155!#endif
156  CALL barrier
157
158  CALL set_bands
159  if (mpi_rank==0) call WriteBands
160  call Set_Distrib(distrib_caldyn)
161
162  !$OMP PARALLEL
163  call Init_Mod_hallo
164  !$OMP END PARALLEL
165
166  !#ifdef CPP_PHYS
167  !c$OMP PARALLEL
168  !      call InitComgeomphy ! now done in iniphysiq
169  !c$OMP END PARALLEL
170  !#endif
171
172  !-----------------------------------------------------------------------
173  !   Choix du calendrier
174  !   -------------------
175
176  !      calend = 'earth_365d'
177
178#ifdef CPP_IOIPSL
179  if (calend == 'earth_360d') then
180     call ioconf_calendar('360_day')
181     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
182     xios_cal_type='d360'
183  else if (calend == 'earth_365d') then
184     call ioconf_calendar('noleap')
185     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
186     xios_cal_type='noleap'
187  else if (calend == 'gregorian') then
188     call ioconf_calendar('gregorian')
189     write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
190     xios_cal_type='gregorian'
191  else
192     abort_message = 'Mauvais choix de calendrier'
193     call abort_gcm(modname,abort_message,1)
194  endif
195#endif
196
197
198  !-----------------------------------------------------------------------
199  !   Initialisation des traceurs
200  !   ---------------------------
201  !  Choix du nombre de traceurs et du schema pour l'advection
202  !  dans fichier traceur.def, par default ou via INCA
203  call init_infotrac
204
205  ! Allocation de la tableau q : champs advectes   
206  ALLOCATE(ucov(ijb_u:ije_u,llm))
207  ALLOCATE(vcov(ijb_v:ije_v,llm))
208  ALLOCATE(teta(ijb_u:ije_u,llm))
209  ALLOCATE(masse(ijb_u:ije_u,llm))
210  ALLOCATE(ps(ijb_u:ije_u))
211  ALLOCATE(phis(ijb_u:ije_u))
212  ALLOCATE(q(ijb_u:ije_u,llm,nqtot))
213
214  !-----------------------------------------------------------------------
215  !   Lecture de l'etat initial :
216  !   ---------------------------
217
218  !  lecture du fichier start.nc
219  if (read_start) then
220     ! we still need to run iniacademic to initialize some
221     ! constants & fields, if we run the 'newtonian' or 'SW' cases:
222     if (iflag_phys/=1) then
223        CALL iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
224     endif
225
226     !        if (planet_type.eq."earth") then
227     ! Load an Earth-format start file
228     CALL dynetat0_loc("start.nc",vcov,ucov, &
229          teta,q,masse,ps,phis, time_0)
230     !        endif ! of if (planet_type.eq."earth")
231
232     !       write(73,*) 'ucov',ucov
233     !       write(74,*) 'vcov',vcov
234     !       write(75,*) 'teta',teta
235     !       write(76,*) 'ps',ps
236     !       write(77,*) 'q',q
237
238  endif ! of if (read_start)
239
240  ! le cas echeant, creation d un etat initial
241  IF (prt_level > 9) WRITE(lunout,*) &
242       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
243  if (.not.read_start) then
244     start_time=0.
245     annee_ref=anneeref
246     CALL iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
247  endif
248
249  !-----------------------------------------------------------------------
250  !   Lecture des parametres de controle pour la simulation :
251  !   -------------------------------------------------------
252  !  on recalcule eventuellement le pas de temps
253
254  IF(MOD(day_step,iperiod)/=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
259
260  IF(MOD(day_step,iphysiq)/=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
265
266  zdtvr    = daysec/REAL(day_step)
267  IF(dtvr/=zdtvr) THEN
268     WRITE(lunout,*) &
269          'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
270  ENDIF
271
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        WRITE(lunout,*)'Je m''arrete'
283        CALL abort
284     ENDIF
285  ENDIF
286  IF (raz_date == 1) THEN
287     annee_ref = anneeref
288     day_ref = dayref
289     day_ini = dayref
290     itau_dyn = 0
291     itau_phy = 0
292     time_0 = 0.
293     write(lunout,*) &
294          'GCM: On reinitialise a la date lue dans gcm.def'
295  ELSE IF (annee_ref /= anneeref .or. day_ref /= dayref) THEN
296     write(lunout,*) &
297          'GCM: Attention les dates initiales lues dans le fichier'
298     write(lunout,*) &
299          ' restart ne correspondent pas a celles lues dans '
300     write(lunout,*)' gcm.def'
301     write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
302     write(lunout,*)' day_ref=',day_ref," dayref=",dayref
303     write(lunout,*)' Pas de remise a zero'
304  ENDIF
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
329
330#ifdef CPP_IOIPSL
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)
336
337  call ioconf_startdate(INT(jD_ref), jH_ref)
338
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,anref, moisref, jourref, heureref)
343  write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
344  write(lunout,*)jD_ref+jH_ref,anref, moisref, jourref, heureref
345#else
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
351#endif
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  !-----------------------------------------------------------------------
381  !   Initialisation des I/O :
382  !   ------------------------
383
384
385  if (nday>=0) then
386     day_end = day_ini + nday
387  else
388     day_end = day_ini - nday/day_step
389  endif
390
391  WRITE(lunout,300)day_ini,day_end
392300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
393
394#ifdef CPP_IOIPSL
395  call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
396  write (lunout,301)jour, mois, an
397  call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
398  write (lunout,302)jour, mois, an
399301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
400302 FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
401#endif
402
403  !-----------------------------------------------------------------------
404  !   Initialisation de la physique :
405  !   -------------------------------
406
407  !  Choix des frequences de stokage pour le offline
408  !      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
409  !      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
410  istdyn=day_step/8     ! stockage toutes les 6h=1jour/12
411  istphy=istdyn/iphysiq
412
413  IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
414     ! Physics:
415    IF (CPPKEY_PHYS) THEN
416      CALL iniphysiq(iim,jjm,llm, &
417            distrib_phys(mpi_rank),comm_lmdz, &
418            daysec,day_ini,dtphys/nsplit_phys, &
419            rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
420            iflag_phys)
421    END IF
422  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
423
424
425  !      if (planet_type.eq."earth") then
426  ! Write an Earth-format restart file
427  CALL dynredem0_loc("restart.nc", day_end, phis)
428  !      endif
429
430  ecripar = .TRUE.
431
432#define CPP_IOIPSL
433#ifdef CPP_IOIPSL
434  time_step = zdtvr
435     if (ok_dyn_ins) then
436        ! initialize output file for instantaneous outputs
437        ! t_ops = iecri * daysec ! do operations every t_ops
438        t_ops =((1.0*iecri)/day_step) * daysec 
439        t_wrt = daysec ! iecri * daysec ! write output every t_wrt
440        CALL inithist_loc(day_ref,annee_ref,time_step, &
441             t_ops,t_wrt)
442     endif
443
444     IF (ok_dyn_ave) THEN
445        ! initialize output file for averaged outputs
446        t_ops = iperiod * time_step ! do operations every t_ops
447        t_wrt = periodav * daysec   ! write output every t_wrt
448        CALL initdynav_loc(day_ref,annee_ref,time_step,t_ops,t_wrt)
449     END IF
450  dtav = iperiod*dtvr/daysec
451#endif
452#undef CPP_IOIPSL
453
454! setting up DYN3D/XIOS inerface
455  if (ok_dyn_xios) then
456      CALL xios_dyn3dmem_init(xios_cal_type, anref, moisref, jourref,heureref, an,   &
457          mois, jour, heure, zdtvr)
458  endif
459
460  ! #endif of #ifdef CPP_IOIPSL
461  !
462  !-----------------------------------------------------------------------
463  !   Integration temporelle du modele :
464  !   ----------------------------------
465
466  !       write(78,*) 'ucov',ucov
467  !       write(78,*) 'vcov',vcov
468  !       write(78,*) 'teta',teta
469  !       write(78,*) 'ps',ps
470  !       write(78,*) 'q',q
471
472  !!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
473  !     Copy all threadprivate variables in temps_mod logic_mod
474  !$OMP PARALLEL DEFAULT(SHARED) &
475  !$OMP COPYIN(dt,jD_ref,jH_ref,start_time,hour_ini,day_ini,day_end) &
476  !$OMP COPYIN(annee_ref,day_ref,itau_dyn,itau_phy,itaufin,calend) &
477  !$OMP COPYIN(purmats,forward,leapf,apphys,statcl,conser,apdiss,apdelq) &
478  !$OMP COPYIN(saison,ecripar,fxyhypb,ysinus,read_start,ok_guide) &
479  !$OMP COPYIN(ok_strato,ok_gradsfile,ok_limit,ok_etat0) &
480  !$OMP COPYIN(iflag_phys,iflag_trac,adv_qsat_liq)
481  CALL leapfrog_loc(ucov,vcov,teta,ps,masse,phis,q,time_0)
482  !$OMP END PARALLEL
483
484  !      OPEN(unit=5487,file='ok_lmdz',status='replace')
485  !      WRITE(5487,*) 'ok_lmdz'
486  !      CLOSE(5487)
487END PROGRAM gcm
Note: See TracBrowser for help on using the repository browser.