Ignore:
Timestamp:
Jun 25, 2015, 5:25:50 PM (10 years ago)
Author:
Ehouarn Millour
Message:

More on physics/dynamics separation: make a vertical_layers_mod module to contain information on the vertical discretization. This module should be used from within the physics (instead of including comvert.h from dynamics).
EM

Location:
LMDZ5/trunk/libf/phylmd
Files:
1 added
9 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/dyn1d/lmdz1d.F90

    r2311 r2315  
    2323      USE mod_1D_amma_read
    2424      USE print_control_mod, ONLY: prt_level
     25      USE vertical_layers_mod, ONLY: init_vertical_layers
    2526
    2627      implicit none
     
    540541!       Dans ce cas, on lit ap,bp dans le fichier hybrid.txt
    541542      ENDIF
     543      ! initialize ap,bp, etc. in vertical_layers_mod
     544      call init_vertical_layers(llm,preff,scaleheight, &
     545                            ap,bp,presnivs,pseudoalt)
     546
    542547      sig_s=presnivs/preff
    543548      plev =ap+bp*psurf
  • LMDZ5/trunk/libf/phylmd/ecribin.F90

    r1992 r2315  
    1010  include "paramet.h"
    1111  include "comgeom.h"
    12   include "comvert.h"
    1312
    1413  ! arguments:
     
    5251  include "paramet.h"
    5352  include "comgeom.h"
    54   include "comvert.h"
    5553
    5654  ! arguments:
  • LMDZ5/trunk/libf/phylmd/ecrireg.F90

    r1992 r2315  
    1010  include "paramet.h"
    1111  include "comgeom.h"
    12   include "comvert.h"
    1312  include "regdim.h"
    1413
     
    6665  include "paramet.h"
    6766  include "comgeom.h"
    68   include "comvert.h"
    6967  include "regdim.h"
    7068
  • LMDZ5/trunk/libf/phylmd/inistats.F90

    r1992 r2315  
    11SUBROUTINE inistats(ierr)
     2
     3  USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs,pseudoalt
    24
    35  IMPLICIT NONE
     
    68  include "paramet.h"
    79  include "comgeom.h"
    8   include "comvert.h"
    910  include "comconst.h"
    1011  include "statto.h"
     
    4041  DO l = 1, llm
    4142    sig_s(l) = ((ap(l)+ap(l+1))/preff+bp(l)+bp(l+1))/2.
    42     pseudoalt(l) = log(preff/presnivs(l))*8.
    4343  END DO
    4444
  • LMDZ5/trunk/libf/phylmd/limit_netcdf.F90

    r2311 r2315  
    4242! Local variables:
    4343  include "logic.h"
    44   include "comvert.h"
    4544  include "comgeom2.h"
    4645  include "comconst.h"
  • LMDZ5/trunk/libf/phylmd/phys_output_mod.F90

    r2311 r2315  
    4646    USE mod_grid_phy_lmdz, only: klon_glo
    4747    USE print_control_mod, ONLY: prt_level,lunout
     48    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs
    4849
    4950#ifdef CPP_XIOS
     
    5758    include "clesphys.h"
    5859    include "thermcell.h"
    59     include "comvert.h"
    6060
    6161    ! ug Nouveaux arguments n\'ecessaires au histwrite_mod:
  • LMDZ5/trunk/libf/phylmd/readaerosol_interp.F90

    r2311 r2315  
    3030  INCLUDE "clesphys.h"
    3131  INCLUDE "dimensions.h"
    32   INCLUDE "comvert.h"
    3332!
    3433! Input:
  • LMDZ5/trunk/libf/phylmd/rrtm/suphec.F90

    r2043 r2315  
    8787USE YOM_PHYS_GRID ,ONLY : PHYS_GRID
    8888USE YOMCT0  , ONLY  : LSCMEC   ,LROUGH   ,REXTZ0M  ,REXTZ0H
     89USE vertical_layers_mod, ONLY: ap,bp
    8990
    9091IMPLICIT NONE
     
    115116#include "suwcou.intfb.h"
    116117#include "dimensions.h"
    117 #include "comvert.h"
    118118
    119119!     ------------------------------------------------------------------
     
    168168!ALLOCATE(VBH    (0:MAX(JPMXLE,NFLEVG)))  from suallo.F90
    169169!!
    170 !! ATTENTION, il faut que ~dyn3d/comvert.h soit conforme au Fortran 90 !!
    171 !!
    172170ALLOCATE(VAH    (0:NFLEVG))  ! Ajout ALLOCATE MPL 200509
    173171ALLOCATE(VBH    (0:NFLEVG))
     
    177175VP00=101325.     !!!!! A REVOIR (MPL)
    178176ZPRES(NFLEVG)=VP00
    179 ! on recupere ap et bp de dyn3d (comvert.h) MPL 19.05.09
     177! on recupere ap et bp de dyn3d (vertical_layers_mod) MPL 19.05.09
    180178! Attention, VAH et VBH sont inverses, comme les niveaux
    181179! plev(l)=PAPRS(klon,nlayer+1-l) de 1 a nlayer (apllmd.F)
  • LMDZ5/trunk/libf/phylmd/test_disvert_m.F90

    r2311 r2315  
    1414
    1515    use exner_hyb_m, only: exner_hyb
     16    use vertical_layers_mod, only: ap,bp,preff
    1617
    1718    ! For llm:
    1819    include "dimensions.h"
    19 
    20     ! For ap, bp, preff:
    21     include "comvert.h"
    2220
    2321    ! For kappa, cpp:
Note: See TracChangeset for help on using the changeset viewer.