source: LMDZ4/branches/LMDZ4-dev/libf/phylmd/readaerosol_interp.F90 @ 1248

Last change on this file since 1248 was 1246, checked in by Laurent Fairhead, 15 years ago
  • En deconnectant les aérosols (ok_ade=ok_aie=n) on a les mêmes

résultats avant et après les modifs.

  • preindustrial readin fields are used to compute natural aerosol fields

to allow for clean double calls to radiation

  • full forcing diagnostics (NAT, ANT, ZERO, Cloud forcing, CS,AS) are

activated with lev_histmth 4, If lev_histmth is not 4, the call to the
radiation is minimized, for efficiency, but ade and aie are computed and
applied (however for species wise forcing one would need to do
difference runs) (still quite a bit new forcing info, requires probably

some more explanation)

  • there is a hardcoded key in sw_aeroAR4.F90 which lets you choose to use the zero aerosol, or natural aerosol perturbation acting on the meteorology, but still would put out the full forcing diagnostics.
  • aod fields from offline aerosol fields are also output in histmth for

all aerosol tracers read in and available for evaluation

  • aeropt contains the ss humidity correction from nicolas&yves
File size: 20.1 KB
Line 
1! $Id$
2!
3SUBROUTINE readaerosol_interp(id_aero, itap, pdtphys, r_day, first, pplay, paprs, t_seri, mass_out, pi_mass_out)
4!
5! This routine will return the mass concentration at actual day(mass_out) and
6! the pre-industrial values(pi_mass_out) for aerosol corresponding to "id_aero".
7! The mass concentrations for all aerosols are saved in this routine but each
8! call to this routine only treats the aerosol "id_aero".
9!
10! 1) Read in data for the whole year, only at first time step
11! 2) Interpolate to the actual day, only at new day
12! 3) Interpolate to the model vertical grid (target grid), only at new day
13! 4) Test for negative mass values
14
15  USE dimphy, ONLY : klev,klon
16  USE mod_phys_lmdz_para, ONLY : mpi_rank 
17  USE readaerosol_mod
18  USE aero_mod, ONLY : naero_spc, name_aero
19  USE write_field_phy
20  USE phys_cal_mod
21
22  IMPLICIT NONE
23
24  INCLUDE "YOMCST.h"
25  INCLUDE "chem.h"     
26  INCLUDE "temps.h"     
27  INCLUDE "clesphys.h"
28  INCLUDE "iniprint.h"
29  INCLUDE "dimensions.h"
30  INCLUDE "comvert.h"
31!
32! Input:
33!****************************************************************************************
34  INTEGER, INTENT(IN)                    :: id_aero! Identity number for the aerosol to treat
35  INTEGER, INTENT(IN)                    :: itap   ! Physic step count
36  REAL, INTENT(IN)                       :: pdtphys! Physic day step
37  REAL, INTENT(IN)                       :: r_day  ! Day of integration
38  LOGICAL, INTENT(IN)                    :: first  ! First model timestep
39  REAL, DIMENSION(klon,klev), INTENT(IN) :: pplay  ! pression at model mid-layers
40  REAL, DIMENSION(klon,klev+1),INTENT(IN):: paprs  ! pression between model layers
41  REAL, DIMENSION(klon,klev), INTENT(IN) :: t_seri ! air temperature
42!     
43! Output:     
44!****************************************************************************************
45  REAL, INTENT(OUT) :: mass_out(klon,klev)    ! Mass of aerosol (monthly mean data,from file) [ug AIBCM/m3]
46  REAL, INTENT(OUT) :: pi_mass_out(klon,klev) ! Mass of preindustrial aerosol (monthly mean data,from file) [ug AIBCM/m3]
47!     
48! Local Variables:
49!****************************************************************************************
50  INTEGER                         :: i, k, ierr
51  INTEGER                         :: iday, iyr, lmt_pas
52  INTEGER                         :: im, day1, day2, im2
53  INTEGER                         :: pi_klev_src ! Only for testing purpose
54  INTEGER, SAVE                   :: klev_src    ! Number of vertical levles in source field
55!$OMP THREADPRIVATE(klev_src)
56
57  REAL                              :: zrho      ! Air density [kg/m3]
58  REAL                              :: volm      ! Volyme de melange [kg/kg]
59  REAL, DIMENSION(klon)             :: psurf_day, pi_psurf_day
60  REAL, DIMENSION(klon)             :: load_src, pi_load_src  ! Mass load at source grid
61  REAL, DIMENSION(klon)             :: load_tgt, load_tgt_test
62  REAL, DIMENSION(klon,klev)        :: delp ! pressure difference in each model layer
63
64  REAL, ALLOCATABLE, DIMENSION(:,:)            :: pplay_src ! pression mid-layer at source levels
65  REAL, ALLOCATABLE, DIMENSION(:,:)            :: tmp1, tmp2  ! Temporary variables
66  REAL, ALLOCATABLE, DIMENSION(:,:,:,:), SAVE  :: var_year    ! VAR in right dimension for the total year
67  REAL, ALLOCATABLE, DIMENSION(:,:,:,:), SAVE  :: pi_var_year ! pre-industrial VAR, -"-
68!$OMP THREADPRIVATE(var_year,pi_var_year)
69  REAL, ALLOCATABLE, DIMENSION(:,:,:),SAVE     :: var_day     ! VAR interpolated to the actual day and model grid
70  REAL, ALLOCATABLE, DIMENSION(:,:,:),SAVE     :: pi_var_day  ! pre-industrial VAR, -"-
71!$OMP THREADPRIVATE(var_day,pi_var_day)
72  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE    :: psurf_year, pi_psurf_year ! surface pressure for the total year
73!$OMP THREADPRIVATE(psurf_year, pi_psurf_year)
74  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE    :: load_year, pi_load_year   ! load in the column for the total year
75!$OMP THREADPRIVATE(load_year, pi_load_year)
76
77  REAL, DIMENSION(:,:,:), POINTER   :: pt_tmp      ! Pointer allocated in readaerosol
78  REAL, POINTER, DIMENSION(:), SAVE :: pt_ap, pt_b ! Pointer for describing the vertical levels
79!$OMP THREADPRIVATE(pt_ap, pt_b)
80
81  LOGICAL            :: lnewday      ! Indicates if first time step at a new day
82  LOGICAL            :: OLDNEWDAY
83  LOGICAL,SAVE       :: vert_interp  ! Indicates if vertical interpolation will be done
84  LOGICAL,SAVE       :: debug=.FALSE.! Debugging in this subroutine
85!$OMP THREADPRIVATE(vert_interp, debug)
86
87
88!****************************************************************************************
89! Initialization
90!
91!****************************************************************************************
92
93! Calculation to find if it is a new day
94
95  IF(mpi_rank == 0)then
96     PRINT*,'CONTROL PANEL REGARDING TIME STEPING'
97  ENDIF
98
99  ! Use phys_cal_mod
100  !iday= day_cur
101  !iyr = year_cur
102  !im  = mth_cur
103
104  iday = INT(r_day)
105  iyr  = iday/360
106  iday = iday-iyr*360         ! day of the actual year
107  iyr  = iyr + annee_ref      ! year of the run   
108  im   = iday/30 +1           ! the actual month
109
110  IF(MOD(itap-1,NINT(86400./pdtphys)) == 0)THEN
111     lnewday=.TRUE.
112  ENDIF
113
114  IF(mpi_rank == 0)then
115     ! 0.02 is about 0.5/24, namly less than half an hour
116     OLDNEWDAY = (r_day-FLOAT(iday) < 0.02)
117     ! Once per day, update aerosol fields
118     lmt_pas = NINT(86400./pdtphys)
119     PRINT*,'r_day-FLOAT(iday) =',r_day-FLOAT(iday)
120     PRINT*,'itap =',itap
121     PRINT*,'pdtphys =',pdtphys
122     PRINT*,'lmt_pas =',lmt_pas
123     PRINT*,'iday =',iday
124     PRINT*,'r_day =',r_day
125     PRINT*,'day_cur =',day_cur
126     PRINT*,'mth_cur =',mth_cur
127     PRINT*,'year_cur =',year_cur
128     PRINT*,'NINT(86400./pdtphys) =',NINT(86400./pdtphys)
129     PRINT*,'MOD(0,1) =',MOD(0,1)
130     PRINT*,'lnewday =',lnewday
131     PRINT*,'OLDNEWDAY =',OLDNEWDAY
132  ENDIF
133
134  IF (.NOT. ALLOCATED(var_day)) THEN
135     ALLOCATE( var_day(klon, klev, naero_spc), stat=ierr)
136     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 1',1)
137     ALLOCATE( pi_var_day(klon, klev, naero_spc), stat=ierr)
138     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 2',1)
139
140     ALLOCATE( psurf_year(klon, 12, naero_spc), pi_psurf_year(klon, 12, naero_spc), stat=ierr)
141     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 3',1)
142
143     ALLOCATE( load_year(klon, 12, naero_spc), pi_load_year(klon, 12, naero_spc), stat=ierr)
144     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 4',1)
145
146     lnewday=.TRUE.
147
148     NULLIFY(pt_ap)
149     NULLIFY(pt_b)
150  END IF
151
152!****************************************************************************************
153! 1) Read in data : corresponding to the actual year and preindustrial data.
154!    Only for the first day of the year.
155!
156!****************************************************************************************
157  IF ( (first .OR. iday==0) .AND. lnewday ) THEN
158     NULLIFY(pt_tmp)
159
160     ! Reading values corresponding to the closest year taking into count the choice of aer_type.
161     ! For aer_type=scenario interpolation between 2 data sets is done in readaerosol.
162     CALL readaerosol(name_aero(id_aero), aer_type, iyr, klev_src, pt_ap, pt_b, pt_tmp, &
163          psurf_year(:,:,id_aero), load_year(:,:,id_aero))
164     IF (.NOT. ALLOCATED(var_year)) THEN
165        ALLOCATE(var_year(klon, klev_src, 12, naero_spc), stat=ierr)
166        IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 5',1)
167     END IF
168     var_year(:,:,:,id_aero) = pt_tmp(:,:,:)
169
170     ! Reading values corresponding to the preindustrial concentrations.
171     CALL readaerosol(name_aero(id_aero), 'preind', iyr, pi_klev_src, pt_ap, pt_b, pt_tmp, &
172          pi_psurf_year(:,:,id_aero), pi_load_year(:,:,id_aero))
173
174     ! klev_src must be the same in both files.
175     ! Also supposing pt_ap and pt_b to be the same in the 2 files without testing.
176     IF (pi_klev_src /= klev_src) THEN
177        WRITE(lunout,*) 'Error! All forcing files for the same aerosol must have the same vertical dimension'
178        WRITE(lunout,*) 'Aerosol : ', name_aero(id_aero)
179        CALL abort_gcm('readaerosol_interp','Differnt vertical axes in aerosol forcing files',1)
180     END IF
181
182     IF (.NOT. ALLOCATED(pi_var_year)) THEN
183        ALLOCATE(pi_var_year(klon, klev_src, 12, naero_spc), stat=ierr)
184        IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 6',1)
185     END IF
186     pi_var_year(:,:,:,id_aero) = pt_tmp(:,:,:)
187   
188     IF (debug) THEN
189        CALL writefield_phy('var_year_jan',var_year(:,:,1,id_aero),klev_src)
190        CALL writefield_phy('var_year_dec',var_year(:,:,12,id_aero),klev_src)
191        CALL writefield_phy('psurf_src',psurf_year(:,:,id_aero),1)
192        CALL writefield_phy('pi_psurf_src',pi_psurf_year(:,:,id_aero),1)
193        CALL writefield_phy('load_year_src',load_year(:,:,id_aero),1)
194        CALL writefield_phy('pi_load_year_src',pi_load_year(:,:,id_aero),1)
195     END IF
196
197     ! Pointer no more useful, deallocate.
198     DEALLOCATE(pt_tmp)
199
200     ! Test if vertical interpolation will be needed.
201     IF (psurf_year(1,1,id_aero)==not_valid .OR. pi_psurf_year(1,1,id_aero)==not_valid ) THEN
202        ! Pressure=not_valid indicates old file format, see module readaerosol
203        vert_interp = .FALSE.
204
205        ! If old file format, both psurf_year and pi_psurf_year must be not_valid
206        IF (  psurf_year(1,1,id_aero) /= pi_psurf_year(1,1,id_aero) ) THEN
207           WRITE(lunout,*) 'Warning! All forcing files for the same aerosol must have the same structure'
208           CALL abort_gcm('readaerosol_interp', 'The aerosol files have not the same format',1)
209        END IF
210       
211        IF (klev /= klev_src) THEN
212           WRITE(lunout,*) 'Old format of aerosol file do not allowed vertical interpolation'
213           CALL abort_gcm('readaerosol_interp', 'Old aerosol file not possible',1)
214        END IF
215
216     ELSE
217        vert_interp = .TRUE.
218     END IF
219
220  END IF  ! IF ( (first .OR. iday==0) .AND. lnewday ) THEN
221 
222!****************************************************************************************
223! - 2) Interpolate to the actual day.
224! - 3) Interpolate to the model vertical grid.
225!
226!****************************************************************************************
227
228  IF (lnewday) THEN ! only if new day
229!****************************************************************************************
230! 2) Interpolate to the actual day
231!
232!****************************************************************************************
233     ! Find which months and days to use for time interpolation
234     IF (iday < im*30-15) THEN
235        ! in the first half of the month use month before and actual month
236        im2=im-1
237        day2 = im2*30-15
238        day1 = im2*30+15
239        IF (im2 <= 0) THEN
240           ! the month is january, thus the month before december
241           im2=12
242        END IF
243     ELSE
244        ! the second half of the month
245        im2=im+1
246        IF (im2 > 12) THEN
247           ! the month is december, the following thus january
248           im2=1
249        ENDIF
250        day2 = im*30-15
251        day1 = im*30+15
252     END IF
253     
254     ! Time interpolation, still on vertical source grid
255     ALLOCATE(tmp1(klon,klev_src), tmp2(klon,klev_src),stat=ierr)
256     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 7',1)
257
258     ALLOCATE(pplay_src(klon,klev_src), stat=ierr)
259     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 8',1)
260     
261
262     DO k=1,klev_src
263        DO i=1,klon
264           tmp1(i,k) = &
265                var_year(i,k,im2,id_aero) - FLOAT(iday-day2)/FLOAT(day1-day2) * &
266                (var_year(i,k,im2,id_aero) - var_year(i,k,im,id_aero))
267           
268           tmp2(i,k) = &
269                pi_var_year(i,k,im2,id_aero) - FLOAT(iday-day2)/FLOAT(day1-day2) * &
270                (pi_var_year(i,k,im2,id_aero) - pi_var_year(i,k,im,id_aero))
271        END DO
272     END DO
273
274     ! Time interpolation for pressure at surface, still on vertical source grid
275     DO i=1,klon
276        psurf_day(i) = &
277             psurf_year(i,im2,id_aero) - FLOAT(iday-day2)/FLOAT(day1-day2) * &
278             (psurf_year(i,im2,id_aero) - psurf_year(i,im,id_aero))
279       
280        pi_psurf_day(i) = &
281             pi_psurf_year(i,im2,id_aero) - FLOAT(iday-day2)/FLOAT(day1-day2) * &
282             (pi_psurf_year(i,im2,id_aero) - pi_psurf_year(i,im,id_aero))
283     END DO
284
285     ! Time interpolation for the load, still on vertical source grid
286     DO i=1,klon
287        load_src(i) = &
288             load_year(i,im2,id_aero) - FLOAT(iday-day2)/FLOAT(day1-day2) * &
289             (load_year(i,im2,id_aero) - load_year(i,im,id_aero))
290       
291        pi_load_src(i) = &
292             pi_load_year(i,im2,id_aero) - FLOAT(iday-day2)/FLOAT(day1-day2) * &
293             (pi_load_year(i,im2,id_aero) - pi_load_year(i,im,id_aero))
294     END DO
295
296!****************************************************************************************
297! 3) Interpolate to the model vertical grid (target grid)
298!
299!****************************************************************************************
300
301     IF (vert_interp) THEN
302
303        ! - Interpolate variable tmp1 (on source grid) to var_day (on target grid)
304        !********************************************************************************
305        ! a) calculate pression at vertical levels for the source grid using the
306        !    hybrid-sigma coordinates ap and b and the surface pressure, variables from file.
307        DO k = 1, klev_src
308           DO i = 1, klon
309              pplay_src(i,k)= pt_ap(k) + pt_b(k)*psurf_day(i)
310           END DO
311        END DO
312       
313        IF (debug) THEN
314           CALL writefield_phy('psurf_day_src',psurf_day(:),1)
315           CALL writefield_phy('pplay_src',pplay_src(:,:),klev_src)
316           CALL writefield_phy('pplay',pplay(:,:),klev)
317           CALL writefield_phy('day_src',tmp1,klev_src)
318           CALL writefield_phy('pi_day_src',tmp2,klev_src)
319        END IF
320
321        ! b) vertical interpolation on pressure leveles
322        CALL pres2lev(tmp1(:,:), var_day(:,:,id_aero), klev_src, klev, pplay_src, pplay, &
323             1, klon, .FALSE.)
324       
325        IF (debug) CALL writefield_phy('day_tgt',var_day(:,:,id_aero),klev)
326       
327        ! c) adjust to conserve total aerosol mass load in the vertical pillar
328        !    Calculate the load in the actual pillar and compare with the load
329        !    read from aerosol file.
330       
331        ! Find the pressure difference in each model layer
332        DO k = 1, klev
333           DO i = 1, klon
334              delp(i,k) = paprs(i,k) - paprs (i,k+1)
335           END DO
336        END DO
337
338        ! Find the mass load in the actual pillar, on target grid
339        load_tgt(:) = 0.
340        DO k= 1, klev
341           DO i = 1, klon
342              zrho = pplay(i,k)/t_seri(i,k)/RD       ! [kg/m3]
343              volm = var_day(i,k,id_aero)*1.E-9/zrho ! [kg/kg]
344              load_tgt(i) = load_tgt(i) + 1/RG * volm *delp(i,k)
345           END DO
346        END DO
347       
348        ! Adjust, uniform
349        DO k = 1, klev
350           DO i = 1, klon
351              var_day(i,k,id_aero) = var_day(i,k,id_aero)*load_src(i)/load_tgt(i)
352           END DO
353        END DO
354       
355        IF (debug) THEN
356           load_tgt_test(:) = 0.
357           DO k= 1, klev
358              DO i = 1, klon
359                 zrho = pplay(i,k)/t_seri(i,k)/RD       ! [kg/m3]
360                 volm = var_day(i,k,id_aero)*1.E-9/zrho ! [kg/kg]
361                 load_tgt_test(i) = load_tgt_test(i) + 1/RG * volm*delp(i,k)
362              END DO
363           END DO
364           
365           CALL writefield_phy('day_tgt2',var_day(:,:,id_aero),klev)
366           CALL writefield_phy('load_tgt',load_tgt(:),1)
367           CALL writefield_phy('load_tgt_test',load_tgt_test(:),1)
368           CALL writefield_phy('load_src',load_src(:),1)
369        END IF
370
371        ! - Interpolate variable tmp2 (source grid) to pi_var_day (target grid)
372        !********************************************************************************
373        ! a) calculate pression at vertical levels at source grid   
374        DO k = 1, klev_src
375           DO i = 1, klon
376              pplay_src(i,k)= pt_ap(k) + pt_b(k)*pi_psurf_day(i)
377           END DO
378        END DO
379
380        IF (debug) THEN
381           CALL writefield_phy('pi_psurf_day_src',pi_psurf_day(:),1)
382           CALL writefield_phy('pi_pplay_src',pplay_src(:,:),klev_src)
383        END IF
384
385        ! b) vertical interpolation on pressure leveles
386        CALL pres2lev(tmp2(:,:), pi_var_day(:,:,id_aero), klev_src, klev, pplay_src, pplay, &
387             1, klon, .FALSE.)
388
389        IF (debug) CALL writefield_phy('pi_day_tgt',pi_var_day(:,:,id_aero),klev)
390
391        ! c) adjust to conserve total aerosol mass load in the vertical pillar
392        !    Calculate the load in the actual pillar and compare with the load
393        !    read from aerosol file.
394
395        ! Find the load in the actual pillar, on target grid
396        load_tgt(:) = 0.
397        DO k = 1, klev
398           DO i = 1, klon
399              zrho = pplay(i,k)/t_seri(i,k)/RD          ! [kg/m3]
400              volm = pi_var_day(i,k,id_aero)*1.E-9/zrho ! [kg/kg]
401              load_tgt(i) = load_tgt(i) + 1/RG * volm * delp(i,k)
402           END DO
403        END DO
404
405        DO k = 1, klev
406           DO i = 1, klon
407              pi_var_day(i,k,id_aero) = pi_var_day(i,k,id_aero)*pi_load_src(i)/load_tgt(i)
408           END DO
409        END DO
410
411        IF (debug) THEN
412           load_tgt_test(:) = 0.
413           DO k = 1, klev
414              DO i = 1, klon
415                 zrho = pplay(i,k)/t_seri(i,k)/RD          ! [kg/m3]
416                 volm = pi_var_day(i,k,id_aero)*1.E-9/zrho ! [kg/kg]
417                 load_tgt_test(i) = load_tgt_test(i) + 1/RG * volm * delp(i,k)
418              END DO
419           END DO
420           CALL writefield_phy('pi_day_tgt2',pi_var_day(:,:,id_aero),klev)
421           CALL writefield_phy('pi_load_tgt',load_tgt(:),1)
422           CALL writefield_phy('pi_load_tgt_test',load_tgt_test(:),1)
423           CALL writefield_phy('pi_load_src',pi_load_src(:),1)
424        END IF
425
426
427     ELSE   ! No vertical interpolation done
428
429        var_day(:,:,id_aero)    = tmp1(:,:)
430        pi_var_day(:,:,id_aero) = tmp2(:,:)
431
432     END IF ! vert_interp
433
434
435     ! Deallocation
436     DEALLOCATE(tmp1, tmp2, pplay_src, stat=ierr)
437
438!****************************************************************************************
439! 4) Test for negative mass values
440!
441!****************************************************************************************
442     IF (MINVAL(var_day(:,:,id_aero)) < 0.) THEN
443        DO k=1,klev
444           DO i=1,klon
445              ! Test for var_day
446              IF (var_day(i,k,id_aero) < 0.) THEN
447                 IF (iday-day2 < 0.) WRITE(lunout,*) 'iday-day2=',iday-day2
448                 IF (var_year(i,k,im2,id_aero) - var_year(i,k,im,id_aero) < 0.) THEN
449                    WRITE(lunout,*) trim(name_aero(id_aero)),'(i,k,im2)-', &
450                         trim(name_aero(id_aero)),'(i,k,im)=',           &
451                         var_year(i,k,im2,id_aero) - var_year(i,k,im,id_aero)
452                 END IF
453                 
454                 WRITE(lunout,*) 'stop for aerosol : ',name_aero(id_aero)
455                 CALL abort_gcm('readaerosol_interp','Error in interpolation 1',1)
456              END IF
457           END DO
458        END DO
459     END IF
460
461     IF (MINVAL(pi_var_day(:,:,id_aero)) < 0. ) THEN
462        DO k=1, klev
463           DO i=1,klon
464              ! Test for pi_var_day
465              IF (pi_var_day(i,k,id_aero) < 0.) THEN
466                 IF (iday-day2 < 0.) WRITE(lunout,*) 'iday-day2=',iday-day2
467                 IF (pi_var_year(i,k,im2,id_aero) - pi_var_year(i,k,im,id_aero) < 0.) THEN
468                    WRITE(lunout,*) trim(name_aero(id_aero)),'(i,k,im2)-', &
469                         trim(name_aero(id_aero)),'(i,k,im)=',           &
470                         pi_var_year(i,k,im2,id_aero) - pi_var_year(i,k,im,id_aero)
471                 END IF
472                 
473                 WRITE(lunout,*) 'stop for aerosol : ',name_aero(id_aero)
474                 CALL abort_gcm('readaerosol_interp','Error in interpolation 2',1)
475              END IF
476           END DO
477        END DO
478     END IF
479
480  END IF ! lnewday
481
482!****************************************************************************************
483! Copy output from saved variables
484!
485!****************************************************************************************
486
487  mass_out(:,:)    = var_day(:,:,id_aero)
488  pi_mass_out(:,:) = pi_var_day(:,:,id_aero)
489 
490END SUBROUTINE readaerosol_interp
Note: See TracBrowser for help on using the repository browser.