Changeset 2315


Ignore:
Timestamp:
Jun 25, 2015, 5:25:50 PM (9 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
Files:
1 added
10 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90

    r2311 r2315  
    33
    44
    5 SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep,         &
     5SUBROUTINE iniphysiq(ii,jj,nlayer,punjours, pdayref,ptimestep,           &
    66                     rlatu,rlonv,aire,cu,cv,                             &
    77                     prad,pg,pr,pcpp,iflag_phys)
     
    1313                                klon_omp_end, & ! end index of local omp subgrid
    1414                                klon_mpi_begin ! start indes of columns (on local mpi grid)
     15  USE vertical_layers_mod, ONLY : init_vertical_layers
    1516  USE comgeomphy, ONLY: initcomgeomphy, &
    1617                        airephy, & ! physics grid area (m2)
     
    2829  ! =======================================================================
    2930
     31  include "dimensions.h"
     32  include "comvert.h"
    3033  include "iniprint.h"
    3134
     
    3639  REAL, INTENT (IN) :: punjours ! length (in s) of a standard day
    3740  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
    38   INTEGER, INTENT (IN) :: iim ! number of atmospheric columns along longitudes
    39   INTEGER, INTENT (IN) :: jjm ! number of atompsheric columns along latitudes
    40   REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
    41   REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
    42   REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
    43   REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
    44   REAL, INTENT (IN) :: cv((iim+1)*jjm) ! cv coeff. (v_covariant = cv * v)
     41  INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes
     42  INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes
     43  REAL, INTENT (IN) :: rlatu(jj+1) ! latitudes of the physics grid
     44  REAL, INTENT (IN) :: rlonv(ii+1) ! longitudes of the physics grid
     45  REAL, INTENT (IN) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
     46  REAL, INTENT (IN) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
     47  REAL, INTENT (IN) :: cv((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
    4548  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
    4649  REAL, INTENT (IN) :: ptimestep !physics time step (s)
     
    7073  END IF
    7174
    72   !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
     75  !call init_phys_lmdz(ii,jj+1,llm,1,(/(jj-1)*ii+2/))
    7376 
    7477  ! Generate global arrays on full physics grid
     
    8285    cufi(1) = cu(1)
    8386    cvfi(1) = cv(1)
    84     DO j=2,jjm
    85       DO i=1,iim
    86         latfi((j-2)*iim+1+i)= rlatu(j)
    87         lonfi((j-2)*iim+1+i)= rlonv(i)
    88         cufi((j-2)*iim+1+i) = cu((j-1)*(iim+1)+i)
    89         cvfi((j-2)*iim+1+i) = cv((j-1)*(iim+1)+i)
     87    DO j=2,jj
     88      DO i=1,ii
     89        latfi((j-2)*ii+1+i)= rlatu(j)
     90        lonfi((j-2)*ii+1+i)= rlonv(i)
     91        cufi((j-2)*ii+1+i) = cu((j-1)*(ii+1)+i)
     92        cvfi((j-2)*ii+1+i) = cv((j-1)*(ii+1)+i)
    9093      ENDDO
    9194    ENDDO
    9295    ! South pole
    93     latfi(klon_glo)= rlatu(jjm+1)
     96    latfi(klon_glo)= rlatu(jj+1)
    9497    lonfi(klon_glo)= 0.
    95     cufi(klon_glo) = cu((iim+1)*jjm+1)
    96     cvfi(klon_glo) = cv((iim+1)*jjm-iim)
     98    cufi(klon_glo) = cu((ii+1)*jj+1)
     99    cvfi(klon_glo) = cv((ii+1)*jj-ii)
    97100
    98101    ! build airefi(), mesh area on physics grid
    99     CALL gr_dyn_fi(1,iim+1,jjm+1,klon_glo,aire,airefi)
     102    CALL gr_dyn_fi(1,ii+1,jj+1,klon_glo,aire,airefi)
    100103    ! Poles are single points on physics grid
    101     airefi(1)=sum(aire(1:iim,1))
    102     airefi(klon_glo)=sum(aire(1:iim,jjm+1))
     104    airefi(1)=sum(aire(1:ii,1))
     105    airefi(klon_glo)=sum(aire(1:ii,jj+1))
    103106
    104107    ! Sanity check: do total planet area match between physics and dynamics?
    105     total_area_dyn=sum(aire(1:iim,1:jjm+1))
     108    total_area_dyn=sum(aire(1:ii,1:jj+1))
    106109    total_area_phy=sum(airefi(1:klon_glo))
    107110    IF (total_area_dyn/=total_area_phy) THEN
     
    128131  CALL inifis(punjours,prad,pg,pr,pcpp)
    129132 
     133  ! copy over preff , ap(), bp(), etc
     134  CALL init_vertical_layers(nlayer,preff,scaleheight, &
     135                            ap,bp,presnivs,pseudoalt)
     136
    130137  ! Now generate local lon/lat/cu/cv/area arrays
    131138  CALL initcomgeomphy
  • 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.