source: LMDZ5/trunk/libf/dyn3dpar/gcm.F @ 1577

Last change on this file since 1577 was 1577, checked in by Laurent Fairhead, 13 years ago

Modifications au code qui permettent de commencer une simulation à n'importe
quelle heure de la journée. On fait toujours un nombre entier de jours de
simulation.
On spécifie cette heure de départ dans la variable starttime du run.def (la
valeur est en jour et elle est à zéro par défaut).
La valeur est sauvegardée dans le fichier restart.nc. Les valeurs lues dans
le fichier start et le run.def sont comparées en début de simulation. La
simulation s'arrête si elles ne sont pas égales sauf si une remise à zéro de
la date a été demandée.
Par ailleurs, la fréquence de lecture des conditions aux limites a été modifiée
pour qu'à chaque changement de jour, celles-ci soient mises à jour (jusqu'à
maintenant elles étaient mises à jour à une fréquence donnée qui, en cas de
départ de simulation à une heure différente de minuit, ne correspondait pas
forcèment à un changement dans la date).
Validation effectuée en traçant le flux solaire descendant au sommet de
l'atmosphère à différentes heures de la journée, après un redémarrage, en
s'assurant que le maximum est bien là où il est sensé être.


Modifications to the code to enable it to be started at any time of the day.
The code still runs for an integer number of days.
The start time is specified using variable starttime in the run.def file (the
value is in days and is zero by default).
The start time is saved in the restart.nc file at the end of the simulation.
The values read in from the start.nc file and the run.def file are compared
at the start of the simulation. If they differ, the simulation is aborted
unless the raz_date variable has been set.
Furthermore, the frequency at which boundary conditions are read in has been
modified so that they are updated everyday at midnight (until now, they were
updated at a certain frequency that, in case of a simulation starting at a time
other than midnight, did not ensure that those conditions would be updated each
day at midnight)
The modifications were validated by plotting the downward solaf flux at TOA at
different times of the day (and after having restarted the simulation) and
ensuring that the maximum of flux was at the right place according to local
time.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 17.1 KB
Line 
1!
2! $Id: gcm.F 1577 2011-10-20 15:06:47Z fairhead $
3!
4c
5c
6      PROGRAM gcm
7
8#ifdef CPP_IOIPSL
9      USE IOIPSL
10#endif
11
12      USE mod_const_mpi, ONLY: init_const_mpi
13      USE parallel
14      USE infotrac
15      USE mod_interface_dyn_phys
16      USE mod_hallo
17      USE Bands
18      USE getparam
19      USE filtreg_mod
20      USE control_mod
21
22! Ehouarn: for now these only apply to Earth:
23#ifdef CPP_EARTH
24      USE mod_grid_phy_lmdz
25      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
26      USE mod_phys_lmdz_omp_data, ONLY: klon_omp
27      USE dimphy
28      USE comgeomphy
29#endif
30      IMPLICIT NONE
31
32c      ......   Version  du 10/01/98    ..........
33
34c             avec  coordonnees  verticales hybrides
35c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
36
37c=======================================================================
38c
39c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
40c   -------
41c
42c   Objet:
43c   ------
44c
45c   GCM LMD nouvelle grille
46c
47c=======================================================================
48c
49c  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
50c      et possibilite d'appeler une fonction f(y)  a derivee tangente
51c      hyperbolique a la  place de la fonction a derivee sinusoidale.
52c  ... Possibilite de choisir le schema pour l'advection de
53c        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
54c
55c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
56c      Pour Van-Leer iadv=10
57c
58c-----------------------------------------------------------------------
59c   Declarations:
60c   -------------
61#include "dimensions.h"
62#include "paramet.h"
63#include "comconst.h"
64#include "comdissnew.h"
65#include "comvert.h"
66#include "comgeom.h"
67#include "logic.h"
68#include "temps.h"
69#include "ener.h"
70#include "description.h"
71#include "serre.h"
72!#include "com_io_dyn.h"
73#include "iniprint.h"
74#include "tracstoke.h"
75
76#ifdef INCA
77! Only INCA needs these informations (from the Earth's physics)
78#include "indicesol.h"
79#endif
80
81      INTEGER         longcles
82      PARAMETER     ( longcles = 20 )
83      REAL  clesphy0( longcles )
84      SAVE  clesphy0
85
86
87
88      REAL zdtvr
89c      INTEGER nbetatmoy, nbetatdem,nbetat
90      INTEGER nbetatmoy, nbetatdem
91
92c   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
97c      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
98c      REAL pks(ip1jmp1)                      ! exner au  sol
99c      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
100c      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
101      REAL masse(ip1jmp1,llm)                ! masse d'air
102      REAL phis(ip1jmp1)                     ! geopotentiel au sol
103c      REAL phi(ip1jmp1,llm)                  ! geopotentiel
104c      REAL w(ip1jmp1,llm)                    ! vitesse verticale
105
106c variables dynamiques intermediaire pour le transport
107
108c   variables pour le fichier histoire
109      REAL dtav      ! intervalle de temps elementaire
110
111      REAL time_0
112
113      LOGICAL lafin
114c      INTEGER ij,iq,l,i,j
115      INTEGER i,j
116
117
118      real time_step, t_wrt, t_ops
119
120
121      LOGICAL call_iniphys
122      data call_iniphys/.true./
123
124c      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm)
125c+jld variables test conservation energie
126c      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
127C     Tendance de la temp. potentiel d (theta)/ d t due a la
128C     tansformation d'energie cinetique en energie thermique
129C     cree par la dissipation
130c      REAL dhecdt(ip1jmp1,llm)
131c      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
132c      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
133c      CHARACTER (len=15) :: ztit
134c-jld
135
136
137      character (len=80) :: dynhist_file, dynhistave_file
138      character (len=20) :: modname
139      character (len=80) :: abort_message
140! locales pour gestion du temps
141      INTEGER :: an, mois, jour
142      REAL :: heure
143
144
145c-----------------------------------------------------------------------
146c    variables pour l'initialisation de la physique :
147c    ------------------------------------------------
148      INTEGER ngridmx
149      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
150      REAL zcufi(ngridmx),zcvfi(ngridmx)
151      REAL latfi(ngridmx),lonfi(ngridmx)
152      REAL airefi(ngridmx)
153      SAVE latfi, lonfi, airefi
154     
155      INTEGER :: ierr
156
157
158c-----------------------------------------------------------------------
159c   Initialisations:
160c   ----------------
161
162      abort_message = 'last timestep reached'
163      modname = 'gcm'
164      descript = 'Run GCM LMDZ'
165      lafin    = .FALSE.
166      dynhist_file = 'dyn_hist'
167      dynhistave_file = 'dyn_hist_ave'
168
169
170
171c----------------------------------------------------------------------
172c  lecture des fichiers gcm.def ou run.def
173c  ---------------------------------------
174c
175! Ehouarn: dump possibility of using defrun
176!#ifdef CPP_IOIPSL
177      CALL conf_gcm( 99, .TRUE. , clesphy0 )
178!#else
179!      CALL defrun( 99, .TRUE. , clesphy0 )
180!#endif
181c
182c
183c------------------------------------
184c   Initialisation partie parallele
185c------------------------------------
186      CALL init_const_mpi
187
188      call init_parallel
189      call ini_getparam("out.def")
190      call Read_Distrib
191! Ehouarn : temporarily (?) keep this only for Earth
192      if (planet_type.eq."earth") then
193#ifdef CPP_EARTH
194        CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
195#endif
196      endif ! of if (planet_type.eq."earth")
197      CALL set_bands
198#ifdef CPP_EARTH
199! Ehouarn: For now only Earth physics is parallel
200      CALL Init_interface_dyn_phys
201#endif
202      CALL barrier
203
204      if (mpi_rank==0) call WriteBands
205      call SetDistrib(jj_Nb_Caldyn)
206
207c$OMP PARALLEL
208      call Init_Mod_hallo
209c$OMP END PARALLEL
210
211! Ehouarn : temporarily (?) keep this only for Earth
212      if (planet_type.eq."earth") then
213#ifdef CPP_EARTH
214c$OMP PARALLEL
215      call InitComgeomphy
216c$OMP END PARALLEL
217#endif
218      endif ! of if (planet_type.eq."earth")
219
220c-----------------------------------------------------------------------
221c   Choix du calendrier
222c   -------------------
223
224c      calend = 'earth_365d'
225
226#ifdef CPP_IOIPSL
227      if (calend == 'earth_360d') then
228        call ioconf_calendar('360d')
229        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
230      else if (calend == 'earth_365d') then
231        call ioconf_calendar('noleap')
232        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
233      else if (calend == 'earth_366d') then
234        call ioconf_calendar('gregorian')
235        write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
236      else
237        abort_message = 'Mauvais choix de calendrier'
238        call abort_gcm(modname,abort_message,1)
239      endif
240#endif
241
242      IF (type_trac == 'inca') THEN
243#ifdef INCA
244         call init_const_lmdz(
245     $        nbtr,anneeref,dayref,
246     $        iphysiq,day_step,nday,
247     $        nbsrf, is_oce,is_sic,
248     $        is_ter,is_lic)
249
250         call init_inca_para(
251     $        iim,jjm+1,llm,klon_glo,mpi_size,
252     $        distrib_phys,COMM_LMDZ)
253#endif
254      END IF
255
256c-----------------------------------------------------------------------
257c   Initialisation des traceurs
258c   ---------------------------
259c  Choix du nombre de traceurs et du schema pour l'advection
260c  dans fichier traceur.def, par default ou via INCA
261      call infotrac_init
262
263c Allocation de la tableau q : champs advectes   
264      ALLOCATE(q(ip1jmp1,llm,nqtot))
265
266c-----------------------------------------------------------------------
267c   Lecture de l'etat initial :
268c   ---------------------------
269
270c  lecture du fichier start.nc
271      if (read_start) then
272      ! we still need to run iniacademic to initialize some
273      ! constants & fields, if we run the 'newtonian' or 'SW' cases:
274        if (iflag_phys.ne.1) then
275          CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
276        endif
277
278!        if (planet_type.eq."earth") then
279! Load an Earth-format start file
280         CALL dynetat0("start.nc",vcov,ucov,
281     &              teta,q,masse,ps,phis, time_0)
282!        endif ! of if (planet_type.eq."earth")
283
284c       write(73,*) 'ucov',ucov
285c       write(74,*) 'vcov',vcov
286c       write(75,*) 'teta',teta
287c       write(76,*) 'ps',ps
288c       write(77,*) 'q',q
289
290      endif ! of if (read_start)
291
292c le cas echeant, creation d un etat initial
293      IF (prt_level > 9) WRITE(lunout,*)
294     .              'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
295      if (.not.read_start) then
296         CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
297      endif
298
299c-----------------------------------------------------------------------
300c   Lecture des parametres de controle pour la simulation :
301c   -------------------------------------------------------
302c  on recalcule eventuellement le pas de temps
303
304      IF(MOD(day_step,iperiod).NE.0) THEN
305        abort_message =
306     .  'Il faut choisir un nb de pas par jour multiple de iperiod'
307        call abort_gcm(modname,abort_message,1)
308      ENDIF
309
310      IF(MOD(day_step,iphysiq).NE.0) THEN
311        abort_message =
312     * 'Il faut choisir un nb de pas par jour multiple de iphysiq'
313        call abort_gcm(modname,abort_message,1)
314      ENDIF
315
316      zdtvr    = daysec/REAL(day_step)
317        IF(dtvr.NE.zdtvr) THEN
318         WRITE(lunout,*)
319     .    'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
320        ENDIF
321
322C
323C on remet le calendrier à zero si demande
324c
325      IF (start_time /= starttime) then
326        WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le'
327     &,' fichier restart ne correspond pas à celle lue dans le run.def'
328        IF (raz_date == 1) then
329          WRITE(lunout,*)'Je prends l''heure lue dans run.def'
330          start_time = starttime
331        ELSE
332          WRITE(lunout,*)'Je m''arrete'
333          CALL abort
334        ENDIF
335      ENDIF
336      IF (raz_date == 1) THEN
337        annee_ref = anneeref
338        day_ref = dayref
339        day_ini = dayref
340        itau_dyn = 0
341        itau_phy = 0
342        time_0 = 0.
343        write(lunout,*)
344     .   'GCM: On reinitialise a la date lue dans gcm.def'
345      ELSE IF (annee_ref .ne. anneeref .or. day_ref .ne. dayref) THEN
346        write(lunout,*)
347     .  'GCM: Attention les dates initiales lues dans le fichier'
348        write(lunout,*)
349     .  ' restart ne correspondent pas a celles lues dans '
350        write(lunout,*)' gcm.def'
351        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
352        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
353        write(lunout,*)' Pas de remise a zero'
354      ENDIF
355c      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
356c        write(lunout,*)
357c     .  'GCM: Attention les dates initiales lues dans le fichier'
358c        write(lunout,*)
359c     .  ' restart ne correspondent pas a celles lues dans '
360c        write(lunout,*)' gcm.def'
361c        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
362c        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
363c        if (raz_date .ne. 1) then
364c          write(lunout,*)
365c     .    'GCM: On garde les dates du fichier restart'
366c        else
367c          annee_ref = anneeref
368c          day_ref = dayref
369c          day_ini = dayref
370c          itau_dyn = 0
371c          itau_phy = 0
372c          time_0 = 0.
373c          write(lunout,*)
374c     .   'GCM: On reinitialise a la date lue dans gcm.def'
375c        endif
376c      ELSE
377c        raz_date = 0
378c      endif
379
380#ifdef CPP_IOIPSL
381      mois = 1
382      heure = 0.
383      call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
384      jH_ref = jD_ref - int(jD_ref)
385      jD_ref = int(jD_ref)
386
387      call ioconf_startdate(INT(jD_ref), jH_ref)
388
389      write(lunout,*)'DEBUG'
390      write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
391      write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
392      call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure)
393      write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
394      write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
395#else
396! Ehouarn: we still need to define JD_ref and JH_ref
397! and since we don't know how many days there are in a year
398! we set JD_ref to 0 (this should be improved ...)
399      jD_ref=0
400      jH_ref=0
401#endif
402
403c  nombre d'etats dans les fichiers demarrage et histoire
404      nbetatdem = nday / iecri
405      nbetatmoy = nday / periodav + 1
406
407      if (iflag_phys.eq.1) then
408      ! these initialisations have already been done (via iniacademic)
409      ! if running in SW or Newtonian mode
410c-----------------------------------------------------------------------
411c   Initialisation des constantes dynamiques :
412c   ------------------------------------------
413        dtvr = zdtvr
414        CALL iniconst
415
416c-----------------------------------------------------------------------
417c   Initialisation de la geometrie :
418c   --------------------------------
419        CALL inigeom
420
421c-----------------------------------------------------------------------
422c   Initialisation du filtre :
423c   --------------------------
424        CALL inifilr
425      endif ! of if (iflag_phys.eq.1)
426c
427c-----------------------------------------------------------------------
428c   Initialisation de la dissipation :
429c   ----------------------------------
430
431      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
432     *                tetagdiv, tetagrot , tetatemp              )
433
434c-----------------------------------------------------------------------
435c   Initialisation de la physique :
436c   -------------------------------
437      IF (call_iniphys.and.iflag_phys.eq.1) THEN
438         latfi(1)=rlatu(1)
439         lonfi(1)=0.
440         zcufi(1) = cu(1)
441         zcvfi(1) = cv(1)
442         DO j=2,jjm
443            DO i=1,iim
444               latfi((j-2)*iim+1+i)= rlatu(j)
445               lonfi((j-2)*iim+1+i)= rlonv(i)
446               zcufi((j-2)*iim+1+i) = cu((j-1)*iip1+i)
447               zcvfi((j-2)*iim+1+i) = cv((j-1)*iip1+i)
448            ENDDO
449         ENDDO
450         latfi(ngridmx)= rlatu(jjp1)
451         lonfi(ngridmx)= 0.
452         zcufi(ngridmx) = cu(ip1jm+1)
453         zcvfi(ngridmx) = cv(ip1jm-iim)
454         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
455
456         WRITE(lunout,*)
457     .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
458! Earth:
459         if (planet_type.eq."earth") then
460#ifdef CPP_EARTH
461         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys ,
462     ,                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp     )
463#endif
464         endif ! of if (planet_type.eq."earth")
465         call_iniphys=.false.
466      ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1))
467
468
469c-----------------------------------------------------------------------
470c   Initialisation des dimensions d'INCA :
471c   --------------------------------------
472      IF (type_trac == 'inca') THEN
473!$OMP PARALLEL
474#ifdef INCA
475         CALL init_inca_dim(klon_omp,llm,iim,jjm,
476     $        rlonu,rlatu,rlonv,rlatv)
477#endif
478!$OMP END PARALLEL
479      END IF
480
481c-----------------------------------------------------------------------
482c   Initialisation des I/O :
483c   ------------------------
484
485
486      day_end = day_ini + nday
487      WRITE(lunout,300)day_ini,day_end
488 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
489
490#ifdef CPP_IOIPSL
491      call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
492      write (lunout,301)jour, mois, an
493      call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
494      write (lunout,302)jour, mois, an
495 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
496 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
497#endif
498
499!      if (planet_type.eq."earth") then
500! Write an Earth-format restart file
501        CALL dynredem0_p("restart.nc", day_end, phis)
502!      endif
503
504      ecripar = .TRUE.
505
506#ifdef CPP_IOIPSL
507      time_step = zdtvr
508      IF (mpi_rank==0) then
509        if (ok_dyn_ins) then
510          ! initialize output file for instantaneous outputs
511          ! t_ops = iecri * daysec ! do operations every t_ops
512          t_ops =((1.0*iecri)/day_step) * daysec 
513          t_wrt = daysec ! iecri * daysec ! write output every t_wrt
514          t_wrt = daysec ! iecri * daysec ! write output every t_wrt
515          CALL inithist(day_ref,annee_ref,time_step,
516     &                  t_ops,t_wrt)
517        endif
518
519        IF (ok_dyn_ave) THEN
520          ! initialize output file for averaged outputs
521          t_ops = iperiod * time_step ! do operations every t_ops
522          t_wrt = periodav * daysec   ! write output every t_wrt
523          CALL initdynav(day_ref,annee_ref,time_step,
524     &                   t_ops,t_wrt)
525!         CALL initdynav_p(dynhistave_file,day_ref,annee_ref,time_step,
526!     .        t_ops, t_wrt, histaveid)
527        END IF
528      ENDIF
529      dtav = iperiod*dtvr/daysec
530#endif
531! #endif of #ifdef CPP_IOIPSL
532
533c  Choix des frequences de stokage pour le offline
534c      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
535c      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
536      istdyn=day_step/4     ! stockage toutes les 6h=1jour/12
537      istphy=istdyn/iphysiq     
538
539
540c
541c-----------------------------------------------------------------------
542c   Integration temporelle du modele :
543c   ----------------------------------
544
545c       write(78,*) 'ucov',ucov
546c       write(78,*) 'vcov',vcov
547c       write(78,*) 'teta',teta
548c       write(78,*) 'ps',ps
549c       write(78,*) 'q',q
550
551c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
552      CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
553     .              time_0)
554c$OMP END PARALLEL
555
556
557      END
558
Note: See TracBrowser for help on using the repository browser.