New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 679 for trunk/NEMO/OPA_SRC/IOM/iom_nf90.F90 – NEMO

Ignore:
Timestamp:
2007-06-29T18:29:31+02:00 (17 years ago)
Author:
rblod
Message:

nemo_v2_update_018 : SM : improve IOM
nemo_v2_bugfix_049 : SM : Patch to work when jpni*jpnj /= jpnij
nemo_v2_update_020 : SM : add jpdom_autoglo and jpdom_autodta
nemo_v2_bugfix_053 : SM : make sure everything is ok when kiomid <= 0
nemo_v2_bugfix_054 : RB : correct a bug in mpp with iom and suppress useless dummy arguments

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r588 r679  
    3636   !!---------------------------------------------------------------------- 
    3737   !!  OPA 9.0 , LOCEAN-IPSL (2006) 
    38    !! $Header$ 
     38   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/IOM/iom_nf90.F90,v 1.8 2007/06/29 14:10:50 opalod Exp $ 
    3939   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4040   !!---------------------------------------------------------------------- 
     
    4848      !! ** Purpose : open an input file with NF90 
    4949      !!--------------------------------------------------------------------- 
    50       CHARACTER(len=*)       , INTENT(inout) ::   cdname    ! File name 
    51       INTEGER                , INTENT(  out) ::   kiomid    ! nf90 identifier of the opened file 
    52       LOGICAL                , INTENT(in   ) ::   ldwrt     ! read or write the file? 
    53       LOGICAL                , INTENT(in   ) ::   ldok      ! check the existence  
    54       INTEGER, DIMENSION(2,5), INTENT(in   ) ::   kdompar   ! domain parameters:  
     50      CHARACTER(len=*)       , INTENT(inout)           ::   cdname    ! File name 
     51      INTEGER                , INTENT(  out)           ::   kiomid    ! nf90 identifier of the opened file 
     52      LOGICAL                , INTENT(in   )           ::   ldwrt     ! read or write the file? 
     53      LOGICAL                , INTENT(in   )           ::   ldok      ! check the existence  
     54      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar   ! domain parameters:  
    5555 
    5656      CHARACTER(LEN=100) ::   clinfo   ! info character 
     
    104104            CALL iom_nf90_check(NF90_PUT_ATT( if90id, NF90_GLOBAL, 'DOMAIN_type'           , 'BOX'              ), clinfo) 
    105105         ELSE              ! the file should be open for read mode so it must exist... 
    106             CALL ctl_stop( TRIM(clinfo), 'File '//cdname(1:iln-1)//'* not found' ) 
     106            CALL ctl_stop( TRIM(clinfo), ' should be impossible case...' ) 
    107107         ENDIF 
    108108      ENDIF 
     
    232232 
    233233 
    234    SUBROUTINE iom_nf90_g123d( kiomid, kdom, kvid, knbdim, kstart, kcount,    & 
    235          &                          pv_r1d, pv_r2d, pv_r3d) 
     234   SUBROUTINE iom_nf90_g123d( kiomid, kvid, knbdim, kstart, kcount, kx1, kx2, ky1, ky2,   & 
     235         &                    pv_r1d, pv_r2d, pv_r3d ) 
    236236      !!----------------------------------------------------------------------- 
    237237      !!                  ***  ROUTINE  iom_nf90_g123d  *** 
     
    242242      !!----------------------------------------------------------------------- 
    243243      INTEGER                    , INTENT(in   )           ::   kiomid    ! iom identifier of the file 
    244       INTEGER                    , INTENT(in   )           ::   kdom      ! Type of domain to be read 
    245244      INTEGER                    , INTENT(in   )           ::   kvid      ! Name of the variable 
    246245      INTEGER                    , INTENT(in   )           ::   knbdim    ! number of dimensions of the variable 
    247246      INTEGER , DIMENSION(:)     , INTENT(in   )           ::   kstart    ! start position of the reading in each axis  
    248247      INTEGER , DIMENSION(:)     , INTENT(in   )           ::   kcount    ! number of points to be read in each axis 
     248      INTEGER ,                    INTENT(in   )           ::   kx1, kx2, ky1, ky2   ! subdomain indexes 
    249249      REAL(wp), DIMENSION(:)     , INTENT(  out), OPTIONAL ::   pv_r1d    ! read field (1D case) 
    250250      REAL(wp), DIMENSION(:,:)   , INTENT(  out), OPTIONAL ::   pv_r2d    ! read field (2D case) 
    251251      REAL(wp), DIMENSION(:,:,:) , INTENT(  out), OPTIONAL ::   pv_r3d    ! read field (3D case) 
    252252      ! 
    253       CHARACTER(LEN=100) ::   clinfo   ! info character 
    254       INTEGER            ::   if90id   ! nf90 identifier of the opened file 
    255       INTEGER            ::   ivid     ! nf90 variable id 
     253      CHARACTER(LEN=100) ::   clinfo               ! info character 
     254      INTEGER            ::   if90id               ! nf90 identifier of the opened file 
     255      INTEGER            ::   ivid                 ! nf90 variable id 
    256256      !--------------------------------------------------------------------- 
    257257      clinfo = 'iom_nf90_g123d , file: '//TRIM(iom_file(kiomid)%name)//', var: '//TRIM(iom_file(kiomid)%cn_var(kvid)) 
    258258      if90id = iom_file(kiomid)%nfid         ! get back NetCDF file id 
    259259      ivid   = iom_file(kiomid)%nvid(kvid)   ! get back NetCDF var id 
    260       IF( PRESENT(pv_r1d) ) THEN 
    261          CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r1d(:), start=kstart(1:knbdim), count=kcount(1:knbdim)), clinfo ) 
     260      ! 
     261      IF(     PRESENT(pv_r1d) ) THEN 
     262         CALL iom_nf90_check( NF90_GET_VAR(if90id, ivid, pv_r1d(:                ), start = kstart(1:knbdim),   & 
     263            &                                                                       count = kcount(1:knbdim)), clinfo ) 
    262264      ELSEIF( PRESENT(pv_r2d) ) THEN 
    263          IF( kdom /= jpdom_unknown ) THEN 
    264             CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r2d(nldi:nlei,nldj:nlej),   & 
    265                   &                           start=kstart(1:knbdim), count=kcount(1:knbdim)), clinfo) 
    266             !--- Fill the overlap areas and extra hallows (mpp) 
    267             CALL lbc_lnk (pv_r2d,'Z',-999.,'no0') 
    268          ELSE 
    269             CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r2d(:,:), start=kstart(1:knbdim), count=kcount(1:knbdim)), clinfo) 
    270          ENDIF 
     265         CALL iom_nf90_check( NF90_GET_VAR(if90id, ivid, pv_r2d(kx1:kx2,ky1:ky2  ), start = kstart(1:knbdim),   & 
     266            &                                                                       count = kcount(1:knbdim)), clinfo ) 
    271267      ELSEIF( PRESENT(pv_r3d) ) THEN 
    272          IF( kdom /= jpdom_unknown ) THEN 
    273             CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r3d(nldi:nlei,nldj:nlej,:),   & 
    274                   &                           start=kstart(1:knbdim), count=kcount  (1:knbdim)), clinfo) 
    275             !--- Fill the overlap areas and extra hallows (mpp) 
    276             ! this if could be simplified with the new lbc_lnk that works with any size of the 3rd dimension 
    277             IF( kcount(3) == jpk ) THEN 
    278                CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) 
    279             ELSE   ! put some arbitrary value (a call to lbc_lnk will be done later...) 
    280                pv_r3d(nlei+1:jpi,      :   ,:) = 1.             
    281                pv_r3d(      :   ,nlej+1:jpj,:) = 1.             
    282             ENDIF 
    283          ELSE 
    284             CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r3d(:,:,:),   & 
    285                   &                           start=kstart(1:knbdim), count=kcount  (1:knbdim)), clinfo) 
    286          ENDIF 
     268         CALL iom_nf90_check( NF90_GET_VAR(if90id, ivid, pv_r3d(kx1:kx2,ky1:ky2,:), start = kstart(1:knbdim),   & 
     269            &                                                                       count = kcount(1:knbdim)), clinfo ) 
    287270      ENDIF 
    288271      ! 
Note: See TracChangeset for help on using the changeset viewer.