source: trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F @ 1384

Last change on this file since 1384 was 1315, checked in by milmd, 11 years ago

LMDZ.GENERIC. OpenMP directives added in generic physic. When running in pure OpenMP or hybrid OpenMP/MPI, may have some bugs with condense_cloud and wstats routines.

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