source: LMDZ6/trunk/libf/phylmd/rrtm/read_rsun_rrtm.F90 @ 3981

Last change on this file since 3981 was 2803, checked in by oboucher, 7 years ago

Correcting bug on current day in the year in RSUN forcing

File size: 3.2 KB
Line 
1SUBROUTINE read_rsun_rrtm(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
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  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 :: wlen(:), time(:)
30  REAL, ALLOCATABLE, SAVE, DIMENSION(:,:) :: SSI_FRAC
31!$OMP THREADPRIVATE(SSI_FRAC)
32  REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: TSI(:)
33!$OMP THREADPRIVATE(TSI)
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    ALLOCATE(TSI(year_len))
43
44    IF (is_mpi_root.AND.is_omp_root) THEN
45
46       CALL nf95_open('solarforcing.nc', NF90_NOWRITE, ncid)
47
48       CALL nf95_inq_varid(ncid, 'wlen', varid)
49       CALL nf95_gw_var(ncid, varid, wlen)
50
51       CALL nf95_inq_varid(ncid, 'time', varid)
52       CALL nf95_gw_var(ncid, varid, time)
53
54       IF (NSW.NE.size(wlen)) THEN
55         PRINT *,'read_rsun_rrtm NSW <> wlen = ',NSW, size(wlen)
56         CALL abort_physic('read_rsun_rrtm','size of SSI is different from NSW',1)
57       ENDIF
58
59!--test if time is different from year_len but allow a mismatch of 1 day
60       IF (size(time).NE.year_len.AND.size(time).NE.year_len+1) THEN
61         PRINT *,'read_rsun_rrtm time <> year_len = ', size(time), year_len
62         CALL abort_physic('read_rsun_rrtm','time dim should be the number of days in year',1)
63       ENDIF
64!--warning only if forcing file has 366 days but year_len has only 365
65       IF (size(time).EQ.year_len+1) THEN
66         PRINT *,'Warning read_rsun_rrtm uses a leap year rsun for a noleap year'
67       ENDIF
68
69       CALL nf95_inq_varid(ncid, 'ssi_frac', varid)
70       ncerr = nf90_get_var(ncid, varid, SSI_FRAC)
71
72       CALL nf95_inq_varid(ncid, 'tsi', varid)
73       ncerr = nf90_get_var(ncid, varid, TSI)
74
75       CALL nf95_close(ncid)
76
77       DO nbday=1, year_len
78         IF (ABS(SUM(SSI_FRAC(:,nbday))-1.).GT.1.e-6) THEN
79           PRINT *,'somme SSI_FRAC=', SUM(SSI_FRAC(:,nbday))
80           CALL abort_physic('read_rsun_rrtm','somme SSI_FRAC <> 1',1)
81         ENDIF
82       ENDDO
83     
84    ENDIF ! is_mpi_root .AND. is_omp_root
85
86!$OMP BARRIER
87    CALL bcast(SSI_FRAC)
88    CALL bcast(TSI)
89
90    ENDIF
91
92!--only read at beginning of day
93!--day in year is provided as days_elapsed since the beginning of the year +1
94    IF (debut.OR.days_elapsed+1.NE.day_pre) THEN
95
96!--keep memory of previous day
97      day_pre=days_elapsed+1
98
99!--copy
100      RSUN(1:NSW)=SSI_FRAC(:,days_elapsed+1)
101      solaire=TSI(days_elapsed+1)
102
103      print *,'READ_RSUN_RRTM day=', days_elapsed+1,' solaire=', solaire, ' RSUN=', RSUN(1:NSW)
104
105    ENDIF !--fin allocation
106
107END SUBROUTINE read_rsun_rrtm
Note: See TracBrowser for help on using the repository browser.