Ignore:
Timestamp:
Aug 21, 2015, 5:13:46 PM (10 years ago)
Author:
Ehouarn Millour
Message:

Physics/dynamics separation:

  • remove all references to dimensions.h from physics. nbp_lon (==iim) , nbp_lat (==jjm+1) and nbp_lev (==llm) from mod_grid_phy_lmdz should be used instead.
  • added module regular_lonlat_mod in phy_common to store information about the global (lon-lat) grid cell boundaries and centers.

EM

File:
1 edited

Legend:

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

    r2320 r2346  
    22! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
    33!
    4 SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep,         &
    5                      rlatu,rlonv,aire,cu,cv,                            &
     4SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep, &
     5                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv, &
    66                     prad,pg,pr,pcpp,iflag_phys)
    77  USE dimphy, ONLY: klev ! number of atmospheric levels
     
    2626  USE inifis_mod, ONLY: inifis
    2727  USE phyaqua_mod, ONLY: iniaqua
     28  USE regular_lonlat_mod, ONLY : init_regular_lonlat, &
     29                                 east, west, north, south, &
     30                                 north_east, north_west, &
     31                                 south_west, south_east
     32  USE nrtype, ONLY: pi
    2833  IMPLICIT NONE
    2934  !
     
    4550  INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
    4651  REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
     52  REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
    4753  REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
     54  REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
    4855  REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
    4956  REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
     
    5966  REAL :: total_area_phy, total_area_dyn
    6067
     68  ! boundaries, on global grid
     69  REAL,ALLOCATABLE :: boundslon_reg(:,:)
     70  REAL,ALLOCATABLE :: boundslat_reg(:,:)
    6171
    6272  ! global array, on full physics grid:
     
    7888  !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
    7989 
     90  ! init regular global longitude-latitude grid points and boundaries
     91  ALLOCATE(boundslon_reg(iim,2))
     92  ALLOCATE(boundslat_reg(jjm+1,2))
     93 
     94  DO i=1,iim
     95   boundslon_reg(i,east)=rlonu(i)
     96   boundslon_reg(i,west)=rlonu(i+1)
     97  ENDDO
     98
     99  boundslat_reg(1,north)= PI/2
     100  boundslat_reg(1,south)= rlatv(1)
     101  DO j=2,jjm
     102   boundslat_reg(j,north)=rlatv(j-1)
     103   boundslat_reg(j,south)=rlatv(j)
     104  ENDDO
     105  boundslat_reg(jjm+1,north)= rlatv(jjm)
     106  boundslat_reg(jjm+1,south)= -PI/2
     107
     108  ! Write values in module regular_lonlat_mod
     109  CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, &
     110                           boundslon_reg, boundslat_reg)
     111
    80112  ! Generate global arrays on full physics grid
    81113  ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
Note: See TracChangeset for help on using the changeset viewer.