Ignore:
Timestamp:
Jan 23, 2017, 2:55:32 PM (7 years ago)
Author:
dcugnet
Message:

Fix a bug about limit.nc file checking.
The limit.nc number of days does not need to be checked every day ; it
is now checked only at the start of the run ; this avoids the gcm to
stop because of a mismatch between the file and model number of days
(in the case of an irregular calendar) on last day due to the fact
that the calendar is updated before the end of the day.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/limit_read_mod.F90

    r2667 r2768  
    204204       END IF
    205205
    206        first_call=.FALSE.
    207     ENDIF
    208  
    209 !****************************************************************************************
    210 ! 1) Open the file limit.nc if it is the right moment to read, once a day.
    211 !    The file is read only by the master thread of the master mpi process(is_mpi_root)
    212 !    Check by the way if the number of records is correct.
    213 !
    214 !****************************************************************************************
    215 
    216     is_modified = .FALSE.
    217     IF (MOD(itime-1, lmt_pas) == 0 .OR. jour_lu /= jour ) THEN   ! time to read
    218        jour_lu = jour
    219        is_modified = .TRUE.
    220206!$OMP MASTER  ! Only master thread
    221207       IF (is_mpi_root) THEN ! Only master processus
    222 
    223208          ierr = NF90_OPEN ('limit.nc', NF90_NOWRITE, nid)
    224209          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,&
     
    237222          ierr=NF90_INQUIRE(nid, UnlimitedDimID=ndimid)
    238223          ierr=NF90_INQUIRE_DIMENSION(nid, ndimid, len=nn)
    239           CALL num2str(nn,str)
    240           abort_message='limit.nc records number ('//TRIM(str)//') does'//&
    241             ' not match year length ('
    242           CALL num2str(year_len,str)
    243           abort_message=TRIM(abort_message)//TRIM(str)//')'
     224          WRITE(abort_message,'(a,2(i0,a))')'limit.nc records number (',nn,') does no'//&
     225            't match year length (',year_len,')'
    244226          IF(nn/=year_len) CALL abort_physic(modname,abort_message,1)
    245227
     
    247229          ierr=NF90_INQ_DIMID(nid, 'points_physiques', ndimid)
    248230          ierr=NF90_INQUIRE_DIMENSION(nid, ndimid, len=nn)
    249           CALL num2str(nn,str)
    250           abort_message='limit.nc horizontal number of cells ('//TRIM(str)//') does'//&
    251             ' not match LMDZ klon_glo ('
    252           CALL num2str(klon_glo,str)
    253           abort_message=TRIM(abort_message)//TRIM(str)//')'
     231          WRITE(abort_message,'(a,2(i0,a))')'limit.nc horizontal number of cells (',nn, &
     232            ') does not match LMDZ klon_glo (',klon_glo,')'
    254233          IF(nn/=klon_glo) CALL abort_physic(modname,abort_message,1)
     234
     235          ierr = NF90_CLOSE(nid)
     236          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
     237          first_call=.FALSE.
     238       END IF ! is_mpi_root
     239!$OMP END MASTER
     240!$OMP BARRIER
     241    END IF
     242
     243!****************************************************************************************
     244! 1) Open the file limit.nc if it is the right moment to read, once a day.
     245!    The file is read only by the master thread of the master mpi process(is_mpi_root)
     246!    Check by the way if the number of records is correct.
     247!
     248!****************************************************************************************
     249
     250    is_modified = .FALSE.
     251    IF (MOD(itime-1, lmt_pas) == 0 .OR. jour_lu /= jour ) THEN   ! time to read
     252       jour_lu = jour
     253       is_modified = .TRUE.
     254!$OMP MASTER  ! Only master thread
     255       IF (is_mpi_root) THEN ! Only master processus
     256
     257          ierr = NF90_OPEN ('limit.nc', NF90_NOWRITE, nid)
     258          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,&
     259               'Pb d''ouverture du fichier de conditions aux limites',1)
    255260
    256261          ! La tranche de donnees a lire:
     
    370375  END SUBROUTINE limit_read_tot
    371376
    372   !--------------------------------------------------------------------------------------
    373   SUBROUTINE num2str(n,str)
    374   !--------------------------------------------------------------------------------------
    375   ! Arguments:
    376     INTEGER,           INTENT(IN)  :: n
    377     CHARACTER(LEN=99), INTENT(OUT) :: str
    378   !--------------------------------------------------------------------------------------
    379   ! Local variables:
    380     INTEGER :: nn
    381   !--------------------------------------------------------------------------------------
    382     nn=n; str=''; DO WHILE(nn>0); str=CHAR(nn-10*(nn/10)-48)//TRIM(str); nn=nn/10; END DO
    383   END SUBROUTINE num2str
    384   !--------------------------------------------------------------------------------------
    385 
    386377END MODULE limit_read_mod
Note: See TracChangeset for help on using the changeset viewer.