source: trunk/libf/dyn3d/gcm.F @ 98

Last change on this file since 98 was 97, checked in by slebonnois, 14 years ago

Serie de modifs SL pour homogeneisation des phytitan et phyvenus
Ca touche aussi aux liens phy/dyn (surtout a propos de clesphy0),
a verifier avec les autres, donc...

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