source: LMDZ5/branches/testing/libf/phylmd/rrtm/read_rsun_rrtm.F90 @ 2729

Last change on this file since 2729 was 2729, checked in by Laurent Fairhead, 8 years ago

Merged trunk changes r2719:2727 into testing branch

File size: 3.1 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!--test if time is different from year_len but allow a mismatch of 1 day
59       IF (size(time).NE.year_len.AND.size(time).NE.year_len+1) THEN
60         PRINT *,'read_rsun_rrtm time <> year_len = ', size(time), year_len
61         CALL abort_physic('read_rsun_rrtm','time dim should be the number of days in year',1)
62       ENDIF
63!--warning only if forcing file has 366 days but year_len has only 365
64       IF (size(time).EQ.year_len+1) THEN
65         PRINT *,'Warning read_rsun_rrtm uses a leap year rsun for a noleap year'
66       ENDIF
67
68       CALL nf95_inq_varid(ncid, 'ssi_frac', varid)
69       ncerr = nf90_get_var(ncid, varid, SSI_FRAC)
70
71       CALL nf95_inq_varid(ncid, 'tsi', varid)
72       ncerr = nf90_get_var(ncid, varid, TSI)
73
74       CALL nf95_close(ncid)
75
76       DO nbday=1, year_len
77         IF (ABS(SUM(SSI_FRAC(:,nbday))-1.).GT.1.e-6) THEN
78           PRINT *,'somme SSI_FRAC=', SUM(SSI_FRAC(:,nbday))
79           CALL abort_physic('read_rsun_rrtm','somme SSI_FRAC <> 1',1)
80         ENDIF
81       ENDDO
82     
83    ENDIF ! is_mpi_root .AND. is_omp_root
84
85!$OMP BARRIER
86    CALL bcast(SSI_FRAC)
87    CALL bcast(TSI)
88
89    ENDIF
90
91!--only read at beginning of month
92    IF (debut.OR.day_cur.NE.day_pre) THEN
93
94!--keep memory of previous month
95      day_pre=day_cur
96
97!--copy
98      RSUN(1:NSW)=SSI_FRAC(:,day_cur)
99      solaire=TSI(day_cur)
100
101      print *,'READ_RSUN_RRTM day=', day_cur,' solaire=', solaire, ' RSUN=', RSUN(1:NSW)
102
103    ENDIF !--fin allocation
104
105END SUBROUTINE read_rsun_rrtm
Note: See TracBrowser for help on using the repository browser.