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

Last change on this file since 3544 was 3435, checked in by Laurent Fairhead, 5 years ago

"Historic" :-) commit merging the physics branch used for DYNAMICO with the LMDZ trunk.
The same physics branch can now be used seamlessly with the traditional lon-lat LMDZ
dynamical core and DYNAMICO.
Testing consisted in running a lon-lat LMDZ bucket simulation with the NPv6.1 physics package
with the original trunk sources and the merged sources. Tests were succesful in the sense that
numeric continuity was preserved in the restart files from both simulation. Further tests
included running both versions of the physics codes for one year in a LMDZOR setting in which
the restart files also came out identical.

Caution:

  • as the physics package now manages unstructured grids, grid information needs to be transmitted

to the surface scheme ORCHIDEE. This means that the interface defined in surf_land_orchidee_mod.F90
is only compatible with ORCHIDEE version orchidee2.1 and later versions. If previous versions of
ORCHIDEE need to be used, the CPP key ORCHIDEE_NOUNSTRUCT needs to be set at compilation time.
This is done automatically if makelmdz/makelmdz_fcm are called with the veget orchidee2.0 switch

  • due to a limitation in XIOS, the time at which limit conditions will be read in by DYNAMICO will be

delayed by one physic timestep with respect to the time it is read in by the lon-lat model. This is caused
by the line

IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN ! time to read

in limit_read_mod.F90

Work still needed on COSP integration and XML files for DYNAMICO

EM, YM, LF

  • 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
File size: 14.7 KB
Line 
1! $Id: $
2
3PROGRAM gcm
4
5#ifdef CPP_IOIPSL
6  USE IOIPSL
7#endif
8
9  USE mod_const_mpi, ONLY: init_const_mpi
10  USE parallel_lmdz
11  USE infotrac
12!#ifdef CPP_PHYS
13!  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
14!#endif
15  USE mod_hallo
16  USE Bands
17  USE filtreg_mod
18  USE control_mod
19
20#ifdef CPP_PHYS
21  USE iniphysiq_mod, ONLY: iniphysiq
22#endif
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
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
112
113  !-----------------------------------------------------------------------
114  !   Initialisations:
115  !   ----------------
116
117  abort_message = 'last timestep reached'
118  modname = 'gcm'
119  descript = 'Run GCM LMDZ'
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#ifdef CPP_IOIPSL
173  if (calend == 'earth_360d') then
174     call ioconf_calendar('360d')
175     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
176  else if (calend == 'earth_365d') then
177     call ioconf_calendar('noleap')
178     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
179  else if (calend == 'gregorian') then
180     call ioconf_calendar('gregorian')
181     write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
182  else
183     abort_message = 'Mauvais choix de calendrier'
184     call abort_gcm(modname,abort_message,1)
185  endif
186#endif
187
188
189  !-----------------------------------------------------------------------
190  !   Initialisation des traceurs
191  !   ---------------------------
192  !  Choix du nombre de traceurs et du schema pour l'advection
193  !  dans fichier traceur.def, par default ou via INCA
194  call infotrac_init
195
196  ! Allocation de la tableau q : champs advectes   
197  ALLOCATE(ucov(ijb_u:ije_u,llm))
198  ALLOCATE(vcov(ijb_v:ije_v,llm))
199  ALLOCATE(teta(ijb_u:ije_u,llm))
200  ALLOCATE(masse(ijb_u:ije_u,llm))
201  ALLOCATE(ps(ijb_u:ije_u))
202  ALLOCATE(phis(ijb_u:ije_u))
203  ALLOCATE(q(ijb_u:ije_u,llm,nqtot))
204
205  !-----------------------------------------------------------------------
206  !   Lecture de l'etat initial :
207  !   ---------------------------
208
209  !  lecture du fichier start.nc
210  if (read_start) then
211     ! we still need to run iniacademic to initialize some
212     ! constants & fields, if we run the 'newtonian' or 'SW' cases:
213     if (iflag_phys.ne.1) then
214        CALL iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
215     endif
216
217     !        if (planet_type.eq."earth") then
218     ! Load an Earth-format start file
219     CALL dynetat0_loc("start.nc",vcov,ucov, &
220          teta,q,masse,ps,phis, time_0)
221     !        endif ! of if (planet_type.eq."earth")
222
223     !       write(73,*) 'ucov',ucov
224     !       write(74,*) 'vcov',vcov
225     !       write(75,*) 'teta',teta
226     !       write(76,*) 'ps',ps
227     !       write(77,*) 'q',q
228
229  endif ! of if (read_start)
230
231  ! le cas echeant, creation d un etat initial
232  IF (prt_level > 9) WRITE(lunout,*) &
233       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
234  if (.not.read_start) then
235     annee_ref=anneeref
236     CALL iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
237  endif
238
239  !-----------------------------------------------------------------------
240  !   Lecture des parametres de controle pour la simulation :
241  !   -------------------------------------------------------
242  !  on recalcule eventuellement le pas de temps
243
244  IF(MOD(day_step,iperiod).NE.0) THEN
245     abort_message =  &
246          'Il faut choisir un nb de pas par jour multiple de iperiod'
247     call abort_gcm(modname,abort_message,1)
248  ENDIF
249
250  IF(MOD(day_step,iphysiq).NE.0) THEN
251     abort_message =  &
252          'Il faut choisir un nb de pas par jour multiple de iphysiq'
253     call abort_gcm(modname,abort_message,1)
254  ENDIF
255
256  zdtvr    = daysec/REAL(day_step)
257  IF(dtvr.NE.zdtvr) THEN
258     WRITE(lunout,*) &
259          'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
260  ENDIF
261
262  !
263  ! on remet le calendrier \`a zero si demande
264  !
265  IF (start_time /= starttime) then
266     WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le' &
267          ,' fichier restart ne correspond pas a celle lue dans le run.def'
268     IF (raz_date == 1) then
269        WRITE(lunout,*)'Je prends l''heure lue dans run.def'
270        start_time = starttime
271     ELSE
272        WRITE(lunout,*)'Je m''arrete'
273        CALL abort
274     ENDIF
275  ENDIF
276  IF (raz_date == 1) THEN
277     annee_ref = anneeref
278     day_ref = dayref
279     day_ini = dayref
280     itau_dyn = 0
281     itau_phy = 0
282     time_0 = 0.
283     write(lunout,*) &
284          'GCM: On reinitialise a la date lue dans gcm.def'
285  ELSE IF (annee_ref .ne. anneeref .or. day_ref .ne. dayref) THEN
286     write(lunout,*) &
287          'GCM: Attention les dates initiales lues dans le fichier'
288     write(lunout,*) &
289          ' restart ne correspondent pas a celles lues dans '
290     write(lunout,*)' gcm.def'
291     write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
292     write(lunout,*)' day_ref=',day_ref," dayref=",dayref
293     write(lunout,*)' Pas de remise a zero'
294  ENDIF
295  !      if (annee_ref .ne. anneeref .or. day_ref .ne. 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  !        if (raz_date .ne. 1) then
304  !          write(lunout,*)
305  !     .    'GCM: On garde les dates du fichier restart'
306  !        else
307  !          annee_ref = anneeref
308  !          day_ref = dayref
309  !          day_ini = dayref
310  !          itau_dyn = 0
311  !          itau_phy = 0
312  !          time_0 = 0.
313  !          write(lunout,*)
314  !     .   'GCM: On reinitialise a la date lue dans gcm.def'
315  !        endif
316  !      ELSE
317  !        raz_date = 0
318  !      endif
319
320#ifdef CPP_IOIPSL
321  mois = 1
322  heure = 0.
323  call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
324  jH_ref = jD_ref - int(jD_ref)
325  jD_ref = int(jD_ref)
326
327  call ioconf_startdate(INT(jD_ref), jH_ref)
328
329  write(lunout,*)'DEBUG'
330  write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
331  write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
332  call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure)
333  write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
334  write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
335#else
336  ! Ehouarn: we still need to define JD_ref and JH_ref
337  ! and since we don't know how many days there are in a year
338  ! we set JD_ref to 0 (this should be improved ...)
339  jD_ref=0
340  jH_ref=0
341#endif
342
343  if (iflag_phys.eq.1) then
344     ! these initialisations have already been done (via iniacademic)
345     ! if running in SW or Newtonian mode
346     !-----------------------------------------------------------------------
347     !   Initialisation des constantes dynamiques :
348     !   ------------------------------------------
349     dtvr = zdtvr
350     CALL iniconst
351
352     !-----------------------------------------------------------------------
353     !   Initialisation de la geometrie :
354     !   --------------------------------
355     CALL inigeom
356
357     !-----------------------------------------------------------------------
358     !   Initialisation du filtre :
359     !   --------------------------
360     CALL inifilr
361  endif ! of if (iflag_phys.eq.1)
362  !
363  !-----------------------------------------------------------------------
364  !   Initialisation de la dissipation :
365  !   ----------------------------------
366
367  CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   , &
368       tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
369
370  !-----------------------------------------------------------------------
371  !   Initialisation des I/O :
372  !   ------------------------
373
374
375  if (nday>=0) then
376     day_end = day_ini + nday
377  else
378     day_end = day_ini - nday/day_step
379  endif
380
381  WRITE(lunout,300)day_ini,day_end
382300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
383
384#ifdef CPP_IOIPSL
385  call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
386  write (lunout,301)jour, mois, an
387  call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
388  write (lunout,302)jour, mois, an
389301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
390302 FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
391#endif
392
393  !-----------------------------------------------------------------------
394  !   Initialisation de la physique :
395  !   -------------------------------
396  IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
397     ! Physics:
398#ifdef CPP_PHYS
399     CALL iniphysiq(iim,jjm,llm, &
400          distrib_phys(mpi_rank),comm_lmdz, &
401          daysec,day_ini,dtphys/nsplit_phys, &
402          rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
403          iflag_phys)
404#endif
405  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
406
407
408  !      if (planet_type.eq."earth") then
409  ! Write an Earth-format restart file
410  CALL dynredem0_loc("restart.nc", day_end, phis)
411  !      endif
412
413  ecripar = .TRUE.
414
415#ifdef CPP_IOIPSL
416  time_step = zdtvr
417     if (ok_dyn_ins) then
418        ! initialize output file for instantaneous outputs
419        ! t_ops = iecri * daysec ! do operations every t_ops
420        t_ops =((1.0*iecri)/day_step) * daysec 
421        t_wrt = daysec ! iecri * daysec ! write output every t_wrt
422        CALL inithist_loc(day_ref,annee_ref,time_step, &
423             t_ops,t_wrt)
424     endif
425
426     IF (ok_dyn_ave) THEN
427        ! initialize output file for averaged outputs
428        t_ops = iperiod * time_step ! do operations every t_ops
429        t_wrt = periodav * daysec   ! write output every t_wrt
430        CALL initdynav_loc(day_ref,annee_ref,time_step,t_ops,t_wrt)
431     END IF
432  dtav = iperiod*dtvr/daysec
433#endif
434  ! #endif of #ifdef CPP_IOIPSL
435
436  !  Choix des frequences de stokage pour le offline
437  !      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
438  !      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
439  istdyn=day_step/4     ! stockage toutes les 6h=1jour/12
440  istphy=istdyn/iphysiq     
441
442
443  !
444  !-----------------------------------------------------------------------
445  !   Integration temporelle du modele :
446  !   ----------------------------------
447
448  !       write(78,*) 'ucov',ucov
449  !       write(78,*) 'vcov',vcov
450  !       write(78,*) 'teta',teta
451  !       write(78,*) 'ps',ps
452  !       write(78,*) 'q',q
453
454  !!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
455  !$OMP PARALLEL DEFAULT(SHARED) &
456  !     Copy all threadprivate variables in temps_mod
457  !$OMP COPYIN(dt,jD_ref,jH_ref,start_time,hour_ini,day_ini,day_end) &
458  !$OMP COPYIN(annee_ref,day_ref,itau_dyn,itau_phy,itaufin,calend) &
459  !     Copy all threadprivate variables from logic_mod
460  !$OMP COPYIN(purmats,forward,leapf,apphys,statcl,conser,apdiss,apdelq) &
461  !$OMP COPYIN(saison,ecripar,fxyhypb,ysinus,read_start,ok_guide) &
462  !$OMP COPYIN(ok_strato,ok_gradsfile,ok_limit,ok_etat0) &
463  !$OMP COPYIN(iflag_phys,iflag_trac)
464  CALL leapfrog_loc(ucov,vcov,teta,ps,masse,phis,q,time_0)
465  !$OMP END PARALLEL
466
467  !      OPEN(unit=5487,file='ok_lmdz',status='replace')
468  !      WRITE(5487,*) 'ok_lmdz'
469  !      CLOSE(5487)
470END PROGRAM gcm
Note: See TracBrowser for help on using the repository browser.