Class rad_dcpam_E_V2
In: radiation/rad_dcpam_E_V2.f90

dcpam 地球大気向け放射モデル Ver. 2

dcpam radiation model for the Earth‘s atmosphere Ver. 1

Note that Japanese and English are described in parallel.

地球大気向け放射モデル.

This is a radiation model for the Earth‘s atmospehre.

Radiation in the wavenumber range from 0 to 3000 cm-1 is calculated in the routine of long wave radiation. Radiation in the wavenumber range from 1000 to 57143 cm-1 (0.175 to 10 micron) is calculated in the routine of shortwave radiation.

References

Procedures List

RadDcpamEV2Flux :放射フラックスの計算
———— :————
RadDcpamEV2Flux :Calculate radiation flux

NAMELIST

NAMELIST#rad_dcpam_E_V2_nml

Methods

Included Modules

dc_types gridset constants dc_message set_o3 rad_dcpam_E_SW_V2_1 rad_dcpam_E_LW_V2_3 dc_iounit namelist_util

Public Instance methods

Subroutine :
xy_SurfAlbedo(0:imax-1, 1:jmax) :real(DP), intent(in )
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in )
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_QH2OVap(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
: $ q $ . 混合比. Mass mixing ratio of constituents (1)
xyz_QH2OLiq(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(in )
xyr_RadSFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
xyr_RadLFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) :real(DP), intent(out)

[Source]

  subroutine RadDcpamEV2Flux( xy_SurfAlbedo, xyz_Press, xyr_Press, xyz_Temp, xyz_QH2OVap, xyz_QH2OLiq, xy_SurfTemp, xyr_RadSFlux, xyr_RadLFlux, xyra_DelRadLFlux )


    ! USE statements
    !

    real(DP), intent(in ) :: xy_SurfAlbedo   (0:imax-1, 1:jmax)
    real(DP), intent(in ) :: xyz_Press       (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyr_Press       (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(in ) :: xyz_Temp        (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyz_QH2OVap     (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q $ .   混合比. Mass mixing ratio of constituents (1)
    real(DP), intent(in ) :: xyz_QH2OLiq     (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xy_SurfTemp     (0:imax-1, 1:jmax)
    real(DP), intent(out) :: xyr_RadSFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out) :: xyr_RadLFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out) :: xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)


    ! Work variables
    !
    real(DP) :: xyz_DelAtmMass   (0:imax-1, 1:jmax, 1:kmax)

    integer  :: k


    ! 初期化
    ! Initialization
    !
    if ( .not. rad_dcpam_E_V2_inited ) call RadDcpamEV2Init

    do k = 1, kmax
      xyz_DelAtmMass(:,:,k) = ( xyr_Press(:,:,k-1) - xyr_Press(:,:,k ) ) / Grav
    end do

    call RadDcpamEV2FluxCore( xy_SurfAlbedo, xyz_DelAtmMass, xyz_Press, xyz_Temp, xyz_QH2OVap, xyz_QH2OLiq, xy_SurfTemp, xyr_RadSFlux, xyr_RadLFlux, xyra_DelRadLFlux )


  end subroutine RadDcpamEV2Flux
Subroutine :
r_Height(0:kmax) :real(DP), intent(in )
x_SurfAlbedo(0:imax-1) :real(DP), intent(in )
xz_Dens(0:imax-1, 1:kmax) :real(DP), intent(in )
xz_Press(0:imax-1, 1:kmax) :real(DP), intent(in )
xz_Temp(0:imax-1, 1:kmax) :real(DP), intent(in )
xz_QH2OVap(0:imax-1, 1:kmax) :real(DP), intent(in )
xz_QH2OLiq(0:imax-1, 1:kmax) :real(DP), intent(in )
x_SurfTemp(0:imax-1) :real(DP), intent(in )
xr_RadSFlux(0:imax-1, 0:kmax) :real(DP), intent(out)
xr_RadLFlux(0:imax-1, 0:kmax) :real(DP), intent(out)
xra_DelRadLFlux(0:imax-1, 0:kmax, 0:1) :real(DP), intent(out)

[Source]

  subroutine RadDcpamEV2FluxforNHM2DWrapper( r_Height, x_SurfAlbedo, xz_Dens, xz_Press, xz_Temp, xz_QH2OVap, xz_QH2OLiq, x_SurfTemp, xr_RadSFlux, xr_RadLFlux, xra_DelRadLFlux )


    ! USE statements
    !

    ! メッセージ出力
    ! Message output
    !
    use dc_message, only: MessageNotify

    real(DP), intent(in ) :: r_Height                 (0:kmax)
    real(DP), intent(in ) :: x_SurfAlbedo   (0:imax-1)
    real(DP), intent(in ) :: xz_Dens        (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: xz_Press       (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: xz_Temp        (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: xz_QH2OVap     (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: xz_QH2OLiq     (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: x_SurfTemp     (0:imax-1)
    real(DP), intent(out) :: xr_RadSFlux    (0:imax-1, 0:kmax)
    real(DP), intent(out) :: xr_RadLFlux    (0:imax-1, 0:kmax)
    real(DP), intent(out) :: xra_DelRadLFlux(0:imax-1, 0:kmax, 0:1)


    ! Work variables
    !
    real(DP) :: xy_SurfAlbedo   (0:imax-1, 1:jmax)
    real(DP) :: xyz_Dens        (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_Press       (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_Temp        (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_QH2OVap     (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_QH2OLiq     (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xy_SurfTemp     (0:imax-1, 1:jmax)
    real(DP) :: xyr_RadSFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP) :: xyr_RadLFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP) :: xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)

    integer  :: k


    if ( jmax /= 1 ) then
      call MessageNotify( 'E', module_name, 'jmax must be 1.' )
    end if


    xy_SurfAlbedo   (:, 1)       = x_SurfAlbedo   (:)
    do k = 1, kmax
      xyz_Dens        (:, 1, k)    = xz_Dens        (:, k)
      xyz_Press       (:, 1, k)    = xz_Press       (:, k)
      xyz_Temp        (:, 1, k)    = xz_Temp        (:, k)
      xyz_QH2OVap     (:, 1, k)    = xz_QH2OVap     (:, k)
      xyz_QH2OLiq     (:, 1, k)    = xz_QH2OLiq     (:, k)
    end do
    xy_SurfTemp     (:, 1)       = x_SurfTemp     (:)

    call RadDcpamEV2FluxforNHM( r_Height, xy_SurfAlbedo, xyz_Dens, xyz_Press, xyz_Temp, xyz_QH2OVap, xyz_QH2OLiq, xy_SurfTemp, xyr_RadSFlux, xyr_RadLFlux, xyra_DelRadLFlux )

    xr_RadSFlux    (:, :)    = xyr_RadSFlux    (:, 1, :)
    xr_RadLFlux    (:, :)    = xyr_RadLFlux    (:, 1, :)
    xra_DelRadLFlux(:, :, :) = xyra_DelRadLFlux(:, 1, :, :)


  end subroutine RadDcpamEV2FluxforNHM2DWrapper
rad_dcpam_E_V2_inited
Variable :
rad_dcpam_E_V2_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag

Private Instance methods

CO2MolWeight
Variable :
CO2MolWeight :real(DP), save
H2OMolWeight
Variable :
H2OMolWeight :real(DP), save
MeanMolWeight
Variable :
MeanMolWeight :real(DP), save
Subroutine :
x_SurfAlbedo(0:imax-1) :real(DP), intent(in )
xz_Press(0:imax-1, 1:kmax) :real(DP), intent(in )
xr_Press(0:imax-1, 0:kmax) :real(DP), intent(in )
xz_Temp(0:imax-1, 1:kmax) :real(DP), intent(in )
xz_QH2OVap(0:imax-1, 1:kmax) :real(DP), intent(in )
xz_QH2OLiq(0:imax-1, 1:kmax) :real(DP), intent(in )
x_SurfTemp(0:imax-1) :real(DP), intent(in )
xr_RadSFlux(0:imax-1, 0:kmax) :real(DP), intent(out)
xr_RadLFlux(0:imax-1, 0:kmax) :real(DP), intent(out)
xra_DelRadLFlux(0:imax-1, 0:kmax, 0:1) :real(DP), intent(out)

[Source]

  subroutine RadDcpamEV2Flux2DWrapper( x_SurfAlbedo, xz_Press, xr_Press, xz_Temp, xz_QH2OVap, xz_QH2OLiq, x_SurfTemp, xr_RadSFlux, xr_RadLFlux, xra_DelRadLFlux )


    ! USE statements
    !

    ! メッセージ出力
    ! Message output
    !
    use dc_message, only: MessageNotify


    real(DP), intent(in ) :: x_SurfAlbedo   (0:imax-1)
    real(DP), intent(in ) :: xz_Press       (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: xr_Press       (0:imax-1, 0:kmax)
    real(DP), intent(in ) :: xz_Temp        (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: xz_QH2OVap     (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: xz_QH2OLiq     (0:imax-1, 1:kmax)
    real(DP), intent(in ) :: x_SurfTemp     (0:imax-1)
    real(DP), intent(out) :: xr_RadSFlux    (0:imax-1, 0:kmax)
    real(DP), intent(out) :: xr_RadLFlux    (0:imax-1, 0:kmax)
    real(DP), intent(out) :: xra_DelRadLFlux(0:imax-1, 0:kmax, 0:1)


    ! Work variables
    !
    real(DP) :: xy_SurfAlbedo   (0:imax-1, 1:jmax)
    real(DP) :: xyz_Press       (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyr_Press       (0:imax-1, 1:jmax, 0:kmax)
    real(DP) :: xyz_Temp        (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_QH2OVap     (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_QH2OLiq     (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xy_SurfTemp     (0:imax-1, 1:jmax)
    real(DP) :: xyr_RadSFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP) :: xyr_RadLFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP) :: xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)


    if ( jmax /= 1 ) then
      call MessageNotify( 'E', module_name, 'jmax must be 1.' )
    end if


    xy_SurfAlbedo   (:, 1)       = x_SurfAlbedo   (:)
    xyz_Press       (:, 1, :)    = xz_Press       (:, :)
    xyr_Press       (:, 1, :)    = xr_Press       (:, :)
    xyz_Temp        (:, 1, :)    = xz_Temp        (:, :)
    xyz_QH2OVap     (:, 1, :)    = xz_QH2OVap     (:, :)
    xyz_QH2OLiq     (:, 1, :)    = xz_QH2OLiq     (:, :)
    xy_SurfTemp     (:, 1)       = x_SurfTemp     (:)

    call RadDcpamEV2Flux( xy_SurfAlbedo, xyz_Press, xyr_Press, xyz_Temp, xyz_QH2OVap, xyz_QH2OLiq, xy_SurfTemp, xyr_RadSFlux, xyr_RadLFlux, xyra_DelRadLFlux )

    xr_RadSFlux    (:, :)    = xyr_RadSFlux    (:, 1, :)
    xr_RadLFlux    (:, :)    = xyr_RadLFlux    (:, 1, :)
    xra_DelRadLFlux(:, :, :) = xyra_DelRadLFlux(:, 1, :, :)


  end subroutine RadDcpamEV2Flux2DWrapper
Subroutine :
xy_SurfAlbedo(0:imax-1, 1:jmax) :real(DP), intent(in )
xyz_DelAtmMass(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_QH2OVap(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
: $ q $ . 混合比. Mass mixing ratio of constituents (1)
xyz_QH2OLiq(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(in )
xyr_RadSFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
xyr_RadLFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) :real(DP), intent(out)

[Source]

  subroutine RadDcpamEV2FluxCore( xy_SurfAlbedo, xyz_DelAtmMass, xyz_Press, xyz_Temp, xyz_QH2OVap, xyz_QH2OLiq, xy_SurfTemp, xyr_RadSFlux, xyr_RadLFlux, xyra_DelRadLFlux )


    ! USE statements
    !

    ! メッセージ出力
    ! Message output
    !
    use dc_message, only: MessageNotify

    ! O3 分布の設定
    ! Set O3 distribution
    !
    use set_o3, only: SetO3

!!$    ! dcpam 地球大気向け短波放射モデル Ver. 2
!!$    ! dcpam short wave radiation model for the Earth's atmosphere Ver. 2
!!$    !
!!$    use radiation_dcpam_E_SW_V2, only: RadiationDcpamESWV2Flux

    ! dcpam 地球大気向け短波放射モデル Ver. 2.1
    ! dcpam short wave radiation model for the Earth's atmosphere Ver. 2.1
    !
    use rad_dcpam_E_SW_V2_1, only: RadDcpamESWV21Flux

!!$    ! dcpam 地球大気向け長波放射モデル Ver. 2
!!$    ! dcpam long wave radiation model for the Earth's atmosphere Ver. 2
!!$    !
!!$    use radiation_dcpam_E_LW_V2, only : RadiationDcpamELWV2Flux
!!$
!!$    ! dcpam 地球大気向け長波放射モデル Ver. 2.1
!!$    ! dcpam long wave radiation model for the Earth's atmosphere Ver. 2.1
!!$    !
!!$    use radiation_dcpam_E_LW_V2_1, only : RadiationDcpamELWV21Flux
!!$
!!$    ! dcpam 地球大気向け長波放射モデル Ver. 2.2
!!$    ! dcpam long wave radiation model for the Earth's atmosphere Ver. 2.2
!!$    !
!!$    use radiation_dcpam_E_LW_V2_2, only : RadiationDcpamELWV22Flux

    ! dcpam 地球大気向け長波放射モデル Ver. 2.3
    ! dcpam long wave radiation model for the Earth's atmosphere Ver. 2.3
    !
    use rad_dcpam_E_LW_V2_3, only : RadDcpamELWV23Flux

    real(DP), intent(in ) :: xy_SurfAlbedo   (0:imax-1, 1:jmax)
    real(DP), intent(in ) :: xyz_DelAtmMass  (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyz_Press       (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyz_Temp        (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyz_QH2OVap     (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q $ .   混合比. Mass mixing ratio of constituents (1)
    real(DP), intent(in ) :: xyz_QH2OLiq     (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xy_SurfTemp     (0:imax-1, 1:jmax)
    real(DP), intent(out) :: xyr_RadSFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out) :: xyr_RadLFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out) :: xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)


    ! Work variables
    !
    real(DP) :: xyz_QCO2         (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_QH2OSol      (0:imax-1, 1:jmax, 1:kmax)

    real(DP) :: xyz_DelCO2Mass   (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_DelH2OVapMass(0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_DelH2OLiqMass(0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_DelH2OSolMass(0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_DelO3Mass    (0:imax-1, 1:jmax, 1:kmax)

    integer  :: k


    ! 初期化
    ! Initialization
    !
    if ( .not. rad_dcpam_E_V2_inited ) call RadDcpamEV2Init


    xyz_QCO2 = VMRCO2 * CO2MolWeight / MeanMolWeight


    ! Amount of water ice is assumed to be zero, for the moment.
    ! In future, this value will be an argument of this subroutine.
    !
    xyz_QH2OSol = 0.0_DP



    ! O3 分布の設定
    ! Setting of O3 distribution
    !
    call SetO3( xyz_Press, xyz_QO3 )


    xyz_DelCO2Mass    = xyz_DelAtmMass * xyz_QCO2
    xyz_DelH2OVapMass = xyz_DelAtmMass * xyz_QH2OVap
    xyz_DelH2OLiqMass = xyz_DelAtmMass * xyz_QH2OLiq
    xyz_DelH2OSolMass = xyz_DelAtmMass * xyz_QH2OSol
    xyz_DelO3Mass     = xyz_DelAtmMass * xyz_QO3



!!$    select case ( SWVer )
!!$    case ( 0 )
!!$      ! dcpam 地球大気向け短波放射モデル Ver. 2
!!$      ! dcpam short wave radiation model for the Earth's atmosphere Ver. 2
!!$      !
!!$      call RadiationDcpamESWV2Flux(                                 &
!!$        & xy_SurfAlbedo,                                                  &
!!$        & xyz_Press, xyr_Press, xyz_Temp, xyz_QH2OVap, xyz_QO3, xyz_Height,  &
!!$        & xyr_RadSFlux                                                    &
!!$        & )
!!$    case ( 1 )
      ! dcpam 地球大気向け短波放射モデル Ver. 2.1
      ! dcpam short wave radiation model for the Earth's atmosphere Ver. 2.1
      !
      call RadDcpamESWV21Flux( xy_SurfAlbedo, xyz_DelAtmMass, xyz_DelH2OVapMass, xyz_DelH2OLiqMass, xyz_DelH2OSolMass, xyz_DelO3Mass, xyz_Press, xyz_Temp, xyr_RadSFlux )
!!$    case default
!!$      call MessageNotify( 'E', module_name, 'SW model version %d is not supported.', i = (/ LWVer /) )
!!$    end select

!!$    select case ( LWVer )
!!$    case ( 0 )
!!$      call RadiationDcpamELWV2Flux( &
!!$        & xyz_Press, xyr_Press, xyz_Temp, xy_SurfTemp,                    & ! (in )
!!$        & xyz_QH2OVap, xyz_QO3,                                           & ! (in )
!!$        & xyr_RadLFlux, xyra_DelRadLFlux                                  & ! (out)
!!$        & )
!!$    case ( 1 )
!!$      call RadiationDcpamELWV21Flux( &
!!$        & xyz_Press, xyr_Press, xyz_Temp, xy_SurfTemp,                    & ! (in )
!!$        & xyz_QH2OVap, xyz_QO3,                                           & ! (in )
!!$        & xyr_RadLFlux, xyra_DelRadLFlux                                  & ! (out)
!!$        & )
!!$    case ( 2 )
!!$      call RadiationDcpamELWV22Flux( &
!!$        & xyz_Press, xyr_Press, xyz_Temp, xy_SurfTemp,                    & ! (in )
!!$        & xyz_QH2OVap, xyz_QO3,                                           & ! (in )
!!$        & xyr_RadLFlux, xyra_DelRadLFlux                                  & ! (out)
!!$        & )
!!$    case ( 3 )
      call RadDcpamELWV23Flux( xyz_DelCO2Mass, xyz_DelH2OVapMass, xyz_DelH2OLiqMass, xyz_DelH2OSolMass, xyz_DelO3Mass, xyz_Press, xyz_Temp, xy_SurfTemp, xyz_QCO2, xyz_QH2OVap, xyr_RadLFlux, xyra_DelRadLFlux )
!!$    case default
!!$      call MessageNotify( 'E', module_name, 'LW model version %d is not supported.', i = (/ LWVer /) )
!!$    end select


  end subroutine RadDcpamEV2FluxCore
Subroutine :
r_Height(0:kmax) :real(DP), intent(in )
xy_SurfAlbedo(0:imax-1, 1:jmax) :real(DP), intent(in )
xyz_Dens(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xyz_QH2OVap(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
: $ q $ . 混合比. Mass mixing ratio of constituents (1)
xyz_QH2OLiq(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(in )
xyr_RadSFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
xyr_RadLFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) :real(DP), intent(out)

[Source]

  subroutine RadDcpamEV2FluxforNHM( r_Height, xy_SurfAlbedo, xyz_Dens, xyz_Press, xyz_Temp, xyz_QH2OVap, xyz_QH2OLiq, xy_SurfTemp, xyr_RadSFlux, xyr_RadLFlux, xyra_DelRadLFlux )


    ! USE statements
    !

    real(DP), intent(in ) :: r_Height                          (0:kmax)
    real(DP), intent(in ) :: xy_SurfAlbedo   (0:imax-1, 1:jmax)
    real(DP), intent(in ) :: xyz_Dens        (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyz_Press       (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyz_Temp        (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xyz_QH2OVap     (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q $ .   混合比. Mass mixing ratio of constituents (1)
    real(DP), intent(in ) :: xyz_QH2OLiq     (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in ) :: xy_SurfTemp     (0:imax-1, 1:jmax)
    real(DP), intent(out) :: xyr_RadSFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out) :: xyr_RadLFlux    (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out) :: xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)


    ! Work variables
    !
    real(DP) :: xyz_DelAtmMass   (0:imax-1, 1:jmax, 1:kmax)

    integer  :: k


    ! 初期化
    ! Initialization
    !
    if ( .not. rad_dcpam_E_V2_inited ) call RadDcpamEV2Init

    do k = 1, kmax
      xyz_DelAtmMass(:,:,k) = xyz_Dens(:,:,k) * ( r_Height(k) - r_Height(k-1) )
    end do

    call RadDcpamEV2FluxCore( xy_SurfAlbedo, xyz_DelAtmMass, xyz_Press, xyz_Temp, xyz_QH2OVap, xyz_QH2OLiq, xy_SurfTemp, xyr_RadSFlux, xyr_RadLFlux, xyra_DelRadLFlux )


  end subroutine RadDcpamEV2FluxforNHM
Subroutine :

This procedure input/output NAMELIST#rad_dcpam_EV2_nml .

[Source]

  subroutine RadDcpamEV2Init

    ! ファイル入出力補助
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid

    ! メッセージ出力
    ! Message output
    !
    use dc_message, only: MessageNotify


    ! 宣言文 ; Declaration statements
    !

    integer:: unit_nml        ! NAMELIST ファイルオープン用装置番号.
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 読み込み時の IOSTAT.
                              ! IOSTAT of NAMELIST read

    ! NAMELIST 変数群
    ! NAMELIST group name
    !
    namelist /rad_dcpam_EV2_nml/ VMRCO2

!!$      & SWVer, LWVer
          !
          ! デフォルト値については初期化手続 "rad_dcpam_EV2#RadDcpamEV2Init"
          ! のソースコードを参照のこと.
          !
          ! Refer to source codes in the initialization procedure
          ! "rad_dcpam_EV2#RadDcpamEV2Init" for the default values.
          !


    ! Molecular weights of atmosphere, CO2, and H2O
    !
    MeanMolWeight = 28.0d-3
    CO2MolWeight  = 44.0d-3
    H2OMolWeight  = 18.0d-3


    ! デフォルト値の設定
    ! Default values settings
    !
    VMRCO2                = 382.0d-6


!!$    SWVer = 1
!!$    LWVer = 3


    ! NAMELIST の読み込み
    ! NAMELIST is input
    !
    if ( trim(namelist_filename) /= '' ) then
      call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in)

      rewind( unit_nml )
      read( unit_nml, nml = rad_dcpam_EV2_nml, iostat = iostat_nml )             ! (out)
      close( unit_nml )

      call NmlutilMsg( iostat_nml, module_name ) ! (in)
    end if


    ! Allocate a local variable for O3 distribution
    !
    allocate( xyz_QO3(0:imax-1, 1:jmax, 1:kmax) )


    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '  VMRCO2 = %f', d = (/ VMRCO2 /) )
!!$    call MessageNotify( 'M', module_name, 'SWVer = %d', i = (/ SWVer /) )
!!$    call MessageNotify( 'M', module_name, 'LWVer = %d', i = (/ LWVer /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )


    rad_dcpam_E_V2_inited = .true.

  end subroutine RadDcpamEV2Init
VMRCO2
Variable :
VMRCO2 :real(DP), save
: Volume mixing ratio of CO2
module_name
Constant :
module_name = ‘rad_dcpam_E_V2 :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: dcpam5-20110407 $’ // ’$Id: rad_dcpam_E_V2.f90,v 1.2 2011-04-06 15:28:06 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version
xyz_QO3
Variable :
xyz_QO3(:,:,:) :real(DP), allocatable, save
: O3 分布 (1) O3 distribution (1)