LMDZ
gcm.F
Go to the documentation of this file.
1 !
2 ! $Id: gcm.F 2351 2015-08-25 15:14:59Z emillour $
3 !
4 c
5 c
6  PROGRAM gcm
7 
8 #ifdef CPP_IOIPSL
9  USE ioipsl
10 #endif
11 
12 
13  USE mod_const_mpi, ONLY: init_const_mpi
14  USE parallel_lmdz
15  USE infotrac
16 !#ifdef CPP_PHYS
17 ! USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
18 !#endif
19  USE mod_hallo
20  USE bands
21  USE getparam
22  USE filtreg_mod
23  USE control_mod
24 
25 #ifdef INCA
26 ! Only INCA needs these informations (from the Earth's physics)
27  USE indice_sol_mod
29 #endif
30 
31 #ifdef CPP_PHYS
32  USE iniphysiq_mod, ONLY: iniphysiq
33 #endif
34  IMPLICIT NONE
35 
36 c ...... Version du 10/01/98 ..........
37 
38 c avec coordonnees verticales hybrides
39 c avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
40 
41 c=======================================================================
42 c
43 c Auteur: P. Le Van /L. Fairhead/F.Hourdin
44 c -------
45 c
46 c Objet:
47 c ------
48 c
49 c GCM LMD nouvelle grille
50 c
51 c=======================================================================
52 c
53 c ... Dans inigeom , nouveaux calculs pour les elongations cu , cv
54 c et possibilite d'appeler une fonction f(y) a derivee tangente
55 c hyperbolique a la place de la fonction a derivee sinusoidale.
56 c ... Possibilite de choisir le schema pour l'advection de
57 c q , en modifiant iadv dans traceur.def (MAF,10/02) .
58 c
59 c Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
60 c Pour Van-Leer iadv=10
61 c
62 c-----------------------------------------------------------------------
63 c Declarations:
64 c -------------
65 #include "dimensions.h"
66 #include "paramet.h"
67 #include "comconst.h"
68 #include "comdissnew.h"
69 #include "comvert.h"
70 #include "comgeom.h"
71 #include "logic.h"
72 #include "temps.h"
73 #include "ener.h"
74 #include "description.h"
75 #include "serre.h"
76 !#include "com_io_dyn.h"
77 #include "iniprint.h"
78 #include "tracstoke.h"
79 
80 #ifdef INCA
81 ! Only INCA needs these informations (from the Earth's physics)
82 !#include "indicesol.h"
83 #endif
84 
85  REAL zdtvr
86 
87 c variables dynamiques
88  REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
89  REAL teta(ip1jmp1,llm) ! temperature potentielle
90  REAL, ALLOCATABLE, DIMENSION(:,:,:) :: q ! champs advectes
91  REAL ps(ip1jmp1) ! pression au sol
92 c REAL p (ip1jmp1,llmp1 ) ! pression aux interfac.des couches
93  REAL masse(ip1jmp1,llm) ! masse d'air
94  REAL phis(ip1jmp1) ! geopotentiel au sol
95 c REAL phi(ip1jmp1,llm) ! geopotentiel
96 c REAL w(ip1jmp1,llm) ! vitesse verticale
97 
98 c variables dynamiques intermediaire pour le transport
99 
100 c variables pour le fichier histoire
101  REAL dtav ! intervalle de temps elementaire
102 
103  REAL time_0
104 
105  LOGICAL lafin
106 
107  real time_step, t_wrt, t_ops
108 
109 
110 c+jld variables test conservation energie
111 c REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
112 C Tendance de la temp. potentiel d (theta)/ d t due a la
113 C tansformation d'energie cinetique en energie thermique
114 C cree par la dissipation
115 c REAL dhecdt(ip1jmp1,llm)
116 c REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
117 c REAL d_h_vcol, d_qt, d_qw, d_ql, d_ec
118 c CHARACTER (len=15) :: ztit
119 c-jld
120 
121 
122  character (len=80) :: dynhist_file, dynhistave_file
123  character (len=20) :: modname
124  character (len=80) :: abort_message
125 ! locales pour gestion du temps
126  INTEGER :: an, mois, jour
127  REAL :: heure
128 
129 
130 c-----------------------------------------------------------------------
131 c Initialisations:
132 c ----------------
133 
134  abort_message = 'last timestep reached'
135  modname = 'gcm'
136  descript = 'Run GCM LMDZ'
137  lafin = .false.
138  dynhist_file = 'dyn_hist'
139  dynhistave_file = 'dyn_hist_ave'
140 
141 
142 
143 c----------------------------------------------------------------------
144 c lecture des fichiers gcm.def ou run.def
145 c ---------------------------------------
146 c
147  CALL conf_gcm( 99, .true. )
148  if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
149  s "iphysiq must be a multiple of iperiod", 1)
150 c
151 c
152 c------------------------------------
153 c Initialisation partie parallele
154 c------------------------------------
155 
156  CALL init_const_mpi
157  call init_parallel
158  call ini_getparam("out.def")
159  call read_distrib
160 
161 !#ifdef CPP_PHYS
162 ! CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
163 !#endif
164 ! CALL set_bands
165 !#ifdef CPP_PHYS
166 ! CALL Init_interface_dyn_phys
167 !#endif
168  CALL barrier
169 
170  CALL set_bands
171  if (mpi_rank==0) call writebands
173 
174 c$OMP PARALLEL
175  call init_mod_hallo
176 c$OMP END PARALLEL
177 
178 !#ifdef CPP_PHYS
179 !c$OMP PARALLEL
180 ! call InitComgeomphy ! now done in iniphysiq
181 !c$OMP END PARALLEL
182 !#endif
183 
184 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
185 ! Initialisation de XIOS
186 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
187 
188 
189 c-----------------------------------------------------------------------
190 c Choix du calendrier
191 c -------------------
192 
193 c calend = 'earth_365d'
194 
195 #ifdef CPP_IOIPSL
196  if (calend == 'earth_360d') then
197  call ioconf_calendar('360d')
198  write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
199  else if (calend == 'earth_365d') then
200  call ioconf_calendar('noleap')
201  write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
202  else if (calend == 'earth_366d') then
203  call ioconf_calendar('gregorian')
204  write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
205  else
206  abort_message = 'Mauvais choix de calendrier'
207  call abort_gcm(modname,abort_message,1)
208  endif
209 #endif
210 
211  IF (type_trac == 'inca') THEN
212 #ifdef INCA
213  call init_const_lmdz(
214  $ nbtr,anneeref,dayref,
215  $ iphysiq,day_step,nday,
216  $ nbsrf, is_oce,is_sic,
217  $ is_ter,is_lic, calend)
218 
219  call init_inca_para(
220  $ iim,jjm+1,llm,klon_glo,mpi_size,
221  $ distrib_phys,comm_lmdz)
222 #endif
223  END IF
224 
225 c-----------------------------------------------------------------------
226 c Initialisation des traceurs
227 c ---------------------------
228 c Choix du nombre de traceurs et du schema pour l'advection
229 c dans fichier traceur.def, par default ou via INCA
230  call infotrac_init
231 
232 c Allocation de la tableau q : champs advectes
233  ALLOCATE(q(ip1jmp1,llm,nqtot))
234 
235 c-----------------------------------------------------------------------
236 c Lecture de l'etat initial :
237 c ---------------------------
238 
239 c lecture du fichier start.nc
240  if (read_start) then
241  ! we still need to run iniacademic to initialize some
242  ! constants & fields, if we run the 'newtonian' or 'SW' cases:
243  if (iflag_phys.ne.1) then
244  CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
245  endif
246 
247 ! if (planet_type.eq."earth") then
248 ! Load an Earth-format start file
249  CALL dynetat0("start.nc",vcov,ucov,
250  & teta,q,masse,ps,phis, time_0)
251 ! endif ! of if (planet_type.eq."earth")
252 
253 c write(73,*) 'ucov',ucov
254 c write(74,*) 'vcov',vcov
255 c write(75,*) 'teta',teta
256 c write(76,*) 'ps',ps
257 c write(77,*) 'q',q
258 
259  endif ! of if (read_start)
260 
261 c le cas echeant, creation d un etat initial
262  IF (prt_level > 9) WRITE(lunout,*)
263  . 'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
264  if (.not.read_start) then
265  CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
266  endif
267 
268 c-----------------------------------------------------------------------
269 c Lecture des parametres de controle pour la simulation :
270 c -------------------------------------------------------
271 c on recalcule eventuellement le pas de temps
272 
273  IF(mod(day_step,iperiod).NE.0) THEN
274  abort_message =
275  . 'Il faut choisir un nb de pas par jour multiple de iperiod'
276  call abort_gcm(modname,abort_message,1)
277  ENDIF
278 
279  IF(mod(day_step,iphysiq).NE.0) THEN
280  abort_message =
281  * 'Il faut choisir un nb de pas par jour multiple de iphysiq'
282  call abort_gcm(modname,abort_message,1)
283  ENDIF
284 
285  zdtvr = daysec/REAL(day_step)
286  IF(dtvr.NE.zdtvr) THEN
287  WRITE(lunout,*)
288  . 'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
289  ENDIF
290 
291 C
292 C on remet le calendrier à zero si demande
293 c
294  IF (start_time /= starttime) then
295  WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le'
296  &,' fichier restart ne correspond pas à celle lue dans le run.def'
297  IF (raz_date == 1) then
298  WRITE(lunout,*)'Je prends l''heure lue dans run.def'
300  ELSE
301  call abort_gcm("gcm", "'Je m''arrete'", 1)
302  ENDIF
303  ENDIF
304  IF (raz_date == 1) THEN
306  day_ref = dayref
307  day_ini = dayref
308  itau_dyn = 0
309  itau_phy = 0
310  time_0 = 0.
311  write(lunout,*)
312  . 'GCM: On reinitialise a la date lue dans gcm.def'
313  ELSE IF (annee_ref .ne. anneeref .or. day_ref .ne. dayref) THEN
314  write(lunout,*)
315  . 'GCM: Attention les dates initiales lues dans le fichier'
316  write(lunout,*)
317  . ' restart ne correspondent pas a celles lues dans '
318  write(lunout,*)' gcm.def'
319  write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
320  write(lunout,*)' day_ref=',day_ref," dayref=",dayref
321  write(lunout,*)' Pas de remise a zero'
322  ENDIF
323 c if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
324 c write(lunout,*)
325 c . 'GCM: Attention les dates initiales lues dans le fichier'
326 c write(lunout,*)
327 c . ' restart ne correspondent pas a celles lues dans '
328 c write(lunout,*)' gcm.def'
329 c write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
330 c write(lunout,*)' day_ref=',day_ref," dayref=",dayref
331 c if (raz_date .ne. 1) then
332 c write(lunout,*)
333 c . 'GCM: On garde les dates du fichier restart'
334 c else
335 c annee_ref = anneeref
336 c day_ref = dayref
337 c day_ini = dayref
338 c itau_dyn = 0
339 c itau_phy = 0
340 c time_0 = 0.
341 c write(lunout,*)
342 c . 'GCM: On reinitialise a la date lue dans gcm.def'
343 c endif
344 c ELSE
345 c raz_date = 0
346 c endif
347 
348 #ifdef CPP_IOIPSL
349  mois = 1
350  heure = 0.
351  call ymds2ju(annee_ref, mois, day_ref, heure, jd_ref)
352  jh_ref = jd_ref - int(jd_ref)
353  jd_ref = int(jd_ref)
354 
355  call ioconf_startdate(int(jd_ref), jh_ref)
356 
357  write(lunout,*)'DEBUG'
358  write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
359  write(lunout,*)annee_ref, mois, day_ref, heure, jd_ref
360  call ju2ymds(jd_ref+jh_ref,an, mois, jour, heure)
361  write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
362  write(lunout,*)jd_ref+jh_ref,an, mois, jour, heure
363 #else
364 ! Ehouarn: we still need to define JD_ref and JH_ref
365 ! and since we don't know how many days there are in a year
366 ! we set JD_ref to 0 (this should be improved ...)
367  jd_ref=0
368  jh_ref=0
369 #endif
370 
371 
372  if (iflag_phys.eq.1) then
373  ! these initialisations have already been done (via iniacademic)
374  ! if running in SW or Newtonian mode
375 c-----------------------------------------------------------------------
376 c Initialisation des constantes dynamiques :
377 c ------------------------------------------
378  dtvr = zdtvr
379  CALL iniconst
380 
381 c-----------------------------------------------------------------------
382 c Initialisation de la geometrie :
383 c --------------------------------
384  CALL inigeom
385 
386 c-----------------------------------------------------------------------
387 c Initialisation du filtre :
388 c --------------------------
389  CALL inifilr
390  endif ! of if (iflag_phys.eq.1)
391 c
392 c-----------------------------------------------------------------------
393 c Initialisation de la dissipation :
394 c ----------------------------------
395 
396  CALL inidissip( lstardis, nitergdiv, nitergrot, niterh ,
397  * tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
398 
399 c-----------------------------------------------------------------------
400 c Initialisation de la physique :
401 c -------------------------------
402  IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
403 ! Physics:
404 #ifdef CPP_PHYS
405  CALL iniphysiq(iim,jjm,llm,
406  & distrib_phys(mpi_rank),comm_lmdz,
409  & iflag_phys)
410 #endif
411  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
412 
413 
414 c-----------------------------------------------------------------------
415 c Initialisation des dimensions d'INCA :
416 c --------------------------------------
417  IF (type_trac == 'inca') THEN
418 !$OMP PARALLEL
419 #ifdef INCA
420  CALL init_inca_dim(klon_omp,llm,iim,jjm,
422 #endif
423 !$OMP END PARALLEL
424  END IF
425 
426 c-----------------------------------------------------------------------
427 c Initialisation des I/O :
428 c ------------------------
429 
430 
431  if (nday>=0) then
432  day_end = day_ini + nday
433  else
435  endif
436 
437  WRITE(lunout,300)day_ini,day_end
438  300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
439 
440 #ifdef CPP_IOIPSL
441  call ju2ymds(jd_ref + day_ini - day_ref, an, mois, jour, heure)
442  write (lunout,301)jour, mois, an
443  call ju2ymds(jd_ref + day_end - day_ref, an, mois, jour, heure)
444  write (lunout,302)jour, mois, an
445  301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
446  302 FORMAT('1'/,15x,' au ', i2,'/',i2,'/',i4)
447 #endif
448 
449 ! if (planet_type.eq."earth") then
450 ! Write an Earth-format restart file
451  CALL dynredem0_p("restart.nc", day_end, phis)
452 ! endif
453 
454  ecripar = .true.
455 
456 #ifdef CPP_IOIPSL
457  time_step = zdtvr
458  IF (mpi_rank==0) then
459  if (ok_dyn_ins) then
460  ! initialize output file for instantaneous outputs
461  ! t_ops = iecri * daysec ! do operations every t_ops
462  t_ops =((1.0*iecri)/day_step) * daysec
463  t_wrt = daysec ! iecri * daysec ! write output every t_wrt
464  t_wrt = daysec ! iecri * daysec ! write output every t_wrt
465  CALL inithist(day_ref,annee_ref,time_step,
466  & t_ops,t_wrt)
467  endif
468 
469  IF (ok_dyn_ave) THEN
470  ! initialize output file for averaged outputs
471  t_ops = iperiod * time_step ! do operations every t_ops
472  t_wrt = periodav * daysec ! write output every t_wrt
473  CALL initdynav(day_ref,annee_ref,time_step,
474  & t_ops,t_wrt)
475 ! CALL initdynav_p(dynhistave_file,day_ref,annee_ref,time_step,
476 ! . t_ops, t_wrt, histaveid)
477  END IF
478  ENDIF
479  dtav = iperiod*dtvr/daysec
480 #endif
481 ! #endif of #ifdef CPP_IOIPSL
482 
483 c Choix des frequences de stokage pour le offline
484 c istdyn=day_step/4 ! stockage toutes les 6h=1jour/4
485 c istdyn=day_step/12 ! stockage toutes les 2h=1jour/12
486  istdyn=day_step/4 ! stockage toutes les 6h=1jour/12
488 
489 
490 c
491 c-----------------------------------------------------------------------
492 c Integration temporelle du modele :
493 c ----------------------------------
494 
495 c write(78,*) 'ucov',ucov
496 c write(78,*) 'vcov',vcov
497 c write(78,*) 'teta',teta
498 c write(78,*) 'ps',ps
499 c write(78,*) 'q',q
500 
501 c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
502  CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,time_0)
503 c$OMP END PARALLEL
504 
505 
506  END
507 
subroutine barrier
Definition: bands.F90:4
!$Id tetagdiv
Definition: comdissnew.h:13
!$Id && itau_dyn
Definition: temps.h:15
integer, dimension(:), allocatable distrib_phys
Definition: bands.F90:24
!$Id day_end
Definition: temps.h:15
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
subroutine dynredem0_p(fichnom, iday_end, phis)
Definition: dynredem_p.F:6
subroutine iniphysiq(iim, jjm, nlayer, nbp, communicator, punjours, pdayref, ptimestep, rlatu, rlatv, rlonu, rlonv, aire, cu, cv, prad, pg, pr, pcpp, iflag_phys)
integer, parameter is_ter
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL ymds2ju(annee_ref, 1, day_ref, hour, zjulian)!jyg CALL histbeg_phy("histrac"
!$Id mode_top_bound COMMON comconstr r
Definition: comconst.h:7
integer, dimension(:), allocatable jj_nb_caldyn
Definition: bands.F90:10
subroutine dynetat0(fichnom, vcov, ucov, teta, q, masse, ps, phis, time)
Definition: dynetat0.f90:2
!$Id mode_top_bound COMMON comconstr g
Definition: comconst.h:7
!$Id ysinus read_start
Definition: logic.h:10
logical, save ok_dyn_ins
Definition: control_mod.F90:36
!$Header!common tracstoke istphy
Definition: tracstoke.h:4
integer, save mpi_rank
integer, save dayref
Definition: control_mod.F90:26
subroutine writebands
Definition: bands.F90:438
integer, save mpi_size
!$Id nitergdiv
Definition: comdissnew.h:13
subroutine abort_gcm(modname, message, ierr)
Definition: abort_gcm.F:7
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
subroutine inifilr
Definition: filtreg_mod.F90:12
!$Header!CDK comgeom COMMON comgeom aire
Definition: comgeom.h:25
subroutine ini_getparam(fichier)
Definition: getparam.F90:21
!$Header!CDK comgeom COMMON comgeom rlatu
Definition: comgeom.h:25
!$Id ysinus ok_gradsfile hybrid COMMON logici iflag_phys
Definition: logic.h:10
integer, save day_step
Definition: control_mod.F90:15
subroutine leapfrog_p(ucov, vcov, teta, ps, masse, phis, q, time_0)
Definition: leapfrog_p.F:8
integer, save iphysiq
Definition: control_mod.F90:24
!$Id itau_phy
Definition: temps.h:15
integer, save nqtot
Definition: infotrac.F90:6
subroutine init_mod_hallo
Definition: mod_hallo.F90:66
subroutine init_const_mpi
!$Id nitergrot
Definition: comdissnew.h:13
subroutine inigeom
Definition: inigeom.F:7
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
!$Id && day_ini
Definition: temps.h:15
!$Id mode_top_bound COMMON comconstr dtphys
Definition: comconst.h:7
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
!$Id ecripar
Definition: logic.h:10
!$Id mode_top_bound COMMON comconstr rad
Definition: comconst.h:7
!$Id day_ref
Definition: temps.h:15
!$Id mode_top_bound COMMON comconstr cpp
Definition: comconst.h:7
integer, parameter is_lic
program gcm
Definition: gcm.F90:6
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
integer, save raz_date
Definition: control_mod.F90:28
!$Id mode_top_bound COMMON comconstr daysec
Definition: comconst.h:7
subroutine conf_gcm(tapedef, etatinit)
Definition: conf_gcm.F90:5
!$Header!CDK comgeom COMMON comgeom rlonu
Definition: comgeom.h:25
real, save periodav
Definition: control_mod.F90:12
!$Header!CDK comgeom COMMON comgeom rlatv
Definition: comgeom.h:25
subroutine inithist(day0, anne0, tstep, t_ops, t_wrt)
Definition: inithist.F:5
!$Header!c c INCLUDE fxyprim h c c c Fonctions in line c c REAL fyprim REAL rj c c il faut la calculer avant d appeler ces fonctions c c c Fonctions a changer selon x(x) et y(y) choisis.c-----------------------------------------------------------------c c.....ici
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
character(len=4), save type_trac
Definition: infotrac.F90:40
!$Id!Parameters for parameters that control the rate of approach!to quasi equilibrium noff nlm real tlcrit real entp real sigd real coeffs real dtmax real cu real betad real damp real delta COMMON cvparam nlm tlcrit sigd coeffs cu
Definition: cvparam.h:12
integer, save anneeref
Definition: control_mod.F90:27
!$Id && tetagrot
Definition: comdissnew.h:13
integer, parameter nbsrf
subroutine setdistrib(jj_Nb_New)
subroutine set_bands
Definition: bands.F90:106
!$Id mode_top_bound COMMON comconstr dtvr
Definition: comconst.h:7
integer, save iecri
Definition: control_mod.F90:21
logical, save ok_dyn_ave
Definition: control_mod.F90:38
integer, save nsplit_phys
Definition: control_mod.F90:19
subroutine init_parallel
!$Header!INCLUDE comdissip h COMMON comdissip tetatemp
Definition: comdissip.h:8
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
integer, save iperiod
Definition: control_mod.F90:16
integer, save nbtr
Definition: infotrac.F90:12
subroutine iniacademic(vcov, ucov, teta, q, masse, ps, phis, time_0)
Definition: iniacademic.F90:5
subroutine inidissip(lstardis, nitergdiv, nitergrot, niterh, tetagdiv, tetagrot, tetatemp, vert_prof_dissip)
Definition: inidissip.F90:6
!$Header!common tracstoke istdyn
Definition: tracstoke.h:4
integer, parameter is_sic
subroutine read_distrib
Definition: bands.F90:43
subroutine infotrac_init
Definition: infotrac.F90:61
integer, save nday
Definition: control_mod.F90:14
!$Header!CDK comgeom COMMON comgeom cv
Definition: comgeom.h:25
!$Id start_time
Definition: temps.h:15
!$Id niterh
Definition: comdissnew.h:13
integer, parameter is_oce
subroutine initdynav(day0, anne0, tstep, t_ops, t_wrt)
Definition: initdynav.F90:4
subroutine iniconst
Definition: iniconst.F90:5
!$Id annee_ref
Definition: temps.h:15
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7
!$Header!CDK comgeom COMMON comgeom rlonv
Definition: comgeom.h:25
real, save starttime
Definition: control_mod.F90:13