Ignore:
Timestamp:
Jul 18, 2017, 4:15:23 PM (7 years ago)
Author:
jvatant
Message:

Adapt various modifs of LMDZ.GENERIC to LMDZ.TITAN from r1690-1694-1699-1709-1715
--JVO

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/callcorrk.F90

    r1648 r1722  
    88          tau_col,firstcall,lastcall)
    99
     10      use mod_phys_lmdz_para, only : is_master
    1011      use radinc_h
    1112      use radcommon_h
     
    1718      USE tracer_h
    1819      use comcstfi_mod, only: pi, mugaz, cpp
    19       use callkeys_mod, only: diurnal,tracer,nosurf,        &
     20      use callkeys_mod, only: diurnal,tracer,        &
    2021                              strictboundcorrk,specOLR
    2122
     
    7576      REAL,INTENT(OUT) :: OSR_nu(ngrid,L_NSPECTV)        ! Outgoing SW radition in each band (Normalized to the band width (W/m2/cm-1).
    7677      REAL,INTENT(OUT) :: tau_col(ngrid)                 ! Diagnostic from aeropacity.
    77       REAL,INTENT(OUT) :: albedo_equivalent(ngrid)       ! Spectrally Integrated Albedo. For Diagnostic. By MT2015 
     78      REAL,INTENT(OUT) :: albedo_equivalent(ngrid)       ! Spectrally Integrated Albedo. For Diagnostic. By MT2015
    7879     
    7980     
     
    113114      REAL*8 taucumi(L_LEVELS,L_NSPECTI,L_NGAUSS)
    114115
    115       REAL*8 tauaero(L_LEVELS+1,naerkind)
     116      REAL*8 tauaero(L_LEVELS,naerkind)
    116117      REAL*8 nfluxtopv,nfluxtopi,nfluxtop,fluxtopvdn
    117118      REAL*8 nfluxoutv_nu(L_NSPECTV)                 ! Outgoing band-resolved VI flux at TOA (W/m2).
     
    167168
    168169        ! test on allocated necessary because of CLFvarying (two calls to callcorrk in physiq)
    169         if(.not.allocated(QXVAER)) allocate(QXVAER(L_LEVELS+1,L_NSPECTV,naerkind))
    170         if(.not.allocated(QSVAER)) allocate(QSVAER(L_LEVELS+1,L_NSPECTV,naerkind))
    171         if(.not.allocated(GVAER)) allocate(GVAER(L_LEVELS+1,L_NSPECTV,naerkind))
    172         if(.not.allocated(QXIAER)) allocate(QXIAER(L_LEVELS+1,L_NSPECTI,naerkind))
    173         if(.not.allocated(QSIAER)) allocate(QSIAER(L_LEVELS+1,L_NSPECTI,naerkind))
    174         if(.not.allocated(GIAER)) allocate(GIAER(L_LEVELS+1,L_NSPECTI,naerkind))
     170        if(.not.allocated(QXVAER)) allocate(QXVAER(L_LEVELS,L_NSPECTV,naerkind))
     171        if(.not.allocated(QSVAER)) allocate(QSVAER(L_LEVELS,L_NSPECTV,naerkind))
     172        if(.not.allocated(GVAER)) allocate(GVAER(L_LEVELS,L_NSPECTV,naerkind))
     173        if(.not.allocated(QXIAER)) allocate(QXIAER(L_LEVELS,L_NSPECTI,naerkind))
     174        if(.not.allocated(QSIAER)) allocate(QSIAER(L_LEVELS,L_NSPECTI,naerkind))
     175        if(.not.allocated(GIAER)) allocate(GIAER(L_LEVELS,L_NSPECTI,naerkind))
    175176
    176177         !!! ALLOCATED instances are necessary because of CLFvarying (strategy to call callcorrk twice in physiq...)
     
    376377            ! Test / Correct for freaky s. s. albedo values.
    377378            do iaer=1,naerkind
    378                do k=1,L_LEVELS+1
     379               do k=1,L_LEVELS
    379380
    380381                  do nw=1,L_NSPECTV
     
    419420            ! boundary conditions
    420421            tauaero(1,iaer)          = tauaero(2,iaer)
    421             tauaero(L_LEVELS+1,iaer) = tauaero(L_LEVELS,iaer)
    422422            !tauaero(1,iaer)          = 0.
    423             !tauaero(L_LEVELS+1,iaer) = 0.
    424423           
    425424         end do ! naerkind
     
    430429            albv(nw)=albedo(ig,nw)
    431430         ENDDO
    432 
    433          if (nosurf) then ! Case with no surface.
    434             DO nw=1,L_NSPECTV
    435                if(albv(nw).gt.0.0) then
    436                   print*,'For open lower boundary in callcorrk must'
    437                   print*,'have spectral surface band albedos all set to zero!'
    438                   call abort
    439                endif
    440             ENDDO         
    441          endif
    442431
    443432      if ((ngrid.eq.1).and.(global1d)) then ! Fixed zenith angle 'szangle' in 1D simulations w/ globally-averaged sunlight.
Note: See TracChangeset for help on using the changeset viewer.