Ignore:
Timestamp:
Jan 25, 2017, 4:02:54 PM (8 years ago)
Author:
emillour
Message:

Dynamical core: Further adaptations to stick with LMDZ5 (up to rev r2750)

  • libf
  • makelmdz[_fcm] : added Earth-specific "dust" and "strataer" cases and

-arch_path option

  • bld.cfg : added dust and strataer cases
  • dyn3d[par]
  • conf_gcm.F90 : added read_orop parameter (Earth-related) for

loading subgrid orography parameters.

  • guide[_p]_mod.F90: added output of nudging coefficients for winds

and temperature

  • temps_mod.F90 : cosmetics/comments
  • logic_mod.F90 : cosmetics/comments
  • dyn3d_common
  • comconst_mod.F90 : cosmetics/comments + added year_day module variable
  • conf_planete.F90 : added year_day from comconst_mod as done in LMDZ5
  • comvert_mod.F90 : cosmetics/comments
  • infotrac.F90 : added "startAer" case to follow up with LMDZ5
  • misc
  • wxios.F90 : follow up on changes in LMDZ5

EM

Location:
trunk/LMDZ.COMMON/libf/dyn3d_common
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d_common/comconst_mod.F90

    r1572 r1650  
    1212      REAL r ! Reduced Gas constant r=R/mu
    1313             ! with R=8.31.. J.K-1.mol-1, mu: mol mass of atmosphere (kg/mol)
    14       REAL cpp   ! Cp
    15       REAL kappa ! kappa=R/Cp
     14      REAL cpp   ! Specific heat Cp (J.kg-1.K-1)
     15      REAL kappa ! kappa=r/Cp
    1616      REAL cotot
    1717      REAL unsim ! = 1./iim
     
    2323      REAL dissip_fac_mid,dissip_fac_up,dissip_deltaz,dissip_hdelta
    2424      REAL dissip_pupstart
    25       INTEGER iflag_top_bound,mode_top_bound
     25! top_bound sponge:
     26      INTEGER iflag_top_bound ! sponge type
    2627      INTEGER ngroup ! parameter to group points (along longitude) near poles
    27       REAL tau_top_bound
     28      INTEGER mode_top_bound  ! sponge mode
     29      REAL tau_top_bound ! inverse of sponge characteristic time scale (Hz)
    2830      REAL daylen ! length of solar day, in 'standard' day length
     31      REAL year_day ! Number of standard days in a year
    2932      REAL molmass ! (g/mol) molar mass of the atmosphere
    3033
  • trunk/LMDZ.COMMON/libf/dyn3d_common/comvert_mod.F90

    r1422 r1650  
    33IMPLICIT NONE 
    44
    5 include "dimensions.h"
    6 include "paramet.h"
     5PRIVATE
     6INCLUDE "dimensions.h"
    77
    8 REAL ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm),pa,preff,     &
    9         nivsigs(llm),nivsig(llm+1),scaleheight
    10 ! Mars Ce qui suit vient de gcm
    11 REAL sig(llm+1),ds(llm),aps(llm),bps(llm),pseudoalt(llm)
     8PUBLIC :: ap,bp,presnivs,dpres,sig,ds,pa,preff,nivsigs,nivsig, &
     9          aps,bps,scaleheight,pseudoalt,disvert_type, pressure_exner
     10
     11REAL ap(llm+1) ! hybrid pressure contribution at interlayers
     12REAL bp (llm+1) ! hybrid sigma contribution at interlayer
     13REAL presnivs(llm) ! (reference) pressure at mid-layers
     14REAL dpres(llm)
     15REAL sig(llm+1)
     16REAL ds(llm)
     17REAL pa ! reference pressure (Pa) at which hybrid coordinates
     18        ! become purely pressure (more or less)
     19REAL preff  ! reference surface pressure (Pa)
     20REAL nivsigs(llm)
     21REAL nivsig(llm+1)
     22REAL aps(llm) ! hybrid pressure contribution at mid-layers
     23REAL bps(llm) ! hybrid sigma contribution at mid-layers
     24REAL scaleheight ! atmospheric (reference) scale height (km)
     25REAL pseudoalt(llm) ! pseudo-altitude of model levels (km), based on presnivs(),
     26                     ! preff and scaleheight
     27
    1228INTEGER disvert_type ! type of vertical discretization:
    13                            ! 1: Earth (default for planet_type==earth),
    14                            !     automatic generation
    15                            ! 2: Planets (default for planet_type!=earth),
    16                            !     using 'z2sig.def' (or 'esasig.def) file
     29                     ! 1: Earth (default for planet_type==earth),
     30                     !     automatic generation
     31                     ! 2: Planets (default for planet_type!=earth),
     32                     !     using 'z2sig.def' (or 'esasig.def) file
     33
    1734LOGICAL pressure_exner
    1835!     compute pressure inside layers using Exner function, else use mean
  • trunk/LMDZ.COMMON/libf/dyn3d_common/conf_planete.F90

    r1422 r1650  
    1010USE ioipsl_getincom
    1111#endif
    12 USE comvert_mod, ONLY: preff,pa
    13 USE comconst_mod, ONLY: daysec,daylen,kappa,cpp,omeg,rad,g,ihf,pi,molmass
     12USE comconst_mod, ONLY: pi, g, molmass, kappa, cpp, omeg, rad, &
     13                        year_day, daylen, daysec, ihf
     14USE comvert_mod, ONLY: preff, pa
    1415IMPLICIT NONE
    1516!
     
    1718!   Declarations :
    1819!   --------------
    19 #include "dimensions.h"
     20
    2021!
    2122!   local:
    2223!   ------
    23 
    24 real :: year_day_dyn
    2524
    2625! ---------------------------------------------
     
    5958CALL getin('daylen',daylen)
    6059! Number of days (standard) per year:
    61 year_day_dyn = 365.25
    62 CALL getin('year_day',year_day_dyn)
     60year_day = 365.25
     61CALL getin('year_day',year_day)
    6362! Omega
    6463! omeg=2.*pi/86400.
    65 omeg=2.*pi/daysec*(1./daylen+1./year_day_dyn)
     64omeg=2.*pi/daysec*(1./daylen+1./year_day)
    6665CALL getin('omeg',omeg)
    6766
    68 ! Intrinsic heat flux [default is none]
    69 ! Aymeric -- for giant planets
    70 ! [matters only if planet_type="giant"]
     67! Intrinsic heat flux (default: none) (only used if planet_type="giant")
    7168ihf = 0.
    72 CALL getin('ihf',ihf)
    73 
    74 
     69call getin('ihf',ihf)
    7570
    7671END SUBROUTINE conf_planete
  • trunk/LMDZ.COMMON/libf/dyn3d_common/infotrac.F90

    r1575 r1650  
    4545    INTEGER :: niso_possibles   
    4646    PARAMETER ( niso_possibles=5) ! 5 possible water isotopes
    47     real, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
     47    REAL, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
    4848    LOGICAL, DIMENSION(niso_possibles),SAVE ::  use_iso
    4949    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  iqiso ! donne indice iq en fn de (ixt,phase)
     
    5555    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  index_trac ! numéro ixt en fn izone, indnum entre 1 et niso
    5656    INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
     57
     58#ifdef CPP_StratAer
     59!--CK/OB for stratospheric aerosols
     60  INTEGER, SAVE :: nbtr_bin
     61  INTEGER, SAVE :: nbtr_sulgas
     62  INTEGER, SAVE :: id_OCS_strat
     63  INTEGER, SAVE :: id_SO2_strat
     64  INTEGER, SAVE :: id_H2SO4_strat
     65  INTEGER, SAVE :: id_BIN01_strat
     66  INTEGER, SAVE :: id_TEST_strat
     67#endif
    5768
    5869CONTAINS
     
    143154       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
    144155#endif
     156    ELSE IF (type_trac == 'coag') THEN
     157       WRITE(lunout,*) 'Tracers are treated for COAGULATION tests : type_trac=', type_trac
     158#ifndef CPP_StratAer
     159       WRITE(lunout,*) 'To run this option you must add cpp key StratAer and compile with StratAer code'
     160       CALL abort_gcm('infotrac_init','You must compile with cpp key StratAer',1)
     161#endif
    145162     ELSE IF (type_trac == 'lmdz') THEN
    146163       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
     
    166183!-----------------------------------------------------------------------
    167184    IF (planet_type=='earth') THEN
    168      IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
     185     IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag') THEN
    169186       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    170187       IF(ierr.EQ.0) THEN
     
    272289!---------------------------------------------------------------------
    273290    IF (planet_type=='earth') THEN
    274      IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
     291     IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag') THEN
    275292       IF(ierr.EQ.0) THEN
    276293          ! Continue to read tracer.def
     
    352369       END DO
    353370
     371!       IF ( planet_type=='earth') THEN
    354372         !CR: nombre de traceurs de l eau
    355          if (tnom_0(3) == 'H2Oi') then
     373         IF (tnom_0(3) == 'H2Oi') then
    356374            nqo=3
    357          else
     375         ELSE
    358376            nqo=2
    359          endif
     377         ENDIF
    360378         ! For Earth, water vapour & liquid tracers are not in the physics
    361379         nbtr=nqtrue-nqo
    362      ENDIF  ! (type_trac == 'lmdz' .OR. type_trac == 'repr')
     380!       ELSE
     381!         ! Other planets (for now); we have the same number of tracers
     382!         ! in the dynamics than in the physics
     383!         nbtr=nqtrue
     384!       ENDIF
     385
     386#ifdef CPP_StratAer
     387       IF (type_trac == 'coag') THEN
     388         nbtr_bin=0
     389         nbtr_sulgas=0
     390         DO iq=1,nqtrue
     391           IF (tnom_0(iq)(1:3)=='BIN') THEN !check if tracer name contains 'BIN'
     392             nbtr_bin=nbtr_bin+1
     393           ENDIF
     394           IF (tnom_0(iq)(1:3)=='GAS') THEN !check if tracer name contains 'GAS'
     395             nbtr_sulgas=nbtr_sulgas+1
     396           ENDIF
     397         ENDDO
     398         print*,'nbtr_bin=',nbtr_bin
     399         print*,'nbtr_sulgas=',nbtr_sulgas
     400         DO iq=1,nqtrue
     401           IF (tnom_0(iq)=='GASOCS') THEN
     402             id_OCS_strat=iq-nqo
     403           ENDIF
     404           IF (tnom_0(iq)=='GASSO2') THEN
     405             id_SO2_strat=iq-nqo
     406           ENDIF
     407           IF (tnom_0(iq)=='GASH2SO4') THEN
     408             id_H2SO4_strat=iq-nqo
     409           ENDIF
     410           IF (tnom_0(iq)=='BIN01') THEN
     411             id_BIN01_strat=iq-nqo
     412           ENDIF
     413           IF (tnom_0(iq)=='GASTEST') THEN
     414             id_TEST_strat=iq-nqo
     415           ENDIF
     416         ENDDO
     417         print*,'id_OCS_strat  =',id_OCS_strat
     418         print*,'id_SO2_strat  =',id_SO2_strat
     419         print*,'id_H2SO4_strat=',id_H2SO4_strat
     420         print*,'id_BIN01_strat=',id_BIN01_strat
     421       ENDIF
     422#endif
     423
     424     ENDIF  ! (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac = 'coag')
    363425!jyg<
    364426!
Note: See TracChangeset for help on using the changeset viewer.