source: LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/read_rsun_volcanoes.F90 @ 3576

Last change on this file since 3576 was 3576, checked in by acozic, 5 years ago

for IPSLCM5A2CHT we add the possibilty to read solaire and strat aod in forcing files
warning for this we use the flag ok_suntime_rrtm

File size: 3.1 KB
Line 
1SUBROUTINE read_rsun_volcanoes(debut)
2
3!****************************************************************************************
4! This routine will read the solar constant fraction per band
5!
6! Olivier Boucher with inputs from Marion Marchand
7!****************************************************************************************
8
9  USE netcdf95, ONLY: nf95_close, nf95_inq_varid, nf95_open, nf95_gw_var
10  USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
11
12  USE phys_cal_mod, ONLY : days_elapsed, year_len,mth_cur
13
14  USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
15  USE mod_phys_lmdz_omp_data, ONLY: is_omp_root
16  USE mod_phys_lmdz_para
17
18!AC  USE YOESW, ONLY : RSUN
19
20  IMPLICIT NONE
21
22  INCLUDE "clesphys.h"
23
24  ! Input arguments
25  LOGICAL, INTENT(IN) :: debut
26
27! Local variables
28  INTEGER :: ncid, dimid, varid, ncerr, nbday
29  REAL, POINTER :: time(:)
30  REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: TSI(:)
31!$OMP THREADPRIVATE(TSI)
32  REAL, SAVE, DIMENSION(12) :: volc
33!$OMP THREADPRIVATE(volc)
34
35  INTEGER, SAVE :: day_pre=1
36!$OMP THREADPRIVATE(day_pre)
37
38!--only one processor reads
39    IF (debut) THEN
40
41!    ALLOCATE(SSI_FRAC(NSW,year_len))
42!       print *, 'year_len = ', year_len
43       ALLOCATE(TSI(year_len))
44
45       IF (is_mpi_root.AND.is_omp_root) THEN
46
47          CALL nf95_open('solarforcing.nc', NF90_NOWRITE, ncid)
48          CALL nf95_inq_varid(ncid, 'time', varid)
49          CALL nf95_gw_var(ncid, varid, time)
50
51!--test if time is different from year_len but allow a mismatch of 1 day
52          IF (size(time).NE.year_len.AND.size(time).NE.year_len+1) THEN
53             PRINT *,'read_rsun_volcanoes time <> year_len = ', size(time), year_len, year_len+1
54             CALL abort_physic('read_rsun_volcanoes','time dim should be the number of days in year',1)
55          ENDIF
56!--warning only if forcing file has 366 days but year_len has only 365
57          IF (size(time).EQ.year_len+1) THEN
58             PRINT *,'Warning read_rsun_volcanoes uses a leap year rsun for a noleap year'
59          ENDIF
60
61
62          CALL nf95_inq_varid(ncid, 'tsi', varid)
63          ncerr = nf90_get_var(ncid, varid, TSI)
64
65          CALL nf95_close(ncid)
66
67! lecture des aod strato dans le fichier volcanoes.nc
68          CALL nf95_open('volcanoes.nc', NF90_NOWRITE, ncid)
69          CALL nf95_inq_varid(ncid, 'time', varid)
70          CALL nf95_gw_var(ncid, varid, time)
71          CALL nf95_inq_varid(ncid, 'volc', varid)
72          ncerr = nf90_get_var(ncid, varid, volc)
73          CALL nf95_close(ncid)
74         
75
76
77     
78       ENDIF ! is_mpi_root .AND. is_omp_root
79
80!$OMP BARRIER
81
82       CALL bcast(TSI)
83       call bcast(volc)
84    ENDIF
85
86!--only read at beginning of day
87!--day in year is provided as days_elapsed since the beginning of the year +1
88    IF (debut.OR.days_elapsed+1.NE.day_pre) THEN
89
90!--keep memory of previous day
91       day_pre=days_elapsed+1
92
93!--copy
94       solaire=TSI(days_elapsed+1)
95
96       solaire = solaire + volc(mth_cur)
97
98!       print *,'READ_RSUN day=', days_elapsed+1,mth_cur, ' volc = ', volc(mth_cur), ' tsi = ',tsi(days_elapsed+1) , ' solaire=', solaire
99
100    ENDIF !--fin allocation
101
102  END SUBROUTINE read_rsun_volcanoes
Note: See TracBrowser for help on using the repository browser.