source: LMDZ5/trunk/libf/phylmd/rrtm/read_rsun_rrtm.F90 @ 2724

Last change on this file since 2724 was 2724, checked in by oboucher, 8 years ago

Small correction on initialisation of RSUN array as RSUN is declared with dimension NTSW > NSW

File size: 2.8 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 : day_cur, 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
36
37!--only one processor reads
38    IF (debut) THEN
39
40    ALLOCATE(SSI_FRAC(NSW,year_len))
41    ALLOCATE(TSI(year_len))
42
43    IF (is_mpi_root.AND.is_omp_root) THEN
44
45       CALL nf95_open('solarforcing.nc', NF90_NOWRITE, ncid)
46
47       CALL nf95_inq_varid(ncid, 'wlen', varid)
48       CALL nf95_gw_var(ncid, varid, wlen)
49
50       CALL nf95_inq_varid(ncid, 'time', varid)
51       CALL nf95_gw_var(ncid, varid, time)
52
53       IF (NSW.NE.size(wlen)) THEN
54         PRINT *,'read_rsun_rrtm NSW <> wlen = ',NSW, size(wlen)
55         CALL abort_physic('read_rsun_rrtm','size of SSI is different from NSW',1)
56       ENDIF
57
58       IF (size(time).NE.year_len) THEN
59         PRINT *,'read_rsun_rrtm time <> year_len = ', size(time), year_len
60         CALL abort_physic('read_rsun_rrtm','time dim should be the number of days in year',1)
61       ENDIF
62
63       CALL nf95_inq_varid(ncid, 'ssi_frac', varid)
64       ncerr = nf90_get_var(ncid, varid, SSI_FRAC)
65
66       CALL nf95_inq_varid(ncid, 'tsi', varid)
67       ncerr = nf90_get_var(ncid, varid, TSI)
68
69       CALL nf95_close(ncid)
70
71       DO nbday=1, year_len
72         IF (ABS(SUM(SSI_FRAC(:,nbday))-1.).GT.1.e-6) THEN
73           PRINT *,'somme SSI_FRAC=', SUM(SSI_FRAC(:,nbday))
74           CALL abort_physic('read_rsun_rrtm','somme SSI_FRAC <> 1',1)
75         ENDIF
76       ENDDO
77     
78    ENDIF ! is_mpi_root .AND. is_omp_root
79
80!$OMP BARRIER
81    CALL bcast(SSI_FRAC)
82    CALL bcast(TSI)
83
84    ENDIF
85
86!--only read at beginning of month
87    IF (debut.OR.day_cur.NE.day_pre) THEN
88
89!--keep memory of previous month
90      day_pre=day_cur
91
92!--copy
93      RSUN(1:NSW)=SSI_FRAC(:,day_cur)
94      solaire=TSI(day_cur)
95
96      print *,'READ_RSUN_RRTM day=', day_cur,' solaire=', solaire, ' RSUN=', RSUN(1:NSW)
97
98    ENDIF !--fin allocation
99
100END SUBROUTINE read_rsun_rrtm
Note: See TracBrowser for help on using the repository browser.