Changeset 1621


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
Files:
9 added
75 edited

Legend:

Unmodified
Added
Removed
  • trunk/DOC/chantiers/commit_importants.log

    r1592 r1621  
    18831883* misc:
    18841884- added slopes_m.F90 and regr1_conserv_m.F90 used by Earth model
     1885
     1886**********************
     1887**** commit_v1621 ****
     1888**********************
     1889Ehouarn: Further work on full dynamics/physics separation.
     1890
     1891LMDZ.COMMON:
     1892- added phy_common/vertical_layers_mod.F90 to store information on vertical
     1893  grid. This is where routines in the physics should get the information.
     1894- The contents of vertical_layers_mod intialized via
     1895  dynphy_lonlat/inigeomphy_mod.F90.
     1896
     1897LMDZ.MARS:
     1898- physics now completely decoupled from dynamics; the physics package
     1899  may now be compiled as a library (-libphy option of makelmdz_fcm).
     1900- created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner
     1901  initialization of the later.
     1902- removed some purely dynamics-related outputs (etot0, zoom parameters, etc.)
     1903  from diagfi.nc and stats.nc outputs as these informations are not available
     1904  in the physics.
     1905
     1906LMDZ.GENERIC:
     1907- physics now completely decoupled from dynamics; the physics package
     1908  may now be compiled as a library (-libphy option of makelmdz_fcm).
     1909- added nqtot to tracer_h.F90.
     1910- removed some purely dynamics-related outputs (etot0, zoom parameters, etc.)
     1911  from diagfi.nc and stats.nc outputs as these informations are not available
     1912  in the physics.
     1913
     1914LMDZ.VENUS:
     1915- physics now completely decoupled from dynamics; the physics package
     1916  may now be compiled as a library (-libphy option of makelmdz_fcm).
     1917- added infotrac_phy.F90 to store information on tracers in the physics.
     1918  Initialized via iniphysiq.
     1919- added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the
     1920  physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded
     1921  constants! These should match what is in cpdet_mod.F90 in the dynamics.
     1922- got rid of references to moyzon_mod module within the physics. The
     1923  required variables (tmoy, plevmoy) are passed to the physics as arguments
     1924  to physiq.
     1925
     1926LMDZ.TITAN:
     1927- added infotrac_phy.F90 to store information on tracers in the physics.
     1928  Initialized via iniphysiq.
     1929- added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the
     1930  physics.
     1931- Extra work required to completely decouple physics and dynamics: moyzon_mod
     1932  should be cleaned up and information passed from dynamics to physics as
     1933  as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from
     1934  logic_mod (which is in the dynamics).
     1935
  • trunk/LMDZ.COMMON/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.COMMON/libf/dynphy_lonlat/phytitan/iniphysiq_mod.F90

    r1573 r1621  
    1414
    1515  USE temps_mod, ONLY: annee_ref, day_ref, day_ini, day_end
     16  USE comconst_mod, ONLY: cpp
     17  USE cpdet_phy_mod, ONLY: init_cpdet_phy
     18  USE infotrac, ONLY: nqtot, tname, ttext
     19  USE logic_mod, ONLY: iflag_trac
     20  USE infotrac_phy, ONLY: init_infotrac_phy
    1621  USE time_phylmdz_mod, ONLY: init_time
    1722  USE inigeomphy_mod, ONLY: inigeomphy
     
    7378  ! Initialize some physical constants
    7479  call suphec
     80 
     81  ! Initialize cpdet_phy module
     82  call init_cpdet_phy(cpp)
    7583
    7684  ! Initialize some "temporal and calendar" related variables
    7785  CALL init_time(annee_ref,day_ref,day_ini,day_end,nday,ptimestep)
     86
     87  ! Initialize tracers in physics
     88  CALL init_infotrac_phy(iflag_trac,nqtot,tname,ttext)
    7889
    7990!$OMP END PARALLEL
  • trunk/LMDZ.COMMON/libf/dynphy_lonlat/phyvenus/callphysiq_mod.F90

    r1576 r1621  
    2121  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    2222  USE physiq_mod, ONLY: physiq
     23  USE moyzon_mod, ONLY: plevmoy,tmoy ! planetary mean values to send to physics
    2324  IMPLICIT NONE
    2425
     
    8687              zqfi_omp,       &
    8788              flxwfi_omp,     &
     89              plevmoy,        & ! planet-averaged mean pressure (Pa) at interfaces
     90              tmoy,           & ! planet-averaged mean temperature (K) at mid-layers
    8891              zdufi_omp,      &
    8992              zdvfi_omp,      &
  • trunk/LMDZ.COMMON/libf/dynphy_lonlat/phyvenus/iniphysiq_mod.F90

    r1573 r1621  
    1414
    1515  USE temps_mod, ONLY: annee_ref, day_ref, day_ini, day_end
     16  USE comconst_mod, ONLY: nu_venus, t0_venus
     17  USE cpdet_phy_mod, ONLY: init_cpdet_phy
     18  USE infotrac, ONLY: nqtot, tname, ttext
     19  USE logic_mod, ONLY: iflag_trac
     20  USE infotrac_phy, ONLY: init_infotrac_phy
    1621  USE time_phylmdz_mod, ONLY: init_time
    1722  USE inigeomphy_mod, ONLY: inigeomphy
     
    7378  call suphec
    7479
     80  ! Initialize cpdet_phy module
     81  call init_cpdet_phy(pcpp,nu_venus,t0_venus)
     82 
    7583  ! Initialize some "temporal and calendar" related variables
    7684  CALL init_time(annee_ref,day_ref,day_ini,day_end,ptimestep)
     85 
     86  ! Initialize tracers in physics
     87  CALL init_infotrac_phy(iflag_trac,nqtot,tname,ttext)
    7788
    7889!$OMP END PARALLEL
  • 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
  • trunk/LMDZ.MARS/README

    r1617 r1621  
    23472347 tracer_mod.F90 (added some variables needed by CO2 microphysics)
    23482348 updaterad.F90 (added a routine for CO2 clouds)
     2349 
     2350== 25/10/2016 == EM
     2351Updates for full physics/dynamics separation:
     2352- introduced module vertical_layers_mod.F90 in phy_common to store information
     2353  about the vertical grid to be used in the physics. Routines in the physics
     2354  should "use vertical_layers_mod" and not "use comvert_mod".
     2355- created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner
     2356  initialization of the later. Module tracer_mod should be used in the
     2357  physics, not infotrac (belongs to the dynamics).
     2358- removed some purely dynamics-related outputs (etot0, zoom parameters, etc.)
     2359  from diagfi.nc and stats.nc outputs as these informations are not available
     2360  in the physics.
     2361- added scalheight (atmospheric scale height) in comvert_mod
     2362
  • trunk/LMDZ.MARS/libf/aeronomars/inichim_newstart.F90

    r1528 r1621  
    33
    44      use tracer_mod
    5       USE comvert_mod, ONLY: aps,bps
     5      USE vertical_layers_mod, ONLY: aps,bps
    66      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
    77      implicit none
  • trunk/LMDZ.MARS/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.MARS/libf/dyn3d/disvert.F

    r1422 r1621  
    55
    66      USE comvert_mod, ONLY: ap,bp,sig,nivsigs,nivsig,pa,preff,
    7      .                  aps,bps,presnivs,pseudoalt
     7     .                  aps,bps,presnivs,pseudoalt,scaleheight
    88      USE comconst_mod, ONLY: kappa,pi
    99      USE logic_mod, ONLY: hybrid
     
    2525      INTEGER l,ll
    2626      REAL snorm
    27       REAL alpha,beta,gama,delta,deltaz,h,quoi,quand
     27      REAL alpha,beta,gama,delta,deltaz,quoi,quand
    2828      REAL zsig(llm)
    2929      INTEGER np,ierr
     
    7070         PRINT*,'WARNING Lecture de esasig.def'
    7171         PRINT*,'*****************************'
    72          READ(99,*) h
     72         READ(99,*) scaleheight
    7373         READ(99,*) dz0
    7474         READ(99,*) dz1
     
    7676         CLOSE(99)
    7777
    78          dz0=dz0/h
    79          dz1=dz1/h
     78         dz0=dz0/scaleheight
     79         dz1=dz1/scaleheight
    8080
    8181         sig1=(1.-dz1)/tanh(.5*(llm-1)/nhaut)
     
    120120         PRINT*,'****************************'
    121121
    122          READ(99,*) h
     122         READ(99,*) scaleheight
    123123         do l=1,llm
    124124            read(99,*) zsig(l)
     
    128128         sig(1) =1
    129129         do l=2,llm
    130            sig(l) = 0.5 * ( exp(-zsig(l)/h) + exp(-zsig(l-1)/h) )
     130           sig(l) = 0.5 * ( exp(-zsig(l)/scaleheight) +
     131     &                      exp(-zsig(l-1)/scaleheight) )
    131132         end do
    132133         sig(llm+1) =0
  • trunk/LMDZ.MARS/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.MARS/libf/dynphy_lonlat/phymars/iniphysiq_mod.F90

    r1573 r1621  
    1010                     prad,pg,pr,pcpp,iflag_phys)
    1111
    12 use infotrac, only : nqtot ! number of advected tracers
     12use infotrac, only : nqtot, & ! number of advected tracers
     13                     tname ! tracer names
    1314use comgeomfi_h, only: ini_fillgeom
    1415use temps_mod, only: day_ini, hour_ini
     
    6869call init_dimphy(klon_omp,nlayer)
    6970
    70 call phys_state_var_init(klon_omp,nlayer,nqtot, &
     71call phys_state_var_init(klon_omp,nlayer,nqtot,tname, &
    7172                         day_ini,hour_ini,punjours,ptimestep, &
    7273                         prad,pg,pr,pcpp)
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F

    r1576 r1621  
    2121     &                            ecritphy, iphysiq
    2222      use dimradmars_mod, only: tauscaling,tauvis
    23       USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff,sig
     23      USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff,sig,
     24     &                       presnivs,pseudoalt,scaleheight
     25      USE vertical_layers_mod, ONLY: init_vertical_layers
    2426      USE logic_mod, ONLY: hybrid
    2527      use physics_distribution_mod, only: init_physics_distribution
     
    4951c=======================================================================
    5052
    51 #include "dimensions.h"
     53      include "dimensions.h"
    5254      integer, parameter :: ngrid = 1 !(2+(jjm-1)*iim - 1/jjm)
    5355      integer, parameter :: nlayer = llm
     
    5860!#include "comsoil.h"
    5961!#include "comdiurn.h"
    60 #include "callkeys.h"
     62      include "callkeys.h"
    6163!#include "comsaison.h"
    6264!#include "control.h"
    63 #include "netcdf.inc"
    64 #include "comg1d.h"
     65      include "netcdf.inc"
     66      include "comg1d.h"
    6567!#include "advtrac.h"
    6668
     
    494496     &                   (/0.,0.,0.,0./),(/0.,0.,0.,0./),
    495497     &                   cell_area)
     498! Ehouarn: init_vertial_layers called later (because disvert not called yet)
     499!      call init_vertical_layers(nlayer,preff,scaleheight,
     500!     &                      ap,bp,aps,bps,presnivs,pseudoalt)
    496501      call init_dimphy(1,nlayer) ! Initialize dimphy module
    497       call phys_state_var_init(1,llm,nq,
     502      call phys_state_var_init(1,llm,nq,tname,
    498503     .          day0,time,daysec,dtphys,rad,g,r,cpp)
    499504      call ini_fillgeom(1,latitude,longitude,(/1.0/))
     
    611616
    612617      CALL  disvert
     618      ! now that disvert has been called, initialize module vertical_layers_mod
     619      call init_vertical_layers(nlayer,preff,scaleheight,
     620     &                      ap,bp,aps,bps,presnivs,pseudoalt)
    613621
    614622      DO ilevel=1,nlevel
  • trunk/LMDZ.MARS/libf/phymars/eofdump_mod.F90

    r1543 r1621  
    8181
    8282      use geometry_mod, only: longitude, latitude
    83       use comcstfi_h, only: pi
     83      use nrtype, only: pi
    8484      use time_phylmdz_mod, only: daysec, dtphys
    85       USE comvert_mod, ONLY: aps,bps
     85      USE vertical_layers_mod, ONLY: aps,bps
    8686      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat
    8787      implicit none
  • trunk/LMDZ.MARS/libf/phymars/inistats.F

    r1532 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 comcstfi_h, 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.MARS/libf/phymars/initracer.F

    r1617 r1621  
    11      SUBROUTINE initracer(ngrid,nq,qsurf)
    22
    3 #ifndef MESOSCALE
    4        use infotrac, only: tname
    5 #endif
    63       use tracer_mod
    74       USE comcstfi_h
     
    5451c-----------------------------------------------------------------------
    5552
    56 ! Initialization: allocate arrays in tracer_mod
    57       allocate(mmol(nq))
    58       allocate(radius(nq))
    59       allocate(rho_q(nq))
    60       allocate(alpha_lift(nq))
    61       allocate(alpha_devil(nq))
    62       allocate(igcm_dustbin(nq))
    63       allocate(nqdust(nq))
    64 
    65 #ifndef MESOSCALE
    66       allocate(noms(nq))
    67 ! Initialization: get tracer names from the dynamics and check if we are
    68 !                 using 'old' tracer convention ('q01',q02',...)
    69 !                 or new convention (full tracer names)
    70       ! check if tracers have 'old' names
    71 
    72       count=0
    73       do iq=1,nq
    74         txt=" "
    75         write(txt,'(a1,i2.2)') 'q',iq
    76         if (txt.eq.tname(iq)) then
    77           count=count+1
    78         endif
    79       enddo ! of do iq=1,nq
    80      
    81       if (count.eq.nq) then
    82         write(*,*) "initracer: tracers seem to follow old naming ",
    83      &             "convention (q01,q02,...)"
    84         write(*,*) "you should run newstart to rename them"
    85         stop
    86       endif
    87 
    88       ! copy tracer names from dynamics
    89       do iq=1,nq
    90         noms(iq)=tname(iq)
    91         write(*,*) "initracer names : ", noms(iq)
    92       enddo
    93 #endif
    9453
    9554c------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/iniwrite.F

    r1532 r1621  
    33      use comsoil_h, only: mlayer, nsoilmx
    44      USE comcstfi_h, 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: hour_ini, 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
    8282
    8383      tab_cntrl(27) = hour_ini
     
    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.MARS/libf/phymars/iostart.F90

    r1504 r1621  
    464464  USE mod_grid_phy_lmdz, only: klon_glo
    465465  USE dimphy, only: klev, klevp1
    466   USE infotrac, only: nqtot
     466  USE tracer_mod, only: nqmx
    467467  USE comsoil_h, only: nsoilmx
    468468  IMPLICIT NONE
     
    528528      ENDIF
    529529     
    530       if (nqtot.ne.0) then
    531         ierr=NF90_DEF_DIM(nid_restart,"number_of_advected_fields",nqtot,idim5)
     530      if (nqmx.ne.0) then
     531        ierr=NF90_DEF_DIM(nid_restart,"number_of_advected_fields",nqmx,idim5)
    532532      else
    533         ! pretend nqtot=1 because 0 size implies unlimited dimension for NetCDF
     533        ! pretend nqmx=1 because 0 size implies unlimited dimension for NetCDF
    534534        ierr=NF90_DEF_DIM(nid_restart,"number_of_advected_fields",1,idim5)
    535535      endif
  • trunk/LMDZ.MARS/libf/phymars/newcondens.F

    r1543 r1621  
    1212       USE comcstfi_h
    1313#ifndef MESOSCALE
    14        USE comvert_mod, ONLY: bp
     14       USE vertical_layers_mod, ONLY: bp
    1515#endif
    1616       IMPLICIT NONE
  • trunk/LMDZ.MARS/libf/phymars/phyetat0.F90

    r1525 r1621  
    33                     tauscaling)
    44!  use netcdf
    5   use infotrac, only: nqtot, tname
     5  use tracer_mod, only: noms ! tracer names
    66  use surfdat_h, only: phisfi, albedodat, z0, z0_default,&
    77                       zmea, zstd, zsig, zgam, zthe
     
    289289if (nq.ge.1) then
    290290  do iq=1,nq
    291     txt=tname(iq)
     291    txt=noms(iq)
    292292    if (txt.eq."h2o_vap") then
    293293      ! There is no surface tracer for h2o_vap;
  • trunk/LMDZ.MARS/libf/phymars/phyredem.F90

    r1543 r1621  
    1212                         alb,ith,pzmea,pzstd,pzsig,pzgam,pzthe)
    1313! create physics restart file and write time-independent variables
    14   use infotrac, only: nqtot, tname
    1514  use comsoil_h, only: inertiedat, volcapa, mlayer
    1615  use geometry_mod, only: cell_area
     
    150149  use iostart, only : open_restartphy, close_restartphy, &
    151150                      put_var, put_field
    152   use infotrac, only: nqtot, tname
     151  use tracer_mod, only: noms ! tracer names
    153152  implicit none
    154153  character(len=*),intent(in) :: filename
     
    204203  ! preliminary stuff: look for water vapour & water ice tracers (if any)
    205204  do iq=1,nq
    206     if (tname(iq).eq."h2o_vap") then
     205    if (noms(iq).eq."h2o_vap") then
    207206      i_h2o_vap=iq
    208207    endif
    209     if (tname(iq).eq."h2o_ice") then
     208    if (noms(iq).eq."h2o_ice") then
    210209      i_h2o_ice=iq
    211210    endif
     
    214213  if (nq.gt.0) then
    215214    do iq=1,nq
    216       txt=tname(iq)
     215      txt=noms(iq)
    217216      ! Exception: there is no water vapour surface tracer
    218217      if (txt.eq."h2o_vap") then
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90

    r1524 r1621  
    33CONTAINS
    44
    5       SUBROUTINE phys_state_var_init(ngrid,nlayer,nq, &
     5      SUBROUTINE phys_state_var_init(ngrid,nlayer,nq,tname, &
    66                                     day_ini,hour_ini,pdaysec,ptimestep, &
    77                                     prad,pg,pr,pcpp)
     
    4444      use turb_mod, only: ini_turb_mod
    4545      use comcstfi_h, only: pi,rad,cpp,g,r,rcp
    46       use tracer_mod, only: nqmx
     46      use tracer_mod, only: ini_tracer_mod
    4747      use time_phylmdz_mod, only: init_time
    4848
     
    5050     
    5151      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
     52      CHARACTER(len=*),INTENT(IN) :: tname(nq)
    5253      INTEGER,INTENT(IN) :: day_ini
    5354      REAL,INTENT(IN) :: hour_ini
    5455      REAL,INTENT(IN) :: pdaysec,ptimestep,prad,pg,pr,pcpp
    5556
    56       ! set dimension in tracer_mod
    57       nqmx=nq
     57      ! set dimension and allocate arrays in tracer_mod
     58      call ini_tracer_mod(nq,tname)
    5859
    5960      ! set parameters in comcstfi_h
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r1618 r1621  
    5353      use phyredem, only: physdem0, physdem1
    5454      use eofdump_mod, only: eofdump
    55       USE comvert_mod, ONLY: ap,bp,aps,bps
     55      USE vertical_layers_mod, ONLY: ap,bp,aps,bps
    5656#endif
    5757
  • trunk/LMDZ.MARS/libf/phymars/tracer_mod.F90

    r1617 r1621  
    8888!-----------------------------------------------------------------------
    8989
     90  contains
     91 
     92    subroutine ini_tracer_mod(nq,tname)
     93      implicit none
     94     
     95      integer,intent(in) :: nq ! number of tracers
     96      character(len=*),intent(in) :: tname(nq) ! tracer names
     97     
     98      integer :: iq, count
     99      character(len=20) :: txt ! to store some text
     100     
     101      ! set dimension and tracer names
     102      nqmx=nq
     103#ifndef MESOSCALE
     104      allocate(noms(nq))
     105      do iq=1,nq
     106        noms(iq)=tname(iq)
     107        write(*,*) "tracer_mod names : ", trim(noms(iq))
     108      enddo
     109     
     110      ! check if tracers have 'old' names
     111      count=0
     112      do iq=1,nq
     113        txt=" "
     114        write(txt,'(a1,i2.2)') 'q',iq
     115        if (txt.eq.tname(iq)) then
     116          count=count+1
     117        endif
     118      enddo ! of do iq=1,nq
     119     
     120      if (count.eq.nq) then
     121        write(*,*) "ini_tracer_mod: tracers seem to follow old naming ", &
     122                   "convention (q01,q02,...)"
     123        write(*,*) "you should run newstart to rename them"
     124        stop
     125      endif
     126#endif
     127           
     128      ! allocate module arrays:
     129      allocate(mmol(nq))
     130      allocate(radius(nq))
     131      allocate(rho_q(nq))
     132      allocate(alpha_lift(nq))
     133      allocate(alpha_devil(nq))
     134      allocate(igcm_dustbin(nq))
     135      allocate(nqdust(nq))
     136     
     137    end subroutine ini_tracer_mod
     138
    90139end module tracer_mod
  • trunk/LMDZ.TITAN/libf/phytitan/ajsec.F

    r1530 r1621  
    88      use dimphy
    99      use mod_grid_phy_lmdz, only: nbp_lev
    10       use cpdet_mod, only: t2tpot, tpot2t
     10      use cpdet_phy_mod, only: t2tpot, tpot2t
    1111      IMPLICIT none
    1212c======================================================================
  • trunk/LMDZ.TITAN/libf/phytitan/clmain.F

    r1530 r1621  
    3636      use dimphy
    3737      use mod_grid_phy_lmdz, only: nbp_lev
    38       use cpdet_mod, only: t2tpot
     38      use cpdet_phy_mod, only: t2tpot
    3939      IMPLICIT none
    4040c======================================================================
     
    480480      use dimphy
    481481      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev
    482       use cpdet_mod, only: t2tpot,tpot2t,cpdet
     482      use cpdet_phy_mod, only: t2tpot,tpot2t,cpdet
    483483
    484484      IMPLICIT none
     
    887887
    888888      use dimphy
    889       use cpdet_mod, only: cpdet,t2tpot
     889      use cpdet_phy_mod, only: cpdet,t2tpot
    890890      IMPLICIT none
    891891c======================================================================
     
    11711171      use dimphy
    11721172      use mod_grid_phy_lmdz, only: nbp_lev
    1173       use cpdet_mod, only: cpdet
     1173      use cpdet_phy_mod, only: cpdet
    11741174      IMPLICIT none
    11751175c======================================================================
  • trunk/LMDZ.TITAN/libf/phytitan/diagphy.F

    r1530 r1621  
    208208 
    209209      use dimphy
    210       use cpdet_mod, only: cpdet
     210      use cpdet_phy_mod, only: cpdet
    211211      IMPLICIT NONE
    212212C
  • trunk/LMDZ.TITAN/libf/phytitan/interface_surf.F90

    r1056 r1621  
    4646
    4747      use write_field_phy
    48       use cpdet_mod, only: cpdet
     48      use cpdet_phy_mod, only: cpdet
    4949
    5050      IMPLICIT none
     
    197197
    198198  use write_field_phy
    199   use cpdet_mod, only: t2tpot, tpot2t
     199  use cpdet_phy_mod, only: t2tpot, tpot2t
    200200
    201201  IMPLICIT none
  • trunk/LMDZ.TITAN/libf/phytitan/optci.F

    r1461 r1621  
    11      SUBROUTINE OPTCI(ykim,qaer,nmicro,IPRINT)
    22      use dimphy
    3       use infotrac
     3      use infotrac_phy, only: nqtot
    44      use common_mod, only:rmcbar,xfbar,ncount,TauHID,TauCID,TauGID
    55      USE TGMDAT_MOD, ONLY: RHCH4,FH2,FHAZE,FHVIS,FHIR,TAUFAC,
  • trunk/LMDZ.TITAN/libf/phytitan/optcv.F

    r1461 r1621  
    22
    33      use dimphy
    4       use infotrac
     4      use infotrac_phy, only: nqtot
    55      use common_mod, only:rmcbar,xfbar,ncount,TauHVD,TauCVD,TauGVD
    66      USE TGMDAT_MOD, ONLY: RHCH4,FH2,FHAZE,FHVIS,FHIR,TAUFAC,
  • trunk/LMDZ.TITAN/libf/phytitan/phyetat0.F90

    r1545 r1621  
    1212      USE phys_state_var_mod
    1313      USE iostart
    14       USE infotrac
    1514      USE geometry_mod,  only: latitude_deg,longitude_deg
    1615      USE time_phylmdz_mod, only: itau_phy, raz_date
  • trunk/LMDZ.TITAN/libf/phytitan/phyredem.F90

    r1545 r1621  
    1111      USE iostart, only : open_restartphy,close_restartphy, &
    1212                          put_var,put_field
    13       USE infotrac
    1413      USE geometry_mod,  only: longitude_deg, latitude_deg
    1514      USE time_phylmdz_mod, only: day_end, annee_ref, itau_phy, raz_date
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F

    r1572 r1621  
    6161      USE ioipsl
    6262!      USE histcom ! not needed; histcom is included in ioipsl
    63       USE infotrac
     63      USE infotrac_phy, ONLY: iflag_trac, tname, ttext
    6464      use dimphy
    6565      USE geometry_mod, ONLY: longitude, latitude, ! in radians
    6666     &                        longitude_deg, latitude_deg, ! in degrees
    6767     &                        cell_area, dx, dy
    68       use cpdet_mod, only: cpdet, t2tpot
     68      use cpdet_phy_mod, only: cpdet, t2tpot
    6969      USE mod_phys_lmdz_para, only : is_parallel,jj_nb,
    7070     &                               is_north_pole_phy,
     
    8181      USE write_field_phy
    8282      USE time_phylmdz_mod, only: itau_phy,day_ref,annee_ref,nday
    83       USE logic_mod, only: iflag_trac,moyzon_ch,moyzon_mu
     83      USE logic_mod, only: moyzon_ch,moyzon_mu
    8484      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
    8585      IMPLICIT none
  • trunk/LMDZ.TITAN/libf/phytitan/phytrac.F

    r1443 r1621  
    3838c reservoir----outpur-R-un reservoir de surface !!! (m)
    3939c======================================================================
    40       USE infotrac
     40      USE infotrac_phy, ONLY: tname
    4141      use dimphy
    4242      USE common_mod, only: rmcbar,xfbar,ncount,
  • trunk/LMDZ.TITAN/libf/phytitan/radtitan.F

    r1545 r1621  
    3131c   -------------
    3232
    33       USE infotrac
     33      USE infotrac_phy, ONLY: tname
    3434      use dimphy
    3535      USE geometry_mod, ONLY: latitude ! in radians
  • trunk/LMDZ.VENUS/libf/phyvenus/ajsec.F

    r1530 r1621  
    88      use dimphy
    99      use mod_grid_phy_lmdz, only: nbp_lev
    10       use cpdet_mod, only: t2tpot, tpot2t
     10      use cpdet_phy_mod, only: t2tpot, tpot2t
    1111      IMPLICIT none
    1212c======================================================================
  • trunk/LMDZ.VENUS/libf/phyvenus/chemparam_mod.F90

    r1468 r1621  
    671671 
    672672  SUBROUTINE chemparam_ini
    673   USE infotrac
     673  USE infotrac_phy, ONLY: nqtot, tname
    674674  IMPLICIT NONE
    675675  INTEGER :: i
  • trunk/LMDZ.VENUS/libf/phyvenus/clmain.F

    r1591 r1621  
    3636      use dimphy
    3737      use mod_grid_phy_lmdz, only: nbp_lev
    38       use cpdet_mod, only: t2tpot
     38      use cpdet_phy_mod, only: t2tpot
    3939      IMPLICIT none
    4040c======================================================================
     
    480480      use dimphy
    481481      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev
    482       use cpdet_mod, only: t2tpot,tpot2t,cpdet
     482      use cpdet_phy_mod, only: t2tpot,tpot2t,cpdet
    483483
    484484      IMPLICIT none
     
    918918
    919919      use dimphy
    920       use cpdet_mod, only: cpdet,t2tpot
     920      use cpdet_phy_mod, only: cpdet,t2tpot
    921921      IMPLICIT none
    922922c======================================================================
     
    12291229      use dimphy
    12301230      use mod_grid_phy_lmdz, only: nbp_lev
    1231       use cpdet_mod, only: cpdet
     1231      use cpdet_phy_mod, only: cpdet
    12321232      IMPLICIT none
    12331233c======================================================================
  • trunk/LMDZ.VENUS/libf/phyvenus/concentrations2.F

    r1591 r1621  
    33      use dimphy
    44      use conc,  only: mmean, rho, Akknew, rnew, cpnew
    5       use cpdet_mod, only: cpdet                       
     5      use cpdet_phy_mod, only: cpdet                       
    66      USE chemparam_mod
    7       use infotrac
    87
    98      implicit none
  • trunk/LMDZ.VENUS/libf/phyvenus/diagphy.F

    r1530 r1621  
    208208 
    209209      use dimphy
    210       use cpdet_mod, only: cpdet
     210      use cpdet_phy_mod, only: cpdet
    211211      IMPLICIT NONE
    212212C
  • trunk/LMDZ.VENUS/libf/phyvenus/dyn1d/rcm1d.F

    r1549 r1621  
    403403     ,     plev,play,pk,phi,phisfi,
    404404     ,     presnivs,
    405      ,     u,v,temp,q, 
     405     ,     u,v,temp,q,
     406     ,     plev,temp, ! "planetary mean" plev and temperature
    406407     ,     w,
    407408C - sorties
  • trunk/LMDZ.VENUS/libf/phyvenus/flott_gwd_ran.F90

    r1591 r1621  
    11      SUBROUTINE FLOTT_GWD_RAN(NLON,NLEV,DTIME, pp, pn2,  &
    2                   tt,uu,vv,zustr,zvstr,d_t, d_u, d_v)
     2                  tt,uu,vv, plevmoy, &
     3                  zustr,zvstr,d_t, d_u, d_v)
    34
    45    !----------------------------------------------------------------------
     
    1415
    1516      use dimphy
    16       use moyzon_mod, only: plevmoy
    1717      implicit none
    1818
     
    3232    REAL, intent(in):: UU(NLON, NLEV) , VV(NLON, NLEV)
    3333    ! Hor winds at full levels
     34    REAL, intent(in) :: plevmoy(NLEV+1) ! (planet-averaged) mean pressure (Pa) at interlayers
    3435
    3536    ! 0.2 OUTPUTS
  • trunk/LMDZ.VENUS/libf/phyvenus/interface_surf.F90

    r1017 r1621  
    4646
    4747      use write_field_phy
    48       use cpdet_mod, only: cpdet
     48      use cpdet_phy_mod, only: cpdet
    4949
    5050      IMPLICIT none
     
    197197
    198198  use write_field_phy
    199   use cpdet_mod, only: t2tpot, tpot2t
     199  use cpdet_phy_mod, only: t2tpot, tpot2t
    200200
    201201  IMPLICIT none
  • trunk/LMDZ.VENUS/libf/phyvenus/lw_venus_ve.F

    r1530 r1621  
    66     
    77      use dimphy
    8       use cpdet_mod, only: cpdet
     8      use cpdet_phy_mod, only: cpdet
    99      IMPLICIT none
    1010
  • trunk/LMDZ.VENUS/libf/phyvenus/lwi.F

    r1530 r1621  
    22
    33      use dimphy
    4       use cpdet_mod, only: cpdet
     4      use cpdet_phy_mod, only: cpdet
    55      implicit none
    66
  • trunk/LMDZ.VENUS/libf/phyvenus/moldiff_red.F90

    r1609 r1621  
    33
    44USE chemparam_mod
    5 USE infotrac
     5USE infotrac_phy
    66USE dimphy   
    77
     
    935935        SUBROUTINE QMNEW(Q1,DQ,Q2,dtime,nl,nq,gc,ig)
    936936        use chemparam_mod
    937         use infotrac
     937        use infotrac_phy
    938938        IMPLICIT NONE
    939939
     
    971971        SUBROUTINE MMOY(massemoy,mol_tr,qq,gc,nl,nq)
    972972        use chemparam_mod
    973         use infotrac
     973        use infotrac_phy
    974974        IMPLICIT NONE
    975975
     
    10571057     & Nraf,Nrafk,Rraf,Rrafk,il,nl,nq,nlx,ig)
    10581058        use chemparam_mod
    1059         use infotrac
     1059        use infotrac_phy
    10601060        IMPLICIT NONE
    10611061#include "YOMCST.h"
     
    14011401     &    pp,M,gc,nl,nq,nlx,ig)
    14021402        use chemparam_mod
    1403         use infotrac
     1403        use infotrac_phy
    14041404        IMPLICIT NONE
    14051405#include "YOMCST.h"
  • trunk/LMDZ.VENUS/libf/phyvenus/moldiffcoeff_red.F

    r1530 r1621  
    22
    33       USE chemparam_mod
    4        USE infotrac
     4       USE infotrac_phy
    55       USE dimphy   
    6        use infotrac
    76
    87       IMPLICIT NONE
  • trunk/LMDZ.VENUS/libf/phyvenus/new_cloud_sedim.F

    r1543 r1621  
    55
    66      USE ioipsl
    7       USE infotrac
    87      USE dimphy
    98      USE chemparam_mod
  • trunk/LMDZ.VENUS/libf/phyvenus/new_photochemistry_venus.F90

    r1525 r1621  
    55
    66 USE chemparam_mod
    7  USE infotrac
    87     
    98 implicit none
  • trunk/LMDZ.VENUS/libf/phyvenus/phyetat0.F90

    r1545 r1621  
    1212      USE phys_state_var_mod
    1313      USE iostart
    14       USE infotrac
    1514      use geometry_mod, only: longitude_deg, latitude_deg
    1615      USE time_phylmdz_mod, only: itau_phy, raz_date
  • trunk/LMDZ.VENUS/libf/phyvenus/phyredem.F90

    r1545 r1621  
    1111      USE iostart, only : open_restartphy,close_restartphy, &
    1212                          put_var,put_field
    13       USE infotrac
    1413      use geometry_mod, only: longitude_deg, latitude_deg
    1514      USE time_phylmdz_mod, only: day_end, annee_ref, itau_phy, raz_date
  • trunk/LMDZ.VENUS/libf/phyvenus/physiq_mod.F

    r1572 r1621  
    1212     .            paprs,pplay,ppk,pphi,pphis,presnivs,
    1313     .            u,v,t,qx,
    14      .            flxmw,
     14     .            flxmw, plevmoy, tmoy,
    1515     .            d_u, d_v, d_t, d_qx, d_ps)
    1616
     
    6161      USE ioipsl
    6262!      USE histcom ! not needed; histcom is included in ioipsl
    63       USE infotrac
    6463      use dimphy
    6564      USE geometry_mod,only: longitude, latitude, ! in radians
     
    7271      USE write_field_phy
    7372      USE iophy
    74       USE cpdet_mod, only: cpdet, t2tpot
     73      USE cpdet_phy_mod, only: cpdet, t2tpot
    7574      USE chemparam_mod
    7675      USE conc
    7776      USE compo_hedin83_mod2
    78       use moyzon_mod, only: tmoy
    7977!      use ieee_arithmetic
    8078      use time_phylmdz_mod, only: annee_ref, day_ref, itau_phy
    8179      use mod_grid_phy_lmdz, only: nbp_lon
    82       use logic_mod, only: iflag_trac
     80      use infotrac_phy, only: iflag_trac, tname, ttext
    8381      IMPLICIT none
    8482c======================================================================
     
    139137
    140138      REAL flxmw(klon,klev)
     139      REAL,INTENT(IN) :: plevmoy(klev+1) ! planet-averaged mean pressure (Pa) at interfaces
     140      REAL,INTENT(IN) :: tmoy(klev) ! planet-averaged mean temperature (Pa) at mid-layers
    141141
    142142      REAL d_u(klon,klev)
     
    15491549
    15501550      call flott_gwd_ran(klon,klev,dtime,pplay,zn2,
    1551      e               t_seri, u_seri, v_seri,
     1551     e               t_seri, u_seri, v_seri, plevmoy,
    15521552     o               zustrhi,zvstrhi,
    15531553     o               d_t_hin, d_u_hin, d_v_hin)
  • trunk/LMDZ.VENUS/libf/phyvenus/phytrac_emiss.F

    r1543 r1621  
    2828c
    2929c======================================================================
    30       USE infotrac
     30      USE infotrac_phy, ONLY: nqtot
    3131      use dimphy
    3232      USE geometry_mod, only: cell_area
  • trunk/LMDZ.VENUS/libf/phyvenus/phytrac_relax.F

    r1543 r1621  
    2525c
    2626c======================================================================
    27       USE infotrac
     27      USE infotrac_phy, ONLY: nqtot, tname
    2828      use dimphy
    2929      USE chemparam_mod,only:M_tr
  • trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_cl.F

    r1530 r1621  
    55     
    66      use dimphy
    7       use cpdet_mod, only: cpdet
     7      use cpdet_phy_mod, only: cpdet
    88      IMPLICIT none
    99
  • trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_cl_1Dglobave.F

    r1530 r1621  
    55     
    66      use dimphy
    7       use cpdet_mod, only: cpdet
     7      use cpdet_phy_mod, only: cpdet
    88      IMPLICIT none
    99
  • trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_dc.F

    r1530 r1621  
    55     
    66      use dimphy
    7       use cpdet_mod, only: cpdet
     7      use cpdet_phy_mod, only: cpdet
    88      IMPLICIT none
    99
  • trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_dc_1Dglobave.F

    r1530 r1621  
    55     
    66      use dimphy
    7       use cpdet_mod, only: cpdet
     7      use cpdet_phy_mod, only: cpdet
    88      IMPLICIT none
    99
  • trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_rh.F

    r1591 r1621  
    55     
    66      use dimphy
    7       use cpdet_mod, only: cpdet
     7      use cpdet_phy_mod, only: cpdet
    88      IMPLICIT none
    99
  • trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_rh_1Dglobave.F

    r1591 r1621  
    55     
    66      use dimphy
    7       use cpdet_mod, only: cpdet
     7      use cpdet_phy_mod, only: cpdet
    88      IMPLICIT none
    99
  • trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_ve.F

    r1530 r1621  
    55     
    66      use dimphy
    7       use cpdet_mod, only: cpdet
     7      use cpdet_phy_mod, only: cpdet
    88      IMPLICIT none
    99
  • trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_ve_1Dglobave.F

    r1530 r1621  
    55     
    66      use dimphy
    7       use cpdet_mod, only: cpdet
     7      use cpdet_phy_mod, only: cpdet
    88      IMPLICIT none
    99
Note: See TracChangeset for help on using the changeset viewer.