source: LMDZ6/trunk/libf/dyn3dmem/gcm.F90 @ 5301

Last change on this file since 5301 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

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