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 9903 for NEMO/trunk – NEMO

Changeset 9903 for NEMO/trunk


Ignore:
Timestamp:
2018-07-09T15:04:55+02:00 (6 years ago)
Author:
smasson
Message:

trunk: bugfix following [9802], see #2100

Location:
NEMO/trunk/src/OCE/IOM
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/IOM/iom.F90

    r9802 r9903  
    8383      MODULE PROCEDURE iom_p0d, iom_p1d, iom_p2d, iom_p3d 
    8484   END INTERFACE iom_put 
    85     
    86    LOGICAL, PARAMETER ::   ltmppatch = .TRUE.     !: seb: patch before we remove periodicity 
    87    INTEGER            ::   nldi_save, nlei_save   !:      and close boundaries in output files 
    88    INTEGER            ::   nldj_save, nlej_save   !: 
    8985   
    9086   !!---------------------------------------------------------------------- 
     
    9591CONTAINS 
    9692 
    97    SUBROUTINE iom_init( cdname, fname )  
     93   SUBROUTINE iom_init( cdname, fname, ld_tmppatch )  
    9894      !!---------------------------------------------------------------------- 
    9995      !!                     ***  ROUTINE   *** 
     
    10298      !! 
    10399      !!---------------------------------------------------------------------- 
    104       CHARACTER(len=*), INTENT(in)  :: cdname 
     100      CHARACTER(len=*),           INTENT(in)  :: cdname 
    105101      CHARACTER(len=*), OPTIONAL, INTENT(in)  :: fname 
     102      LOGICAL         , OPTIONAL, INTENT(in)  :: ld_tmppatch 
    106103#if defined key_iomput 
    107104      ! 
     
    113110      ! 
    114111      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds 
     112      LOGICAL ::   ll_tmppatch = .TRUE.    !: seb: patch before we remove periodicity 
     113      INTEGER ::   nldi_save, nlei_save    !:      and close boundaries in output files 
     114      INTEGER ::   nldj_save, nlej_save    !: 
    115115      !!---------------------------------------------------------------------- 
    116116      ! 
    117117      ! seb: patch before we remove periodicity and close boundaries in output files 
    118       IF ( ltmppatch ) THEN 
     118      IF( PRESENT(ld_tmppatch) ) THEN   ;   ll_tmppatch = ld_tmppatch 
     119      ELSE                              ;   ll_tmppatch = .TRUE. 
     120      ENDIF 
     121      IF ( ll_tmppatch ) THEN 
    119122         nldi_save = nldi   ;   nlei_save = nlei 
    120123         nldj_save = nldj   ;   nlej_save = nlej 
     
    246249      DEALLOCATE( zt_bnds, zw_bnds ) 
    247250      ! 
    248       IF ( ltmppatch ) THEN 
     251      IF ( ll_tmppatch ) THEN 
    249252         nldi = nldi_save   ;   nlei = nlei_save 
    250253         nldj = nldj_save   ;   nlej = nlej_save 
     
    19241927      !!---------------------------------------------------------------------- 
    19251928      ! 
    1926       ! seb: patch before we remove periodicity and close boundaries in output files 
    1927       IF ( ltmppatch ) THEN 
    1928          nldi_save = nldi   ;   nlei_save = nlei 
    1929          nldj_save = nldj   ;   nlej_save = nlej 
    1930          IF( nimpp           ==      1 ) nldi = 1 
    1931          IF( nimpp + jpi - 1 == jpiglo ) nlei = jpi 
    1932          IF( njmpp           ==      1 ) nldj = 1 
    1933          IF( njmpp + jpj - 1 == jpjglo ) nlej = jpj 
    1934       ENDIF 
    1935       ! 
    19361929      ni = nlei-nldi+1 
    19371930      nj = nlej-nldj+1 
     
    19551948      ENDIF 
    19561949      ! 
    1957       IF ( ltmppatch ) THEN 
    1958          nldi = nldi_save   ;   nlei = nlei_save 
    1959          nldj = nldj_save   ;   nlej = nlej_save 
    1960       ENDIF 
    1961       ! 
    19621950   END SUBROUTINE set_grid 
    19631951 
     
    19811969      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: z_rot       ! Lat/lon working array for rotation of cells 
    19821970      !!---------------------------------------------------------------------- 
    1983       ! 
    1984       ! seb: patch before we remove periodicity and close boundaries in output files 
    1985       IF ( ltmppatch ) THEN 
    1986          nldi_save = nldi   ;   nlei_save = nlei 
    1987          nldj_save = nldj   ;   nlej_save = nlej 
    1988          IF( nimpp           ==      1 ) nldi = 1 
    1989          IF( nimpp + jpi - 1 == jpiglo ) nlei = jpi 
    1990          IF( njmpp           ==      1 ) nldj = 1 
    1991          IF( njmpp + jpj - 1 == jpjglo ) nlej = jpj 
    1992       ENDIF 
    19931971      ! 
    19941972      ALLOCATE( z_bnds(4,jpi,jpj,2), z_fld(jpi,jpj), z_rot(4,2)  ) 
     
    20752053      DEALLOCATE( z_bnds, z_fld, z_rot )  
    20762054      ! 
    2077       IF ( ltmppatch ) THEN 
    2078          nldi = nldi_save   ;   nlei = nlei_save 
    2079          nldj = nldj_save   ;   nlej = nlej_save 
    2080       ENDIF 
    2081       ! 
    20822055   END SUBROUTINE set_grid_bounds 
    20832056 
     
    20952068      REAL(wp), DIMENSION(:), ALLOCATABLE  ::   zlon 
    20962069      !!---------------------------------------------------------------------- 
    2097       ! 
    2098       ! seb: patch before we remove periodicity and close boundaries in output files 
    2099       IF ( ltmppatch ) THEN 
    2100          nldi_save = nldi   ;   nlei_save = nlei 
    2101          nldj_save = nldj   ;   nlej_save = nlej 
    2102          IF( nimpp           ==      1 ) nldi = 1 
    2103          IF( nimpp + jpi - 1 == jpiglo ) nlei = jpi 
    2104          IF( njmpp           ==      1 ) nldj = 1 
    2105          IF( njmpp + jpj - 1 == jpjglo ) nlej = jpj 
    2106       ENDIF 
    21072070      ! 
    21082071      ni=nlei-nldi+1       ! define zonal mean domain (jpj*jpk) 
     
    21192082      ! 
    21202083      CALL iom_update_file_name('ptr') 
    2121       ! 
    2122       IF ( ltmppatch ) THEN 
    2123          nldi = nldi_save   ;   nlei = nlei_save 
    2124          nldj = nldj_save   ;   nlej = nlej_save 
    2125       ENDIF 
    21262084      ! 
    21272085   END SUBROUTINE set_grid_znl 
  • NEMO/trunk/src/OCE/IOM/restart.F90

    r9654 r9903  
    118118                  clpname = TRIM(Agrif_CFixed())//"_"//clname    
    119119               ENDIF 
    120                CALL iom_init( cwxios_context, TRIM(clpath)//TRIM(clpname)) 
     120               CALL iom_init( cwxios_context, TRIM(clpath)//TRIM(clpname), .false. ) 
    121121               CALL xios_update_calendar(nitrst) 
    122122               CALL iom_swap(      cxios_context          ) 
     
    228228             IF( .NOT.lxios_set ) THEN 
    229229                 IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS' 
    230                  CALL iom_init( crxios_context ) 
     230                 CALL iom_init( crxios_context, ld_tmppatch = .false. ) 
    231231                 lxios_set = .TRUE. 
    232232             ENDIF 
    233233         ENDIF 
    234234         IF( TRIM(Agrif_CFixed()) /= '0' .AND. lrxios) THEN 
    235              CALL iom_init( crxios_context ) 
     235             CALL iom_init( crxios_context, ld_tmppatch = .false. ) 
    236236             IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS for AGRIF' 
    237237             lxios_set = .TRUE. 
Note: See TracChangeset for help on using the changeset viewer.