Ignore:
Timestamp:
May 27, 2022, 4:57:03 PM (2 years ago)
Author:
emillour
Message:

Mars GCM:
Add possibility to output either upward or downward SW flux at the surface
and top of atmosphere from physiq. Required adding some output arguments
to callradite.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/callradite_mod.F

    r2678 r2685  
    77      SUBROUTINE callradite(icount,ngrid,nlayer,nq,zday,ls,pq,albedo,
    88     $     emis,mu0,pplev,pplay,pt,tsurf,fract,dist_sol,igout,
    9      $     dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,
    10      $     fluxtop_sw,tau_pref_scenario,tau_pref_gcm,
     9     $     dtlw,dtsw,fluxsurf_lw,fluxsurf_dn_sw,fluxsurf_up_sw,
     10     $     fluxtop_lw,fluxtop_dn_sw,fluxtop_up_sw,
     11     &     tau_pref_scenario,tau_pref_gcm,
    1112     &     tau,aerosol,dsodust,tauscaling,dust_rad_adjust,IRtoVIScoef,
    1213     $     taucloudtes,rdust,rice,nuice,riceco2,nuiceco2,co2ice,
     
    141142c   nueffrad(ngrid,nlayer,naerkind) Aerosol effective variance
    142143
    143 c
    144 c  output:
    145 c  -------
    146 c dtlw (ngrid,nlayer)       longwave (IR) heating rate (K/s)
    147 c dtsw(ngrid,nlayer)        shortwave (Solar) heating rate (K/s)
    148 c fluxsurf_lw(ngrid)        surface downward flux tota LW (thermal IR) (W.m-2)
    149 c fluxsurf_sw(ngrid,1)      surface downward flux SW for solar band#1 (W.m-2)
    150 c fluxsurf_sw(ngrid,2)      surface downward flux SW for solar band#2 (W.m-2)
    151 c
    152 c fluxtop_lw(ngrid)         outgoing upward flux tota LW (thermal IR) (W.m-2)
    153 c fluxtop_sw(ngrid,1)       outgoing upward flux SW for solar band#1 (W.m-2)
    154 c fluxtop_sw(ngrid,2)       outgoing upward flux SW for solar band#2 (W.m-2)
    155 
    156 c   tau          Column total visible dust optical depth at each point
    157 c   aerosol(ngrid,nlayer,naerkind)    aerosol extinction optical depth
    158 c                         at reference wavelength "longrefvis" set
    159 c                         in dimradmars_h , in each layer, for one of
    160 c                         the "naerkind" kind of aerosol optical
    161 c                         properties.
    162144c=======================================================================
    163145c
     
    189171      REAL,INTENT(IN) :: tsurf(ngrid)
    190172      REAL,INTENT(IN) :: dist_sol,mu0(ngrid),fract(ngrid)
    191       REAL,INTENT(OUT) :: dtlw(ngrid,nlayer),dtsw(ngrid,nlayer)
    192       REAL,INTENT(OUT) :: fluxsurf_lw(ngrid), fluxtop_lw(ngrid)
    193       REAL,INTENT(OUT) :: fluxsurf_sw(ngrid,2), fluxtop_sw(ngrid,2)
     173      REAL,INTENT(OUT) :: dtlw(ngrid,nlayer) ! longwave (IR) heating rate (K/s)
     174      REAL,INTENT(OUT) :: dtsw(ngrid,nlayer) ! shortwave (Solar) heating rate (K/s)
     175      REAL,INTENT(OUT) :: fluxsurf_lw(ngrid) ! total LW (thermal IR) downward flux
     176                                             ! (W.m-2) at the surface
     177      REAL,INTENT(OUT) :: fluxtop_lw(ngrid) ! outgoing total LW (thermal IR)
     178                                     ! upward flux (W.m-2) at the top of the atm.
     179      REAL,INTENT(OUT) :: fluxsurf_dn_sw(ngrid,2) ! surface downward SW flux for
     180                                      ! solar bands #1 and #2 (W.m-2)
     181      REAL,INTENT(OUT) :: fluxsurf_up_sw(ngrid,2) ! surface upward SW flux for
     182                                      ! solar bands #1 and #2 (W.m-2)
     183      REAL,INTENT(OUT) :: fluxtop_dn_sw(ngrid,2) ! incoming downward SW flux for
     184                                 ! solar bands #1 and #2 (W.m-2) at top of atm.
     185      REAL,INTENT(OUT) :: fluxtop_up_sw(ngrid,2) ! outgoing upward SW flux for
     186                                 ! solar bands #1 and #2 (W.m-2) at top of atm.
    194187      REAL,INTENT(OUT) :: tau_pref_scenario(ngrid) ! prescribed dust column
    195188                          ! visible opacity at odpref from scenario
    196189      REAL,INTENT(OUT) :: tau_pref_gcm(ngrid) ! computed dust column
    197190                          ! visible opacity at odpref in the GCM
    198       REAL,INTENT(OUT) :: tau(ngrid,naerkind)
     191      REAL,INTENT(OUT) :: tau(ngrid,naerkind) ! Column visible optical depth
     192                          ! for each aerosol
    199193      REAL,INTENT(OUT) :: taucloudtes(ngrid)! Cloud opacity at infrared
    200194                               !   reference wavelength using
    201195                               !   Qabs instead of Qext
    202196                               !   (direct comparison with TES)
    203       REAL,INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind)
     197      REAL,INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind) ! aerosol extinction
     198                          ! optical depth at reference wavelength "longrefvis",
     199                          ! set in dimradmars_h, for each kind of aerosol
    204200      REAL,INTENT(INOUT) :: dsodust(ngrid,nlayer)
    205201      REAL,INTENT(OUT) :: rdust(ngrid,nlayer)  ! Dust geometric mean radius (m)
     
    585581        enddo
    586582
     583        ! copy SW fluxes at surface and TOA
    587584        do ig = 1,nd
    588           fluxsurf_sw(ig0+ig,1) = zfluxd_sw(ig,1,1)
    589           fluxsurf_sw(ig0+ig,2) = zfluxd_sw(ig,1,2)
    590           fluxtop_sw(ig0+ig,1) = zfluxu_sw(ig,nlaylte+1,1)
    591           fluxtop_sw(ig0+ig,2) = zfluxu_sw(ig,nlaylte+1,2)
     585          ! surface downward SW flux
     586          fluxsurf_dn_sw(ig0+ig,1) = zfluxd_sw(ig,1,1)
     587          fluxsurf_dn_sw(ig0+ig,2) = zfluxd_sw(ig,1,2)
     588          ! surface upward SW flux
     589          fluxsurf_up_sw(ig0+ig,1) = zfluxu_sw(ig,1,1)
     590          fluxsurf_up_sw(ig0+ig,2) = zfluxu_sw(ig,1,2)
     591          ! downward SW flux at top of atmosphere
     592          fluxtop_dn_sw(ig0+ig,1) = zfluxd_sw(ig,nlaylte+1,1)
     593          fluxtop_dn_sw(ig0+ig,2) = zfluxd_sw(ig,nlaylte+1,2)         
     594          ! upward SW flux at top of atmosphere
     595          fluxtop_up_sw(ig0+ig,1) = zfluxu_sw(ig,nlaylte+1,1)
     596          fluxtop_up_sw(ig0+ig,2) = zfluxu_sw(ig,nlaylte+1,2)
    592597        enddo
    593598
     
    613618            PRINT*,albedo(igout,1),emis(igout),mu0(igout),
    614619     s           fract(igout), fluxsurf_lw(igout),
    615      $     fluxsurf_sw(igout,1)+fluxsurf_sw(igout,2)
     620     $     fluxsurf_dn_sw(igout,1)+fluxsurf_dn_sw(igout,2)
    616621            PRINT*,'Tlay Tlev Play Plev dT/dt SW dT/dt LW (K/s)'
    617622            PRINT*,'daysec',daysec
Note: See TracChangeset for help on using the changeset viewer.