source: LMDZ6/trunk/libf/phylmd/readaerosolstrato.f90

Last change on this file was 5274, checked in by abarral, 52 minutes ago

Replace yomcst.h by existing module

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 8.6 KB
Line 
1subroutine readaerosolstrato(debut)
2
3    use netcdf95, only: nf95_close, nf95_gw_var, nf95_inq_dimid, &
4                        nf95_inq_varid, nf95_open
5    use netcdf, only: nf90_get_var, nf90_noerr, nf90_nowrite
6
7    USE phys_cal_mod, ONLY : mth_cur
8    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, &
9                                 grid2dto1d_glo, grid_type, unstructured
10    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
11    USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
12    USE mod_phys_lmdz_para
13    USE phys_state_var_mod
14    USE phys_local_var_mod
15    USE aero_mod
16    USE dimphy
17    USE print_control_mod, ONLY: prt_level,lunout
18    USE lmdz_xios
19    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
20          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
21          , R_ecc, R_peri, R_incl                                      &
22          , RA, RG, R1SA                                         &
23          , RSIGMA                                                     &
24          , R, RMD, RMV, RD, RV, RCPD                    &
25          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
26          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
27          , RCW, RCS                                                 &
28          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
29          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
30          , RALPD, RBETD, RGAMD
31implicit none
32
33
34
35! Variable input
36    logical debut
37
38! Variables locales
39    integer n_lat   ! number of latitudes in the input data
40    integer n_lon   ! number of longitudes in the input data
41    integer n_lev   ! number of levels in the input data
42    integer n_month ! number of months in the input data
43    real, allocatable:: latitude(:)
44    real, allocatable:: longitude(:)
45    real, allocatable:: time(:)
46    real, allocatable:: lev(:)
47    integer i, k, band, wave
48    integer, save :: mth_pre=1
49!$OMP THREADPRIVATE(mth_pre)
50
51    real, allocatable, dimension(:,:), save :: tau_aer_strat
52!$OMP THREADPRIVATE(tau_aer_strat)
53
54! Champs reconstitues
55    real, allocatable:: tauaerstrat(:, :, :, :)
56    real, allocatable:: tauaerstrat_mois(:, :, :)
57    real, allocatable:: tauaerstrat_mois_glo(:, :)
58    real, allocatable:: tau_aer_strat_mpi(:, :)
59
60! For NetCDF:
61    integer ncid_in  ! IDs for input files
62    integer varid, ncerr
63
64! Stratospheric aerosols optical properties
65! alpha_strat over the 2 bands is normalised by the 550 nm extinction coefficient
66! alpha_strat_wave is *not* normalised by the 550 nm extinction coefficient
67    real, dimension(nbands) :: alpha_strat, piz_strat, cg_strat
68    data alpha_strat/0.9922547, 0.7114912 /
69    data piz_strat  /0.9999998, 0.99762493/
70    data cg_strat   /0.73107845,0.73229635/
71    real, dimension(nwave_sw) :: alpha_strat_wave
72    data alpha_strat_wave/3.36780953,3.34667683,3.20444202,3.0293026,2.82108808/
73
74    CHARACTER (len = 20)                      :: modname = 'readaerosolstrato'
75    CHARACTER (len = 80)                      :: abort_message
76
77!--------------------------------------------------------
78
79    IF (.not.ALLOCATED(tau_aer_strat)) ALLOCATE(tau_aer_strat(klon,klev))
80
81!--only read file if beginning of run or start of new month
82    IF (debut.OR.mth_cur.NE.mth_pre) THEN
83
84!--only root reads
85    IF (is_mpi_root.AND.is_omp_root) THEN
86
87    IF (nbands.NE.2) THEN
88        abort_message='nbands doit etre egal a 2 dans readaerosolstrat'
89        CALL abort_physic(modname,abort_message,1)
90    ENDIF
91
92    CALL nf95_open("taustrat.nc", nf90_nowrite, ncid_in)
93
94    CALL nf95_inq_varid(ncid_in, "LEV", varid)
95    CALL nf95_gw_var(ncid_in, varid, lev)
96    n_lev = size(lev)
97    IF (n_lev.NE.klev) THEN
98       abort_message='Le nombre de niveaux n est pas egal a klev'
99       CALL abort_physic(modname,abort_message,1)
100    ENDIF
101
102    CALL nf95_inq_varid(ncid_in, "LAT", varid)
103    CALL nf95_gw_var(ncid_in, varid, latitude)
104    n_lat = size(latitude)
105    WRITE(lunout,*) 'LAT aerosol strato=', n_lat, latitude
106    IF (grid_type/=unstructured) THEN
107      IF (n_lat.NE.nbp_lat) THEN
108         abort_message='Le nombre de lat n est pas egal a nbp_lat'
109         CALL abort_physic(modname,abort_message,1)
110      ENDIF
111    ENDIF
112   
113    CALL nf95_inq_varid(ncid_in, "LON", varid)
114    CALL nf95_gw_var(ncid_in, varid, longitude)
115    n_lon = size(longitude)
116    IF (grid_type/=unstructured) THEN
117      WRITE(lunout,*) 'LON aerosol strato=', n_lon, longitude
118      IF (n_lon.NE.nbp_lon) THEN
119         abort_message='Le nombre de lon n est pas egal a nbp_lon'
120         CALL abort_physic(modname,abort_message,1)
121      ENDIF
122    ENDIF
123   
124    CALL nf95_inq_varid(ncid_in, "TIME", varid)
125    CALL nf95_gw_var(ncid_in, varid, time)
126    n_month = size(time)
127    WRITE(lunout,*) 'TIME aerosol strato=', n_month, time
128    IF (n_month.NE.12) THEN
129       abort_message='Le nombre de month n est pas egal a 12'
130       CALL abort_physic(modname,abort_message,1)
131    ENDIF
132
133    IF (.not.ALLOCATED(tauaerstrat))          ALLOCATE(tauaerstrat(n_lon, n_lat, n_lev, n_month))
134    IF (.not.ALLOCATED(tauaerstrat_mois))     ALLOCATE(tauaerstrat_mois(n_lon, n_lat, n_lev))
135    IF (.not.ALLOCATED(tauaerstrat_mois_glo)) ALLOCATE(tauaerstrat_mois_glo(klon_glo, n_lev))
136
137!--reading stratospheric AOD at 550 nm
138    CALL nf95_inq_varid(ncid_in, "TAUSTRAT", varid)
139    ncerr = nf90_get_var(ncid_in, varid, tauaerstrat)
140    WRITE(lunout,*) 'code erreur readaerosolstrato=', ncerr, varid
141
142    CALL nf95_close(ncid_in)
143
144!---select the correct month
145    IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
146     WRITE(lunout,*) 'probleme avec le mois dans readaerosolstrat =', mth_cur
147    ENDIF
148    tauaerstrat_mois(:,:,:) = tauaerstrat(:,:,:,mth_cur)
149
150!---reduce to a klon_glo grid
151    CALL grid2dTo1d_glo(tauaerstrat_mois,tauaerstrat_mois_glo)
152
153    ELSE
154      ALLOCATE(tauaerstrat_mois(0,0,0))
155    ENDIF !--is_mpi_root and is_omp_root
156
157!$OMP BARRIER
158
159    IF (grid_type==unstructured) THEN
160      IF (is_omp_master) THEN
161        CALL xios_send_field("taustrat_in",tauaerstrat_mois)
162        ALLOCATE(tau_aer_strat_mpi(klon_mpi, klev))
163        CALL xios_recv_field("taustrat_out",tau_aer_strat_mpi)
164      ELSE
165        ALLOCATE(tau_aer_strat_mpi(0,0))
166      ENDIF
167      CALL scatter_omp(tau_aer_strat_mpi,tau_aer_strat)
168    ELSE 
169!--scatter on all proc
170      CALL scatter(tauaerstrat_mois_glo,tau_aer_strat)
171    ENDIF
172
173!--keep memory of previous month
174    mth_pre=mth_cur
175!
176    IF (is_mpi_root.AND.is_omp_root) THEN
177!
178    DEALLOCATE(tauaerstrat)
179    DEALLOCATE(tauaerstrat_mois)
180    DEALLOCATE(tauaerstrat_mois_glo)
181!
182    ENDIF !-is_mpi_root and is_omp_root
183
184!$OMP BARRIER
185
186    ENDIF !--debut ou nouveau mois
187
188!--total vertical aod at the 6 wavelengths
189    DO wave=1, nwave_sw
190    DO k=1, klev
191    tausum_aero(:,wave,id_STRAT_phy)=tausum_aero(:,wave,id_STRAT_phy)+tau_aer_strat(:,k)*alpha_strat_wave(wave)/alpha_strat_wave(2)
192    ENDDO
193    ENDDO
194
195!--weighted average for cg, piz and tau, adding strat aerosols on top of tropospheric ones
196    DO band=1, nbands
197!--anthropogenic aerosols bands 1 and 2
198    cg_aero(:,:,3,band)  = ( cg_aero(:,:,3,band)*piz_aero(:,:,3,band)*tau_aero(:,:,3,band) +          &
199                             cg_strat(band)*piz_strat(band)*alpha_strat(band)*tau_aer_strat(:,:) ) /  &
200                             MAX( piz_aero(:,:,3,band)*tau_aero(:,:,3,band) +                         &
201                                  piz_strat(band)*alpha_strat(band)*tau_aer_strat(:,:), 1.e-15 )
202    piz_aero(:,:,3,band)  = ( piz_aero(:,:,3,band)*tau_aero(:,:,3,band) +                             &
203                              piz_strat(band)*alpha_strat(band)*tau_aer_strat(:,:) ) /                &
204                              MAX( tau_aero(:,:,3,band) + alpha_strat(band)*tau_aer_strat(:,:), 1.e-15 )
205    tau_aero(:,:,3,band)  = tau_aero(:,:,3,band) + alpha_strat(band)*tau_aer_strat(:,:)
206!--natural aerosols bands 1 and 2
207    cg_aero(:,:,2,band)  = ( cg_aero(:,:,2,band)*piz_aero(:,:,2,band)*tau_aero(:,:,2,band) +          &
208                             cg_strat(band)*piz_strat(band)*alpha_strat(band)*tau_aer_strat(:,:) ) /  &
209                             MAX( piz_aero(:,:,2,band)*tau_aero(:,:,2,band) +                         &
210                                  piz_strat(band)*alpha_strat(band)*tau_aer_strat(:,:), 1.e-15 )
211    piz_aero(:,:,2,band)  = ( piz_aero(:,:,2,band)*tau_aero(:,:,2,band) +                             &
212                              piz_strat(band)*alpha_strat(band)*tau_aer_strat(:,:) ) /                &
213                              MAX( tau_aero(:,:,2,band) + alpha_strat(band)*tau_aer_strat(:,:),1.e-15 )
214    tau_aero(:,:,2,band)  = tau_aero(:,:,2,band) + alpha_strat(band)*tau_aer_strat(:,:)
215    ENDDO
216
217end subroutine readaerosolstrato
Note: See TracBrowser for help on using the repository browser.