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

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

Replace most uses of CPP_DUST by the corresponding logical defined in lmdz_cppkeys_wrapper.F90
Convert several files from .F to .f90 to allow Dust to compile w/o rrtm/ecrad
Create lmdz_yoerad.f90
(lint) Remove "!" on otherwise empty line

  • 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 5099 2024-07-22 19:29:09Z abarral $
3
4PROGRAM gcm
5
6#ifdef CPP_IOIPSL
7  USE IOIPSL
8#endif
9
10  USE mod_const_mpi, ONLY: init_const_mpi
11  USE parallel_lmdz
12  USE infotrac, ONLY: nqtot, init_infotrac
13  USE mod_hallo
14  USE Bands
15  USE filtreg_mod
16  USE control_mod
17
18
19  USE iniphysiq_mod, ONLY: iniphysiq
20  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS
21
22  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
23  USE logic_mod ! all of it, because of copyin clause when calling leapfrog
24  USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref, &
25                       itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end, &
26                       dt,hour_ini,itaufin
27  USE mod_xios_dyn3dmem, ONLY: xios_dyn3dmem_init
28
29  IMPLICIT NONE
30
31  !      ......   Version  du 10/01/98    ..........
32
33  !             avec  coordonnees  verticales hybrides
34  !   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
35
36  !=======================================================================
37
38  !   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
39  !   -------
40
41  !   Objet:
42  !   ------
43
44  !   GCM LMD nouvelle grille
45
46  !=======================================================================
47
48  !  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
49  !      et possibilite d'appeler une fonction f(y)  a derivee tangente
50  !      hyperbolique a la  place de la fonction a derivee sinusoidale.
51  !  ... Possibilite de choisir le schema pour l'advection de
52  !        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
53
54  !      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
55  !      Pour Van-Leer iadv=10
56
57  !-----------------------------------------------------------------------
58  !   Declarations:
59  !   -------------
60  include "dimensions.h"
61  include "paramet.h"
62  include "comdissnew.h"
63  include "comgeom.h"
64  include "description.h"
65  include "iniprint.h"
66  include "tracstoke.h"
67
68
69  REAL zdtvr
70
71  !   variables dynamiques
72  REAL,ALLOCATABLE,SAVE  :: vcov(:,:),ucov(:,:) ! vents covariants
73  REAL,ALLOCATABLE,SAVE  :: teta(:,:)     ! temperature potentielle
74  REAL, ALLOCATABLE,SAVE :: q(:,:,:)      ! champs advectes
75  REAL,ALLOCATABLE,SAVE  :: ps(:)         ! pression  au sol
76  !      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
77  REAL,ALLOCATABLE,SAVE  :: masse(:,:)    ! masse d'air
78  REAL,ALLOCATABLE,SAVE  :: phis(:)       ! 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  !+jld variables test conservation energie
94  !      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
95  !     Tendance de la temp. potentiel d (theta)/ d t due a la
96  !     tansformation d'energie cinetique en energie thermique
97  !     cree par la dissipation
98  !      REAL dhecdt(ip1jmp1,llm)
99  !      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
100  !      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
101  !      CHARACTER (len=15) :: ztit
102  !-jld
103
104
105  character (len=80) :: dynhist_file, dynhistave_file
106  character (len=20) :: modname
107  character (len=80) :: abort_message
108  ! locales pour gestion du temps
109  INTEGER :: an, mois, jour
110  REAL :: heure
111  ! needed for xios interface
112  character (len=10) :: xios_cal_type
113  INTEGER :: anref, moisref, jourref
114  REAL :: heureref
115 
116
117
118  !-----------------------------------------------------------------------
119  !   Initialisations:
120  !   ----------------
121
122  abort_message = 'last timestep reached'
123  modname = 'gcm'
124  descript = 'Run GCM LMDZ'
125  lafin    = .FALSE.
126  dynhist_file = 'dyn_hist'
127  dynhistave_file = 'dyn_hist_ave'
128
129
130
131  !----------------------------------------------------------------------
132  !  lecture des fichiers gcm.def ou run.def
133  !  ---------------------------------------
134
135  CALL conf_gcm( 99, .TRUE. )
136  if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm", &
137       "iphysiq must be a multiple of iperiod", 1)
138
139
140  !------------------------------------
141  !   Initialisation partie parallele
142  !------------------------------------
143  CALL init_const_mpi
144
145  call init_parallel
146  call Read_Distrib
147
148!#ifdef CPP_PHYS
149!  CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
150  !#endif
151  !      CALL set_bands
152  !#ifdef CPP_PHYS
153!  CALL Init_interface_dyn_phys
154!#endif
155  CALL barrier
156
157  CALL set_bands
158  if (mpi_rank==0) call WriteBands
159  call Set_Distrib(distrib_caldyn)
160
161  !$OMP PARALLEL
162  call Init_Mod_hallo
163  !$OMP END PARALLEL
164
165  !#ifdef CPP_PHYS
166  !c$OMP PARALLEL
167  !      call InitComgeomphy ! now done in iniphysiq
168  !c$OMP END PARALLEL
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     xios_cal_type='d360'
182  else if (calend == 'earth_365d') then
183     call ioconf_calendar('noleap')
184     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
185     xios_cal_type='noleap'
186  else if (calend == 'gregorian') then
187     call ioconf_calendar('gregorian')
188     write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
189     xios_cal_type='gregorian'
190  else
191     abort_message = 'Mauvais choix de calendrier'
192     call abort_gcm(modname,abort_message,1)
193  endif
194#endif
195
196
197  !-----------------------------------------------------------------------
198  !   Initialisation des traceurs
199  !   ---------------------------
200  !  Choix du nombre de traceurs et du schema pour l'advection
201  !  dans fichier traceur.def, par default ou via INCA
202  call init_infotrac
203
204  ! Allocation de la tableau q : champs advectes   
205  ALLOCATE(ucov(ijb_u:ije_u,llm))
206  ALLOCATE(vcov(ijb_v:ije_v,llm))
207  ALLOCATE(teta(ijb_u:ije_u,llm))
208  ALLOCATE(masse(ijb_u:ije_u,llm))
209  ALLOCATE(ps(ijb_u:ije_u))
210  ALLOCATE(phis(ijb_u:ije_u))
211  ALLOCATE(q(ijb_u:ije_u,llm,nqtot))
212
213  !-----------------------------------------------------------------------
214  !   Lecture de l'etat initial :
215  !   ---------------------------
216
217  !  lecture du fichier start.nc
218  if (read_start) then
219     ! we still need to run iniacademic to initialize some
220     ! constants & fields, if we run the 'newtonian' or 'SW' cases:
221     if (iflag_phys/=1) then
222        CALL iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
223     endif
224
225     !        if (planet_type.eq."earth") then
226     ! Load an Earth-format start file
227     CALL dynetat0_loc("start.nc",vcov,ucov, &
228          teta,q,masse,ps,phis, time_0)
229     !        endif ! of if (planet_type.eq."earth")
230
231     !       write(73,*) 'ucov',ucov
232     !       write(74,*) 'vcov',vcov
233     !       write(75,*) 'teta',teta
234     !       write(76,*) 'ps',ps
235     !       write(77,*) 'q',q
236
237  endif ! of if (read_start)
238
239  ! le cas echeant, creation d un etat initial
240  IF (prt_level > 9) WRITE(lunout,*) &
241       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
242  if (.not.read_start) then
243     start_time=0.
244     annee_ref=anneeref
245     CALL iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
246  endif
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  ! on remet le calendrier \`a zero si demande
272
273  IF (start_time /= starttime) then
274     WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le' &
275          ,' fichier restart ne correspond pas a celle lue dans le run.def'
276     IF (raz_date == 1) then
277        WRITE(lunout,*)'Je prends l''heure lue dans run.def'
278        start_time = starttime
279     ELSE
280        WRITE(lunout,*)'Je m''arrete'
281        CALL abort
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  !      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
304  !        write(lunout,*)
305  !     .  'GCM: Attention les dates initiales lues dans le fichier'
306  !        write(lunout,*)
307  !     .  ' restart ne correspondent pas a celles lues dans '
308  !        write(lunout,*)' gcm.def'
309  !        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
310  !        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
311  !        if (raz_date .ne. 1) then
312  !          write(lunout,*)
313  !     .    'GCM: On garde les dates du fichier restart'
314  !        else
315  !          annee_ref = anneeref
316  !          day_ref = dayref
317  !          day_ini = dayref
318  !          itau_dyn = 0
319  !          itau_phy = 0
320  !          time_0 = 0.
321  !          write(lunout,*)
322  !     .   'GCM: On reinitialise a la date lue dans gcm.def'
323  !        endif
324  !      ELSE
325  !        raz_date = 0
326  !      endif
327
328#ifdef CPP_IOIPSL
329  mois = 1
330  heure = 0.
331  call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
332  jH_ref = jD_ref - int(jD_ref)
333  jD_ref = int(jD_ref)
334
335  call ioconf_startdate(INT(jD_ref), jH_ref)
336
337  write(lunout,*)'DEBUG'
338  write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
339  write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
340  call ju2ymds(jD_ref+jH_ref,anref, moisref, jourref, heureref)
341  write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
342  write(lunout,*)jD_ref+jH_ref,anref, moisref, jourref, heureref
343#else
344  ! Ehouarn: we still need to define JD_ref and JH_ref
345  ! and since we don't know how many days there are in a year
346  ! we set JD_ref to 0 (this should be improved ...)
347  jD_ref=0
348  jH_ref=0
349#endif
350
351  if (iflag_phys==1) then
352     ! these initialisations have already been done (via iniacademic)
353     ! if running in SW or Newtonian mode
354     !-----------------------------------------------------------------------
355     !   Initialisation des constantes dynamiques :
356     !   ------------------------------------------
357     dtvr = zdtvr
358     CALL iniconst
359
360     !-----------------------------------------------------------------------
361     !   Initialisation de la geometrie :
362     !   --------------------------------
363     CALL inigeom
364
365     !-----------------------------------------------------------------------
366     !   Initialisation du filtre :
367     !   --------------------------
368     CALL inifilr
369  endif ! of if (iflag_phys.eq.1)
370
371  !-----------------------------------------------------------------------
372  !   Initialisation de la dissipation :
373  !   ----------------------------------
374
375  CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   , &
376       tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
377
378  !-----------------------------------------------------------------------
379  !   Initialisation des I/O :
380  !   ------------------------
381
382
383  if (nday>=0) then
384     day_end = day_ini + nday
385  else
386     day_end = day_ini - nday/day_step
387  endif
388
389  WRITE(lunout,300)day_ini,day_end
390300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
391
392#ifdef CPP_IOIPSL
393  call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
394  write (lunout,301)jour, mois, an
395  call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
396  write (lunout,302)jour, mois, an
397301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
398302 FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
399#endif
400
401  !-----------------------------------------------------------------------
402  !   Initialisation de la physique :
403  !   -------------------------------
404
405  !  Choix des frequences de stokage pour le offline
406  !      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
407  !      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
408  istdyn=day_step/8     ! stockage toutes les 6h=1jour/12
409  istphy=istdyn/iphysiq
410
411  IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
412     ! Physics:
413    IF (CPPKEY_PHYS) THEN
414      CALL iniphysiq(iim,jjm,llm, &
415            distrib_phys(mpi_rank),comm_lmdz, &
416            daysec,day_ini,dtphys/nsplit_phys, &
417            rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
418            iflag_phys)
419    END IF
420  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
421
422
423  !      if (planet_type.eq."earth") then
424  ! Write an Earth-format restart file
425  CALL dynredem0_loc("restart.nc", day_end, phis)
426  !      endif
427
428  ecripar = .TRUE.
429
430#define CPP_IOIPSL
431#ifdef CPP_IOIPSL
432  time_step = zdtvr
433     if (ok_dyn_ins) then
434        ! initialize output file for instantaneous outputs
435        ! t_ops = iecri * daysec ! do operations every t_ops
436        t_ops =((1.0*iecri)/day_step) * daysec 
437        t_wrt = daysec ! iecri * daysec ! write output every t_wrt
438        CALL inithist_loc(day_ref,annee_ref,time_step, &
439             t_ops,t_wrt)
440     endif
441
442     IF (ok_dyn_ave) THEN
443        ! initialize output file for averaged outputs
444        t_ops = iperiod * time_step ! do operations every t_ops
445        t_wrt = periodav * daysec   ! write output every t_wrt
446        CALL initdynav_loc(day_ref,annee_ref,time_step,t_ops,t_wrt)
447     END IF
448  dtav = iperiod*dtvr/daysec
449#endif
450#undef CPP_IOIPSL
451
452! setting up DYN3D/XIOS inerface
453  if (ok_dyn_xios) then
454      CALL xios_dyn3dmem_init(xios_cal_type, anref, moisref, jourref,heureref, an,   &
455          mois, jour, heure, zdtvr)
456  endif
457
458  ! #endif of #ifdef CPP_IOIPSL
459
460  !-----------------------------------------------------------------------
461  !   Integration temporelle du modele :
462  !   ----------------------------------
463
464  !       write(78,*) 'ucov',ucov
465  !       write(78,*) 'vcov',vcov
466  !       write(78,*) 'teta',teta
467  !       write(78,*) 'ps',ps
468  !       write(78,*) 'q',q
469
470  !!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
471  !     Copy all threadprivate variables in temps_mod logic_mod
472  !$OMP PARALLEL DEFAULT(SHARED) &
473  !$OMP COPYIN(dt,jD_ref,jH_ref,start_time,hour_ini,day_ini,day_end) &
474  !$OMP COPYIN(annee_ref,day_ref,itau_dyn,itau_phy,itaufin,calend) &
475  !$OMP COPYIN(purmats,forward,leapf,apphys,statcl,conser,apdiss,apdelq) &
476  !$OMP COPYIN(saison,ecripar,fxyhypb,ysinus,read_start,ok_guide) &
477  !$OMP COPYIN(ok_strato,ok_gradsfile,ok_limit,ok_etat0) &
478  !$OMP COPYIN(iflag_phys,iflag_trac,adv_qsat_liq)
479  CALL leapfrog_loc(ucov,vcov,teta,ps,masse,phis,q,time_0)
480  !$OMP END PARALLEL
481
482  !      OPEN(unit=5487,file='ok_lmdz',status='replace')
483  !      WRITE(5487,*) 'ok_lmdz'
484  !      CLOSE(5487)
485END PROGRAM gcm
Note: See TracBrowser for help on using the repository browser.