source: LMDZ6/trunk/libf/dyn3d/gcm.f90 @ 5401

Last change on this file since 5401 was 5310, checked in by abarral, 6 weeks ago

unify abort_gcm
rename wxios -> wxios_mod

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