source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/gcm.F90 @ 5214

Last change on this file since 5214 was 5195, checked in by abarral, 7 days ago

Correct r5192, some lmdz_description cases were missing

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:keywords set to Id
File size: 15.0 KB
RevLine 
[4146]1! $Id: gcm.F90 5195 2024-09-16 13:18:00Z dcugnet $
[1632]2
[2263]3PROGRAM gcm
4
5  USE IOIPSL
[1632]6
[2263]7  USE mod_const_mpi, ONLY: init_const_mpi
8  USE parallel_lmdz
[5182]9  USE lmdz_infotrac, ONLY: nqtot, init_infotrac
[2263]10  USE mod_hallo
11  USE Bands
[5106]12  USE lmdz_filtreg
[2263]13  USE control_mod
[1632]14
[2347]15  USE iniphysiq_mod, ONLY: iniphysiq
[5090]16  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS
17
[2597]18  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
[2603]19  USE logic_mod ! all of it, because of copyin clause when calling leapfrog
[5186]20  USE temps_mod, ONLY: calend, start_time, annee_ref, day_ref, &
21          itau_dyn, itau_phy, day_ini, jD_ref, jH_ref, day_end, &
22          dt, hour_ini, itaufin
[4146]23  USE mod_xios_dyn3dmem, ONLY: xios_dyn3dmem_init
[5106]24  USE lmdz_filtreg, ONLY: inifilr
[5118]25  USE lmdz_iniprint, ONLY: lunout, prt_level
[5134]26  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
27          tetagrot, tetatemp, coefdis, vert_prof_dissip
[5136]28  USE lmdz_comgeom
[5137]29  USE lmdz_tracstoke
[2601]30
[5159]31  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
32  USE lmdz_paramet
[5186]33  USE lmdz_conf_gcm, ONLY: conf_gcm
34
[2263]35  IMPLICIT NONE
[1632]36
[2263]37  !      ......   Version  du 10/01/98    ..........
[1632]38
[5159]39  !             avec  coordonnees  verticales hybrides
[2263]40  !   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
[1632]41
[2263]42  !=======================================================================
[5099]43
[2263]44  !   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
45  !   -------
[5099]46
[2263]47  !   Objet:
48  !   ------
[5099]49
[2263]50  !   GCM LMD nouvelle grille
[5099]51
[2263]52  !=======================================================================
[5099]53
[2263]54  !  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
55  !      et possibilite d'appeler une fonction f(y)  a derivee tangente
56  !      hyperbolique a la  place de la fonction a derivee sinusoidale.
57  !  ... Possibilite de choisir le schema pour l'advection de
58  !        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
[5099]59
[2263]60  !      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
61  !      Pour Van-Leer iadv=10
[5099]62
[2263]63  !-----------------------------------------------------------------------
64  !   Declarations:
65  !   -------------
[1658]66
[2263]67  REAL zdtvr
[1632]68
[2263]69  !   variables dynamiques
[5186]70  REAL, ALLOCATABLE, SAVE :: vcov(:, :), ucov(:, :) ! vents covariants
71  REAL, ALLOCATABLE, SAVE :: teta(:, :)     ! temperature potentielle
72  REAL, ALLOCATABLE, SAVE :: q(:, :, :)      ! champs advectes
73  REAL, ALLOCATABLE, SAVE :: ps(:)         ! pression  au sol
[2263]74  !      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
[5186]75  REAL, ALLOCATABLE, SAVE :: masse(:, :)    ! masse d'air
76  REAL, ALLOCATABLE, SAVE :: phis(:)       ! geopotentiel au sol
[2263]77  !      REAL phi(ip1jmp1,llm)                  ! geopotentiel
78  !      REAL w(ip1jmp1,llm)                    ! vitesse verticale
[1632]79
[2263]80  ! variables dynamiques intermediaire pour le transport
[1632]81
[2263]82  !   variables pour le fichier histoire
83  REAL dtav      ! intervalle de temps elementaire
[1632]84
[2263]85  REAL time_0
[1632]86
[2263]87  LOGICAL lafin
[1632]88
[5117]89  REAL time_step, t_wrt, t_ops
[1632]90
[2263]91  !+jld variables test conservation energie
92  !      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
93  !     Tendance de la temp. potentiel d (theta)/ d t due a la
94  !     tansformation d'energie cinetique en energie thermique
95  !     cree par la dissipation
96  !      REAL dhecdt(ip1jmp1,llm)
97  !      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
98  !      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
99  !      CHARACTER (len=15) :: ztit
100  !-jld
[1632]101
[5186]102  CHARACTER (LEN = 80) :: dynhist_file, dynhistave_file
103  CHARACTER (LEN = 20) :: modname
104  CHARACTER (LEN = 80) :: abort_message
[2263]105  ! locales pour gestion du temps
106  INTEGER :: an, mois, jour
107  REAL :: heure
[4146]108  ! needed for xios interface
[5186]109  CHARACTER (LEN = 10) :: xios_cal_type
[4146]110  INTEGER :: anref, moisref, jourref
111  REAL :: heureref
[1632]112
113
[5186]114
[2263]115  !-----------------------------------------------------------------------
116  !   Initialisations:
117  !   ----------------
[1632]118
[2263]119  abort_message = 'last timestep reached'
120  modname = 'gcm'
[5186]121  lafin = .FALSE.
[2263]122  dynhist_file = 'dyn_hist'
123  dynhistave_file = 'dyn_hist_ave'
[1632]124
125
126
[2263]127  !----------------------------------------------------------------------
128  !  lecture des fichiers gcm.def ou run.def
129  !  ---------------------------------------
[5099]130
[5186]131  CALL conf_gcm(99, .TRUE.)
[5117]132  IF (mod(iphysiq, iperiod) /= 0) CALL abort_gcm("conf_gcm", &
[5186]133          "iphysiq must be a multiple of iperiod", 1)
[5099]134
135
[2263]136  !------------------------------------
137  !   Initialisation partie parallele
138  !------------------------------------
139  CALL init_const_mpi
[1632]140
[5101]141  CALL init_parallel
142  CALL Read_Distrib
[1673]143
[5186]144  !#ifdef CPP_PHYS
145  !  CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
[2263]146  !#endif
147  !      CALL set_bands
148  !#ifdef CPP_PHYS
[5186]149  !  CALL Init_interface_dyn_phys
150  !#endif
[2263]151  CALL barrier
[1632]152
[2263]153  CALL set_bands
[5117]154  IF (mpi_rank==0) CALL WriteBands
[5101]155  CALL Set_Distrib(distrib_caldyn)
[1632]156
[2263]157  !$OMP PARALLEL
[5101]158  CALL Init_Mod_hallo
[2263]159  !$OMP END PARALLEL
[1632]160
[2263]161  !#ifdef CPP_PHYS
162  !c$OMP PARALLEL
[5101]163  !      CALL InitComgeomphy ! now done in iniphysiq
[2263]164  !c$OMP END PARALLEL
165  !#endif
[1632]166
[2263]167  !-----------------------------------------------------------------------
168  !   Choix du calendrier
169  !   -------------------
[1632]170
[2263]171  !      calend = 'earth_365d'
[1632]172
[5117]173  IF (calend == 'earth_360d') THEN
[5186]174    CALL ioconf_calendar('360_day')
175    WRITE(lunout, *)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
176    xios_cal_type = 'd360'
[5117]177  ELSE IF (calend == 'earth_365d') THEN
[5186]178    CALL ioconf_calendar('noleap')
179    WRITE(lunout, *)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
180    xios_cal_type = 'noleap'
[5117]181  ELSE IF (calend == 'gregorian') THEN
[5186]182    CALL ioconf_calendar('gregorian')
183    WRITE(lunout, *)'CALENDRIER CHOISI: Terrestre bissextile'
184    xios_cal_type = 'gregorian'
[2263]185  else
[5186]186    abort_message = 'Mauvais choix de calendrier'
187    CALL abort_gcm(modname, abort_message, 1)
[5117]188  ENDIF
[1632]189
190
[2263]191  !-----------------------------------------------------------------------
192  !   Initialisation des traceurs
193  !   ---------------------------
194  !  Choix du nombre de traceurs et du schema pour l'advection
195  !  dans fichier traceur.def, par default ou via INCA
[5101]196  CALL init_infotrac
[1632]197
[2263]198  ! Allocation de la tableau q : champs advectes   
[5186]199  ALLOCATE(ucov(ijb_u:ije_u, llm))
200  ALLOCATE(vcov(ijb_v:ije_v, llm))
201  ALLOCATE(teta(ijb_u:ije_u, llm))
202  ALLOCATE(masse(ijb_u:ije_u, llm))
[2263]203  ALLOCATE(ps(ijb_u:ije_u))
204  ALLOCATE(phis(ijb_u:ije_u))
[5186]205  ALLOCATE(q(ijb_u:ije_u, llm, nqtot))
[1632]206
[2263]207  !-----------------------------------------------------------------------
208  !   Lecture de l'etat initial :
209  !   ---------------------------
[1632]210
[2263]211  !  lecture du fichier start.nc
[5117]212  IF (read_start) THEN
[5186]213    ! we still need to run iniacademic to initialize some
214    ! constants & fields, if we run the 'newtonian' or 'SW' cases:
215    IF (iflag_phys/=1) THEN
216      CALL iniacademic_loc(vcov, ucov, teta, q, masse, ps, phis, time_0)
217    endif
[1657]218
[5186]219    !        if (planet_type.EQ."earth") THEN
220    ! Load an Earth-format start file
221    CALL dynetat0_loc("start.nc", vcov, ucov, &
222            teta, q, masse, ps, phis, time_0)
223    !        endif ! of if (planet_type.EQ."earth")
[1673]224
[5186]225    !       WRITE(73,*) 'ucov',ucov
226    !       WRITE(74,*) 'vcov',vcov
227    !       WRITE(75,*) 'teta',teta
228    !       WRITE(76,*) 'ps',ps
229    !       WRITE(77,*) 'q',q
[1632]230
[5117]231  ENDIF ! of if (read_start)
[1632]232
[2263]233  ! le cas echeant, creation d un etat initial
[5186]234  IF (prt_level > 9) WRITE(lunout, *) &
235          'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
[5117]236  IF (.NOT.read_start) THEN
[5186]237    start_time = 0.
238    annee_ref = anneeref
239    CALL iniacademic_loc(vcov, ucov, teta, q, masse, ps, phis, time_0)
[5117]240  ENDIF
[1632]241
[2263]242  !-----------------------------------------------------------------------
243  !   Lecture des parametres de controle pour la simulation :
244  !   -------------------------------------------------------
245  !  on recalcule eventuellement le pas de temps
[1632]246
[5186]247  IF(MOD(day_step, iperiod)/=0) THEN
248    abort_message = &
249            'Il faut choisir un nb de pas par jour multiple de iperiod'
250    CALL abort_gcm(modname, abort_message, 1)
[2263]251  ENDIF
[1632]252
[5186]253  IF(MOD(day_step, iphysiq)/=0) THEN
254    abort_message = &
255            'Il faut choisir un nb de pas par jour multiple de iphysiq'
256    CALL abort_gcm(modname, abort_message, 1)
[2263]257  ENDIF
[1632]258
[5186]259  zdtvr = daysec / REAL(day_step)
[5082]260  IF(dtvr/=zdtvr) THEN
[5186]261    WRITE(lunout, *) &
262            'WARNING!!! changement de pas de temps', dtvr, '>', zdtvr
[2263]263  ENDIF
[1632]264
[2263]265  ! on remet le calendrier \`a zero si demande
[5099]266
[5116]267  IF (start_time /= starttime) THEN
[5186]268    WRITE(lunout, *)' GCM: Attention l''heure de depart lue dans le' &
269            , ' fichier restart ne correspond pas a celle lue dans le run.def'
270    IF (raz_date == 1) THEN
271      WRITE(lunout, *)'Je prends l''heure lue dans run.def'
272      start_time = starttime
273    ELSE
274      WRITE(lunout, *)'Je m''arrete'
275      CALL abort
276    ENDIF
[2263]277  ENDIF
278  IF (raz_date == 1) THEN
[5186]279    annee_ref = anneeref
280    day_ref = dayref
281    day_ini = dayref
282    itau_dyn = 0
283    itau_phy = 0
284    time_0 = 0.
285    WRITE(lunout, *) &
286            'GCM: On reinitialise a la date lue dans gcm.def'
[5117]287  ELSE IF (annee_ref /= anneeref .OR. day_ref /= dayref) THEN
[5186]288    WRITE(lunout, *) &
289            'GCM: Attention les dates initiales lues dans le fichier'
290    WRITE(lunout, *) &
291            ' restart ne correspondent pas a celles lues dans '
292    WRITE(lunout, *)' gcm.def'
293    WRITE(lunout, *)' annee_ref=', annee_ref, " anneeref=", anneeref
294    WRITE(lunout, *)' day_ref=', day_ref, " dayref=", dayref
295    WRITE(lunout, *)' Pas de remise a zero'
[2263]296  ENDIF
[5117]297  !      if (annee_ref .NE. anneeref .OR. day_ref .NE. dayref) THEN
[5116]298  !        WRITE(lunout,*)
[2263]299  !     .  'GCM: Attention les dates initiales lues dans le fichier'
[5116]300  !        WRITE(lunout,*)
[2263]301  !     .  ' restart ne correspondent pas a celles lues dans '
[5116]302  !        WRITE(lunout,*)' gcm.def'
303  !        WRITE(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
304  !        WRITE(lunout,*)' day_ref=',day_ref," dayref=",dayref
[5117]305  !        if (raz_date .NE. 1) THEN
[5116]306  !          WRITE(lunout,*)
[2263]307  !     .    'GCM: On garde les dates du fichier restart'
308  !        else
309  !          annee_ref = anneeref
310  !          day_ref = dayref
311  !          day_ini = dayref
312  !          itau_dyn = 0
313  !          itau_phy = 0
314  !          time_0 = 0.
[5116]315  !          WRITE(lunout,*)
[2263]316  !     .   'GCM: On reinitialise a la date lue dans gcm.def'
317  !        endif
318  !      ELSE
319  !        raz_date = 0
320  !      endif
[1632]321
[2263]322  mois = 1
323  heure = 0.
[5101]324  CALL ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
[2263]325  jH_ref = jD_ref - int(jD_ref)
326  jD_ref = int(jD_ref)
[1632]327
[5101]328  CALL ioconf_startdate(INT(jD_ref), jH_ref)
[1632]329
[5186]330  WRITE(lunout, *)'DEBUG'
331  WRITE(lunout, *)'annee_ref, mois, day_ref, heure, jD_ref'
332  WRITE(lunout, *)annee_ref, mois, day_ref, heure, jD_ref
333  CALL ju2ymds(jD_ref + jH_ref, anref, moisref, jourref, heureref)
334  WRITE(lunout, *)'jD_ref+jH_ref,an, mois, jour, heure'
335  WRITE(lunout, *)jD_ref + jH_ref, anref, moisref, jourref, heureref
[1632]336
[5117]337  IF (iflag_phys==1) THEN
[5186]338    ! these initialisations have already been done (via iniacademic)
339    ! if running in SW or Newtonian mode
340    !-----------------------------------------------------------------------
341    !   Initialisation des constantes dynamiques :
342    !   ------------------------------------------
343    dtvr = zdtvr
344    CALL iniconst
[1632]345
[5186]346    !-----------------------------------------------------------------------
347    !   Initialisation de la geometrie :
348    !   --------------------------------
349    CALL inigeom
[1632]350
[5186]351    !-----------------------------------------------------------------------
352    !   Initialisation du filtre :
353    !   --------------------------
354    CALL inifilr
[5117]355  ENDIF ! of if (iflag_phys.EQ.1)
[5099]356
[2263]357  !-----------------------------------------------------------------------
358  !   Initialisation de la dissipation :
359  !   ----------------------------------
[1632]360
[5186]361  CALL inidissip(lstardis, nitergdiv, nitergrot, niterh, &
362          tetagdiv, tetagrot, tetatemp, vert_prof_dissip)
[1632]363
[2263]364  !-----------------------------------------------------------------------
365  !   Initialisation des I/O :
366  !   ------------------------
[1632]367
[5117]368  IF (nday>=0) THEN
[5186]369    day_end = day_ini + nday
[2263]370  else
[5186]371    day_end = day_ini - nday / day_step
[5117]372  ENDIF
[1632]373
[5186]374  WRITE(lunout, 300)day_ini, day_end
375  300 FORMAT('1'/, 15x, 'run du jour', i7, 2x, 'au jour', i7//)
[2263]376
[5101]377  CALL ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
[5186]378  write (lunout, 301)jour, mois, an
[5101]379  CALL ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
[5186]380  write (lunout, 302)jour, mois, an
381  301 FORMAT('1'/, 15x, 'run du ', i2, '/', i2, '/', i4)
382  302 FORMAT('1'/, 15x, '    au ', i2, '/', i2, '/', i4)
[1632]383
[3435]384  !-----------------------------------------------------------------------
385  !   Initialisation de la physique :
386  !   -------------------------------
[4139]387
388  !  Choix des frequences de stokage pour le offline
389  !      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
390  !      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
[5186]391  istdyn = day_step / 8     ! stockage toutes les 6h=1jour/12
392  istphy = istdyn / iphysiq
[4139]393
[5117]394  IF ((iflag_phys==1).OR.(iflag_phys>=100)) THEN
[5186]395    ! Physics:
[5090]396    IF (CPPKEY_PHYS) THEN
[5186]397      CALL iniphysiq(iim, jjm, llm, &
398              distrib_phys(mpi_rank), comm_lmdz, &
399              daysec, day_ini, dtphys / nsplit_phys, &
400              rlatu, rlatv, rlonu, rlonv, aire, cu, cv, rad, g, r, cpp, &
401              iflag_phys)
[5090]402    END IF
[5117]403  ENDIF ! of IF ((iflag_phys==1).OR.(iflag_phys>=100))
[3435]404
405
[5117]406  !      if (planet_type.EQ."earth") THEN
[2263]407  ! Write an Earth-format restart file
408  CALL dynredem0_loc("restart.nc", day_end, phis)
409  !      endif
[1632]410
[2263]411  ecripar = .TRUE.
[1632]412
[2263]413  time_step = zdtvr
[5186]414  IF (ok_dyn_ins) THEN
415    ! initialize output file for instantaneous outputs
416    ! t_ops = iecri * daysec ! do operations every t_ops
417    t_ops = ((1.0 * iecri) / day_step) * daysec
418    t_wrt = daysec ! iecri * daysec ! write output every t_wrt
419    CALL inithist_loc(day_ref, annee_ref, time_step, &
420            t_ops, t_wrt)
421  endif
[1632]422
[5186]423  IF (ok_dyn_ave) THEN
424    ! initialize output file for averaged outputs
425    t_ops = iperiod * time_step ! do operations every t_ops
426    t_wrt = periodav * daysec   ! write output every t_wrt
427    CALL initdynav_loc(day_ref, annee_ref, time_step, t_ops, t_wrt)
428  END IF
429  dtav = iperiod * dtvr / daysec
[4146]430
[5186]431  ! setting up DYN3D/XIOS inerface
[5117]432  IF (ok_dyn_xios) THEN
[5186]433    CALL xios_dyn3dmem_init(xios_cal_type, anref, moisref, jourref, heureref, an, &
434            mois, jour, heure, zdtvr)
[5117]435  ENDIF
[4146]436
[2263]437  !-----------------------------------------------------------------------
438  !   Integration temporelle du modele :
439  !   ----------------------------------
[1632]440
[5116]441  !       WRITE(78,*) 'ucov',ucov
442  !       WRITE(78,*) 'vcov',vcov
443  !       WRITE(78,*) 'teta',teta
444  !       WRITE(78,*) 'ps',ps
445  !       WRITE(78,*) 'q',q
[1632]446
[2601]447  !!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
[4103]448  !     Copy all threadprivate variables in temps_mod logic_mod
[2603]449  !$OMP PARALLEL DEFAULT(SHARED) &
[2601]450  !$OMP COPYIN(dt,jD_ref,jH_ref,start_time,hour_ini,day_ini,day_end) &
[2603]451  !$OMP COPYIN(annee_ref,day_ref,itau_dyn,itau_phy,itaufin,calend) &
452  !$OMP COPYIN(purmats,forward,leapf,apphys,statcl,conser,apdiss,apdelq) &
453  !$OMP COPYIN(saison,ecripar,fxyhypb,ysinus,read_start,ok_guide) &
454  !$OMP COPYIN(ok_strato,ok_gradsfile,ok_limit,ok_etat0) &
[4996]455  !$OMP COPYIN(iflag_phys,iflag_trac,adv_qsat_liq)
[5186]456  CALL leapfrog_loc(ucov, vcov, teta, ps, masse, phis, q, time_0)
[2263]457  !$OMP END PARALLEL
[1632]458
[2263]459  !      OPEN(unit=5487,file='ok_lmdz',status='replace')
460  !      WRITE(5487,*) 'ok_lmdz'
461  !      CLOSE(5487)
462END PROGRAM gcm
Note: See TracBrowser for help on using the repository browser.