source: trunk/LMDZ.COMMON/libf/dyn3d/gcm.F90 @ 3837

Last change on this file since 3837 was 3836, checked in by jbclement, 3 days ago

COMMON:
Rework related to the command-line parsing:

  • Replace ad-hoc argument parsing with a unified 'parse_args' subroutine, allowing easier extension to other programs and options across models;;
  • Use of '--version' (with ab optional output file) to print compilation/version details;
  • Addition of 'job_timelimit_mod' module to handle SLURM/PBS job time-limit via '--jobid' (currently only used in the PEM), allowing easier extension to other programs;
  • Replace manual SSO handling with 'parse_args' for the Mars start2archive;
  • Clean-up related legacy code in the programs supporting the version option.

JBC

File size: 16.8 KB
Line 
1!
2! $Id: gcm.F 1446 2010-10-22 09:27:25Z emillour $
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, only: planet_type,nday,day_step,iperiod,iphysiq, &
24                             raz_date,anneeref,starttime,dayref,    &
25                             ok_dyn_ins,ok_dyn_ave,iecri,periodav,  &
26                             less1day,fractday,ndynstep,nsplit_phys,&
27                             ecritstart
28  USE mod_const_mpi, ONLY: COMM_LMDZ
29  use cpdet_mod, only: ini_cpdet
30  USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref, &
31                itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end
32  use parse_args_mod, only: parse_args
33
34
35!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
36! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
37! A nettoyer. On ne veut qu'une ou deux routines d'interface
38! dynamique -> physique pour l'initialisation
39! Ehouarn: the following are needed with (parallel) physics:
40#ifdef CPP_PHYS
41  USE iniphysiq_mod, ONLY: iniphysiq
42#endif
43
44  USE comconst_mod, ONLY: daysec,dtvr,dtphys,rad,g,r,cpp
45  USE logic_mod, ONLY: read_start,iflag_phys,ok_guide,ecripar
46
47!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
48
49  IMPLICIT NONE
50
51  !      ......   Version  du 10/01/98    ..........
52
53  !             avec  coordonnees  verticales hybrides
54  !   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
55
56  !=======================================================================
57  !
58  !   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
59  !   -------
60  !
61  !   Objet:
62  !   ------
63  !
64  !   GCM LMD nouvelle grille
65  !
66  !=======================================================================
67  !
68  !  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
69  !      et possibilite d'appeler une fonction f(y)  a derivee tangente
70  !      hyperbolique a la  place de la fonction a derivee sinusoidale.
71  !  ... Possibilite de choisir le schema pour l'advection de
72  !        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
73  !
74  !      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
75  !      Pour Van-Leer iadv=10
76  !
77  !-----------------------------------------------------------------------
78  !   Declarations:
79  !   -------------
80
81  include "dimensions.h"
82  include "paramet.h"
83  include "comdissnew.h"
84  include "comgeom.h"
85!!!!!!!!!!!#include "control.h"
86!#include "com_io_dyn.h"
87  include "iniprint.h"
88  include "tracstoke.h"
89
90  REAL zdtvr
91
92  !   variables dynamiques
93  REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
94  REAL teta(ip1jmp1,llm)                 ! temperature potentielle
95  REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
96  REAL ps(ip1jmp1)                       ! pression  au sol
97  REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
98  REAL masse(ip1jmp1,llm)                ! masse d'air
99  REAL phis(ip1jmp1)                     ! geopotentiel au sol
100  REAL phi(ip1jmp1,llm)                  ! geopotentiel
101  REAL w(ip1jmp1,llm)                    ! vitesse verticale
102
103  ! variables dynamiques intermediaire pour le transport
104
105  !   variables pour le fichier histoire
106  REAL dtav      ! intervalle de temps elementaire
107
108  REAL time_0
109
110  LOGICAL lafin
111  INTEGER ij,iq,l,i,j
112
113
114  real time_step, t_wrt, t_ops
115
116  LOGICAL first
117
118  !      LOGICAL call_iniphys
119  !      data call_iniphys/.true./
120
121  !+jld variables test conservation energie
122  !      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
123  !     Tendance de la temp. potentiel d (theta)/ d t due a la
124  !     tansformation d'energie cinetique en energie thermique
125  !     cree par la dissipation
126  REAL dhecdt(ip1jmp1,llm)
127  !      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
128  !      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
129  CHARACTER (len=15) :: ztit
130  !-jld
131
132
133  character (len=80) :: dynhist_file, dynhistave_file
134  character (len=20) :: modname
135  character (len=80) :: abort_message
136  ! locales pour gestion du temps
137  INTEGER :: an, mois, jour
138  REAL :: heure
139  logical use_filtre_fft
140  logical :: present
141
142!-----------------------------------------------------------------------
143!   Initialisations:
144!   ----------------
145  ! Parse command-line options
146  call parse_args()
147
148  abort_message = 'last timestep reached'
149  modname = 'gcm'
150  lafin    = .FALSE.
151  dynhist_file = 'dyn_hist.nc'
152  dynhistave_file = 'dyn_hist_ave.nc'
153
154
155
156!----------------------------------------------------------------------
157!  Load flags and options from run.def
158!  ---------------------------------------
159!
160! Start by checking that there indeed is a run.def file
161  INQUIRE(file="run.def", EXIST=present)
162  IF(.not. present) then
163    CALL abort_gcm("gcm", "file run.def not found, Aborting!",1)
164  ENDIF
165
166  CALL conf_gcm( 99, .TRUE. )
167  if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm", &
168       "iphysiq must be a multiple of iperiod", 1)
169
170  use_filtre_fft=.FALSE.
171  CALL getin('use_filtre_fft',use_filtre_fft)
172  IF (use_filtre_fft) call abort_gcm("gcm",'FFT filter is not available in the ' &
173          // 'sequential version of the dynamics.', 1)
174
175!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
176! Initialisation de XIOS
177!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
178
179#ifdef CPP_XIOS
180  CALL wxios_init("LMDZ")
181#endif
182
183
184!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
185! FH 2008/05/02
186! A nettoyer. On ne veut qu'une ou deux routines d'interface
187! dynamique -> physique pour l'initialisation
188!#ifdef CPP_PHYS
189!  CALL init_phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
190!!      call initcomgeomphy ! now done in iniphysiq
191!#endif
192!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
193!
194! Initialisations pour Cp(T) Venus
195  call ini_cpdet
196!
197!-----------------------------------------------------------------------
198!   Choix du calendrier
199!   -------------------
200
201!      calend = 'earth_365d'
202
203#ifdef CPP_IOIPSL
204  if (calend == 'earth_360d') then
205    call ioconf_calendar('360d')
206    write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
207  else if (calend == 'earth_365d') then
208    call ioconf_calendar('noleap')
209    write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
210  else if (calend == 'earth_366d') then
211    call ioconf_calendar('gregorian')
212    write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
213  else if (calend == 'titan') then
214!        call ioconf_calendar('titan')
215    write(lunout,*)'CALENDRIER CHOISI: Titan'
216    abort_message = 'A FAIRE...'
217    call abort_gcm(modname,abort_message,1)
218  else if (calend == 'venus') then
219!        call ioconf_calendar('venus')
220    write(lunout,*)'CALENDRIER CHOISI: Venus'
221    abort_message = 'A FAIRE...'
222    call abort_gcm(modname,abort_message,1)
223  else
224    abort_message = 'Mauvais choix de calendrier'
225    call abort_gcm(modname,abort_message,1)
226  endif
227#endif
228!-----------------------------------------------------------------------
229  !
230  !
231  !------------------------------------
232  !   Initialisation partie parallele
233  !------------------------------------
234
235  !
236  !
237  !-----------------------------------------------------------------------
238  !   Initialisation des traceurs
239  !   ---------------------------
240  !  Choix du nombre de traceurs et du schema pour l'advection
241  !  dans fichier traceur.def, par default ou via INCA
242  call infotrac_init
243
244  ! Allocation de la tableau q : champs advectes   
245  allocate(q(ip1jmp1,llm,nqtot))
246
247  !-----------------------------------------------------------------------
248  !   Lecture de l'etat initial :
249  !   ---------------------------
250
251  !  lecture du fichier start.nc
252  if (read_start) then
253     ! we still need to run iniacademic to initialize some
254     ! constants & fields, if we run the 'newtonian' or 'SW' cases:
255     if (iflag_phys.ne.1) then
256        CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
257     endif
258
259     CALL dynetat0("start.nc",vcov,ucov, &
260                    teta,q,masse,ps,phis, time_0)
261       
262     ! Load relaxation fields (simple nudging). AS 09/2013
263     ! ---------------------------------------------------
264     if (planet_type.eq."generic") then
265       if (ok_guide) then
266         CALL relaxetat0("relax.nc")
267       endif
268     endif
269 
270     !       write(73,*) 'ucov',ucov
271     !       write(74,*) 'vcov',vcov
272     !       write(75,*) 'teta',teta
273     !       write(76,*) 'ps',ps
274     !       write(77,*) 'q',q
275
276  endif ! of if (read_start)
277
278
279  ! le cas echeant, creation d un etat initial
280  IF (prt_level > 9) WRITE(lunout,*) &
281       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
282  if (.not.read_start) then
283     CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
284  endif
285
286
287  !-----------------------------------------------------------------------
288  !   Lecture des parametres de controle pour la simulation :
289  !   -------------------------------------------------------
290  !  on recalcule eventuellement le pas de temps
291
292  IF(MOD(day_step,iperiod).NE.0) THEN
293     abort_message = &
294       'Il faut choisir un nb de pas par jour multiple de iperiod'
295     call abort_gcm(modname,abort_message,1)
296  ENDIF
297
298  IF(MOD(day_step,iphysiq).NE.0) THEN
299     abort_message = &
300       'Il faut choisir un nb de pas par jour multiple de iphysiq'
301     call abort_gcm(modname,abort_message,1)
302  ENDIF
303
304  zdtvr    = daysec/REAL(day_step)
305  IF(dtvr.NE.zdtvr) THEN
306     WRITE(lunout,*) &
307          'WARNING!!! time step change: ',dtvr,'>',zdtvr
308  ENDIF
309  dtvr=zdtvr
310
311  !
312  ! reset calendar if requested
313  !
314  IF (raz_date == 1) then
315    WRITE(lunout,*)'Reinitializing to start time from run.def'
316    start_time = starttime
317  ENDIF
318
319  IF (raz_date == 1) THEN
320     annee_ref = anneeref
321     day_ref = dayref
322     day_ini = dayref
323     itau_dyn = 0
324     itau_phy = 0
325     time_0 = 0.
326     write(lunout,*) &
327         'GCM: On reinitialise a la date lue dans gcm.def'
328  ELSE IF (annee_ref .ne. anneeref .or. day_ref .ne. dayref) THEN
329     write(lunout,*) &
330        'GCM: Attention les dates initiales lues dans le fichier'
331     write(lunout,*) &
332        ' restart ne correspondent pas a celles lues dans '
333     write(lunout,*)' gcm.def'
334     write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
335     write(lunout,*)' day_ref=',day_ref," dayref=",dayref
336     write(lunout,*)' Pas de remise a zero'
337  ENDIF
338
339!      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
340!        write(lunout,*)
341!     .  'GCM: Attention les dates initiales lues dans le fichier'
342!        write(lunout,*)
343!     .  ' restart ne correspondent pas a celles lues dans '
344!        write(lunout,*)' gcm.def'
345!        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
346!        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
347!        if (raz_date .ne. 1) then
348!          write(lunout,*)
349!     .    'GCM: On garde les dates du fichier restart'
350!        else
351!          annee_ref = anneeref
352!          day_ref = dayref
353!          day_ini = dayref
354!          itau_dyn = 0
355!          itau_phy = 0
356!          time_0 = 0.
357!          write(lunout,*)
358!     .   'GCM: On reinitialise a la date lue dans gcm.def'
359!        endif
360!      ELSE
361!        raz_date = 0
362!      endif
363
364#ifdef CPP_IOIPSL
365  mois = 1
366  heure = 0.
367! Ce n'est defini pour l'instant que pour la Terre...
368  if (planet_type.eq.'earth') then
369    call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
370    jH_ref = jD_ref - int(jD_ref)
371    jD_ref = int(jD_ref)
372
373    call ioconf_startdate(INT(jD_ref), jH_ref)
374
375    write(lunout,*)'DEBUG'
376    write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
377    write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
378    call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure)
379    write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
380    write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
381!  else if (planet_type.eq.'titan') then
382!    jD_ref=1 ! Only if we use old Titan starts (J.V.O 2016)
383  else
384! A voir pour Titan et Venus
385    jD_ref=0
386    jH_ref=0
387    write(lunout,*)'A VOIR POUR VENUS ET TITAN: jD_ref, jH_ref'
388    write(lunout,*)jD_ref,jH_ref
389  endif ! planet_type
390#else
391  ! Ehouarn: we still need to define JD_ref and JH_ref
392  ! and since we don't know how many days there are in a year
393  ! we set JD_ref to 0 (this should be improved ...)
394  jD_ref=0
395  jH_ref=0
396#endif
397
398  if (iflag_phys.eq.1) then
399     ! these initialisations have already been done (via iniacademic)
400     ! if running in SW or Newtonian mode
401     !-----------------------------------------------------------------------
402     !   Initialisation des constantes dynamiques :
403     !   ------------------------------------------
404     dtvr = zdtvr
405     CALL iniconst
406
407     !-----------------------------------------------------------------------
408     !   Initialisation de la geometrie :
409     !   --------------------------------
410     CALL inigeom
411
412     !-----------------------------------------------------------------------
413     !   Initialisation du filtre :
414     !   --------------------------
415     CALL inifilr
416  endif ! of if (iflag_phys.eq.1)
417  !
418  !-----------------------------------------------------------------------
419  !   Initialisation de la dissipation :
420  !   ----------------------------------
421
422  CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   , &
423                  tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
424
425  !-----------------------------------------------------------------------
426  !   Initialisation des I/O :
427  !   ------------------------
428
429  if (nday>=0) then ! standard case
430     day_end=day_ini+nday
431  else ! special case when nday <0, run -nday dynamical steps
432     day_end=day_ini-nday/day_step
433  endif
434  if (less1day) then
435     day_end=day_ini+floor(time_0+fractday)
436  endif
437  if (ndynstep.gt.0) then
438     day_end=day_ini+floor(time_0+float(ndynstep)/float(day_step))
439  endif
440     
441  WRITE(lunout,'(a,i7,a,i7)') &
442               "run from day ",day_ini,"  to day",day_end
443
444#ifdef CPP_IOIPSL
445  ! Ce n'est defini pour l'instant que pour la Terre...
446  if (planet_type.eq.'earth') then
447    call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
448    write (lunout,301)jour, mois, an
449    call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
450    write (lunout,302)jour, mois, an
451  else
452  ! A voir pour Titan et Venus
453    write(lunout,*)'A VOIR POUR VENUS/TITAN: separation en annees...'
454  endif ! planet_type
455301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
456302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
457#endif
458
459
460  !-----------------------------------------------------------------------
461  !   Initialisation de la physique :
462  !   -------------------------------
463
464  IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
465     ! Physics:
466#ifdef CPP_PHYS
467     CALL iniphysiq(iim,jjm,llm,                        &
468                    (jjm-1)*iim+2,comm_lmdz,            &
469                    daysec,day_ini,dtphys/nsplit_phys,  &
470                    rlatu,rlatv,rlonu,rlonv,aire,cu,cv, &
471                    rad,g,r,cpp,iflag_phys)
472#endif
473  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
474
475
476! If we want to save multiple restart at different time (ecritstart.GT.0)
477! We will write in restart the initial day of the simulation and put all
478! the different time in the Time variable
479! However, if we write only one restart, we save the last day of the
480! simulation and put the remaining time (which is 0 if we do fulls days)
481! in the Time variable
482
483  if (planet_type=="mars") then
484    if (ecritstart.GT.0) then
485    ! For Mars we transmit day_ini
486      CALL dynredem0("restart.nc", day_ini, phis)
487    else
488      CALL dynredem0("restart.nc", day_end, phis)
489    endif
490  else
491    CALL dynredem0("restart.nc", day_end, phis)
492  endif
493  ecripar = .TRUE.
494
495#ifdef CPP_IOIPSL
496  time_step = zdtvr
497  if (ok_dyn_ins) then
498    ! initialize output file for instantaneous outputs
499    ! t_ops = iecri * daysec ! do operations every t_ops
500    t_ops =((1.0*iecri)/day_step) * daysec 
501    t_wrt = daysec ! iecri * daysec ! write output every t_wrt
502    CALL inithist(day_ref,annee_ref,time_step,t_ops,t_wrt)
503  endif
504
505  IF (ok_dyn_ave) THEN
506    ! initialize output file for averaged outputs
507    t_ops = iperiod * time_step ! do operations every t_ops
508    t_wrt = periodav * daysec   ! write output every t_wrt
509    CALL initdynav(day_ref,annee_ref,time_step,t_ops,t_wrt)
510  END IF
511  dtav = iperiod*dtvr/daysec
512#endif
513! #endif of #ifdef CPP_IOIPSL
514
515  !  Choix des frequences de stokage pour le offline
516  !      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
517  !      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
518  istdyn=day_step/4     ! stockage toutes les 6h=1jour/12
519  istphy=istdyn/iphysiq     
520
521
522  !
523  !-----------------------------------------------------------------------
524  !   Integration temporelle du modele :
525  !   ----------------------------------
526
527  !       write(78,*) 'ucov',ucov
528  !       write(78,*) 'vcov',vcov
529  !       write(78,*) 'teta',teta
530  !       write(78,*) 'ps',ps
531  !       write(78,*) 'q',q
532
533
534  CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,time_0)
535
536END PROGRAM gcm
537
Note: See TracBrowser for help on using the repository browser.