Changeset 1621 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Oct 25, 2016, 9:23:21 AM (8 years ago)
Author:
emillour
Message:

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

Location:
trunk/LMDZ.GENERIC
Files:
1 added
14 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r1600 r1621  
    12621262  should not return the maximum index (leads to out-of-bounds index use in
    12631263  the caller).
     1264
     1265== 25/10/2016 == EM
     1266Updates for full physics/dynamics separation:
     1267- introduced module vertical_layers_mod.F90 in phy_common to store information
     1268  about the vertical grid to be used in the physics. Routines in the physics
     1269  should "use vertical_layers_mod" and not "use comvert_mod".
     1270- added nqtot to tracer_h.F90. Always "use tracer_h" in physics instead of
     1271  infotrac (which is in the dynamics).
     1272- removed some purely dynamics-related outputs (etot0, zoom parameters, etc.)
     1273  from diagfi.nc and stats.nc outputs as these informations are not available
     1274  in the physics.
     1275- added scalheight (atmospheric scale height) in comvert_mod.
     1276
  • trunk/LMDZ.GENERIC/libf/dyn3d/comvert_mod.F90

    r1422 r1621  
    1010! Mars Ce qui suit vient de gcm
    1111REAL sig(llm+1),ds(llm),aps(llm),bps(llm),pseudoalt(llm)
     12REAL scaleheight ! atmospheric scale height (km)
    1213
    1314END MODULE comvert_mod
  • trunk/LMDZ.GENERIC/libf/dyn3d/disvert.F

    r1422 r1621  
    55      USE callkeys_mod, ONLY: kastprof,pceil
    66      USE comvert_mod, ONLY: ap,bp,sig,nivsigs,nivsig,pa,preff,
    7      .                  aps,bps,presnivs,pseudoalt
     7     .                  aps,bps,presnivs,pseudoalt,scaleheight
    88
    99c    Auteur :  F. Forget Y. Wanherdrick, P. Levan
     
    3131      INTEGER l,ll
    3232      REAL snorm
    33       REAL alpha,beta,gama,delta,deltaz,h,quoi,quand
     33      REAL alpha,beta,gama,delta,deltaz,quoi,quand
    3434      REAL zsig(llm)
    3535      INTEGER np,ierr
     
    108108         PRINT*,'****************************'
    109109
    110          READ(99,*) h
     110         READ(99,*) scaleheight
    111111         do l=1,llm
    112112            read(99,*) zsig(l)
     
    117117         if(autozlevs)then
    118118            open(91,file="z2sig.def",form='formatted')
    119             read(91,*) h
     119            read(91,*) scaleheight
    120120            DO l=1,llm-2
    121121               read(91,*) Hmax
     
    126126            print*,'Auto-shifting h in disvert.F to:'
    127127!            h = Hmax / log(psurf/100.0)
    128             h = Hmax / log(psurf/pceil)
    129             print*,'h = ',h,' km'
     128            scaleheight = Hmax / log(psurf/pceil)
     129            print*,'h = ',scaleheight,' km'
    130130        endif
    131131       
    132132        sig(1)=1
    133133        do l=2,llm
    134            sig(l) = 0.5 * ( exp(-zsig(l)/h) + exp(-zsig(l-1)/h) )
     134           sig(l) = 0.5 * ( exp(-zsig(l)/scaleheight) +
     135     &                      exp(-zsig(l-1)/scaleheight) )
    135136        end do
    136137        sig(llm+1)=0
     
    223224      DO l = 1, llm
    224225       presnivs(l) = aps(l)+bps(l)*preff
    225        pseudoalt(l) = -h*log(presnivs(l)/preff)
     226       pseudoalt(l) = -scaleheight*log(presnivs(l)/preff)
    226227      ENDDO
    227228
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/inigeomphy_mod.F90

    r1573 r1621  
    2121  USE mod_interface_dyn_phys, ONLY :  init_interface_dyn_phys
    2222  USE nrtype, ONLY: pi
     23  USE comvert_mod, ONLY: preff, ap, bp, aps, bps, presnivs, &
     24                         scaleheight, pseudoalt
     25  USE vertical_layers_mod, ONLY: init_vertical_layers
    2326  IMPLICIT NONE
    2427
     
    213216                     airefi,cufi,cvfi)
    214217
     218  ! copy over preff , ap(), bp(), etc
     219  CALL init_vertical_layers(nlayer,preff,scaleheight, &
     220                            ap,bp,aps,bps,presnivs,pseudoalt)
     221
    215222!$OMP END PARALLEL
    216223
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r1576 r1621  
    2424      use callkeys_mod, only: tracer,check_cpp_match,rings_shadow,
    2525     &                        specOLR,water,pceil,ok_slab_ocean
    26       USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff
     26      USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff, sig,
     27     &                       presnivs,pseudoalt,scaleheight
     28      USE vertical_layers_mod, ONLY: init_vertical_layers
    2729      USE logic_mod, ONLY: hybrid,autozlevs
    2830      use regular_lonlat_mod, only: init_regular_lonlat
     
    502504     &                   (/0.,0.,0.,0./),(/0.,0.,0.,0./),
    503505     &                   cell_area)
     506! Ehouarn: init_vertial_layers called later (because disvert not called yet)
     507!      call init_vertical_layers(nlayer,preff,scaleheight,
     508!     &                      ap,bp,aps,bps,presnivs,pseudoalt)
    504509      call init_dimphy(1,nlayer) ! Initialize dimphy module
    505510      call ini_planete_mod(nlayer,preff,ap,bp)
     
    734739
    735740      call disvert
     741      ! now that disvert has been called, initialize module vertical_layers_mod
     742      call init_vertical_layers(nlayer,preff,scaleheight,
     743     &                      ap,bp,aps,bps,presnivs,pseudoalt)
    736744
    737745         if(.not.autozlevs)then
  • trunk/LMDZ.GENERIC/libf/phystd/inistats.F

    r1531 r1621  
    33      use statto_mod, only: istats,istime
    44      use mod_phys_lmdz_para, only : is_master
    5       USE comvert_mod, ONLY: ap,bp,aps,bps,preff,pseudoalt,presnivs
    6       USE comconst_mod, ONLY: pi
     5      USE vertical_layers_mod, ONLY: ap,bp,aps,bps,preff,
     6     &                               pseudoalt,presnivs
     7      USE nrtype, ONLY: pi
    78      USE time_phylmdz_mod, ONLY: daysec,dtphys
    89      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
  • trunk/LMDZ.GENERIC/libf/phystd/initracer.F

    r1542 r1621  
    4646c-----------------------------------------------------------------------
    4747
     48       nqtot=nq
    4849       !! we allocate once for all arrays in common in tracer_h.F90
    4950       !! (supposedly those are not used before call to initracer)
  • trunk/LMDZ.GENERIC/libf/phystd/iniwrite.F

    r1531 r1621  
    33      use comsoil_h, only: mlayer, nsoilmx
    44      USE comcstfi_mod, only: g, mugaz, omeg, rad, rcp, pi
    5       USE comvert_mod, ONLY: ap,bp,aps,bps,pseudoalt
    6       USE logic_mod, ONLY: fxyhypb,ysinus
    7       USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
     5      USE vertical_layers_mod, ONLY: ap,bp,aps,bps,pseudoalt
     6!      USE logic_mod, ONLY: fxyhypb,ysinus
     7!      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
    88      USE time_phylmdz_mod, ONLY: daysec, dtphys
    9       USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     9!      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    1010      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
    1111      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
     
    7575      tab_cntrl(10) = daysec
    7676      tab_cntrl(11) = dtphys
    77       tab_cntrl(12) = etot0
    78       tab_cntrl(13) = ptot0
    79       tab_cntrl(14) = ztot0
    80       tab_cntrl(15) = stot0
    81       tab_cntrl(16) = ang0
     77!      tab_cntrl(12) = etot0
     78!      tab_cntrl(13) = ptot0
     79!      tab_cntrl(14) = ztot0
     80!      tab_cntrl(15) = stot0
     81!      tab_cntrl(16) = ang0
    8282c
    8383c    ..........    P.Le Van  ( ajout le 8/04/96 )    .........
    8484c         .....        parametres  pour le zoom          ......   
    85       tab_cntrl(17)  = clon
    86       tab_cntrl(18)  = clat
    87       tab_cntrl(19)  = grossismx
    88       tab_cntrl(20)  = grossismy
     85!      tab_cntrl(17)  = clon
     86!      tab_cntrl(18)  = clat
     87!      tab_cntrl(19)  = grossismx
     88!      tab_cntrl(20)  = grossismy
    8989c
    9090c     .....   ajout  le 6/05/97 et le 15/10/97  .......
    9191c
    92       IF ( fxyhypb )   THEN
    93         tab_cntrl(21) = 1.
    94         tab_cntrl(22) = dzoomx
    95         tab_cntrl(23) = dzoomy
    96       ELSE
    97         tab_cntrl(21) = 0.
    98         tab_cntrl(22) = dzoomx
    99         tab_cntrl(23) = dzoomy
    100         tab_cntrl(24) = 0.
    101         IF( ysinus )  tab_cntrl(24) = 1.
    102       ENDIF
     92!      IF ( fxyhypb )   THEN
     93!        tab_cntrl(21) = 1.
     94!        tab_cntrl(22) = dzoomx
     95!        tab_cntrl(23) = dzoomy
     96!      ELSE
     97!        tab_cntrl(21) = 0.
     98!        tab_cntrl(22) = dzoomx
     99!        tab_cntrl(23) = dzoomy
     100!        tab_cntrl(24) = 0.
     101!        IF( ysinus )  tab_cntrl(24) = 1.
     102!      ENDIF
    103103
    104104c    .........................................................
  • trunk/LMDZ.GENERIC/libf/phystd/iniwrite_specIR.F

    r1531 r1621  
    55      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, pi
    66      use time_phylmdz_mod, only: daysec, dtphys
    7       USE logic_mod, ONLY: fxyhypb,ysinus
    8       USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
    9       USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     7!      USE logic_mod, ONLY: fxyhypb,ysinus
     8!      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
     9!      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    1010      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
    1111      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
     
    7777      tab_cntrl(10) = daysec
    7878      tab_cntrl(11) = dtphys
    79       tab_cntrl(12) = etot0
    80       tab_cntrl(13) = ptot0
    81       tab_cntrl(14) = ztot0
    82       tab_cntrl(15) = stot0
    83       tab_cntrl(16) = ang0
     79!      tab_cntrl(12) = etot0
     80!      tab_cntrl(13) = ptot0
     81!      tab_cntrl(14) = ztot0
     82!      tab_cntrl(15) = stot0
     83!      tab_cntrl(16) = ang0
    8484c
    8585c    ..........    P.Le Van  ( ajout le 8/04/96 )    .........
    8686c         .....        parametres  pour le zoom          ......   
    87       tab_cntrl(17)  = clon
    88       tab_cntrl(18)  = clat
    89       tab_cntrl(19)  = grossismx
    90       tab_cntrl(20)  = grossismy
     87!      tab_cntrl(17)  = clon
     88!      tab_cntrl(18)  = clat
     89!      tab_cntrl(19)  = grossismx
     90!      tab_cntrl(20)  = grossismy
    9191c
    9292c     .....   ajout  le 6/05/97 et le 15/10/97  .......
    9393c
    94       IF ( fxyhypb )   THEN
    95         tab_cntrl(21) = 1.
    96         tab_cntrl(22) = dzoomx
    97         tab_cntrl(23) = dzoomy
    98       ELSE
    99         tab_cntrl(21) = 0.
    100         tab_cntrl(22) = dzoomx
    101         tab_cntrl(23) = dzoomy
    102         tab_cntrl(24) = 0.
    103         IF( ysinus )  tab_cntrl(24) = 1.
    104       ENDIF
     94!      IF ( fxyhypb )   THEN
     95!        tab_cntrl(21) = 1.
     96!        tab_cntrl(22) = dzoomx
     97!        tab_cntrl(23) = dzoomy
     98!      ELSE
     99!        tab_cntrl(21) = 0.
     100!        tab_cntrl(22) = dzoomx
     101!        tab_cntrl(23) = dzoomy
     102!        tab_cntrl(24) = 0.
     103!        IF( ysinus )  tab_cntrl(24) = 1.
     104!      ENDIF
    105105
    106106c    .........................................................
  • trunk/LMDZ.GENERIC/libf/phystd/iniwrite_specVI.F

    r1531 r1621  
    55      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, pi
    66      use time_phylmdz_mod, only: daysec, dtphys
    7       USE logic_mod, ONLY: fxyhypb,ysinus
    8       USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
    9       USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     7!      USE logic_mod, ONLY: fxyhypb,ysinus
     8!      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
     9!      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    1010      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
    1111      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
     
    7777      tab_cntrl(10) = daysec
    7878      tab_cntrl(11) = dtphys
    79       tab_cntrl(12) = etot0
    80       tab_cntrl(13) = ptot0
    81       tab_cntrl(14) = ztot0
    82       tab_cntrl(15) = stot0
    83       tab_cntrl(16) = ang0
     79!      tab_cntrl(12) = etot0
     80!      tab_cntrl(13) = ptot0
     81!      tab_cntrl(14) = ztot0
     82!      tab_cntrl(15) = stot0
     83!      tab_cntrl(16) = ang0
    8484c
    8585c    ..........    P.Le Van  ( ajout le 8/04/96 )    .........
    8686c         .....        parametres  pour le zoom          ......   
    87       tab_cntrl(17)  = clon
    88       tab_cntrl(18)  = clat
    89       tab_cntrl(19)  = grossismx
    90       tab_cntrl(20)  = grossismy
     87!      tab_cntrl(17)  = clon
     88!      tab_cntrl(18)  = clat
     89!      tab_cntrl(19)  = grossismx
     90!      tab_cntrl(20)  = grossismy
    9191c
    9292c     .....   ajout  le 6/05/97 et le 15/10/97  .......
    9393c
    94       IF ( fxyhypb )   THEN
    95         tab_cntrl(21) = 1.
    96         tab_cntrl(22) = dzoomx
    97         tab_cntrl(23) = dzoomy
    98       ELSE
    99         tab_cntrl(21) = 0.
    100         tab_cntrl(22) = dzoomx
    101         tab_cntrl(23) = dzoomy
    102         tab_cntrl(24) = 0.
    103         IF( ysinus )  tab_cntrl(24) = 1.
    104       ENDIF
     94!      IF ( fxyhypb )   THEN
     95!        tab_cntrl(21) = 1.
     96!        tab_cntrl(22) = dzoomx
     97!        tab_cntrl(23) = dzoomy
     98!      ELSE
     99!        tab_cntrl(21) = 0.
     100!        tab_cntrl(22) = dzoomx
     101!        tab_cntrl(23) = dzoomy
     102!        tab_cntrl(24) = 0.
     103!        IF( ysinus )  tab_cntrl(24) = 1.
     104!      ENDIF
    105105
    106106c    .........................................................
  • trunk/LMDZ.GENERIC/libf/phystd/iostart.F90

    r1315 r1621  
    467467  USE mod_grid_phy_lmdz, only: klon_glo
    468468  USE dimphy, only: klev, klevp1
    469   USE infotrac, only: nqtot
     469  USE tracer_h, only: nqtot
    470470  USE comsoil_h, only: nsoilmx
    471471  USE slab_ice_h, only: noceanmx
  • trunk/LMDZ.GENERIC/libf/phystd/phyetat0.F90

    r1493 r1621  
    55
    66
    7   USE infotrac, ONLY: tname
     7  USE tracer_h, ONLY: noms
    88  USE surfdat_h, only: phisfi, albedodat, zmea, zstd, zsig, zgam, zthe
    99  use iostart, only: nid_start, open_startphy, close_startphy, &
     
    375375if (nq.ge.1) then
    376376  do iq=1,nq
    377     txt=tname(iq)
     377    txt=noms(iq)
    378378   
    379379    !! There was a bug here. MT2015.
  • trunk/LMDZ.GENERIC/libf/phystd/phyredem.F90

    r1543 r1621  
    141141  use iostart, only : open_restartphy, close_restartphy, &
    142142                      put_var, put_field
    143   use infotrac, only: tname
     143  use tracer_h, only: noms
    144144  use slab_ice_h, only: noceanmx
    145145  use callkeys_mod, only: ok_slab_ocean
     
    207207  if (nq>0) then
    208208    do iq=1,nq
    209       call put_field(tname(iq),"tracer on surface",qsurf(:,iq))
     209      call put_field(noms(iq),"tracer on surface",qsurf(:,iq))
    210210    enddo
    211211  endif ! of if (nq>0)
  • trunk/LMDZ.GENERIC/libf/phystd/tracer_h.F90

    r1315 r1621  
    33
    44       implicit none
     5
     6! nqtot : total number of tracers
     7       INTEGER, SAVE :: nqtot
     8!$OMP THREADPRIVATE(nqtot)
    59
    610       character*20, DIMENSION(:), ALLOCATABLE :: noms   ! name of the tracer
Note: See TracChangeset for help on using the changeset viewer.