source: LMDZ6/trunk/libf/dyn3d/gcm.F90 @ 3540

Last change on this file since 3540 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 14.6 KB
Line 
1!
2! $Id: gcm.F90 3435 2019-01-22 15:21:59Z fairhead $
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#ifdef CPP_XIOS
17  ! ug Pour les sorties XIOS
18  USE wxios
19#endif
20
21  USE filtreg_mod
22  USE infotrac
23  USE control_mod
24  USE mod_const_mpi, ONLY: COMM_LMDZ
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  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
28  USE logic_mod, ONLY: ecripar, iflag_phys, read_start
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#ifdef CPP_PHYS
35  USE iniphysiq_mod, ONLY: iniphysiq
36#endif
37!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
38
39  IMPLICIT NONE
40
41  !      ......   Version  du 10/01/98    ..........
42
43  !             avec  coordonnees  verticales hybrides
44  !   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
45
46  !=======================================================================
47  !
48  !   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
49  !   -------
50  !
51  !   Objet:
52  !   ------
53  !
54  !   GCM LMD nouvelle grille
55  !
56  !=======================================================================
57  !
58  !  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
59  !      et possibilite d'appeler une fonction f(y)  a derivee tangente
60  !      hyperbolique a la  place de la fonction a derivee sinusoidale.
61  !  ... Possibilite de choisir le schema pour l'advection de
62  !        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
63  !
64  !      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
65  !      Pour Van-Leer iadv=10
66  !
67  !-----------------------------------------------------------------------
68  !   Declarations:
69  !   -------------
70
71  include "dimensions.h"
72  include "paramet.h"
73  include "comdissnew.h"
74  include "comgeom.h"
75  include "description.h"
76  include "iniprint.h"
77  include "tracstoke.h"
78
79  REAL zdtvr
80
81  !   variables dynamiques
82  REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
83  REAL teta(ip1jmp1,llm)                 ! temperature potentielle
84  REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
85  REAL ps(ip1jmp1)                       ! pression  au sol
86!  REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
87  REAL masse(ip1jmp1,llm)                ! masse d'air
88  REAL phis(ip1jmp1)                     ! geopotentiel au sol
89!  REAL phi(ip1jmp1,llm)                  ! geopotentiel
90!  REAL w(ip1jmp1,llm)                    ! vitesse verticale
91
92  ! variables dynamiques intermediaire pour le transport
93
94  !   variables pour le fichier histoire
95  REAL dtav      ! intervalle de temps elementaire
96
97  REAL time_0
98
99  LOGICAL lafin
100
101
102  real time_step, t_wrt, t_ops
103
104  !      LOGICAL call_iniphys
105  !      data call_iniphys/.true./
106
107  !+jld variables test conservation energie
108  !      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
109  !     Tendance de la temp. potentiel d (theta)/ d t due a la
110  !     tansformation d'energie cinetique en energie thermique
111  !     cree par la dissipation
112!  REAL dhecdt(ip1jmp1,llm)
113  !      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
114  !      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
115!  CHARACTER (len=15) :: ztit
116  !-jld
117
118
119  character (len=80) :: dynhist_file, dynhistave_file
120  character (len=20) :: modname
121  character (len=80) :: abort_message
122  ! locales pour gestion du temps
123  INTEGER :: an, mois, jour
124  REAL :: heure
125  logical use_filtre_fft
126
127  !-----------------------------------------------------------------------
128  !   Initialisations:
129  !   ----------------
130
131  abort_message = 'last timestep reached'
132  modname = 'gcm'
133  descript = 'Run GCM LMDZ'
134  lafin    = .FALSE.
135  dynhist_file = 'dyn_hist.nc'
136  dynhistave_file = 'dyn_hist_ave.nc'
137
138
139
140  !----------------------------------------------------------------------
141  !  lecture des fichiers gcm.def ou run.def
142  !  ---------------------------------------
143  !
144  CALL conf_gcm( 99, .TRUE.)
145
146  if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm", &
147       "iphysiq must be a multiple of iperiod", 1)
148
149  use_filtre_fft=.FALSE.
150  CALL getin('use_filtre_fft',use_filtre_fft)
151  IF (use_filtre_fft) call abort_gcm("gcm", 'FFT filter is not available in ' &
152          // 'the sequential version of the dynamics.', 1)
153
154!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
155  ! Initialisation de XIOS
156!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
157
158#ifdef CPP_XIOS
159  CALL wxios_init("LMDZ")
160#endif
161
162
163!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
164  ! FH 2008/05/02
165  ! A nettoyer. On ne veut qu'une ou deux routines d'interface
166  ! dynamique -> physique pour l'initialisation
167!#ifdef CPP_PHYS
168!  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
169!  !      call InitComgeomphy ! now done in iniphysiq
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('360d')
181     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
182  else if (calend == 'earth_365d') then
183     call ioconf_calendar('noleap')
184     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
185  else if (calend == 'gregorian') then
186     call ioconf_calendar('gregorian')
187     write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
188  else
189     abort_message = 'Mauvais choix de calendrier'
190     call abort_gcm(modname,abort_message,1)
191  endif
192#endif
193  !-----------------------------------------------------------------------
194  !
195  !
196  !------------------------------------
197  !   Initialisation partie parallele
198  !------------------------------------
199
200  !
201  !
202  !-----------------------------------------------------------------------
203  !   Initialisation des traceurs
204  !   ---------------------------
205  !  Choix du nombre de traceurs et du schema pour l'advection
206  !  dans fichier traceur.def, par default ou via INCA
207  call infotrac_init
208
209  ! Allocation de la tableau q : champs advectes   
210  allocate(q(ip1jmp1,llm,nqtot))
211
212  !-----------------------------------------------------------------------
213  !   Lecture de l'etat initial :
214  !   ---------------------------
215
216  !  lecture du fichier start.nc
217  if (read_start) then
218     ! we still need to run iniacademic to initialize some
219     ! constants & fields, if we run the 'newtonian' or 'SW' cases:
220     if (iflag_phys.ne.1) then
221        CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
222     endif
223
224     !        if (planet_type.eq."earth") then
225     ! Load an Earth-format start file
226     CALL dynetat0("start.nc",vcov,ucov, &
227          teta,q,masse,ps,phis, time_0)
228     !        endif ! of if (planet_type.eq."earth")
229
230     !       write(73,*) 'ucov',ucov
231     !       write(74,*) 'vcov',vcov
232     !       write(75,*) 'teta',teta
233     !       write(76,*) 'ps',ps
234     !       write(77,*) 'q',q
235
236  endif ! of if (read_start)
237
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     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).NE.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).NE.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.NE.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 .ne. anneeref .or. day_ref .ne. 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.eq.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#ifdef CPP_PHYS
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#endif
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.