Class phy_implicit_atmonly
In: phy_implicit/phy_implicit_atmonly.f90

�°è§£æ³�����������ç©��� (大æ����� / ����è¡��¢æ¸©åº��»å��å£�æ¸�º¦è¨�ç®�����)

Time integration by using implicit scheme in case without calculation of surface and soil temperature

Note that Japanese and English are described in parallel.

Procedures List

PhyImplTendency :�������������
———— :————
PhyImplTendency :Calculate tendency

Methods

Included Modules

gridset composition dc_types dc_message constants timeset phy_implicit_utils namelist_util dc_iounit dc_string

Public Instance methods

Subroutine :

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

"phy_implicit_atmonly" module is initialized. "NAMELIST#phy_implicit_atmonly_nml" is loaded in this procedure.

This procedure input/output NAMELIST#phy_implicit_atmonly_nml .

[Source]

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

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

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

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

    ! ç¨��¥å�������¡ã��
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! æ¨�æº��ºå�����ç½����. Unit number of standard output

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

    ! 宣�� ; Declaration statements
    !
    implicit none

    ! �業��
    ! Work variables
    !
    integer:: unit_nml        ! NAMELIST ���¡ã�¤ã�����¼ã���³ç���ç½����. 
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 読ã�¿è¾¼�¿æ���� IOSTAT. 
                              ! IOSTAT of NAMELIST read

    ! NAMELIST å¤��°ç¾¤
    ! NAMELIST group name
    !
    namelist /phy_implicit_atmonly_nml/ FlagPresSurfTemp, FlagPresSurfQMix
          !
          ! �����������¤ã���¤ã��������������ç¶� "phy_implicit_atmonly#PhyImplInit" 
          ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������. 
          !
          ! Refer to source codes in the initialization procedure
          ! "phy_implicit_atmonly#PhyImplInit" for the default values. 
          !

    ! ���� ; Executable statement
    !

    if ( phy_implicit_atmonly_inited ) return

    ! �����������¤ã��¨­å®�
    ! Default values settings
    !
    FlagPresSurfTemp = .false.
    FlagPresSurfQMix = .false.


    ! 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 = phy_implicit_atmonly_nml, iostat = iostat_nml )              ! (out)
      close( unit_nml )

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


    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '  FlagPresSurfTemp = %b', l = (/ FlagPresSurfTemp /) )
    call MessageNotify( 'M', module_name, '  FlagPresSurfQMix = %b', l = (/ FlagPresSurfQMix /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    phy_implicit_atmonly_inited = .true.

  end subroutine PhyImplAtmOnlyInit
Subroutine :
xyr_MomFluxX(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �±è¥¿�¹å�����������������. Eastward momentum flux
xyr_MomFluxY(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �����¹å�����������������. Northward momentum flux
xyr_HeatFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �±ã����������. Heat flux
xyrf_QMixFlux(0:imax-1, 1:jmax, 0:kmax, 1:ncmax) :real(DP), intent(in)
: �湿���������. Specific humidity flux
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ hat{p} $ . æ°��� (���´æ�°ã������). Air pressure (half level)
xyz_Exner(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: Exner �¢æ�� (�´æ�°ã������). Exner function (full level)
xyr_Exner(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: Exner �¢æ�� (���´æ�°ã������). Exner function (half level)
xyr_VirTemp(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ hat{T}_v $ . ä»�¸©åº� (���´æ�°ã������). Virtual temperature (half level)
xyz_Height(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: é«�åº� (�´æ�°ã������). Height (full level)
xyr_VelDiffCoef(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �¡æ�£ä��°ï�������. Diffusion coefficient: velocity
xyr_TempDiffCoef(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �¡æ�£ä��°ï�æ¸�º¦. Transfer coefficient: temperature
xyr_QMixDiffCoef(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �¡æ�£ä��°ï�æ¯�æ¹�. Diffusion coefficient: specific humidity
xy_SurfVelTransCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: 輸é��ä¿��°ï�������. Diffusion coefficient: velocity
xy_SurfTempTransCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: 輸é��ä¿��°ï�æ¸�º¦. Transfer coefficient: temperature
xy_SurfQVapTransCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: 輸é��ä¿��°ï�æ¯�æ¹�. Transfer coefficient: specific humidity
xyz_DUDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ DP{u}{t} $ . �±è¥¿é¢���å¤���. Eastward wind tendency
xyz_DVDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ DP{v}{t} $ . ����������. Northward wind tendency
xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ DP{T}{t} $ . æ¸�º¦å¤���. Temperature tendency
xyzf_DQMixDt(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(out)
: $ DP{q}{t} $ . è³��闋·å��æ¯�å¤���. Mass mixing ratio tendency

����å¤��������ç®���è¡����¾ã��.

Calculate tendencies.

[Source]

  subroutine PhyImplAtmOnlyTendency( xyr_MomFluxX, xyr_MomFluxY, xyr_HeatFlux, xyrf_QMixFlux, xyr_Press, xyz_Exner, xyr_Exner, xyr_VirTemp, xyz_Height, xyr_VelDiffCoef, xyr_TempDiffCoef, xyr_QMixDiffCoef, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyzf_DQMixDt )
    !
    ! ����å¤��������ç®���è¡����¾ã��. 
    !
    ! Calculate tendencies. 
    !

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

    ! ����å®��°è¨­å®�
    ! Physical constants settings
    !
    use constants, only: Grav, CpDry, LatentHeat, GasRDry
                              ! $ R $ [J kg-1 K-1]. 
                              ! 乾�大��������. 
                              ! Gas constant of air

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

    ! �°è§£æ³�����������ç©��������������¼ã����
    ! Routines for time integration with implicit scheme
    !
    use phy_implicit_utils, only : PhyImplLUDecomp3, PhyImplLUSolve3

    ! 宣�� ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xyr_MomFluxX (0:imax-1, 1:jmax, 0:kmax)
                              ! �±è¥¿�¹å�����������������. 
                              ! Eastward momentum flux
    real(DP), intent(in):: xyr_MomFluxY (0:imax-1, 1:jmax, 0:kmax)
                              ! �����¹å�����������������. 
                              ! Northward momentum flux
    real(DP), intent(in):: xyr_HeatFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! �±ã����������. 
                              ! Heat flux
    real(DP), intent(in):: xyrf_QMixFlux(0:imax-1, 1:jmax, 0:kmax, 1:ncmax)
                              ! �湿���������. 
                              ! Specific humidity flux

    real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
                              ! $ \hat{p} $ . æ°��� (���´æ�°ã������). 
                              ! Air pressure (half level)
    real(DP), intent(in):: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
                              ! Exner �¢æ�� (�´æ�°ã������). 
                              ! Exner function (full level)
    real(DP), intent(in):: xyr_Exner (0:imax-1, 1:jmax, 0:kmax)
                              ! Exner �¢æ�� (���´æ�°ã������). 
                              ! Exner function (half level)

    real(DP), intent(in):: xyr_VirTemp (0:imax-1, 1:jmax, 0:kmax)
                              ! $ \hat{T}_v $ . ä»�¸©åº� (���´æ�°ã������). 
                              ! Virtual temperature (half level)
    real(DP), intent(in):: xyz_Height (0:imax-1, 1:jmax, 1:kmax)
                              ! é«�åº� (�´æ�°ã������). 
                              ! Height (full level)

    real(DP), intent(in):: xyr_VelDiffCoef (0:imax-1, 1:jmax, 0:kmax)
                              ! �¡æ�£ä��°ï�������. 
                              ! Diffusion coefficient: velocity
    real(DP), intent(in):: xyr_TempDiffCoef (0:imax-1, 1:jmax, 0:kmax)
                              ! �¡æ�£ä��°ï�æ¸�º¦. 
                              ! Transfer coefficient: temperature
    real(DP), intent(in):: xyr_QMixDiffCoef (0:imax-1, 1:jmax, 0:kmax)
                              ! �¡æ�£ä��°ï�æ¯�æ¹�. 
                              ! Diffusion coefficient: specific humidity

    real(DP), intent(in):: xy_SurfVelTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�������. 
                              ! Diffusion coefficient: velocity
    real(DP), intent(in):: xy_SurfTempTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�æ¸�º¦. 
                              ! Transfer coefficient: temperature
    real(DP), intent(in):: xy_SurfQVapTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�æ¯�æ¹�. 
                              ! Transfer coefficient: specific humidity

    real(DP), intent(out):: xyz_DUDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{u}{t} $ . �±è¥¿é¢���å¤���. 
                              ! Eastward wind tendency
    real(DP), intent(out):: xyz_DVDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{v}{t} $ . ����������. 
                              ! Northward wind tendency
    real(DP), intent(out):: xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{T}{t} $ . æ¸�º¦å¤���. 
                              ! Temperature tendency
    real(DP), intent(out):: xyzf_DQMixDt(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ \DP{q}{t} $ . è³��闋·å��æ¯�å¤���. 
                              ! Mass mixing ratio tendency

    ! �業��
    ! Work variables
    !

    real(DP) :: xyr_VelTransCoef (0:imax-1, 1:jmax, 0:kmax)
                              ! 輸é��ä¿��°ï�������. 
                              ! Transfer coefficient: velocity
    real(DP) :: xyr_TempTransCoef (0:imax-1, 1:jmax, 0:kmax)
                              ! 輸é��ä¿��°ï�æ¸�º¦. 
                              ! Transfer coefficient: temperature
    real(DP) :: xyr_QMixTransCoef(0:imax-1, 1:jmax, 0:kmax)
                              ! 輸é��ä¿��°ï�è³���. 
                              ! Transfer coefficient: mass of constituents

    real(DP):: xyza_UVMtx  (0:imax-1, 1:jmax, 1:kmax, -1:1)
                              ! ��åº��°è§£è¡���. 
                              ! Implicit matrix about velocity 
    real(DP):: xyra_TempMtx(0:imax-1, 1:jmax, 1:kmax, -1:1)
                              ! æ¸�º¦�°è§£è¡���. 
                              ! Implicit matrix about temperature
    real(DP):: xyza_QMixMtx(0:imax-1, 1:jmax, 1:kmax, -1:1)
                              ! è³��闋·å��æ¯��°è§£è¡���. 
                              ! Implicit matrix about mass mixing ratio

    real(DP):: xyza_UVLUMtx    (0:imax-1, 1:jmax, 1:kmax,-1:1)
                              ! LU ���. 
                              ! LU matrix
    real(DP):: xyza_QMixLUMtx  (0:imax-1, 1:jmax, 1:kmax, -1:1)
                              ! LU ���.
                              ! LU matrix
    real(DP):: xyz_DelQMixLUVec(0:imax-1, 1:jmax, 1:kmax)
                              ! $ q $ ���������.
                              ! Tendency of $ q $

    real(DP):: xyaa_TempLUMtx  (0:imax-1, 1:jmax, 1:kmax, -1:1)
                              ! LU ���.
                              ! LU matrix
    real(DP):: xya_DelTempLUVec(0:imax-1, 1:jmax, 1:kmax)
                              ! $ T, Tg $ ���������.
                              ! Tendency of $ T $ and $ Tg |


!!$    integer:: i               ! çµ�åº��¹å�������� DO ���¼ã�����業å���
!!$                              ! Work variables for DO loop in longitude
!!$    integer:: j               ! ç·�º¦�¹å�������� DO ���¼ã�����業å���
!!$                              ! Work variables for DO loop in latitude
    integer:: k               ! ���´æ�¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in vertical direction
!!$    integer:: l               ! è¡����� DO ���¼ã�����業å���
!!$                              ! Work variables for DO loop of matrices
    integer:: n               ! çµ����¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in dimension of constituents

    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. phy_implicit_atmonly_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 transfer coefficient
    !
    xyr_VelTransCoef (:,:,0)    = 0.0_DP
    xyr_VelTransCoef (:,:,kmax) = 0.0_DP
    xyr_TempTransCoef(:,:,0)    = 0.0_DP
    xyr_TempTransCoef(:,:,kmax) = 0.0_DP
    xyr_QMixTransCoef(:,:,0)    = 0.0_DP
    xyr_QMixTransCoef(:,:,kmax) = 0.0_DP

    do k = 1, kmax-1
      xyr_VelTransCoef(:,:,k) = xyr_VelDiffCoef(:,:,k) * xyr_Press(:,:,k) / ( GasRDry * xyr_VirTemp(:,:,k) ) / ( xyz_Height(:,:,k+1) - xyz_Height(:,:,k) )

      xyr_TempTransCoef(:,:,k) = xyr_TempDiffCoef(:,:,k) * xyr_Press(:,:,k) / ( GasRDry * xyr_VirTemp(:,:,k) ) / ( xyz_Height(:,:,k+1) - xyz_Height(:,:,k) )

      xyr_QMixTransCoef(:,:,k) = xyr_QMixDiffCoef(:,:,k) * xyr_Press(:,:,k) / ( GasRDry * xyr_VirTemp(:,:,k) ) / ( xyz_Height(:,:,k+1) - xyz_Height(:,:,k) )
    end do


    ! �°è§£æ³������������ä½���
    ! Create matrices for implicit scheme
    !

    ! ���´æ�¡æ�£ã�¹ã�­ã�¼ã����¼¸��ä¿��°ã�����°è§£è¡������ç®� (��åº�)
    ! Calculate implicit matrices from transfer coefficient of vertical diffusion scheme (velocity)
    !
    k = 1
    xyza_UVMtx  (:,:,k,-1) = 0.0_DP
    xyza_UVMtx  (:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + xy_SurfVelTransCoef(:,:) + xyr_VelTransCoef(:,:,k  )
    xyza_UVMtx  (:,:,k, 1) = - xyr_VelTransCoef(:,:,k)

    do k = 2, kmax-1
      xyza_UVMtx  (:,:,k,-1) = - xyr_VelTransCoef(:,:,k-1)
      xyza_UVMtx  (:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + xyr_VelTransCoef(:,:,k-1) + xyr_VelTransCoef(:,:,k  )
      xyza_UVMtx  (:,:,k, 1) = - xyr_VelTransCoef(:,:,k)
    end do

    k = kmax
    xyza_UVMtx  (:,:,k,-1) = - xyr_VelTransCoef(:,:,k-1)
    xyza_UVMtx  (:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + xyr_VelTransCoef(:,:,k-1)
    xyza_UVMtx  (:,:,k, 1) = 0.0_DP


    ! ���´æ�¡æ�£ã�¹ã�­ã�¼ã����¼¸��ä¿��°ã�����°è§£è¡������ç®� (æ¸�º¦)
    ! Calculate implicit matrices from transfer coefficient of vertical diffusion scheme (temperature)
    !
    k = 1
    xyra_TempMtx(:,:,k,-1) = 0.0_DP
    if ( FlagPresSurfTemp ) then
      ! Prescribe surface temperature
      xyra_TempMtx(:,:,k, 0) = - CpDry * ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k  ) * xy_SurfTempTransCoef(:,:) + CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k  )
    else
      ! Prescribe surface flux
      xyra_TempMtx(:,:,k, 0) = - CpDry * ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k  )
    end if
    xyra_TempMtx(:,:,k, 1) = - CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k+1) * xyr_TempTransCoef(:,:,k  )

    do k = 2, kmax-1
      xyra_TempMtx(:,:,k,-1) = - CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k-1) * xyr_TempTransCoef(:,:,k-1)
      xyra_TempMtx(:,:,k, 0) = - CpDry * ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k-1) + CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k  )
      xyra_TempMtx(:,:,k, 1) = - CpDry * xyr_Exner(:,:,k  ) / xyz_Exner(:,:,k+1) * xyr_TempTransCoef(:,:,k  )
    end do

    k = kmax
    xyra_TempMtx(:,:,k,-1) = - CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k-1) * xyr_TempTransCoef(:,:,k-1)
    xyra_TempMtx(:,:,k, 0) = - CpDry * ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + CpDry * xyr_Exner(:,:,k-1) / xyz_Exner(:,:,k  ) * xyr_TempTransCoef(:,:,k-1)
    xyra_TempMtx(:,:,k, 1) = 0.0_DP



    ! ���´æ�¡æ�£ã�¹ã�­ã�¼ã����¼¸��ä¿��°ã�����°è§£è¡������ç®� (æ¯�æ¹�)
    ! Calculate implicit matrices from transfer coefficient of vertical diffusion scheme (specific humidity)
    !

    k = 1
    xyza_QMixMtx(:,:,k,-1) = 0.0_DP
    if ( FlagPresSurfQMix ) then
      ! Prescribe surface mixing ratio
      xyza_QMixMtx(:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + xy_SurfQVapTransCoef(:,:) + xyr_QMixTransCoef(:,:,k  )
    else
      ! Prescribe surface flux
      xyza_QMixMtx(:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + xyr_QMixTransCoef(:,:,k  )
    end if
    xyza_QMixMtx(:,:,k, 1) = - xyr_QMixTransCoef(:,:,k  )

    do k = 2, kmax-1
      xyza_QMixMtx(:,:,k,-1) = - xyr_QMixTransCoef(:,:,k-1)
      xyza_QMixMtx(:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + xyr_QMixTransCoef(:,:,k-1) + xyr_QMixTransCoef(:,:,k  )
      xyza_QMixMtx(:,:,k, 1) = - xyr_QMixTransCoef(:,:,k  )
    end do

    k = kmax
    xyza_QMixMtx(:,:,k,-1) = - xyr_QMixTransCoef(:,:,k-1)
    xyza_QMixMtx(:,:,k, 0) = - ( xyr_Press(:,:,k) - xyr_Press(:,:,k-1) ) / Grav / ( 2.0_DP * DelTime ) + xyr_QMixTransCoef(:,:,k-1)
    xyza_QMixMtx(:,:,k, 1) = 0.0_DP




    ! �±è¥¿é¢���, ����é¢������ç®�
    ! Calculate eastward and northward wind
    !
    xyza_UVLUMtx = xyza_UVMtx

    call PhyImplLUDecomp3( xyza_UVLUMtx, imax * jmax, kmax ) ! (in)

    do k = 1, kmax
      xyz_DUDt(:,:,k) = - ( xyr_MomFluxX(:,:,k) - xyr_MomFluxX(:,:,k-1) )
      xyz_DVDt(:,:,k) = - ( xyr_MomFluxY(:,:,k) - xyr_MomFluxY(:,:,k-1) )
    end do

    call PhyImplLUSolve3( xyz_DUDt, xyza_UVLUMtx, 1, imax * jmax, kmax ) ! (in)

    call PhyImplLUSolve3( xyz_DVDt, xyza_UVLUMtx, 1, imax * jmax, kmax ) ! (in)

    do k = 1, kmax
      xyz_DUDt(:,:,k) = xyz_DUDt(:,:,k) / ( 2.0_DP * DelTime )
      xyz_DVDt(:,:,k) = xyz_DVDt(:,:,k) / ( 2.0_DP * DelTime )
    end do


    ! æ¸�º¦���ç®�
    ! Calculate temperature
    !
    xyaa_TempLUMtx = xyra_TempMtx

    call PhyImplLUDecomp3( xyaa_TempLUMtx, imax * jmax, kmax )

    do k = 1, kmax
      xya_DelTempLUVec(:,:,k) = - ( xyr_HeatFlux(:,:,k) - xyr_HeatFlux(:,:,k-1) )
    end do

    call PhyImplLUSolve3( xya_DelTempLUVec, xyaa_TempLUMtx, 1, imax * jmax , kmax )

    xyz_DTempDt = xya_DelTempLUVec / ( 2.0_DP * DelTime )


    ! �湿���
    ! Calculate specific humidity
    !
    xyza_QMixLUMtx = xyza_QMixMtx

    call PhyImplLUDecomp3( xyza_QMixLUMtx, imax * jmax, kmax )

    do n = 1, ncmax
      do k = 1, kmax
        xyz_DelQMixLUVec(:,:,k) = - ( xyrf_QMixFlux(:,:,k,n) - xyrf_QMixFlux(:,:,k-1,n) )
      end do

      call PhyImplLUSolve3( xyz_DelQMixLUVec, xyza_QMixLUMtx, 1, imax * jmax , kmax )

      xyzf_DQMixDt(:,:,:,n) = xyz_DelQMixLUVec(:,:,:) / ( 2.0_DP * DelTime )
    end do


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

  end subroutine PhyImplAtmOnlyTendency

Private Instance methods

FlagPresSurfQMix
Variable :
FlagPresSurfQMix :logical, save
FlagPresSurfTemp
Variable :
FlagPresSurfTemp :logical, save
module_name
Constant :
module_name = ‘phy_implicit_atmonly :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
phy_implicit_atmonly_inited
Variable :
phy_implicit_atmonly_inited = .false. :logical, save
: ����設������. Initialization flag
version
Constant :
version = ’$Name: $’ // ’$Id: phy_implicit_atmonly.f90,v 1.5 2015/01/29 12:05:01 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version