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

Location:
LMDZ5/trunk/libf/dynlonlat_phylonlat
Files:
3 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))
  • LMDZ5/trunk/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90

    r2343 r2346  
    33
    44
    5 SUBROUTINE iniphysiq(ii,jj,nlayer,punjours, pdayref,ptimestep,           &
    6                      rlatu,rlonv,aire,cu,cv,                             &
     5SUBROUTINE iniphysiq(ii,jj,nlayer,punjours, pdayref,ptimestep, &
     6                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,       &
    77                     prad,pg,pr,pcpp,iflag_phys)
    88  USE dimphy, ONLY: klev ! number of atmospheric levels
     
    3535  USE phystokenc_mod, ONLY: init_phystokenc
    3636  USE phyaqua_mod, ONLY: iniaqua
     37  USE regular_lonlat_mod, ONLY : init_regular_lonlat, &
     38                                 east, west, north, south, &
     39                                 north_east, north_west, &
     40                                 south_west, south_east
    3741  IMPLICIT NONE
    3842
     
    4448  include "dimensions.h"
    4549  include "comvert.h"
     50  include "comconst.h"
    4651  include "iniprint.h"
    4752  include "temps.h"
     
    5762  INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes
    5863  REAL, INTENT (IN) :: rlatu(jj+1) ! latitudes of the physics grid
     64  REAL, INTENT (IN) :: rlatv(jj) ! latitude boundaries of the physics grid
    5965  REAL, INTENT (IN) :: rlonv(ii+1) ! longitudes of the physics grid
     66  REAL, INTENT (IN) :: rlonu(ii+1) ! longitude boundaries of the physics grid
    6067  REAL, INTENT (IN) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
    6168  REAL, INTENT (IN) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
     
    7178  REAL :: total_area_phy, total_area_dyn
    7279
     80  ! boundaries, on global grid
     81  REAL,ALLOCATABLE :: boundslon_reg(:,:)
     82  REAL,ALLOCATABLE :: boundslat_reg(:,:)
    7383
    7484  ! global array, on full physics grid:
     
    8797  !call init_phys_lmdz(ii,jj+1,llm,1,(/(jj-1)*ii+2/))
    8898 
     99  ! init regular global longitude-latitude grid points and boundaries
     100  ALLOCATE(boundslon_reg(ii,2))
     101  ALLOCATE(boundslat_reg(jj+1,2))
     102 
     103  DO i=1,ii
     104   boundslon_reg(i,east)=rlonu(i)
     105   boundslon_reg(i,west)=rlonu(i+1)
     106  ENDDO
     107
     108  boundslat_reg(1,north)= PI/2
     109  boundslat_reg(1,south)= rlatv(1)
     110  DO j=2,jj
     111   boundslat_reg(j,north)=rlatv(j-1)
     112   boundslat_reg(j,south)=rlatv(j)
     113  ENDDO
     114  boundslat_reg(jj+1,north)= rlatv(jj)
     115  boundslat_reg(jj+1,south)= -PI/2
     116
     117  ! Write values in module regular_lonlat_mod
     118  CALL init_regular_lonlat(ii,jj+1, rlonv(1:ii), rlatu, &
     119                           boundslon_reg, boundslat_reg)
     120
    89121  ! Generate global arrays on full physics grid
    90122  ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
  • 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.