Class rad_utils
In: radiation/rad_utils.f90

�¾å��¢é�£ã���¼ã����

Routines for radiation calculation

Note that Japanese and English are described in parallel.

Procedures List

RadDTempDt :�¾å����������¹ã������æ¸�º¦å¤������ç®�
RadFluxOutput :�¾å����������¹ã���ºå��
———— :————
RadDTempDt :Calculate temperature tendency with radiation flux
RadFluxOutput :Output radiation fluxes

NAMELIST

NAMELIST#rad_utils_nml

Methods

Included Modules

dc_types constants0 constants gridset dc_message timeset gtool_historyauto dc_string dc_iounit namelist_util

Public Instance methods

Subroutine :
xyr_RadLFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �·æ³¢����������. Longwave flux
xyr_RadSFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �­æ³¢ (�¥å�) ����������. Shortwave (insolation) flux
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ hat{p} $ . æ°��� (���´æ�°ã������). Air pressure (half level)
xyz_DTempDtRadL(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: �·æ³¢���±ç�. Temperature tendency with longwave
xyz_DTempDtRadS(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: �­æ³¢���±ç�. Temperature tendency with shortwave

�¾å�������æ¸�º¦å¤�������è¨�ç®����¾ã��.

Temperature tendency with radiation is calculated.

[Source]

  subroutine RadDTempDt( xyr_RadLFlux, xyr_RadSFlux, xyr_Press, xyz_DTempDtRadL, xyz_DTempDtRadS )
    !
    ! �¾å�������æ¸�º¦å¤�������è¨�ç®����¾ã��. 
    ! 
    ! Temperature tendency with radiation is calculated. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimeN, TimesetClockStart, TimesetClockStop

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut


    ! 宣�� ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xyr_RadLFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! �·æ³¢����������. 
                              ! Longwave flux
    real(DP), intent(in):: xyr_RadSFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! �­æ³¢ (�¥å�) ����������. 
                              ! Shortwave (insolation) flux
    real(DP), intent(in):: xyr_Press    (0:imax-1, 1:jmax, 0:kmax)
                              ! $ \hat{p} $ . æ°��� (���´æ�°ã������). 
                              ! Air pressure (half level)
    real(DP), intent(out):: xyz_DTempDtRadL (0:imax-1, 1:jmax, 1:kmax)
                              ! �·æ³¢���±ç�. 
                              ! Temperature tendency with longwave
    real(DP), intent(out):: xyz_DTempDtRadS (0:imax-1, 1:jmax, 1:kmax)
                              ! �­æ³¢���±ç�. 
                              ! Temperature tendency with shortwave

    ! �業��
    ! Work variables
    !
    integer:: k               ! ���´æ�¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in vertical direction

    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. rad_utils_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    ! �����������
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )


    ! �¾å��·å�´ç����ç®�
    ! Calculate radiation cooling rate
    !
    do k = 1, kmax
      xyz_DTempDtRadL(:,:,k) = (     xyr_RadLFlux(:,:,k-1) - xyr_RadLFlux(:,:,k) ) / ( xyr_Press(:,:,k-1)    - xyr_Press(:,:,k) ) / CpDry * Grav

      xyz_DTempDtRadS(:,:,k) = (     xyr_RadSFlux(:,:,k-1) - xyr_RadSFlux(:,:,k) ) / ( xyr_Press(:,:,k-1)    - xyr_Press(:,:,k) ) / CpDry * Grav
    end do


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'DTempDtRadL' , xyz_DTempDtRadL )
    call HistoryAutoPut( TimeN, 'DTempDtRadS' , xyz_DTempDtRadS )


    ! ��������������
    ! Pause measurement of computation time
    !
    call TimesetClockStop( module_name )

  end subroutine RadDTempDt
Subroutine :
xr_RadLFlux(0:imax-1, 0:kmax) :real(DP), intent(in)
: �·æ³¢����������. Longwave flux
xr_RadSFlux(0:imax-1, 0:kmax) :real(DP), intent(in)
: �­æ³¢ (�¥å�) ����������. Shortwave (insolation) flux
r_Height(0:kmax) :real(DP), intent(in)
: $ hat{p} $ . æ°��� (���´æ�°ã������). Air pressure (half level)
xz_Dens(0:imax-1, 1:kmax) :real(DP), intent(in)
xz_DTempDtRadL(0:imax-1, 1:kmax) :real(DP), intent(out)
: �·æ³¢���±ç�. Temperature tendency with longwave
xz_DTempDtRadS(0:imax-1, 1:kmax) :real(DP), intent(out)
: �­æ³¢���±ç�. Temperature tendency with shortwave

�¾å�������æ¸�º¦å¤�������è¨�ç®����¾ã��.

Temperature tendency with radiation is calculated.

[Source]

  subroutine RadDTempDtforNHM2DWrapper( xr_RadLFlux, xr_RadSFlux, r_Height, xz_Dens, xz_DTempDtRadL, xz_DTempDtRadS )
    !
    ! �¾å�������æ¸�º¦å¤�������è¨�ç®����¾ã��. 
    ! 
    ! Temperature tendency with radiation is calculated. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! 宣�� ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xr_RadLFlux (0:imax-1, 0:kmax)
                              ! �·æ³¢����������. 
                              ! Longwave flux
    real(DP), intent(in):: xr_RadSFlux (0:imax-1, 0:kmax)
                              ! �­æ³¢ (�¥å�) ����������. 
                              ! Shortwave (insolation) flux
    real(DP), intent(in):: r_Height    (0:kmax)
                              ! $ \hat{p} $ . æ°��� (���´æ�°ã������). 
                              ! Air pressure (half level)
    real(DP), intent(in):: xz_Dens     (0:imax-1, 1:kmax)
    real(DP), intent(out):: xz_DTempDtRadL (0:imax-1, 1:kmax)
                              ! �·æ³¢���±ç�. 
                              ! Temperature tendency with longwave
    real(DP), intent(out):: xz_DTempDtRadS (0:imax-1, 1:kmax)
                              ! �­æ³¢���±ç�. 
                              ! Temperature tendency with shortwave

    ! �業��
    ! Work variables
    !
    real(DP) :: xyr_RadLFlux   (0:imax-1, 1:jmax, 0:kmax)
    real(DP) :: xyr_RadSFlux   (0:imax-1, 1:jmax, 0:kmax)
    real(DP) :: xyz_Dens       (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_DTempDtRadL(0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_DTempDtRadS(0:imax-1, 1:jmax, 1:kmax)


    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. rad_utils_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    xyr_RadLFlux(:,1,:) = xr_RadLFlux(:,:)
    xyr_RadSFlux(:,1,:) = xr_RadSFlux(:,:)
    xyz_Dens    (:,1,:) = xz_Dens    (:,:)

    call RadDTempDtforNHM( xyr_RadLFlux, xyr_RadSFlux, r_Height, xyz_Dens, xyz_DTempDtRadL, xyz_DTempDtRadS )

    xz_DTempDtRadL(:,:) = xyz_DTempDtRadL(:,1,:)
    xz_DTempDtRadS(:,:) = xyz_DTempDtRadS(:,1,:)


  end subroutine RadDTempDtforNHM2DWrapper
Subroutine :
xyr_RadSUwFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �­æ³¢ (�¥å�) ����������. Upward shortwave (insolation) flux
xyr_RadSDwFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �­æ³¢ (�¥å�) ����������. Downward shortwave (insolation) flux
xyr_RadLUwFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �·æ³¢����������. Upward longwave flux
xyr_RadLDwFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �·æ³¢����������. Downward longwave flux
xyra_DelRadLUwFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) :real(DP), intent(in)
: �·æ³¢�°è¡¨æ¸�º¦å¤���.
xyra_DelRadLDwFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) :real(DP), intent(in)
: �·æ³¢�°è¡¨æ¸�º¦å¤���.
xy_DSurfTempDt(0:imax-1, 1:jmax) :real(DP), intent(in)
: �°è¡¨�¢æ¸©åº������. Surface temperature tendency
xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ DP{T}{t} $ . æ¸�º¦å¤��� (K s-1) Temperature tendency (K s-1)

�¾å����������� (xyr_RadSFlux, xyr_RadLFlux) ���¤ã����, ���������°ã���������æ­£ã��, �ºå����è¡���.

Radiation fluxes (xyr_RadSFlux, xyr_RadLFlux) are corrected by using other arguments, and the corrected values are output.

[Source]

  subroutine RadFluxOutput( xyr_RadSUwFlux, xyr_RadSDwFlux, xyr_RadLUwFlux, xyr_RadLDwFlux, xyra_DelRadLUwFlux, xyra_DelRadLDwFlux, xy_DSurfTempDt, xyz_DTempDt )
    !
    ! �¾å����������� (xyr_RadSFlux, xyr_RadLFlux) 
    ! ���¤ã����, ���������°ã���������æ­£ã��, �ºå����è¡���. 
    !
    ! Radiation fluxes (xyr_RadSFlux, xyr_RadLFlux) are
    ! corrected by using other arguments, and the corrected values are output.
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ���»ç���
    ! Time control
    !
    use timeset, only: DelTime, TimeN, TimesetClockStart, TimesetClockStop

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut

    ! 宣�� ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xyr_RadSUwFlux  (0:imax-1, 1:jmax, 0:kmax)
                              ! �­æ³¢ (�¥å�) ����������. 
                              ! Upward shortwave (insolation) flux
    real(DP), intent(in):: xyr_RadSDwFlux  (0:imax-1, 1:jmax, 0:kmax)
                              ! �­æ³¢ (�¥å�) ����������. 
                              ! Downward shortwave (insolation) flux

    real(DP), intent(in):: xyr_RadLUwFlux    (0:imax-1, 1:jmax, 0:kmax)
                              ! �·æ³¢����������. 
                              ! Upward longwave flux
    real(DP), intent(in):: xyr_RadLDwFlux    (0:imax-1, 1:jmax, 0:kmax)
                              ! �·æ³¢����������. 
                              ! Downward longwave flux
    real(DP), intent(in):: xyra_DelRadLUwFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)
                              ! �·æ³¢�°è¡¨æ¸�º¦å¤���. 
                              ! 
    real(DP), intent(in):: xyra_DelRadLDwFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)
                              ! �·æ³¢�°è¡¨æ¸�º¦å¤���. 
                              ! 

    real(DP), intent(in):: xy_DSurfTempDt  (0:imax-1, 1:jmax)
                              ! �°è¡¨�¢æ¸©åº������. 
                              ! Surface temperature tendency
    real(DP), intent(in):: xyz_DTempDt     (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{T}{t} $ . æ¸�º¦å¤��� (K s-1)
                              ! Temperature tendency (K s-1)

    ! �ºå�����������業å���
    ! Work variables for output
    !
    real(DP):: xyr_RadSFlux    (0:imax-1, 1:jmax, 0:kmax)
                              ! �­æ³¢ (�¥å�) ����������. 
                              ! Shortwave (insolation) flux
    real(DP):: xyr_RadLFlux    (0:imax-1, 1:jmax, 0:kmax)
                              ! �·æ³¢����������. 
                              ! Longwave flux
    real(DP):: xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1)
                              ! �·æ³¢�°è¡¨æ¸�º¦å¤���. 
                              ! Surface temperature tendency with longwave
    real(DP):: xyr_RadLUwFluxCor(0:imax-1, 1:jmax, 0:kmax)
                              ! è£�æ­£ã�������·æ³¢����������. 
                              ! Corrected longwave flux
    real(DP):: xyr_RadLDwFluxCor(0:imax-1, 1:jmax, 0:kmax)
                              ! è£�æ­£ã�������·æ³¢����������. 
                              ! Corrected longwave flux
    real(DP):: xyr_RadLFluxCor  (0:imax-1, 1:jmax, 0:kmax)
                              ! è£�æ­£ã�������·æ³¢����������. 
                              ! Corrected longwave flux

    ! �業��
    ! Work variables
    !
    integer:: k               ! ���´æ�¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in vertical direction
    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. rad_utils_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    ! �����������
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )


    xyr_RadSFlux     = xyr_RadSUwFlux     - xyr_RadSDwFlux
    xyr_RadLFlux     = xyr_RadLUwFlux     - xyr_RadLDwFlux
    xyra_DelRadLFlux = xyra_DelRadLUwFlux - xyra_DelRadLDwFlux


    ! �·æ³¢���������¹ã���æ­� ( �°è¡¨���������¹å�����æ­� )
    ! Correct longwave flux ( amount of surface flux )
    !
    ! Lines commented out below will be deleted soon (yot, 2010/10/31).
!!$    do k = 0, kmax
!!$      xyr_RadLFluxCor (:,:,k) = &
!!$        &     xyr_RadLFlux (:,:,k) &
!!$        &   + xyra_DelRadLFlux(:,:,k,0) * xy_DSurfTempDt (:,:) * DelTime
!!$    end do
!!$    do k = 0, kmax
!!$      xyr_RadLFluxCor(:,:,k) = &
!!$        &   xyr_RadLFlux(:,:,k) &
!!$        & + (   xy_DSurfTempDt     * xyra_DelRadLFlux(:,:,k,0)   &
!!$        &     + xyz_DTempDt(:,:,1) * xyra_DelRadLFlux(:,:,k,1) ) &
!!$        &   * DelTime
!!$    end do
    do k = 0, kmax
      xyr_RadLUwFluxCor(:,:,k) = xyr_RadLUwFlux(:,:,k) + (   xy_DSurfTempDt     * xyra_DelRadLUwFlux(:,:,k,0) + xyz_DTempDt(:,:,1) * xyra_DelRadLUwFlux(:,:,k,1) ) * DelTime
      xyr_RadLDwFluxCor(:,:,k) = xyr_RadLDwFlux(:,:,k) + (   xy_DSurfTempDt     * xyra_DelRadLDwFlux(:,:,k,0) + xyz_DTempDt(:,:,1) * xyra_DelRadLDwFlux(:,:,k,1) ) * DelTime
    end do
    xyr_RadLFluxCor = xyr_RadLUwFluxCor - xyr_RadLDwFluxCor


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'OLR', xyr_RadLFluxCor(:,:,kmax) )
    call HistoryAutoPut( TimeN, 'SLR', xyr_RadLFluxCor(:,:,0)    )
    call HistoryAutoPut( TimeN, 'OSR', xyr_RadSFlux   (:,:,kmax) )
    call HistoryAutoPut( TimeN, 'SSR', xyr_RadSFlux   (:,:,0)    )
    call HistoryAutoPut( TimeN, 'RadLUWFLX', xyr_RadLUwFluxCor )
    call HistoryAutoPut( TimeN, 'RadLDWFLX', xyr_RadLDwFluxCor )
    call HistoryAutoPut( TimeN, 'RadSUWFLX', xyr_RadSUwFlux    )
    call HistoryAutoPut( TimeN, 'RadSDWFLX', xyr_RadSDwFlux    )


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'OLRB', xyr_RadLFlux(:,:,kmax) )
    call HistoryAutoPut( TimeN, 'SLRB', xyr_RadLFlux(:,:,0)    )
    call HistoryAutoPut( TimeN, 'OSRB', xyr_RadSFlux(:,:,kmax) )
    call HistoryAutoPut( TimeN, 'SSRB', xyr_RadSFlux(:,:,0)    )
    call HistoryAutoPut( TimeN, 'RadLUWFLXB', xyr_RadLUwFlux )
    call HistoryAutoPut( TimeN, 'RadLDWFLXB', xyr_RadLDwFlux )
    call HistoryAutoPut( TimeN, 'RadSUWFLXB', xyr_RadSUwFlux )
    call HistoryAutoPut( TimeN, 'RadSDWFLXB', xyr_RadSDwFlux )


    ! �·æ³¢���������¹ã���æ­� ( �°è¡¨���������¹å�����æ­� )
    ! Correct longwave flux ( amount of surface flux )
    !
    ! Lines commented out below will be deleted soon (yot, 2010/10/31).
!!$    do k = 0, kmax
!!$      xyr_RadLFluxCor (:,:,k) = &
!!$        &     xyr_RadLFlux (:,:,k) &
!!$        &   + xyra_DelRadLFlux(:,:,k,0) * xy_DSurfTempDt (:,:) * 2.0d0 * DelTime
!!$    end do
!!$    do k = 0, kmax
!!$      xyr_RadLFluxCor(:,:,k) = &
!!$        &   xyr_RadLFlux(:,:,k) &
!!$        & + (   xy_DSurfTempDt     * xyra_DelRadLFlux(:,:,k,0)   &
!!$        &     + xyz_DTempDt(:,:,1) * xyra_DelRadLFlux(:,:,k,1) ) &
!!$        &   * 2.0_DP * DelTime
!!$    end do
    do k = 0, kmax
      xyr_RadLUwFluxCor(:,:,k) = xyr_RadLUwFlux(:,:,k) + (   xy_DSurfTempDt     * xyra_DelRadLUwFlux(:,:,k,0) + xyz_DTempDt(:,:,1) * xyra_DelRadLUwFlux(:,:,k,1) ) * 2.0_DP * DelTime
      xyr_RadLDwFluxCor(:,:,k) = xyr_RadLDwFlux(:,:,k) + (   xy_DSurfTempDt     * xyra_DelRadLDwFlux(:,:,k,0) + xyz_DTempDt(:,:,1) * xyra_DelRadLDwFlux(:,:,k,1) ) * 2.0_DP * DelTime
    end do
    xyr_RadLFluxCor = xyr_RadLUwFluxCor - xyr_RadLDwFluxCor


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'OLRA', xyr_RadLFluxCor(:,:,kmax) )
    call HistoryAutoPut( TimeN, 'SLRA', xyr_RadLFluxCor(:,:,0)    )
    call HistoryAutoPut( TimeN, 'OSRA', xyr_RadSFlux   (:,:,kmax) )
    call HistoryAutoPut( TimeN, 'SSRA', xyr_RadSFlux   (:,:,0)    )
    call HistoryAutoPut( TimeN, 'RadLUWFLXA', xyr_RadLUwFluxCor )
    call HistoryAutoPut( TimeN, 'RadLDWFLXA', xyr_RadLDwFluxCor )
    call HistoryAutoPut( TimeN, 'RadSUWFLXA', xyr_RadSUwFlux    )
    call HistoryAutoPut( TimeN, 'RadSDWFLXA', xyr_RadSDwFlux    )


    ! ��������������
    ! Pause measurement of computation time
    !
    call TimesetClockStop( module_name )

  end subroutine RadFluxOutput
Subroutine :

rad_utils �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. NAMELIST#rad_utils_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��.

"rad_utils" module is initialized. "NAMELIST#rad_utils_nml" is loaded in this procedure.

[Source]

  subroutine RadUtilsInit
    !
    ! rad_utils �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. 
    ! NAMELIST#rad_utils_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��. 
    !
    ! "rad_utils" module is initialized. 
    ! "NAMELIST#rad_utils_nml" is loaded in this procedure. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ��������
    ! Character handling
    !
    use dc_string, only: toChar

    ! ���¡ã�¤ã���¥å�ºå��è£���
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoAddVariable

    ! NAMELIST ���¡ã�¤ã���¥å�����¢ã�������¼ã���£ã������
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid

    ! 宣�� ; 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_utils_nml/ &
!!$      & DiffFact
!!$      & DelTimeLongValue, DelTimeLongUnit, &
!!$      & DelTimeShortValue, DelTimeShortUnit, &
!!$!
!!$      & LongBandNum, &
!!$      & LongAbsorpCoefQVap, LongAbsorpCoefDryAir, &
!!$      & LongBandWeight, LongPathLengthFact, &
!!$!
!!$      & ShortBandNum, &
!!$      & ShortAbsorpCoefQVap, ShortAbsorpCoefDryAir, &
!!$      & ShortBandWeight, ShortSecScat, &
!!$      & ShortAtmosAlbedo, &
!!$!
!!$      & RstInputFile, RstOutputFile
          !
          ! �����������¤ã���¤ã��������������ç¶� "rad_utils#RadInit" 
          ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������. 
          !
          ! Refer to source codes in the initialization procedure
          ! "rad_utils#RadInit" for the default values. 
          !

    ! ���� ; Executable statement
    !

    if ( rad_utils_inited ) return


    ! �����������¤ã��¨­å®�
    ! Default values settings
    !

    ! NAMELIST ����¿è¾¼��
    ! NAMELIST is input
    !
!!$    if ( trim(namelist_filename) /= '' ) then
!!$      call FileOpen( unit_nml, &          ! (out)
!!$        & namelist_filename, mode = 'r' ) ! (in)
!!$
!!$      rewind( unit_nml )
!!$      read( unit_nml,                     & ! (in)
!!$        & nml = rad_utils_nml,            & ! (out)
!!$        & iostat = iostat_nml )             ! (out)
!!$      close( unit_nml )
!!$
!!$      call NmlutilMsg( iostat_nml, module_name ) ! (in)
!!$    end if


    ! ���¹ã�������¼ã�¿å�ºå�����������¸ã����°ç�»é��
    ! Register of variables for history data output
    !
    call HistoryAutoAddVariable( 'OLR', (/ 'lon ', 'lat ', 'time' /), 'outgoing longwave', 'W m-2' )
    call HistoryAutoAddVariable( 'SLR', (/ 'lon ', 'lat ', 'time' /), 'surface longwave', 'W m-2' )
    call HistoryAutoAddVariable( 'OSR', (/ 'lon ', 'lat ', 'time' /), 'outgoing shortwave', 'W m-2' )
    call HistoryAutoAddVariable( 'SSR', (/ 'lon ', 'lat ', 'time' /), 'surface shortwave', 'W m-2' )

    call HistoryAutoAddVariable( 'RadLUWFLX', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'upward longwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadLDWFLX', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'downward longwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadSUWFLX', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'upward shortwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadSDWFLX', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'downward shortwave flux', 'W m-2' )

    call HistoryAutoAddVariable( 'OLRB', (/ 'lon ', 'lat ', 'time' /), 'outgoing longwave', 'W m-2' )
    call HistoryAutoAddVariable( 'SLRB', (/ 'lon ', 'lat ', 'time' /), 'surface longwave', 'W m-2' )
    call HistoryAutoAddVariable( 'OSRB', (/ 'lon ', 'lat ', 'time' /), 'outgoing shortwave', 'W m-2' )
    call HistoryAutoAddVariable( 'SSRB', (/ 'lon ', 'lat ', 'time' /), 'surface shortwave', 'W m-2' )

    call HistoryAutoAddVariable( 'RadLUWFLXB', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'upward longwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadLDWFLXB', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'downward longwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadSUWFLXB', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'upward shortwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadSDWFLXB', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'downward shortwave flux', 'W m-2' )

    call HistoryAutoAddVariable( 'OLRA', (/ 'lon ', 'lat ', 'time' /), 'outgoing longwave', 'W m-2' )
    call HistoryAutoAddVariable( 'SLRA', (/ 'lon ', 'lat ', 'time' /), 'surface longwave', 'W m-2' )
    call HistoryAutoAddVariable( 'OSRA', (/ 'lon ', 'lat ', 'time' /), 'outgoing shortwave', 'W m-2' )
    call HistoryAutoAddVariable( 'SSRA', (/ 'lon ', 'lat ', 'time' /), 'surface shortwave', 'W m-2' )

    call HistoryAutoAddVariable( 'RadLUWFLXA', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'upward longwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadLDWFLXA', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'downward longwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadSUWFLXA', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'upward shortwave flux', 'W m-2' )
    call HistoryAutoAddVariable( 'RadSDWFLXA', (/ 'lon ', 'lat ', 'sigm', 'time' /), 'downward shortwave flux', 'W m-2' )

    call HistoryAutoAddVariable( 'DTempDtRadL', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'long wave radiative heating rate', 'K s-1' )
    call HistoryAutoAddVariable( 'DTempDtRadS', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'short wave radiative heating rate', 'K s-1' )


    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
!!$    call MessageNotify( 'M', module_name, 'DiffFact = %f', d = (/ DiffFact /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    rad_utils_inited = .true.

  end subroutine RadUtilsInit
rad_utils_inited
Variable :
rad_utils_inited = .false. :logical, save, public
: ����設������. Initialization flag

Private Instance methods

Subroutine :
xyr_RadLFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �·æ³¢����������. Longwave flux
xyr_RadSFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �­æ³¢ (�¥å�) ����������. Shortwave (insolation) flux
r_Height(0:kmax) :real(DP), intent(in)
: $ hat{p} $ . æ°��� (���´æ�°ã������). Air pressure (half level)
xyz_Dens(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
xyz_DTempDtRadL(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: �·æ³¢���±ç�. Temperature tendency with longwave
xyz_DTempDtRadS(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: �­æ³¢���±ç�. Temperature tendency with shortwave

������å­�³»���������¾å�������æ¸�º¦å¤�������è¨�ç®����¾ã��.

Temperature tendency with radiation is calculated for non-hydrodynamic system.

[Source]

  subroutine RadDTempDtforNHM( xyr_RadLFlux, xyr_RadSFlux, r_Height, xyz_Dens, xyz_DTempDtRadL, xyz_DTempDtRadS )
    !
    ! ������å­�³»���������¾å�������æ¸�º¦å¤�������è¨�ç®����¾ã��. 
    ! 
    ! Temperature tendency with radiation is calculated for non-hydrodynamic system. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimeN, TimesetClockStart, TimesetClockStop

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut


    ! 宣�� ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xyr_RadLFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! �·æ³¢����������. 
                              ! Longwave flux
    real(DP), intent(in):: xyr_RadSFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! �­æ³¢ (�¥å�) ����������. 
                              ! Shortwave (insolation) flux
    real(DP), intent(in):: r_Height                       (0:kmax)
                              ! $ \hat{p} $ . æ°��� (���´æ�°ã������). 
                              ! Air pressure (half level)
    real(DP), intent(in):: xyz_Dens     (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(out):: xyz_DTempDtRadL (0:imax-1, 1:jmax, 1:kmax)
                              ! �·æ³¢���±ç�. 
                              ! Temperature tendency with longwave
    real(DP), intent(out):: xyz_DTempDtRadS (0:imax-1, 1:jmax, 1:kmax)
                              ! �­æ³¢���±ç�. 
                              ! Temperature tendency with shortwave

    ! �業��
    ! Work variables
    !
    integer:: k               ! ���´æ�¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in vertical direction

    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. rad_utils_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    ! �����������
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )


    ! �¾å��·å�´ç����ç®�
    ! Calculate radiation cooling rate
    !
    do k = 1, kmax
      xyz_DTempDtRadL(:,:,k) = - ( xyr_RadLFlux(:,:,k) - xyr_RadLFlux(:,:,k-1) ) / (   r_Height      (k) -   r_Height      (k-1) ) / ( CpDry * xyz_Dens(:,:,k) )

      xyz_DTempDtRadS(:,:,k) = - ( xyr_RadSFlux(:,:,k) - xyr_RadSFlux(:,:,k-1) ) / (   r_Height      (k) -   r_Height      (k-1) ) / ( CpDry * xyz_Dens(:,:,k) )
    end do


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'DTempDtRadL' , xyz_DTempDtRadL )
    call HistoryAutoPut( TimeN, 'DTempDtRadS' , xyz_DTempDtRadS )


    ! ��������������
    ! Pause measurement of computation time
    !
    call TimesetClockStop( module_name )

  end subroutine RadDTempDtforNHM
module_name
Constant :
module_name = ‘rad_utils :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: rad_utils.f90,v 1.7 2012/10/08 12:48:45 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version