Ignore:
Timestamp:
Dec 14, 2015, 11:43:09 AM (9 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2298:2396 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/readaerosol.F90

    r1910 r2408  
    2020!****************************************************************************************
    2121  USE dimphy
     22  USE print_control_mod, ONLY: lunout
    2223
    2324  IMPLICIT NONE
    24 
    25  INCLUDE "iniprint.h"
    2625
    2726  ! Input arguments
     
    130129           IF (klev_src /= klev_src2) THEN
    131130              WRITE(lunout,*) 'Two aerosols files with different number of vertical levels is not allowded'
    132               CALL abort_gcm('readaersosol','Error in number of vertical levels',1)
     131              CALL abort_physic('readaersosol','Error in number of vertical levels',1)
    133132           END IF
    134133           
     
    162161  ELSE
    163162     WRITE(lunout,*)'This option is not implemented : aer_type = ', type,' name_aero=',name_aero
    164      CALL abort_gcm('readaerosol','Error : aer_type parameter not accepted',1)
     163     CALL abort_physic('readaerosol','Error : aer_type parameter not accepted',1)
    165164  END IF ! type
    166165
     
    179178! 3) Read field month by month
    180179! 4) Close file 
    181 ! 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)
    182181!     - Also the levels and the latitudes have to be inversed
    183182!
     
    189188    USE netcdf
    190189    USE dimphy
    191     USE mod_grid_phy_lmdz
     190    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, &
     191                                 grid2Dto1D_glo
    192192    USE mod_phys_lmdz_para
    193193    USE iophy, ONLY : io_lon, io_lat
     194    USE print_control_mod, ONLY: lunout
    194195
    195196    IMPLICIT NONE
    196197     
    197     INCLUDE "dimensions.h"     
    198     INCLUDE "iniprint.h"
    199 
    200198! Input argumets
    201199    CHARACTER(len=7), INTENT(IN)          :: varname
     
    224222    REAL, ALLOCATABLE, DIMENSION(:)       :: varktmp
    225223
    226     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
    227225    REAL, DIMENSION(klon_glo,12)          :: psurf_glo1D   ! -"- on physical global grid
    228     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
    229227    REAL, DIMENSION(klon_glo,12)          :: load_glo1D    ! -"- on physical global grid
    230     REAL, DIMENSION(iim,jjm+1)            :: vartmp
    231     REAL, DIMENSION(iim)                  :: lon_src              ! longitudes in file
    232     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
    233231    LOGICAL                               :: new_file             ! true if new file format detected
    234232    LOGICAL                               :: invert_lat           ! true if the field has to be inverted for latitudes
     
    260258          WRITE(lunout,*) 'longitudes in model :', io_lon
    261259         
    262           CALL abort_gcm('get_aero_fromfile', 'longitudes are not the same in file and model',1)
     260          CALL abort_physic('get_aero_fromfile', 'longitudes are not the same in file and model',1)
    263261       END IF
    264262
     
    268266
    269267       ! Invert source latitudes
    270        DO j = 1, jjm+1
    271           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)
    272270       END DO
    273271
     
    283281          WRITE(lunout,*) 'latitudes in file ', TRIM(fname),' : ', lat_src     
    284282          WRITE(lunout,*) 'latitudes in model :', io_lat
    285           CALL abort_gcm('get_aero_fromfile', 'latitudes do not correspond between file and model',1)
     283          CALL abort_physic('get_aero_fromfile', 'latitudes do not correspond between file and model',1)
    286284       END IF
    287285
     
    297295          IF (ierr /= NF90_NOERR) THEN
    298296             ! Dimension PRESNIVS not found either
    299              CALL abort_gcm('get_aero_fromfile', 'dimension lev or presnivs not in file',1)
     297             CALL abort_physic('get_aero_fromfile', 'dimension lev or presnivs not in file',1)
    300298          ELSE
    301299             ! Old file found
     
    314312       
    315313     ! Allocate variables depending on the number of vertical levels
    316        ALLOCATE(varmth(iim, jjm+1, klev_src), varyear(iim, jjm+1, klev_src, 12), stat=ierr)
    317        IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 1',1)
     314       ALLOCATE(varmth(nbp_lon,nbp_lat, klev_src), varyear(nbp_lon,nbp_lat, klev_src, 12), stat=ierr)
     315       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 1',1)
    318316
    319317       ALLOCATE(pt_ap(klev_src), pt_b(klev_src), varktmp(klev_src), stat=ierr)
    320        IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 2',1)
     318       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 2',1)
    321319
    322320! 3) Read all variables from file
     
    333331!       IF (nbr_tsteps /= 12 .AND. nbr_tsteps /= 14) THEN
    334332       IF (nbr_tsteps /= 12 ) THEN
    335          CALL abort_gcm('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)',1)
     333    CALL abort_physic('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)' &
     334                     ,1)
    336335       ENDIF
    337336
     
    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
    522521       
    523522       ALLOCATE(varyear_glo1D(klon_glo, klev_src, 12), stat=ierr)
    524        IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 3',1)
     523       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 3',1)
    525524       
    526525       ! Transform from 2D to 1D field
     
    546545    IF (.NOT. ASSOCIATED(pt_ap)) THEN  ! if pt_ap is allocated also pt_b is allocated
    547546       ALLOCATE(pt_ap(klev_src), pt_b(klev_src), stat=ierr)
    548        IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 4',1)
     547       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 4',1)
    549548    END IF
    550549    CALL bcast(pt_ap)
     
    554553    IF (ASSOCIATED(pt_year)) DEALLOCATE(pt_year)
    555554    ALLOCATE(pt_year(klon, klev_src, 12), stat=ierr)
    556     IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 5',1)
     555    IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 5',1)
    557556
    558557    ! Scatter global field to local domain at local process
     
    572571  SUBROUTINE check_err(status,text)
    573572    USE netcdf
     573    USE print_control_mod, ONLY: lunout
    574574    IMPLICIT NONE
    575575
    576     INCLUDE "iniprint.h"
    577576    INTEGER, INTENT (IN) :: status
    578577    CHARACTER(len=*), INTENT (IN), OPTIONAL :: text
     
    583582          WRITE(lunout,*) 'Error in get_aero_fromfile : ',text
    584583       END IF
    585        CALL abort_gcm('get_aero_fromfile',trim(nf90_strerror(status)),1)
     584       CALL abort_physic('get_aero_fromfile',trim(nf90_strerror(status)),1)
    586585    END IF
    587586
Note: See TracChangeset for help on using the changeset viewer.