Ignore:
Timestamp:
Aug 21, 2015, 5:13:46 PM (9 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/phymar/iniphysiq.F90

    r2242 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
     
    2323                       rcpp  ! specific heat of the atmosphere
    2424!  USE phyaqua_mod, ONLY: iniaqua
     25  USE regular_lonlat_mod, ONLY : init_regular_lonlat, &
     26                                 east, west, north, south, &
     27                                 north_east, north_west, &
     28                                 south_west, south_east
     29  USE nrtype, ONLY: pi
    2530  IMPLICIT NONE
    2631  !
     
    4247  INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
    4348  REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
     49  REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
    4450  REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
     51  REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
    4552  REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
    4653  REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
     
    5663  REAL :: total_area_phy, total_area_dyn
    5764
     65  ! boundaries, on global grid
     66  REAL,ALLOCATABLE :: boundslon_reg(:,:)
     67  REAL,ALLOCATABLE :: boundslat_reg(:,:)
    5868
    5969  ! global array, on full physics grid:
     
    7383  ENDIF
    7484
     85  ! init regular global longitude-latitude grid points and boundaries
     86  ALLOCATE(boundslon_reg(iim,2))
     87  ALLOCATE(boundslat_reg(jjm+1,2))
     88 
     89  DO i=1,iim
     90   boundslon_reg(i,east)=rlonu(i)
     91   boundslon_reg(i,west)=rlonu(i+1)
     92  ENDDO
     93
     94  boundslat_reg(1,north)= PI/2
     95  boundslat_reg(1,south)= rlatv(1)
     96  DO j=2,jjm
     97   boundslat_reg(j,north)=rlatv(j-1)
     98   boundslat_reg(j,south)=rlatv(j)
     99  ENDDO
     100  boundslat_reg(jjm+1,north)= rlatv(jjm)
     101  boundslat_reg(jjm+1,south)= -PI/2
     102
     103  ! Write values in module regular_lonlat_mod
     104  CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, &
     105                           boundslon_reg, boundslat_reg)
    75106
    76107  ! Generate global arrays on full physics grid
Note: See TracChangeset for help on using the changeset viewer.