Ignore:
Timestamp:
Nov 14, 2024, 11:53:17 AM (25 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

Location:
LMDZ6/trunk/libf/phylmd/Dust
Files:
2 edited
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
  • LMDZ6/trunk/libf/phylmd/Dust/phytracr_spl_mod.F90

    r5292 r5326  
    99  USE chem_spla_mod_h
    1010
     11  IMPLICIT NONE
     12  PRIVATE handle_err
     13
    1114  REAL,SAVE  :: scale_param_ssacc  !Scaling parameter for Fine Sea Salt
    1215  REAL,SAVE ::  scale_param_sscoa  !Scaling parameter for Coarse Sea Salt
    13 
    14 
    1516
    1617  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: scale_param_ind !Scaling parameter for industrial emissions of SO2
     
    426427
    427428CONTAINS
    428 !
     429
     430  SUBROUTINE handle_err(status)
     431    USE netcdf, ONLY: nf90_noerr, nf90_strerror
     432    IMPLICIT NONE
     433
     434    INTEGER status
     435    IF (status/=nf90_noerr) THEN
     436      PRINT *, nf90_strerror(status)
     437      CALL abort_gcm('phytrac_spl_mod', 'netcdf error', 1)
     438    ENDIF
     439  END SUBROUTINE handle_err
     440
    429441!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    430442SUBROUTINE phytracr_spl_out_init()
  • LMDZ6/trunk/libf/phylmd/Dust/read_newemissions.f90

    r5292 r5326  
    2626
    2727  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    28 USE paramet_mod_h
     28  USE paramet_mod_h
     29  USE condsurfs_new_mod, ONLY: condsurfs_new
    2930IMPLICIT NONE
    3031
Note: See TracChangeset for help on using the changeset viewer.