Ignore:
Timestamp:
Nov 14, 2024, 11:53:17 AM (24 hours ago)
Author:
abarral
Message:

Turn condsurfs_new.f90 into module
Add own handle_err subroutine to condsurfs_new_mod.f90 phytracr_spl_mod.F90, as they were using incorrectly the one from grilles_gcm_netcdf_sub

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/Dust/condsurfs_new_mod.f90

    r5325 r5326  
     1MODULE condsurfs_new_mod
     2  IMPLICIT NONE; PRIVATE
     3  PUBLIC condsurfs_new
     4
     5CONTAINS
     6
     7  SUBROUTINE handle_err(status)
     8    USE netcdf, ONLY: nf90_noerr, nf90_strerror
     9    IMPLICIT NONE
     10
     11    INTEGER status
     12    IF (status/=nf90_noerr) THEN
     13      PRINT *, nf90_strerror(status)
     14      CALL abort_gcm('condsurfs_new', 'netcdf error', 1)
     15    ENDIF
     16  END SUBROUTINE handle_err
     17
    118SUBROUTINE condsurfs_new(jour, edgar, flag_dms, &
    219        lmt_so2b, lmt_so2h, lmt_so2nff, &
     
    273290  RETURN
    274291END SUBROUTINE condsurfs_new
     292
     293
     294END MODULE condsurfs_new_mod
Note: See TracChangeset for help on using the changeset viewer.