Class phy_implicit_utils
In: phy_implicit/phy_implicit_utils.f90

�°è§£æ³�����������ç©��������������¼ã����

Routines for time integration with implicit scheme

Note that Japanese and English are described in parallel.

Procedures List

PhyImplEvalRadLFluxA :�·æ³¢���������¹è�æ­�
———— :————
PhyImplEvalRadLFluxA :Longwave flux correction

Methods

Included Modules

gridset composition dc_types dc_message timeset namelist_util dc_iounit dc_string gtool_historyauto

Public Instance methods

Subroutine :
xyr_RadLFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �·æ³¢����������. Longwave flux
xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ DP{T}{t} $ . æ¸�º¦å¤���. Temperature tendency
xy_DSurfTempDt(0:imax-1, 1:jmax) :real(DP), intent(in)
: �°è¡¨�¢æ¸©åº������. Surface temperature tendency
xyra_DelRadLFlux(0:imax-1, 1:jmax, 0:kmax, 0:1) :real(DP), intent(in)
: �·æ³¢�°è¡¨æ¸�º¦å¤���. Surface temperature tendency with longwave
xyr_RadLFluxA(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(out)
: $ t-\Delta t $ ��������å¤����������� ç®��ºã������ $ t+Delta t $ �������� �·æ³¢����������.

Longwave flux at $ t+Delta t $ calculated from the tendency at $ t-\Delta t $ .

$ t-\Delta t $ ��������å¤�����������, $ t+Delta t $ ���·æ³¢���������� (xyr_RadLFluxA) ��ç®��ºã���¾ã��.

Evaluate longwave flux at $ t+Delta t $ (xyr_RadLFluxA) from the tendency at $ t-\Delta t $ .

[Source]

  subroutine PhyImplEvalRadLFluxA( xyr_RadLFlux, xyz_DTempDt, xy_DSurfTempDt, xyra_DelRadLFlux, xyr_RadLFluxA )
    !
    ! $ t-\Delta t $ �������������������, 
    ! $ t+\Delta t $ ���·æ³¢���������� (xyr_RadLFluxA) ��ç®��ºã���¾ã��. 
    ! 
    ! Evaluate longwave flux at $ t+\Delta t $ (xyr_RadLFluxA) 
    ! from the tendency at $ t-\Delta t $ . 
    !

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

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

    ! 宣�� ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xyr_RadLFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! �·æ³¢����������. 
                              ! Longwave flux
    real(DP), intent(in):: xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{T}{t} $ . æ¸�º¦å¤���. 
                              ! Temperature tendency
    real(DP), intent(in):: xy_DSurfTempDt (0:imax-1, 1:jmax)
                              ! �°è¡¨�¢æ¸©åº������. 
                              ! Surface temperature tendency
    real(DP), intent(in):: xyra_DelRadLFlux (0:imax-1, 1:jmax, 0:kmax,  0:1)
                              ! �·æ³¢�°è¡¨æ¸�º¦å¤���. 
                              ! Surface temperature tendency with longwave
    real(DP), intent(out):: xyr_RadLFluxA (0:imax-1, 1:jmax, 0:kmax)
                              ! $ t-\Delta t $ �������������������
                              ! ç®��ºã������ $ t+\Delta t $ ��������
                              ! �·æ³¢����������. 
                              !
                              ! Longwave flux at $ t+\Delta t $ 
                              ! calculated from the tendency at 
                              ! $ t-\Delta t $ . 

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

    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. phy_implicit_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 )


    ! $ t+\Delta t $ ���·æ³¢���������� (xyr_RadLFluxA) ��ç®���
    ! Evaluate longwave flux at $ t+\Delta t $ (xyr_RadLFluxA)
    !
    do k = 0, kmax
      xyr_RadLFluxA(:,:,k) = xyr_RadLFlux(:,:,k) + (   xy_DSurfTempDt     * xyra_DelRadLFlux(:,:,k,0) + xyz_DTempDt(:,:,1) * xyra_DelRadLFlux(:,:,k,1) ) * 2.0_DP * DelTime
    end do

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

  end subroutine PhyImplEvalRadLFluxA
Subroutine :
jna_LUMtx(JDim, NDim, -1:1) :real(DP), intent(inout)
: LU ���. LU matrix
JDim :integer, intent(in)
NDim :integer, intent(in)

3 ��対è�è¡����� LU ��解ã��è¡����¾ã��.

LU decomposition of triple diagonal matrix.

[Source]

  subroutine PhyImplLUDecomp3( jna_LUMtx, JDim, NDim )
    !
    ! 3 ��対è�è¡����� LU ��解ã��è¡����¾ã��. 
    !
    ! LU decomposition of triple diagonal matrix.
    !

    ! 宣�� ; Declaration statements
    !
    implicit none
    integer, intent(in):: JDim
    integer, intent(in):: NDim
    real(DP), intent(inout):: jna_LUMtx(JDim, NDim, -1:1)
                              ! LU ���. 
                              ! LU matrix

    ! �業��
    ! Work variables
    ! 
    integer:: j, n            ! DO ���¼ã�����業å���
                              ! Work variables for DO loop

    ! ���� ; Executable statement
    !

    ! LU ���
    ! LU decomposition
    !
    do j = 1, JDim
      jna_LUMtx(j,1,1) = jna_LUMtx(j,1,1) / jna_LUMtx(j,1,0)
    end do

    do n = 2, NDim-1
      do j = 1, JDim
        jna_LUMtx(j,n,0)  =   jna_LUMtx(j,n,0) - jna_LUMtx(j,n,-1) * jna_LUMtx(j,n-1,1)

        jna_LUMtx(j,n,1)  =   jna_LUMtx(j,n,1) / jna_LUMtx(j,n,0)
      end do
    end do

    do j = 1, JDim
      jna_LUMtx(j,NDim,0) =   jna_LUMtx(j,NDim, 0) - jna_LUMtx(j,NDim,-1) * jna_LUMtx(j,NDim-1,1)
    end do

  end subroutine PhyImplLUDecomp3
Subroutine :
ijn_Vector(IDim, JDim, NDim) :real(DP), intent(inout)
: �³è¾º�������� / è§�. Right-hand side vector / solution
jna_LUMtx(JDim, NDim, -1:1) :real(DP), intent(in)
: LU ���. LU matrix
IDim :integer, intent(in)
JDim :integer, intent(in)
NDim :integer, intent(in)

LU ��解ã������解ã���ç®� (3��対è�è¡�����) ��è¡����¾ã��.

Solve with LU decomposition (For triple diagonal matrix).

[Source]

  subroutine PhyImplLUSolve3( ijn_Vector, jna_LUMtx, IDim, JDim, NDim )
    !
    ! LU ��解ã������解ã���ç®� (3��対è�è¡�����) ��è¡����¾ã��.
    !
    ! Solve with LU decomposition (For triple diagonal matrix). 
    !

    ! 宣�� ; Declaration statements
    !
    implicit none
    integer, intent(in):: IDim
    integer, intent(in):: JDim
    integer, intent(in):: NDim
    real(DP), intent(in):: jna_LUMtx(JDim, NDim, -1:1)
                              ! LU ���. 
                              ! LU matrix
    real(DP), intent(inout):: ijn_Vector(IDim, JDim, NDim)
                              ! �³è¾º�������� / è§�. 
                              ! Right-hand side vector / solution

    ! �業��
    ! Work variables
    ! 
    integer:: i, j, n         ! DO ���¼ã�����業å���
                              ! Work variables for DO loop

    ! ���� ; Executable statement
    !

    ! ���²ä»£��
    ! Forward substitution
    !
    do i = 1, IDim
      do j = 1, JDim
        ijn_Vector(i,j,1) = ijn_Vector(i,j,1) / jna_LUMtx(j,1,0)
      end do
    end do

    do n = 2, NDim
      do i = 1, IDim
        do j = 1, JDim
          ijn_Vector(i,j,n) = (   ijn_Vector(i,j,n) - ijn_Vector(i,j,n-1) * jna_LUMtx(j,n,-1) ) / jna_LUMtx(j,n,0)
        end do
      end do
    end do

    ! ���代�
    ! Backward substitution
    !
    do n = NDim-1, 1, -1
      do i = 1, IDim
        do j = 1, JDim
          ijn_Vector(i,j,n) =   ijn_Vector(i,j,n) - ijn_Vector(i,j,n+1) * jna_LUMtx(j,n,1)
        end do
      end do
    end do

  end subroutine PhyImplLUSolve3
Subroutine :

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

"phy_implicit_utils" module is initialized. "NAMELIST#phy_implicit_utils_nml" is loaded in this procedure.

[Source]

  subroutine PhyImplUtilsInit
    !
    ! phy_implicit_utils �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. 
    ! NAMELIST#phy_implicit_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��. 
    !
    ! "phy_implicit_utils" module is initialized. 
    ! "NAMELIST#phy_implicit_utils_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

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

    ! 宣�� ; 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_nml/
!!$          !
!!$          ! �����������¤ã���¤ã��������������ç¶� "phy_implicit#PhyImplInit" 
!!$          ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������. 
!!$          !
!!$          ! Refer to source codes in the initialization procedure
!!$          ! "phy_implicit#PhyImplInit" for the default values. 
!!$          !

    ! ���� ; Executable statement
    !

    if ( phy_implicit_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 = phy_implicit_nml, &  ! (out)
!!$        & 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, '-- version = %c', c1 = trim(version) )

    phy_implicit_utils_inited = .true.

  end subroutine PhyImplUtilsInit

Private Instance methods

module_name
Constant :
module_name = ‘phy_implicit_utils :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
phy_implicit_utils_inited
Variable :
phy_implicit_utils_inited = .false. :logical, save
: ����設������. Initialization flag
version
Constant :
version = ’$Name: $’ // ’$Id: phy_implicit_utils.f90,v 1.3 2014/05/07 09:39:20 murashin Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version