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/phylmd/readaerosol.F90

    r2317 r2346  
    178178! 3) Read field month by month
    179179! 4) Close file 
    180 ! 5) Transform the global field from 2D(iim, jjp+1) to 1D(klon_glo)
     180! 5) Transform the global field from 2D(nbp_lon,nbp_lat) to 1D(klon_glo)
    181181!     - Also the levels and the latitudes have to be inversed
    182182!
     
    188188    USE netcdf
    189189    USE dimphy
    190     USE mod_grid_phy_lmdz
     190    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, &
     191                                 grid2Dto1D_glo
    191192    USE mod_phys_lmdz_para
    192193    USE iophy, ONLY : io_lon, io_lat
     
    195196    IMPLICIT NONE
    196197     
    197     INCLUDE "dimensions.h"     
    198 
    199198! Input argumets
    200199    CHARACTER(len=7), INTENT(IN)          :: varname
     
    223222    REAL, ALLOCATABLE, DIMENSION(:)       :: varktmp
    224223
    225     REAL, DIMENSION(iim,jjm+1,12)         :: psurf_glo2D   ! Surface pression for 12 months on dynamics global grid
     224    REAL, DIMENSION(nbp_lon,nbp_lat,12)         :: psurf_glo2D   ! Surface pression for 12 months on dynamics global grid
    226225    REAL, DIMENSION(klon_glo,12)          :: psurf_glo1D   ! -"- on physical global grid
    227     REAL, DIMENSION(iim,jjm+1,12)         :: load_glo2D    ! Load for 12 months on dynamics global grid
     226    REAL, DIMENSION(nbp_lon,nbp_lat,12)         :: load_glo2D    ! Load for 12 months on dynamics global grid
    228227    REAL, DIMENSION(klon_glo,12)          :: load_glo1D    ! -"- on physical global grid
    229     REAL, DIMENSION(iim,jjm+1)            :: vartmp
    230     REAL, DIMENSION(iim)                  :: lon_src              ! longitudes in file
    231     REAL, DIMENSION(jjm+1)                :: lat_src, lat_src_inv ! latitudes in file
     228    REAL, DIMENSION(nbp_lon,nbp_lat)            :: vartmp
     229    REAL, DIMENSION(nbp_lon)                  :: lon_src              ! longitudes in file
     230    REAL, DIMENSION(nbp_lat)                :: lat_src, lat_src_inv ! latitudes in file
    232231    LOGICAL                               :: new_file             ! true if new file format detected
    233232    LOGICAL                               :: invert_lat           ! true if the field has to be inverted for latitudes
     
    267266
    268267       ! Invert source latitudes
    269        DO j = 1, jjm+1
    270           lat_src_inv(j) = lat_src(jjm+1 +1 -j)
     268       DO j = 1, nbp_lat
     269          lat_src_inv(j) = lat_src(nbp_lat +1 -j)
    271270       END DO
    272271
     
    313312       
    314313     ! Allocate variables depending on the number of vertical levels
    315        ALLOCATE(varmth(iim, jjm+1, klev_src), varyear(iim, jjm+1, klev_src, 12), stat=ierr)
     314       ALLOCATE(varmth(nbp_lon,nbp_lat, klev_src), varyear(nbp_lon,nbp_lat, klev_src, 12), stat=ierr)
    316315       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 1',1)
    317316
     
    435434     
    436435
    437 ! 5) Transform the global field from 2D(iim, jjp+1) to 1D(klon_glo)
     436! 5) Transform the global field from 2D(nbp_lon,nbp_lat) to 1D(klon_glo)
    438437!****************************************************************************************
    439438! Test if vertical levels have to be inversed
     
    448447             varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly
    449448             DO k=1, klev_src
    450                 DO j=1, jjm+1
    451                    DO i=1,iim
     449                DO j=1, nbp_lat
     450                   DO i=1, nbp_lon
    452451                      varyear(i,j,k,imth) = varmth(i,j,klev_src+1-k)
    453452                   END DO
     
    482481             varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly
    483482             DO k=1,klev_src
    484                 DO j=1,jjm+1
    485                    DO i=1,iim
    486                       varyear(i,j,k,imth) = varmth(i,jjm+1+1-j,k)
     483                DO j=1,nbp_lat
     484                   DO i=1,nbp_lon
     485                      varyear(i,j,k,imth) = varmth(i,nbp_lat+1-j,k)
    487486                   END DO
    488487                END DO
     
    491490             ! Invert latitudes for surface pressure
    492491             vartmp(:,:) = psurf_glo2D(:,:,imth)
    493              DO j=1, jjm+1
    494                 DO i=1,iim
    495                    psurf_glo2D(i,j,imth)= vartmp(i,jjm+1+1-j)
     492             DO j=1,nbp_lat
     493                DO i=1,nbp_lon
     494                   psurf_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j)
    496495                END DO
    497496             END DO
     
    499498             ! Invert latitudes for the load
    500499             vartmp(:,:) = load_glo2D(:,:,imth)
    501              DO j=1, jjm+1
    502                 DO i=1,iim
    503                    load_glo2D(i,j,imth)= vartmp(i,jjm+1+1-j)
     500             DO j=1,nbp_lat
     501                DO i=1,nbp_lon
     502                   load_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j)
    504503                END DO
    505504             END DO
     
    509508          DO k=1, klev_src
    510509             npole=0.  ! North pole, j=1
    511              spole=0.  ! South pole, j=jjm+1        
    512              DO i=1,iim
     510             spole=0.  ! South pole, j=nbp_lat       
     511             DO i=1,nbp_lon
    513512                npole = npole + varyear(i,1,k,imth)
    514                 spole = spole + varyear(i,jjm+1,k,imth)
     513                spole = spole + varyear(i,nbp_lat,k,imth)
    515514             END DO
    516              npole = npole/REAL(iim)
    517              spole = spole/REAL(iim)
     515             npole = npole/REAL(nbp_lon)
     516             spole = spole/REAL(nbp_lon)
    518517             varyear(:,1,    k,imth) = npole
    519              varyear(:,jjm+1,k,imth) = spole
     518             varyear(:,nbp_lat,k,imth) = spole
    520519          END DO
    521520       END DO ! imth
Note: See TracChangeset for help on using the changeset viewer.