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

Last change on this file was 4619, checked in by yann meurdesoif, 12 months ago

Suppress usage of preprocessing key CPP_XIOS.
Wrapper file is used to suppress XIOS symbol when xios is not linked and not used (-io ioipsl)
The CPP_XIOS key is replaced in model by "using_xios" boolean variable to switch between IOIPSL or XIOS output.

YM

  • 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
RevLine 
[1279]1!
2! $Id: gcm.F90 4619 2023-07-09 23:40:39Z fhourdin $
3!
[2247]4!
5!
6PROGRAM gcm
[524]7
8#ifdef CPP_IOIPSL
[2247]9  USE IOIPSL
[1146]10#else
[2247]11  ! if not using IOIPSL, we still need to use (a local version of) getin
12  USE ioipsl_getincom
[524]13#endif
[956]14
[1825]15
[4619]16! ug Pour les sorties XIOS
[2247]17  USE wxios
[1825]18
[2247]19  USE filtreg_mod
[4325]20  USE infotrac, ONLY: nqtot, init_infotrac
[2247]21  USE control_mod
[2351]22  USE mod_const_mpi, ONLY: COMM_LMDZ
[2601]23  USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref, &
24                     itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end
[2597]25  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
[2603]26  USE logic_mod, ONLY: ecripar, iflag_phys, read_start
[1146]27
[956]28!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2247]29  ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
30  ! A nettoyer. On ne veut qu'une ou deux routines d'interface
31  ! dynamique -> physique pour l'initialisation
[1615]32#ifdef CPP_PHYS
[2347]33  USE iniphysiq_mod, ONLY: iniphysiq
[956]34#endif
35!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
36
[2247]37  IMPLICIT NONE
[524]38
[2247]39  !      ......   Version  du 10/01/98    ..........
[524]40
[2247]41  !             avec  coordonnees  verticales hybrides
42  !   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
[524]43
[2247]44  !=======================================================================
45  !
46  !   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
47  !   -------
48  !
49  !   Objet:
50  !   ------
51  !
52  !   GCM LMD nouvelle grille
53  !
54  !=======================================================================
55  !
56  !  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
57  !      et possibilite d'appeler une fonction f(y)  a derivee tangente
58  !      hyperbolique a la  place de la fonction a derivee sinusoidale.
59  !  ... Possibilite de choisir le schema pour l'advection de
60  !        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
61  !
62  !      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
63  !      Pour Van-Leer iadv=10
64  !
65  !-----------------------------------------------------------------------
66  !   Declarations:
67  !   -------------
[524]68
[2247]69  include "dimensions.h"
70  include "paramet.h"
71  include "comdissnew.h"
72  include "comgeom.h"
73  include "description.h"
74  include "iniprint.h"
75  include "tracstoke.h"
[524]76
[2247]77  REAL zdtvr
[524]78
[2247]79  !   variables dynamiques
80  REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
81  REAL teta(ip1jmp1,llm)                 ! temperature potentielle
82  REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
83  REAL ps(ip1jmp1)                       ! pression  au sol
[2597]84!  REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
[2247]85  REAL masse(ip1jmp1,llm)                ! masse d'air
86  REAL phis(ip1jmp1)                     ! geopotentiel au sol
[2597]87!  REAL phi(ip1jmp1,llm)                  ! geopotentiel
88!  REAL w(ip1jmp1,llm)                    ! vitesse verticale
[524]89
[2247]90  ! variables dynamiques intermediaire pour le transport
[524]91
[2247]92  !   variables pour le fichier histoire
93  REAL dtav      ! intervalle de temps elementaire
[524]94
[2247]95  REAL time_0
[524]96
[2247]97  LOGICAL lafin
[524]98
99
[2247]100  real time_step, t_wrt, t_ops
[524]101
[2247]102  !      LOGICAL call_iniphys
103  !      data call_iniphys/.true./
[524]104
[2247]105  !+jld variables test conservation energie
106  !      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
107  !     Tendance de la temp. potentiel d (theta)/ d t due a la
108  !     tansformation d'energie cinetique en energie thermique
109  !     cree par la dissipation
[2597]110!  REAL dhecdt(ip1jmp1,llm)
[2247]111  !      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
112  !      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
[2597]113!  CHARACTER (len=15) :: ztit
[2247]114  !-jld
[524]115
116
[2247]117  character (len=80) :: dynhist_file, dynhistave_file
118  character (len=20) :: modname
119  character (len=80) :: abort_message
120  ! locales pour gestion du temps
121  INTEGER :: an, mois, jour
122  REAL :: heure
123  logical use_filtre_fft
[524]124
[2247]125  !-----------------------------------------------------------------------
126  !   Initialisations:
127  !   ----------------
[524]128
[2247]129  abort_message = 'last timestep reached'
130  modname = 'gcm'
131  descript = 'Run GCM LMDZ'
132  lafin    = .FALSE.
133  dynhist_file = 'dyn_hist.nc'
134  dynhistave_file = 'dyn_hist_ave.nc'
[524]135
[762]136
137
[2247]138  !----------------------------------------------------------------------
139  !  lecture des fichiers gcm.def ou run.def
140  !  ---------------------------------------
141  !
142  CALL conf_gcm( 99, .TRUE.)
[762]143
[2247]144  if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm", &
145       "iphysiq must be a multiple of iperiod", 1)
146
147  use_filtre_fft=.FALSE.
148  CALL getin('use_filtre_fft',use_filtre_fft)
[2438]149  IF (use_filtre_fft) call abort_gcm("gcm", 'FFT filter is not available in ' &
150          // 'the sequential version of the dynamics.', 1)
[2247]151
[956]152!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2247]153  ! Initialisation de XIOS
[1825]154!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
155
[4619]156  IF (using_xios) THEN
157    CALL wxios_init("LMDZ")
158  ENDIF
[1825]159
160
161!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2247]162  ! FH 2008/05/02
163  ! A nettoyer. On ne veut qu'une ou deux routines d'interface
164  ! dynamique -> physique pour l'initialisation
[2351]165!#ifdef CPP_PHYS
166!  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
167!  !      call InitComgeomphy ! now done in iniphysiq
168!#endif
[956]169!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2247]170  !-----------------------------------------------------------------------
171  !   Choix du calendrier
172  !   -------------------
[762]173
[2247]174  !      calend = 'earth_365d'
[1279]175
176#ifdef CPP_IOIPSL
[2247]177  if (calend == 'earth_360d') then
[4361]178     call ioconf_calendar('360_day')
[2247]179     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
180  else if (calend == 'earth_365d') then
181     call ioconf_calendar('noleap')
182     write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
183  else if (calend == 'gregorian') then
184     call ioconf_calendar('gregorian')
185     write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
186  else
187     abort_message = 'Mauvais choix de calendrier'
188     call abort_gcm(modname,abort_message,1)
189  endif
[1279]190#endif
[2247]191  !-----------------------------------------------------------------------
192  !
193  !
194  !------------------------------------
195  !   Initialisation partie parallele
196  !------------------------------------
[762]197
[2247]198  !
199  !
200  !-----------------------------------------------------------------------
201  !   Initialisation des traceurs
202  !   ---------------------------
203  !  Choix du nombre de traceurs et du schema pour l'advection
204  !  dans fichier traceur.def, par default ou via INCA
[4325]205  call init_infotrac
[524]206
[2247]207  ! Allocation de la tableau q : champs advectes   
208  allocate(q(ip1jmp1,llm,nqtot))
[1146]209
[2247]210  !-----------------------------------------------------------------------
211  !   Lecture de l'etat initial :
212  !   ---------------------------
[524]213
[2247]214  !  lecture du fichier start.nc
215  if (read_start) then
216     ! we still need to run iniacademic to initialize some
217     ! constants & fields, if we run the 'newtonian' or 'SW' cases:
218     if (iflag_phys.ne.1) then
219        CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
220     endif
[1403]221
[2247]222     !        if (planet_type.eq."earth") then
223     ! Load an Earth-format start file
224     CALL dynetat0("start.nc",vcov,ucov, &
225          teta,q,masse,ps,phis, time_0)
226     !        endif ! of if (planet_type.eq."earth")
[524]227
[2247]228     !       write(73,*) 'ucov',ucov
229     !       write(74,*) 'vcov',vcov
230     !       write(75,*) 'teta',teta
231     !       write(76,*) 'ps',ps
232     !       write(77,*) 'q',q
[524]233
[2247]234  endif ! of if (read_start)
235
[524]236
[2247]237  ! le cas echeant, creation d un etat initial
238  IF (prt_level > 9) WRITE(lunout,*) &
239       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
240  if (.not.read_start) then
[3579]241     start_time=0.
[3435]242     annee_ref=anneeref
[2247]243     CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
244  endif
[524]245
246
[2247]247  !-----------------------------------------------------------------------
248  !   Lecture des parametres de controle pour la simulation :
249  !   -------------------------------------------------------
250  !  on recalcule eventuellement le pas de temps
[524]251
[2247]252  IF(MOD(day_step,iperiod).NE.0) THEN
253     abort_message =  &
254          'Il faut choisir un nb de pas par jour multiple de iperiod'
255     call abort_gcm(modname,abort_message,1)
256  ENDIF
[524]257
[2247]258  IF(MOD(day_step,iphysiq).NE.0) THEN
259     abort_message =  &
260          'Il faut choisir un nb de pas par jour multiple de iphysiq'
261     call abort_gcm(modname,abort_message,1)
262  ENDIF
[524]263
[2247]264  zdtvr    = daysec/REAL(day_step)
265  IF(dtvr.NE.zdtvr) THEN
266     WRITE(lunout,*) &
267          'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
268  ENDIF
[524]269
[2247]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        call abort_gcm("gcm", "'Je m''arrete'", 1)
281     ENDIF
282  ENDIF
283  IF (raz_date == 1) THEN
284     annee_ref = anneeref
285     day_ref = dayref
286     day_ini = dayref
287     itau_dyn = 0
288     itau_phy = 0
289     time_0 = 0.
290     write(lunout,*) &
291          'GCM: On reinitialise a la date lue dans gcm.def'
292  ELSE IF (annee_ref .ne. anneeref .or. day_ref .ne. dayref) THEN
293     write(lunout,*) &
294          'GCM: Attention les dates initiales lues dans le fichier'
295     write(lunout,*) &
296          ' restart ne correspondent pas a celles lues dans '
297     write(lunout,*)' gcm.def'
298     write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
299     write(lunout,*)' day_ref=',day_ref," dayref=",dayref
300     write(lunout,*)' Pas de remise a zero'
301  ENDIF
[1279]302
[2247]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
[1403]327
[1147]328#ifdef CPP_IOIPSL
[2247]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)
[1279]334
[2247]335  call ioconf_startdate(INT(jD_ref), jH_ref)
[1279]336
[2247]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,an, mois, jour, heure)
341  write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
342  write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
[1279]343#else
[2247]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
[1147]349#endif
[524]350
351
[2247]352  if (iflag_phys.eq.1) then
353     ! these initialisations have already been done (via iniacademic)
354     ! if running in SW or Newtonian mode
355     !-----------------------------------------------------------------------
356     !   Initialisation des constantes dynamiques :
357     !   ------------------------------------------
358     dtvr = zdtvr
359     CALL iniconst
[524]360
[2247]361     !-----------------------------------------------------------------------
362     !   Initialisation de la geometrie :
363     !   --------------------------------
364     CALL inigeom
[524]365
[2247]366     !-----------------------------------------------------------------------
367     !   Initialisation du filtre :
368     !   --------------------------
369     CALL inifilr
370  endif ! of if (iflag_phys.eq.1)
371  !
372  !-----------------------------------------------------------------------
373  !   Initialisation de la dissipation :
374  !   ----------------------------------
[524]375
[2247]376  CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   , &
377       tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
[524]378
[2247]379  !  numero de stockage pour les fichiers de redemarrage:
[524]380
[2247]381  !-----------------------------------------------------------------------
382  !   Initialisation des I/O :
383  !   ------------------------
[524]384
385
[2247]386  if (nday>=0) then
387     day_end = day_ini + nday
388  else
389     day_end = day_ini - nday/day_step
390  endif
391  WRITE(lunout,300)day_ini,day_end
392300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
[524]393
[1279]394#ifdef CPP_IOIPSL
[2247]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)
[1279]401#endif
402
[3435]403  !-----------------------------------------------------------------------
404  !   Initialisation de la physique :
405  !   -------------------------------
406
407  IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
408     ! Physics:
409#ifdef CPP_PHYS
410     CALL iniphysiq(iim,jjm,llm, &
411          (jjm-1)*iim+2,comm_lmdz, &
412          daysec,day_ini,dtphys/nsplit_phys, &
413          rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
414          iflag_phys)
415#endif
416  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
417
[2247]418  !      if (planet_type.eq."earth") then
419  ! Write an Earth-format restart file
[1529]420
[2247]421  CALL dynredem0("restart.nc", day_end, phis)
422  !      endif
[524]423
[2247]424  ecripar = .TRUE.
[524]425
[1146]426#ifdef CPP_IOIPSL
[2247]427  time_step = zdtvr
428  if (ok_dyn_ins) then
429     ! initialize output file for instantaneous outputs
430     ! t_ops = iecri * daysec ! do operations every t_ops
431     t_ops =((1.0*iecri)/day_step) * daysec 
432     t_wrt = daysec ! iecri * daysec ! write output every t_wrt
433     CALL inithist(day_ref,annee_ref,time_step, &
434          t_ops,t_wrt)
435  endif
[524]436
[2247]437  IF (ok_dyn_ave) THEN
438     ! initialize output file for averaged outputs
439     t_ops = iperiod * time_step ! do operations every t_ops
440     t_wrt = periodav * daysec   ! write output every t_wrt
441     CALL initdynav(day_ref,annee_ref,time_step, &
442          t_ops,t_wrt)
443  END IF
444  dtav = iperiod*dtvr/daysec
[524]445#endif
[2247]446  ! #endif of #ifdef CPP_IOIPSL
[524]447
[2247]448  !  Choix des frequences de stokage pour le offline
449  !      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
450  !      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
451  istdyn=day_step/4     ! stockage toutes les 6h=1jour/12
452  istphy=istdyn/iphysiq     
[541]453
454
[2247]455  !
456  !-----------------------------------------------------------------------
457  !   Integration temporelle du modele :
458  !   ----------------------------------
[524]459
[2247]460  !       write(78,*) 'ucov',ucov
461  !       write(78,*) 'vcov',vcov
462  !       write(78,*) 'teta',teta
463  !       write(78,*) 'ps',ps
464  !       write(78,*) 'q',q
[524]465
466
[2247]467  CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,time_0)
[524]468
[2247]469END PROGRAM gcm
Note: See TracBrowser for help on using the repository browser.