SUBROUTINE read_rsun_volcanoes(debut) !**************************************************************************************** ! This routine will read the solar constant fraction per band ! ! Olivier Boucher with inputs from Marion Marchand !**************************************************************************************** USE netcdf95, ONLY: nf95_close, nf95_inq_varid, nf95_open, nf95_gw_var USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite USE phys_cal_mod, ONLY : days_elapsed, year_len,mth_cur USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root USE mod_phys_lmdz_omp_data, ONLY: is_omp_root USE mod_phys_lmdz_para !AC USE YOESW, ONLY : RSUN IMPLICIT NONE INCLUDE "clesphys.h" ! Input arguments LOGICAL, INTENT(IN) :: debut ! Local variables INTEGER :: ncid, dimid, varid, ncerr, nbday REAL, POINTER :: time(:) REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: TSI(:) !$OMP THREADPRIVATE(TSI) REAL, SAVE, DIMENSION(12) :: volc !$OMP THREADPRIVATE(volc) INTEGER, SAVE :: day_pre=1 !$OMP THREADPRIVATE(day_pre) !--only one processor reads IF (debut) THEN ! ALLOCATE(SSI_FRAC(NSW,year_len)) ! print *, 'year_len = ', year_len ALLOCATE(TSI(year_len)) IF (is_mpi_root.AND.is_omp_root) THEN CALL nf95_open('solarforcing.nc', NF90_NOWRITE, ncid) CALL nf95_inq_varid(ncid, 'time', varid) CALL nf95_gw_var(ncid, varid, time) !--test if time is different from year_len but allow a mismatch of 1 day IF (size(time).NE.year_len.AND.size(time).NE.year_len+1) THEN PRINT *,'read_rsun_volcanoes time <> year_len = ', size(time), year_len, year_len+1 CALL abort_physic('read_rsun_volcanoes','time dim should be the number of days in year',1) ENDIF !--warning only if forcing file has 366 days but year_len has only 365 IF (size(time).EQ.year_len+1) THEN PRINT *,'Warning read_rsun_volcanoes uses a leap year rsun for a noleap year' ENDIF CALL nf95_inq_varid(ncid, 'tsi', varid) ncerr = nf90_get_var(ncid, varid, TSI) CALL nf95_close(ncid) ! lecture des aod strato dans le fichier volcanoes.nc CALL nf95_open('volcanoes.nc', NF90_NOWRITE, ncid) CALL nf95_inq_varid(ncid, 'time', varid) CALL nf95_gw_var(ncid, varid, time) CALL nf95_inq_varid(ncid, 'volc', varid) ncerr = nf90_get_var(ncid, varid, volc) CALL nf95_close(ncid) ENDIF ! is_mpi_root .AND. is_omp_root !$OMP BARRIER CALL bcast(TSI) call bcast(volc) ENDIF !--only read at beginning of day !--day in year is provided as days_elapsed since the beginning of the year +1 IF (debut.OR.days_elapsed+1.NE.day_pre) THEN !--keep memory of previous day day_pre=days_elapsed+1 !--copy solaire=TSI(days_elapsed+1) solaire = solaire + volc(mth_cur) ! print *,'READ_RSUN day=', days_elapsed+1,mth_cur, ' volc = ', volc(mth_cur), ' tsi = ',tsi(days_elapsed+1) , ' solaire=', solaire ENDIF !--fin allocation END SUBROUTINE read_rsun_volcanoes