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

Last change on this file since 5418 was 5294, checked in by Laurent Fairhead, 7 weeks ago

Keeping clesphys.h was not the right solution
LF

File size: 3.3 KB
RevLine 
[2524]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
[5084]10  USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
[2524]11
[2803]12  USE phys_cal_mod, ONLY : days_elapsed, year_len
[2524]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
[2742]18  USE YOESW, ONLY : RSUN
[5294]19! Temporary fix waiting for cleaner interface (or not)
20  USE clesphys_mod_h, ONLY: NSW, solaire
21 
[2524]22  IMPLICIT NONE
23
[5294]24!!  INCLUDE "clesphys.h"
[2524]25
26  ! Input arguments
[2803]27  LOGICAL, INTENT(IN) :: debut
[2524]28
29! Local variables
[2803]30  INTEGER :: ncid, dimid, varid, ncerr, nbday
[4489]31  REAL, ALLOCATABLE :: wlen(:), time(:)
[2803]32  REAL, ALLOCATABLE, SAVE, DIMENSION(:,:) :: SSI_FRAC
[2524]33!$OMP THREADPRIVATE(SSI_FRAC)
34  REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: TSI(:)
35!$OMP THREADPRIVATE(TSI)
36
[2742]37  INTEGER, SAVE :: day_pre=1
38!$OMP THREADPRIVATE(day_pre)
[2524]39
40!--only one processor reads
41    IF (debut) THEN
42
43    ALLOCATE(SSI_FRAC(NSW,year_len))
44    ALLOCATE(TSI(year_len))
45
46    IF (is_mpi_root.AND.is_omp_root) THEN
47
48       CALL nf95_open('solarforcing.nc', NF90_NOWRITE, ncid)
49
50       CALL nf95_inq_varid(ncid, 'wlen', varid)
51       CALL nf95_gw_var(ncid, varid, wlen)
52
53       CALL nf95_inq_varid(ncid, 'time', varid)
54       CALL nf95_gw_var(ncid, varid, time)
55
56       IF (NSW.NE.size(wlen)) THEN
57         PRINT *,'read_rsun_rrtm NSW <> wlen = ',NSW, size(wlen)
58         CALL abort_physic('read_rsun_rrtm','size of SSI is different from NSW',1)
59       ENDIF
60
[2726]61!--test if time is different from year_len but allow a mismatch of 1 day
62       IF (size(time).NE.year_len.AND.size(time).NE.year_len+1) THEN
[2524]63         PRINT *,'read_rsun_rrtm time <> year_len = ', size(time), year_len
64         CALL abort_physic('read_rsun_rrtm','time dim should be the number of days in year',1)
65       ENDIF
[2726]66!--warning only if forcing file has 366 days but year_len has only 365
67       IF (size(time).EQ.year_len+1) THEN
68         PRINT *,'Warning read_rsun_rrtm uses a leap year rsun for a noleap year'
69       ENDIF
[2524]70
71       CALL nf95_inq_varid(ncid, 'ssi_frac', varid)
72       ncerr = nf90_get_var(ncid, varid, SSI_FRAC)
73
74       CALL nf95_inq_varid(ncid, 'tsi', varid)
75       ncerr = nf90_get_var(ncid, varid, TSI)
76
77       CALL nf95_close(ncid)
78
79       DO nbday=1, year_len
80         IF (ABS(SUM(SSI_FRAC(:,nbday))-1.).GT.1.e-6) THEN
81           PRINT *,'somme SSI_FRAC=', SUM(SSI_FRAC(:,nbday))
82           CALL abort_physic('read_rsun_rrtm','somme SSI_FRAC <> 1',1)
83         ENDIF
84       ENDDO
85     
86    ENDIF ! is_mpi_root .AND. is_omp_root
87
88!$OMP BARRIER
89    CALL bcast(SSI_FRAC)
90    CALL bcast(TSI)
91
92    ENDIF
93
[2803]94!--only read at beginning of day
95!--day in year is provided as days_elapsed since the beginning of the year +1
96    IF (debut.OR.days_elapsed+1.NE.day_pre) THEN
[2524]97
[2803]98!--keep memory of previous day
99      day_pre=days_elapsed+1
[2524]100
101!--copy
[2803]102      RSUN(1:NSW)=SSI_FRAC(:,days_elapsed+1)
103      solaire=TSI(days_elapsed+1)
[2524]104
[2803]105      print *,'READ_RSUN_RRTM day=', days_elapsed+1,' solaire=', solaire, ' RSUN=', RSUN(1:NSW)
[2524]106
107    ENDIF !--fin allocation
108
109END SUBROUTINE read_rsun_rrtm
Note: See TracBrowser for help on using the repository browser.