Changeset 3929 for trunk


Ignore:
Timestamp:
Oct 20, 2025, 10:36:45 AM (6 weeks ago)
Author:
debatzbr
Message:

Pluto PCM: Add optical diagnostics for aerosols
BBT

Location:
trunk/LMDZ.PLUTO/libf/phypluto
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/callcorrk.F90

    r3917 r3929  
    1212          fluxabs_sw,fluxtop_dn,                               &
    1313          OLR_nu,OSR_nu,GSR_nu,                                &
    14           int_dtaui,int_dtauv,                                 &
     14          int_dtaui,int_dtauv,int_dtauv_aer,int_wbarv_aer,     &
    1515          tau_col,firstcall,lastcall)
    1616
     
    104104      REAL,INTENT(OUT) :: OSR_nu(ngrid,L_NSPECTV)         ! Outgoing SW radiation in each band (Normalized to the band width (W/m2/cm-1).
    105105      REAL,INTENT(OUT) :: GSR_nu(ngrid,L_NSPECTV)         ! Surface SW radiation in each band (Normalized to the band width (W/m2/cm-1).
    106       REAL,INTENT(OUT) :: int_dtaui(ngrid,nlayer,L_NSPECTI) ! VI optical thickness of layers within narrowbands for diags ().
    107       REAL,INTENT(OUT) :: int_dtauv(ngrid,nlayer,L_NSPECTV) ! IR optical thickness of layers within narrowbands for diags ().
     106      REAL,INTENT(OUT) :: int_dtaui(ngrid,nlayer,L_NSPECTI)              ! IR optical thickness of layers within narrowbands for diags ().
     107      REAL,INTENT(OUT) :: int_dtauv(ngrid,nlayer,L_NSPECTV)              ! VI optical thickness of layers within narrowbands for diags ().
     108      REAL,INTENT(OUT) :: int_dtauv_aer(ngrid,nlayer,L_NSPECTV,naerkind) ! Aerosol VI optical thickness of layers within narrowbands for diags ().
     109      REAL,INTENT(OUT) :: int_wbarv_aer(ngrid,nlayer,L_NSPECTV,naerkind) ! Aerosol VI single scattering albedo within narrowbands for diags ().
    108110      REAL,INTENT(OUT) :: tau_col(ngrid)                  ! Diagnostic from aeropacity.
    109111      REAL,INTENT(OUT) :: albedo_equivalent(ngrid)        ! Spectrally Integrated Albedo. For Diagnostic. By MT2015
     
    143145      REAL*8,allocatable,save :: dtaui(:,:,:)
    144146      REAL*8,allocatable,save :: dtauv(:,:,:)
     147      REAL*8,allocatable,save :: dtauv_aer(:,:,:)
    145148      REAL*8,allocatable,save :: cosbv(:,:,:)
    146149      REAL*8,allocatable,save :: cosbi(:,:,:)
    147150      REAL*8,allocatable,save :: wbari(:,:,:)
    148151      REAL*8,allocatable,save :: wbarv(:,:,:)
    149 !$OMP THREADPRIVATE(dtaui,dtauv,cosbv,cosbi,wbari,wbarv)
     152      REAL*8,allocatable,save :: wbarv_aer(:,:,:)
     153!$OMP THREADPRIVATE(dtaui,dtauv,dtauv_aer,cosbv,cosbi,wbari,wbarv,wbarv_aer)
    150154      REAL*8,allocatable,save :: tauv(:,:,:)
    151155      REAL*8,allocatable,save :: taucumv(:,:,:)
     
    367371           endif
    368372         endif
     373         if(.not.allocated(dtauv_aer)) then
     374           ALLOCATE(dtauv_aer(L_NLAYRAD,L_NSPECTV,naerkind), stat=ok)
     375           if (ok/=0) then
     376              write(*,*) "memory allocation failed for dtauv_aer!"
     377              call abort_physic(subname,'allocation failure for dtauv_aer',1)
     378           endif
     379         endif
    369380         if(.not.allocated(cosbv)) then
    370381           ALLOCATE(cosbv(L_NLAYRAD,L_NSPECTV,L_NGAUSS), stat=ok)
     
    393404              write(*,*) "memory allocation failed for wbarv!"
    394405              call abort_physic(subname,'allocation failure for wbarv',1)
     406           endif
     407         endif
     408         if(.not.allocated(wbarv_aer)) then
     409           ALLOCATE(wbarv_aer(L_NLAYRAD,L_NSPECTV,naerkind), stat=ok)
     410           if (ok/=0) then
     411              write(*,*) "memory allocation failed for wbarv_aer!"
     412              call abort_physic(subname,'allocation failure for wbarv_aer',1)
    395413           endif
    396414         endif
     
    809827
    810828      ! Test for out-of-bounds pressure.
    811       if(plevrad(3).lt.pgasmin)then
    812          print*,'Warning: minimum pressure is outside the radiative'
    813          print*,'transfer kmatrix bounds, exiting.'
    814          print*,'Pressure:', plevrad(3), 'Pa'
    815          message="Minimum pressure outside of kmatrix bounds"
    816          !call abort_physic(subname,message,1)
    817       elseif(plevrad(L_LEVELS).gt.pgasmax)then
    818          print*,'Maximum pressure is outside the radiative'
    819          print*,'transfer kmatrix bounds, exiting.'
    820          message="Minimum pressure outside of kmatrix bounds"
    821          call abort_physic(subname,message,1)
     829      if (is_master) then
     830         if(plevrad(3).lt.pgasmin)then
     831            print*,'Warning: minimum pressure is outside the radiative'
     832            print*,'transfer kmatrix bounds, exiting.'
     833            print*,'Pressure:', plevrad(3), 'Pa'
     834            message="Minimum pressure outside of kmatrix bounds"
     835            !call abort_physic(subname,message,1)
     836         elseif(plevrad(L_LEVELS).gt.pgasmax)then
     837            print*,'Maximum pressure is outside the radiative'
     838            print*,'transfer kmatrix bounds, exiting.'
     839            message="Minimum pressure outside of kmatrix bounds"
     840            call abort_physic(subname,message,1)
     841         endif
    822842      endif
    823843
     
    937957         call optcv(dtauv,tauv,taucumv,plevrad,                 &
    938958                 qxvaer,qsvaer,gvaer,wbarv,cosbv,tauray,tauaero,   &
    939                  tmid,pmid,taugsurf,qvar,muvarrad)
     959                 tmid,pmid,taugsurf,qvar,muvarrad,dtauv_aer,wbarv_aer)
    940960
    941961         if(fract(ig) .ge. 1.0e-4) then ! Only during daylight.
     
    10671087         end do
    10681088
    1069          ! Optical thickness diagnostics
    1070          ! Output exp(-tau) because gweight ponderates exp and not tau itself
     1089         ! Aerosol optical thickness diagnostics
     1090         int_dtauv_aer(ig,:,:,:) = dtauv_aer(:,:,:)
     1091         int_wbarv_aer(ig,:,:,:) = wbarv_aer(:,:,:)
     1092         ! Total optical thickness diagnostics
     1093         ! Output exp(-dtau) because gweight ponderates exp and not tau itself
    10711094         int_dtauv(ig,:,:) = 0.0d0
    10721095         int_dtaui(ig,:,:) = 0.0d0
  • trunk/LMDZ.PLUTO/libf/phypluto/dyn1d/kcm1d.F90

    r3718 r3929  
    8484  real int_dtaui(1,llm,L_NSPECTI)
    8585  real int_dtauv(1,llm,L_NSPECTV)
     86  real int_dtauv_aer(1,llm,L_NSPECTV,naerkind)
     87  real int_wbarv_aer(1,llm,L_NSPECTV,naerkind)
    8688  real Eatmtot
    8789
     
    374376          albedo_wv,albedo_equivalent,                    &
    375377          emis,mu0,plev,play,temp,                        &
    376           tsurf,fract,dist_star,dtau_aer,muvar,            &
     378          tsurf,fract,dist_star,dtau_aer,muvar,           &
    377379          dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,              &
    378380          fluxsurfabs_sw,fluxtop_lw,                      &
    379381          fluxabs_sw,fluxtop_dn,OLR_nu,OSR_nu,GSR_nu,     &
    380           int_dtaui,int_dtauv,                            &
     382          int_dtaui,int_dtauv,int_dtauv_aer,int_wbarv_aer,&
    381383          tau_col,firstcall,lastcall)
    382384
     
    426428  call callcorrk(1,nlayer,q,nq,qsurf,                          &
    427429       albedo_wv,albedo_equivalent,emis,mu0,plev,play,temp,    &
    428        tsurf,fract,dist_star,dtau_aer,muvar,                    &
     430       tsurf,fract,dist_star,dtau_aer,muvar,                   &
    429431       dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxsurfabs_sw,       &
    430432       fluxtop_lw, fluxabs_sw,fluxtop_dn,OLR_nu,OSR_nu,GSR_nu, &
    431        int_dtaui,int_dtauv,                                    &
     433       int_dtaui,int_dtauv,int_dtauv_aer,int_wbarv_aer,        &
    432434       tau_col,firstcall,lastcall)
    433435
  • trunk/LMDZ.PLUTO/libf/phypluto/hazecloud.F90

    r3917 r3929  
    5757!      REAL,INTENT(IN) :: mmol(nq)
    5858      REAL,INTENT(IN) :: pdist_sol    ! distance SUN-pluto in AU
    59       REAL,INTENT(IN) :: pfluxuv    ! Lyman alpha flux at specific Ls (ph/cm/s)
     59      REAL,INTENT(IN) :: pfluxuv    ! Lyman alpha flux at specific Ls (ph/cm2/s)
    6060      REAL,INTENT(IN) :: mu0(ngrid)  ! cosinus of solar incident flux
    6161      REAL,INTENT(IN) :: declin    ! distance SUN-pluto in AU
  • trunk/LMDZ.PLUTO/libf/phypluto/optcv.F90

    r3889 r3929  
    55CONTAINS
    66
    7 SUBROUTINE OPTCV(DTAUV,TAUV,TAUCUMV,PLEV,  &
    8      QXVAER,QSVAER,GVAER,WBARV,COSBV,       &
    9      TAURAY,TAUAERO,TMID,PMID,TAUGSURF,QVAR,MUVAR)
     7SUBROUTINE OPTCV(DTAUV,TAUV,TAUCUMV,PLEV,         &
     8     QXVAER,QSVAER,GVAER,WBARV,COSBV,             &
     9     TAURAY,TAUAERO,TMID,PMID,TAUGSURF,QVAR,MUVAR,&
     10     DTAUV_AER,WBARV_AER)
    1011
    1112  use radinc_h, only: L_NLAYRAD, L_NLEVRAD, L_LEVELS, L_NSPECTV, L_NGAUSS, L_REFVAR, NAERKIND
     
    5152  real*8,intent(out) :: TAUV(L_NLEVRAD,L_NSPECTV,L_NGAUSS)
    5253  real*8,intent(out) :: TAUCUMV(L_LEVELS,L_NSPECTV,L_NGAUSS)
    53   real*8,intent(in) :: PLEV(L_LEVELS)
    54   real*8,intent(in) :: TMID(L_LEVELS), PMID(L_LEVELS)
     54  real*8,intent(in)  :: PLEV(L_LEVELS)
     55  real*8,intent(in)  :: TMID(L_LEVELS), PMID(L_LEVELS)
    5556  real*8,intent(out) :: COSBV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
    5657  real*8,intent(out) :: WBARV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
    5758
    5859  ! for aerosols
    59   real*8,intent(in) :: QXVAER(L_LEVELS,L_NSPECTV,NAERKIND)
    60   real*8,intent(in) :: QSVAER(L_LEVELS,L_NSPECTV,NAERKIND)
    61   real*8,intent(in) :: GVAER(L_LEVELS,L_NSPECTV,NAERKIND)
    62   real*8,intent(in) :: TAUAERO(L_LEVELS,NAERKIND)
     60  real*8,intent(in)  :: QXVAER(L_LEVELS,L_NSPECTV,NAERKIND)
     61  real*8,intent(in)  :: QSVAER(L_LEVELS,L_NSPECTV,NAERKIND)
     62  real*8,intent(in)  :: GVAER(L_LEVELS,L_NSPECTV,NAERKIND)
     63  real*8,intent(in)  :: TAUAERO(L_LEVELS,NAERKIND)
     64  real*8,intent(out) :: DTAUV_AER(L_NLAYRAD,L_NSPECTV,NAERKIND)
     65  real*8,intent(out) :: WBARV_AER(L_NLAYRAD,L_NSPECTV,NAERKIND)
    6366
    6467  ! local arrays (saved for convenience as need be allocated)
     
    102105  ! Variables for aerosol absorption
    103106  real*8 Fabs_aer(NAERKIND)
     107  real*8 wbarv_prime
    104108
    105109  integer igas, jgas
     
    135139  taucumv(:,:,:) = 0.0
    136140
    137   taugsurf(:,:) = 0.0
    138   dpr(:)        = 0.0 ! pressure difference between levels
    139   lkcoef(:,:)   = 0.0
    140   DTAUKV(:,:,:) = 0.0
     141  taugsurf(:,:)    = 0.0
     142  dpr(:)           = 0.0 ! pressure difference between levels
     143  lkcoef(:,:)      = 0.0
     144  DTAUKV(:,:,:)    = 0.0
     145  dtauv_aer(:,:,:) = 0.0
     146  wbarv_aer(:,:,:) = 0.0
    141147
    142148  if(callmufi) then
     
    429435  END DO                    ! NG Gauss loop
    430436
     437  ! Aerosols extinction optical depths
     438  DO iaer = 1, naerkind
     439   DO nw = 1, L_NSPECTV
     440     DO L = 1, L_NLAYRAD-1
     441      K = 2*L+1
     442      DTAUV_AER(L,nw,iaer) = TAEROS(K,nw,iaer) + TAEROS(K+1,nw,iaer)
     443
     444      wbarv_prime = (QSVAER(K,nw,iaer)/QXVAER(K,nw,iaer)) / &
     445                    (QSVAER(K,nw,iaer)/QXVAER(K,nw,iaer) + Fabs_aer(iaer)*(1.-QSVAER(K,nw,iaer)/QXVAER(K,nw,iaer)))
     446      WBARV_AER(L,nw,iaer) = wbarv_prime * TAEROS(K,nw,iaer)
     447      wbarv_prime = (QSVAER(K+1,nw,iaer)/QXVAER(K+1,nw,iaer)) / &
     448                    (QSVAER(K+1,nw,iaer)/QXVAER(K+1,nw,iaer) + Fabs_aer(iaer)*(1.-QSVAER(K+1,nw,iaer)/QXVAER(K+1,nw,iaer)))
     449      WBARV_AER(L,nw,iaer) = WBARV_AER(L,nw,iaer) + (wbarv_prime * TAEROS(K+1,nw,iaer))
     450      WBARV_AER(L,nw,iaer) = WBARV_AER(L,nw,iaer) / DTAUV_AER(L,nw,iaer)
     451      END DO ! L vertical loop
     452      ! Last level
     453      L              = L_NLAYRAD
     454      K              = 2*L+1
     455      DTAUV_AER(L,nw,iaer) = TAEROS(K,nw,iaer)
     456      WBARV_AER(L,nw,iaer) = (QSVAER(K,nw,iaer)/QXVAER(K,nw,iaer)) / &
     457                             (QSVAER(K,nw,iaer)/QXVAER(K,nw,iaer) + Fabs_aer(iaer)*(1.-QSVAER(K,nw,iaer)/QXVAER(K,nw,iaer)))
     458   END DO ! nw spectral loop
     459  END DO ! iaer Gauss loop
     460
    431461  ! Total extinction optical depths
    432462  DO NG=1,L_NGAUSS ! full gauss loop
  • trunk/LMDZ.PLUTO/libf/phypluto/phys_state_var_mod.F90

    r3910 r3929  
    7070!$OMP THREADPRIVATE(OLR_nu,OSR_nu,GSR_nu,zdtlw,zdtsw)
    7171
    72       real,dimension(:,:,:),allocatable,save :: int_dtauv   ! VI optical thickness of layers within narrowbands for diags ().
    73       real,dimension(:,:,:),allocatable,save :: int_dtaui   ! IR optical thickness of layers within narrowbands for diags ().
    74 !$OMP THREADPRIVATE(int_dtaui,int_dtauv)
     72      real,dimension(:,:,:),allocatable,save :: int_dtauv       ! VI optical thickness of layers within narrowbands for diags ().
     73      real,dimension(:,:,:),allocatable,save :: int_dtaui       ! IR optical thickness of layers within narrowbands for diags ().
     74      real,dimension(:,:,:,:),allocatable,save :: int_dtauv_aer ! Aerosol VI optical thickness of layers within narrowbands for diags ().
     75      real,dimension(:,:,:,:),allocatable,save :: int_wbarv_aer ! Aerosol VI single scattering albedo within narrowbands for diags ().
     76!$OMP THREADPRIVATE(int_dtaui,int_dtauv,int_dtauv_aer,int_wbarv_aer)
    7577
    7678      real,allocatable,dimension(:),save :: tau_col ! Total Aerosol Optical Depth.
     
    157159        ALLOCATE(int_dtaui(klon,klev,L_NSPECTI))
    158160        ALLOCATE(int_dtauv(klon,klev,L_NSPECTV))
     161        ALLOCATE(int_dtauv_aer(klon,klev,L_NSPECTV,naerkind))
     162        ALLOCATE(int_wbarv_aer(klon,klev,L_NSPECTV,naerkind))
    159163        ALLOCATE(sensibFlux(klon))
    160164        ALLOCATE(zdtlw(klon,klev))
     
    233237        DEALLOCATE(int_dtaui)
    234238        DEALLOCATE(int_dtauv)
     239        DEALLOCATE(int_dtauv_aer)
     240        DEALLOCATE(int_wbarv_aer)
    235241        DEALLOCATE(sensibFlux)
    236242        DEALLOCATE(zdtlw)
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3910 r3929  
    10471047                              fluxsurfabs_sw,fluxtop_lw,                          &
    10481048                              fluxabs_sw,fluxtop_dn,OLR_nu,OSR_nu,GSR_nu,         &
    1049                               int_dtaui,int_dtauv,                                &
     1049                              int_dtaui,int_dtauv,int_dtauv_aer,int_wbarv_aer,    &
    10501050                              tau_col,firstcall,lastcall)
    10511051                  ! Radiative flux from the sky absorbed by the surface (W.m-2).
     
    22552255            "Aerosol surface opacity at reference visible wavelength","",tau_col)
    22562256      ! Diagnostics of optical thickness (dtau = dtau_gas + dtau_rayaer + dtau_cont).
    2257       ! Warning this is exp(-tau), I let you postproc with -log to have tau itself
    2258       call write_output('dtauv_01','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,1))  ! 5.398 um (17x27)
    2259       call write_output('dtauv_23','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,23)) ! 0.941 um (17x27)
    2260       call write_output('dtauv_24','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,24)) ! 0.700 um (17x27)
    2261       call write_output('dtauv_27','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,27)) ! 0.119 um (17x27)
    2262       call write_output('dtaui_01','Layer optical thickness attenuation in IR band','',int_dtaui(:,nlayer:1:-1,1))  ! 550.0 um (17x27)
    2263       call write_output('dtaui_17','Layer optical thickness attenuation in IR band','',int_dtaui(:,nlayer:1:-1,17)) ! 3.531 um (17x27)
     2257      ! Warning this is exp(-dtau), I let you postproc with -log to have tau and k itself
     2258      ! VI
     2259      call write_output('dtauv_4656nm','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,2))  ! 4.656 um (17x28)
     2260      call write_output('dtauv_1181nm','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,21)) ! 1.181 um (17x28)
     2261      call write_output('dtauv_700nm','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,24))  ! 0.700 um (17x28)
     2262      call write_output('dtauv_185nm','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,27))  ! 0.185 um (17x28)
     2263      call write_output('dtauv_118nm','Layer optical thickness attenuation in VI band','',int_dtauv(:,nlayer:1:-1,28))  ! 0.118 um (17x28)
     2264      ! IR
     2265      call write_output('dtaui_81250nm','Layer optical thickness attenuation in IR band','',int_dtaui(:,nlayer:1:-1,2)) ! 81.250 um (17x27)
     2266      call write_output('dtaui_3859nm','Layer optical thickness attenuation in IR band','',int_dtaui(:,nlayer:1:-1,16)) ! 3.859 um (17x27)
     2267      if (callmufi) then
     2268         ! Aerosol optical thickness
     2269         call write_output('dtauv_aers_4656nm','Layer sph. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,2,1))
     2270         call write_output('dtauv_aerf_4656nm','Layer fra. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,2,2))
     2271         call write_output('dtauv_aers_1181nm','Layer sph. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,21,1))
     2272         call write_output('dtauv_aerf_1181nm','Layer fra. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,21,2))
     2273         call write_output('dtauv_aers_700nm','Layer sph. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,24,1))
     2274         call write_output('dtauv_aerf_700nm','Layer fra. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,24,2))
     2275         call write_output('dtauv_aers_185nm','Layer sph. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,27,1))
     2276         call write_output('dtauv_aerf_185nm','Layer fra. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,27,2))
     2277         call write_output('dtauv_aers_118nm','Layer sph. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,28,1))
     2278         call write_output('dtauv_aerf_118nm','Layer fra. aer. optical thickness attenuation in VI band','',int_dtauv_aer(:,nlayer:1:-1,28,2))
     2279         ! Aerosols single scattering albedo
     2280         call write_output('wbarv_aers_4656nm','Layer sph. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,2,1))
     2281         call write_output('wbarv_aerf_4656nm','Layer fra. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,2,2))
     2282         call write_output('wbarv_aers_1181nm','Layer sph. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,21,1))
     2283         call write_output('wbarv_aerf_1181nm','Layer fra. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,21,2))
     2284         call write_output('wbarv_aers_700nm','Layer sph. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,24,1))
     2285         call write_output('wbarv_aerf_700nm','Layer fra. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,24,2))
     2286         call write_output('wbarv_aers_185nm','Layer sph. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,27,1))
     2287         call write_output('wbarv_aerf_185nm','Layer fra. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,27,2))
     2288         call write_output('wbarv_aers_118nm','Layer sph. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,28,1))
     2289         call write_output('wbarv_aerf_118nm','Layer fra. aer. single scattering albedo in VI band','',int_wbarv_aer(:,nlayer:1:-1,28,2))
     2290      endif ! end callmufi
    22642291
    22652292      if (calllott) then
Note: See TracChangeset for help on using the changeset viewer.