source: LMDZ4/branches/LMDZ4-dev/libf/dyn3d/gcm.F @ 1226

Last change on this file since 1226 was 1222, checked in by Ehouarn Millour, 15 years ago

Changes and cleanups to enable compiling without physics
and without ioipsl.

IOIPSL related cleanups:

  • bibio/writehist.F encapsulate the routine (which needs IOIPSL to function)

with #ifdef IOIPSL flag.

  • dyn3d/abort_gcm.F, dyn3dpar/abort_gcm.F and dyn3dpar/getparam.F90: use ioipsl_getincom module when not compiling with IOIPSL library, in order to always be able to use getin() routine.
  • removed unused "use IOIPSL" in dyn3dpar/guide_p_mod.F90
  • calendar related issue: Initialize day_ref and annee_ref in iniacademic.F (i.e. when they are not read from start.nc file)

Earth-specific programs/routines/modules:
create_etat0.F, fluxstokenc.F, limit_netcdf.F, startvar.F
(versions in dyn3d and dyn3dpar)
These routines and modules, which by design and porpose are made to function with
Earth physics are encapsulated with #CPP_EARTH cpp flag.

Earth-specific instructions:

  • calls to qminimum (specific treatment of first 2 tracers, i.e. water) in dyn3d/caladvtrac.F, dyn3d/integrd.F, dyn3dpar/caladvtrac_p.F, dyn3dpar/integrd_p.F only if (planet_type == 'earth')

Interaction with parallel physics:

  • routine dyn3dpar/parallel.F90 uses "surface_data" module (which is in the physics ...) to know value of "type_ocean" . Encapsulated that with #ifdef CPP_EARTH and set to a default type_ocean="dummy" otherwise.
  • So far, only Earth physics are parallelized, so all the interaction between parallel dynamics and parallel physics are encapsulated with #ifdef CCP_EARTH (this way we can run parallel without any physics). The (dyn3dpar) routines which contains such interaction are: bands.F90, gr_dyn_fi_p.F, gr_fi_dyn_p.F, mod_interface_dyn_phys.F90 This should later (when improving dyn/phys interface) be encapsulated with a more general and appropriate #ifdef CPP_PHYS cpp flag.

I checked that these changes do not alter results (on the simple
32x24x11 bench) on Ciclad (seq & mpi), Brodie (seq, mpi & omp) and
Vargas (seq, mpi & omp).

EM

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 14.7 KB
Line 
1!
2! $Id: gcm.F 1222 2009-08-07 11:48:33Z jghattas $
3!
4c
5c
6      PROGRAM 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      USE filtreg_mod
16      USE infotrac
17
18!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
19! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
20! A nettoyer. On ne veut qu'une ou deux routines d'interface
21! dynamique -> physique pour l'initialisation
22! Ehouarn: for now these only apply to Earth:
23#ifdef CPP_EARTH
24      USE dimphy
25      USE comgeomphy
26      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
27#endif
28!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
29
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
62#include "dimensions.h"
63#include "paramet.h"
64#include "comconst.h"
65#include "comdissnew.h"
66#include "comvert.h"
67#include "comgeom.h"
68#include "logic.h"
69#include "temps.h"
70#include "control.h"
71#include "ener.h"
72#include "description.h"
73#include "serre.h"
74#include "com_io_dyn.h"
75#include "iniprint.h"
76#include "tracstoke.h"
77
78      INTEGER         longcles
79      PARAMETER     ( longcles = 20 )
80      REAL  clesphy0( longcles )
81      SAVE  clesphy0
82
83
84
85      REAL zdtvr
86      INTEGER nbetatmoy, nbetatdem,nbetat
87
88c   variables dynamiques
89      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
90      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
91      REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
92      REAL ps(ip1jmp1)                       ! pression  au sol
93      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
94      REAL pks(ip1jmp1)                      ! exner au  sol
95      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
96      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
97      REAL masse(ip1jmp1,llm)                ! masse d'air
98      REAL phis(ip1jmp1)                     ! geopotentiel au sol
99      REAL phi(ip1jmp1,llm)                  ! geopotentiel
100      REAL w(ip1jmp1,llm)                    ! vitesse verticale
101
102c variables dynamiques intermediaire pour le transport
103
104c   variables pour le fichier histoire
105      REAL dtav      ! intervalle de temps elementaire
106
107      REAL time_0
108
109      LOGICAL lafin
110      INTEGER ij,iq,l,i,j
111
112
113      real time_step, t_wrt, t_ops
114
115      LOGICAL first
116
117      LOGICAL call_iniphys
118      data call_iniphys/.true./
119
120      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm)
121c+jld variables test conservation energie
122c      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
123C     Tendance de la temp. potentiel d (theta)/ d t due a la
124C     tansformation d'energie cinetique en energie thermique
125C     cree par la dissipation
126      REAL dhecdt(ip1jmp1,llm)
127c      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
128c      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
129      CHARACTER (len=15) :: ztit
130c-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
140
141c-----------------------------------------------------------------------
142c    variables pour l'initialisation de la physique :
143c    ------------------------------------------------
144      INTEGER ngridmx
145      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
146      REAL zcufi(ngridmx),zcvfi(ngridmx)
147      REAL latfi(ngridmx),lonfi(ngridmx)
148      REAL airefi(ngridmx)
149      SAVE latfi, lonfi, airefi
150
151c-----------------------------------------------------------------------
152c   Initialisations:
153c   ----------------
154
155      abort_message = 'last timestep reached'
156      modname = 'gcm'
157      descript = 'Run GCM LMDZ'
158      lafin    = .FALSE.
159      dynhist_file = 'dyn_hist.nc'
160      dynhistave_file = 'dyn_hist_ave.nc'
161
162
163
164c----------------------------------------------------------------------
165c  lecture des fichiers gcm.def ou run.def
166c  ---------------------------------------
167c
168! Ehouarn: dump possibility of using defrun
169!#ifdef CPP_IOIPSL
170      CALL conf_gcm( 99, .TRUE. , clesphy0 )
171!#else
172!      CALL defrun( 99, .TRUE. , clesphy0 )
173!#endif
174
175!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
176! FH 2008/05/02
177! A nettoyer. On ne veut qu'une ou deux routines d'interface
178! dynamique -> physique pour l'initialisation
179! Ehouarn : temporarily (?) keep this only for Earth
180      if (planet_type.eq."earth") then
181#ifdef CPP_EARTH
182      CALL Init_Phys_lmdz(iim,jjp1,llm,1,(jjm-1)*iim+2)
183      call InitComgeomphy
184#endif
185      endif
186!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
187c-----------------------------------------------------------------------
188c   Choix du calendrier
189c   -------------------
190
191c      calend = 'earth_365d'
192
193#ifdef CPP_IOIPSL
194      if (calend == 'earth_360d') then
195        call ioconf_calendar('360d')
196        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
197      else if (calend == 'earth_365d') then
198        call ioconf_calendar('noleap')
199        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
200      else if (calend == 'earth_366d') then
201        call ioconf_calendar('gregorian')
202        write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
203      else
204        abort_message = 'Mauvais choix de calendrier'
205        call abort_gcm(modname,abort_message,1)
206      endif
207#endif
208c-----------------------------------------------------------------------
209
210      IF (config_inca /= 'none') THEN
211#ifdef INCA
212      call init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
213      call init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
214#endif
215      END IF
216c
217c
218c------------------------------------
219c   Initialisation partie parallele
220c------------------------------------
221
222c
223c
224c-----------------------------------------------------------------------
225c   Initialisation des traceurs
226c   ---------------------------
227c  Choix du nombre de traceurs et du schema pour l'advection
228c  dans fichier traceur.def, par default ou via INCA
229      call infotrac_init
230
231c Allocation de la tableau q : champs advectes   
232      allocate(q(ip1jmp1,llm,nqtot))
233
234c-----------------------------------------------------------------------
235c   Lecture de l'etat initial :
236c   ---------------------------
237
238c  lecture du fichier start.nc
239      if (read_start) then
240      ! we still need to run iniacademic to initialize some
241      ! constants & fields, if we run the 'newtonian' case:
242        if (iflag_phys.eq.2) then
243          CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
244        endif
245!#ifdef CPP_IOIPSL
246        if (planet_type.eq."earth") then
247#ifdef CPP_EARTH
248! Load an Earth-format start file
249         CALL dynetat0("start.nc",vcov,ucov,
250     .              teta,q,masse,ps,phis, time_0)
251#endif
252        endif ! of if (planet_type.eq."earth")
253c       write(73,*) 'ucov',ucov
254c       write(74,*) 'vcov',vcov
255c       write(75,*) 'teta',teta
256c       write(76,*) 'ps',ps
257c       write(77,*) 'q',q
258
259      endif ! of if (read_start)
260
261      IF (config_inca /= 'none') THEN
262#ifdef INCA
263         call init_inca_dim(klon,llm,iim,jjm,
264     $        rlonu,rlatu,rlonv,rlatv)
265#endif
266      END IF
267
268
269c le cas echeant, creation d un etat initial
270      IF (prt_level > 9) WRITE(lunout,*)
271     .              'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
272      if (.not.read_start) then
273         CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
274      endif
275
276
277c-----------------------------------------------------------------------
278c   Lecture des parametres de controle pour la simulation :
279c   -------------------------------------------------------
280c  on recalcule eventuellement le pas de temps
281
282      IF(MOD(day_step,iperiod).NE.0) THEN
283        abort_message =
284     .  'Il faut choisir un nb de pas par jour multiple de iperiod'
285        call abort_gcm(modname,abort_message,1)
286      ENDIF
287
288      IF(MOD(day_step,iphysiq).NE.0) THEN
289        abort_message =
290     * 'Il faut choisir un nb de pas par jour multiple de iphysiq'
291        call abort_gcm(modname,abort_message,1)
292      ENDIF
293
294      zdtvr    = daysec/FLOAT(day_step)
295        IF(dtvr.NE.zdtvr) THEN
296         WRITE(lunout,*)
297     .    'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
298        ENDIF
299
300C
301C on remet le calendrier à zero si demande
302c
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
327
328#ifdef CPP_IOIPSL
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)
334
335      call ioconf_startdate(annee_ref,1,day_ref, 0.)
336
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
343#else
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
349#endif
350
351c  nombre d'etats dans les fichiers demarrage et histoire
352      nbetatdem = nday / iecri
353      nbetatmoy = nday / periodav + 1
354
355c-----------------------------------------------------------------------
356c   Initialisation des constantes dynamiques :
357c   ------------------------------------------
358      dtvr = zdtvr
359      CALL iniconst
360
361c-----------------------------------------------------------------------
362c   Initialisation de la geometrie :
363c   --------------------------------
364      CALL inigeom
365
366c-----------------------------------------------------------------------
367c   Initialisation du filtre :
368c   --------------------------
369      CALL inifilr
370c
371c-----------------------------------------------------------------------
372c   Initialisation de la dissipation :
373c   ----------------------------------
374
375      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
376     *                tetagdiv, tetagrot , tetatemp              )
377
378c-----------------------------------------------------------------------
379c   Initialisation de la physique :
380c   -------------------------------
381
382      IF (call_iniphys.and.(iflag_phys.eq.1)) THEN
383         latfi(1)=rlatu(1)
384         lonfi(1)=0.
385         zcufi(1) = cu(1)
386         zcvfi(1) = cv(1)
387         DO j=2,jjm
388            DO i=1,iim
389               latfi((j-2)*iim+1+i)= rlatu(j)
390               lonfi((j-2)*iim+1+i)= rlonv(i)
391               zcufi((j-2)*iim+1+i) = cu((j-1)*iip1+i)
392               zcvfi((j-2)*iim+1+i) = cv((j-1)*iip1+i)
393            ENDDO
394         ENDDO
395         latfi(ngridmx)= rlatu(jjp1)
396         lonfi(ngridmx)= 0.
397         zcufi(ngridmx) = cu(ip1jm+1)
398         zcvfi(ngridmx) = cv(ip1jm-iim)
399         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
400         WRITE(lunout,*)
401     .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
402! Earth:
403         if (planet_type.eq."earth") then
404#ifdef CPP_EARTH
405         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys ,
406     ,                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp     )
407#endif
408         endif ! of if (planet_type.eq."earth")
409         call_iniphys=.false.
410      ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1))
411!#endif
412
413c  numero de stockage pour les fichiers de redemarrage:
414
415c-----------------------------------------------------------------------
416c   Initialisation des I/O :
417c   ------------------------
418
419
420      day_end = day_ini + nday
421      WRITE(lunout,300)day_ini,day_end
422 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
423
424#ifdef CPP_IOIPSL
425      call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
426      write (lunout,301)jour, mois, an
427      call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
428      write (lunout,302)jour, mois, an
429 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
430 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
431#endif
432
433      if (planet_type.eq."earth") then
434        CALL dynredem0("restart.nc", day_end, phis)
435      endif
436
437      ecripar = .TRUE.
438
439#ifdef CPP_IOIPSL
440      if ( 1.eq.1) then
441      time_step = zdtvr
442      t_ops = iecri * daysec
443      t_wrt = iecri * daysec
444      CALL inithist(dynhist_file,day_ref,annee_ref,time_step,
445     .              t_ops, t_wrt, histid, histvid)
446
447      IF (ok_dynzon) THEN
448         t_ops = iperiod * time_step
449         t_wrt = periodav * daysec
450         CALL initdynav(dynhistave_file,day_ref,annee_ref,time_step,
451     .        t_ops, t_wrt, histaveid)
452      END IF
453      dtav = iperiod*dtvr/daysec
454      endif
455
456
457#endif
458! #endif of #ifdef CPP_IOIPSL
459
460c  Choix des frequences de stokage pour le offline
461c      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
462c      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
463      istdyn=day_step/4     ! stockage toutes les 6h=1jour/12
464      istphy=istdyn/iphysiq     
465
466
467c
468c-----------------------------------------------------------------------
469c   Integration temporelle du modele :
470c   ----------------------------------
471
472c       write(78,*) 'ucov',ucov
473c       write(78,*) 'vcov',vcov
474c       write(78,*) 'teta',teta
475c       write(78,*) 'ps',ps
476c       write(78,*) 'q',q
477
478
479      CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
480     .              time_0)
481
482      END
483
Note: See TracBrowser for help on using the repository browser.