Class dynamics_physicsonly
In: dynamics/dynamics_physicsonly.f90

����������¿ã���ç®�����������å­����

A dynamics for calculation with physical processes only

Note that Japanese and English are described in parallel.

Procedures List

NAMELIST

Methods

Included Modules

gridset composition dc_types dc_message timeset dc_trace dynamics_1d_utils constants axesset namelist_util dc_iounit

Public Instance methods

Subroutine :
xyz_Exner(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
xy_SurfHeight(0:imax-1, 1:jmax) :real(DP), intent(in)
xyz_Height(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
xyz_DUDtPhy(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ left(DP{u}{t}right)^{phy} $ . å¤����� (�������) �������±è¥¿é¢���å¤���. Eastward wind tendency by external force terms (physical processes)
xyz_DVDtPhy(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ left(DP{v}{t}right)^{phy} $ . ����� (�������) ����������������. Northward wind tendency by external force terms (physicalprocesses)
xyz_DTempDtPhy(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ left(DP{T}{t}right)^{phy} $ . å¤����� (�������) ������æ¸�º¦å¤���. Temperature tendency by external force terms (physical processes)
xyzf_DQMixDtPhy(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(in)
: $ left(DP{q}{t}right)^{phy} $ . ����� (�������) �������湿��. Temperature tendency by external force terms (physical processes)
xy_PsB(0:imax-1, 1:jmax) :real(DP), intent(in )
: $ p_s $ . �°è¡¨�¢æ��� (���´æ�°ã������). Surface pressure (half level)
xyz_UB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
: $ u $ . �±è¥¿é¢���. Eastward wind
xyz_VB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
: $ v $ . �������. Northward wind
xyz_TempB(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in )
: $ T $ . æ¸�º¦ (�´æ�°ã������). Temperature (full level)
xyzf_QMixB(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(in )
: $ q $ . ��. Specific humidity
xy_PsN(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p_s (t) $ . �°è¡¨�¢æ���. Surface pressure
xyz_UN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ u (t) $ . �±è¥¿é¢���. Eastward wind
xyz_VN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ v (t) $ . �������. Northward wind
xyz_TempN(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T (t) $ . æ¸�º¦. Temperature
xyzf_QMixN(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(in)
: $ q (t) $ . ��. Specific humidity
xy_PsA(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ p_s $ . �°è¡¨�¢æ��� (���´æ�°ã������). Surface pressure (half level)
xyz_UA(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ u $ . �±è¥¿é¢���. Eastward wind
xyz_VA(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ v $ . �������. Northward wind
xyz_TempA(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ T $ . æ¸�º¦ (�´æ�°ã������). Temperature (full level)
xyzf_QMixA(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(out)
: $ q $ . ��. Specific humidity

[Source]

  subroutine DynamicsPhysicsOnly( xyz_Exner, xy_SurfHeight, xyz_Height, xyz_DUDtPhy, xyz_DVDtPhy, xyz_DTempDtPhy, xyzf_DQMixDtPhy, xy_PsB, xyz_UB, xyz_VB, xyz_TempB, xyzf_QMixB, xy_PsN, xyz_UN, xyz_VN, xyz_TempN, xyzf_QMixN, xy_PsA, xyz_UA, xyz_VA, xyz_TempA, xyzf_QMixA )

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

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

    ! �������°ç�����¼ã���£ã������
    ! Utilities for debug
    !
    use dc_trace, only: DbgMessage, BeginSub, EndSub

    ! çµ������¢ã���������¨­å®�
    ! Settings of array for atmospheric composition
    !
    use composition, only: ncmax, CompositionInqFlagAdv

    ! 1 次å��è¨�ç®�����å­�������¼ã���£ã�����£ã�¢ã�¸ã�¥ã�¼ã��
    ! Utility module for dynamics for 1-D calculation
    !
    use dynamics_1d_utils, only : Dynamics1DUtilsVerAdv

!!$    ! ������
!!$    ! Mass fixer
!!$    !
!!$    use mass_fixer, only: MassFixerColumn


    ! 宣�� ; Declaration statements
    !

    real(DP), intent(in):: xyz_Exner      (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in):: xy_SurfHeight  (0:imax-1, 1:jmax)
    real(DP), intent(in):: xyz_Height     (0:imax-1, 1:jmax, 1:kmax)

    real(DP), intent(in):: xyz_DUDtPhy    (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \left(\DP{u}{t}\right)^{phy} $ .
                              ! å¤����� (�������) �������±è¥¿é¢���å¤���.
                              ! Eastward wind tendency by external force terms (physical processes)
    real(DP), intent(in):: xyz_DVDtPhy    (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \left(\DP{v}{t}\right)^{phy} $ .
                              ! ����� (�������) ����������������.
                              ! Northward wind tendency by external force terms (physicalprocesses)
    real(DP), intent(in):: xyz_DTempDtPhy (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \left(\DP{T}{t}\right)^{phy} $ .
                              ! å¤����� (�������) ������æ¸�º¦å¤���.
                              ! Temperature tendency by external force terms (physical processes)
    real(DP), intent(in):: xyzf_DQMixDtPhy (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ \left(\DP{q}{t}\right)^{phy} $ .
                              ! ����� (�������) �������湿��.
                              ! Temperature tendency by external force terms (physical processes)
    real(DP), intent(in ):: xy_PsB(0:imax-1, 1:jmax)
                              ! $ p_s $ . �°è¡¨�¢æ��� (���´æ�°ã������). 
                              ! Surface pressure (half level)
    real(DP), intent(in ):: xyz_UB(0:imax-1, 1:jmax, 1:kmax)
                              ! $ u $ . �±è¥¿é¢���. Eastward wind
    real(DP), intent(in ):: xyz_VB(0:imax-1, 1:jmax, 1:kmax)
                              ! $ v $ . �������. Northward wind
    real(DP), intent(in ):: xyz_TempB(0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ . æ¸�º¦ (�´æ�°ã������). 
                              ! Temperature (full level)
    real(DP), intent(in ):: xyzf_QMixB(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ q $ .     ��. Specific humidity
    real(DP), intent(in):: xy_PsN    (0:imax-1, 1:jmax)
                              ! $ p_s (t) $ .   �°è¡¨�¢æ���. Surface pressure
    real(DP), intent(in):: xyz_UN   (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u (t) $ .     �±è¥¿é¢���. Eastward wind
    real(DP), intent(in):: xyz_VN   (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v (t) $ .     �������. Northward wind
    real(DP), intent(in):: xyz_TempN (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T (t) $ .     æ¸�º¦. Temperature
    real(DP), intent(in):: xyzf_QMixN(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ q (t) $ .     ��. Specific humidity
    real(DP), intent(out):: xy_PsA(0:imax-1, 1:jmax)
                              ! $ p_s $ . �°è¡¨�¢æ��� (���´æ�°ã������). 
                              ! Surface pressure (half level)
    real(DP), intent(out):: xyz_UA(0:imax-1, 1:jmax, 1:kmax)
                              ! $ u $ . �±è¥¿é¢���. Eastward wind
    real(DP), intent(out):: xyz_VA(0:imax-1, 1:jmax, 1:kmax)
                              ! $ v $ . �������. Northward wind
    real(DP), intent(out):: xyz_TempA(0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ . æ¸�º¦ (�´æ�°ã������). 
                              ! Temperature (full level)
    real(DP), intent(out):: xyzf_QMixA(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ q $ .     ��. Specific humidity


    ! �業��
    ! Work variables
    !
    real(DP) :: xyz_PotTempB     (0:imax-1, 1:jmax, 1:kmax)

    real(DP) :: xyz_W            (0:imax-1, 1:jmax, 1:kmax)

    real(DP) :: xyz_DUDtAdv      (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_DVDtAdv      (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_DPotTempDtAdv(0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyzf_DQMixDtAdv  (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)

    real(DP) :: xyz_UT           (0:imax-1, 1:jmax, 1:kmax)
    real(DP) :: xyz_VT           (0:imax-1, 1:jmax, 1:kmax)

    real(DP) :: DelTimeX2

    integer:: k
    integer:: n

    ! ���� ; Executable statement
    !

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


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


    DelTimeX2 = 2.0_DP * DelTime


    xyz_PotTempB = xyz_TempB / xyz_Exner

    if ( TimeN >= WTimeInit ) then
      if ( WHeight > 0.0_DP ) then
        do k = 1, kmax
          xyz_W(:,:,k) = WMagnitude * min( xyz_Height(:,:,k) - xy_SurfHeight, WHeight ) / WHeight
        end do
      else
        xyz_W = 0.0_DP
      end if
    else
      xyz_W = 0.0_DP
    end if

    ! 1 次å��è¨�ç®�����å­�������¼ã���£ã�����£ã�¢ã�¸ã�¥ã�¼ã��
    ! Utility module for dynamics for 1-D calculation
    !
    call Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyz_UB, xyz_DUDtAdv )
    call Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyz_VB, xyz_DVDtAdv )
    call Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyz_PotTempB, xyz_DPotTempDtAdv )
    do n = 1, ncmax
      if ( CompositionInqFlagAdv( n ) ) then
        call Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyzf_QMixB(:,:,:,n), xyzf_DQMixDtAdv(:,:,:,n) )
      else
        xyzf_DQMixDtAdv(:,:,:,n) = 0.0_DP
      end if
    end do

    xy_PsA = xy_PsB

    if ( FlagDynExp ) then
      xyz_UA = xyz_UB + ( xyz_DUDtAdv + xyz_CorPar * xyz_VB + xyz_DUDtPhy ) * DelTimeX2
      xyz_VA = xyz_VB + ( xyz_DVDtAdv - xyz_CorPar * xyz_UB + xyz_DVDtPhy ) * DelTimeX2
    else
      xyz_UT = xyz_UB + ( xyz_DUDtAdv + xyz_DUDtPhy ) * DelTimeX2
      xyz_VT = xyz_VB + ( xyz_DVDtAdv + xyz_DVDtPhy ) * DelTimeX2
      xyz_UA = (   xyz_UT + DelTimeX2 * xyz_CorPar * ( xyz_VT - VGeo + DelTimeX2 * xyz_CorPar * UGeo ) ) / ( 1.0_DP + ( DelTimeX2 * xyz_CorPar )**2 )
      xyz_VA = (   xyz_VT - DelTimeX2 * xyz_CorPar * ( xyz_UT - UGeo - DelTimeX2 * xyz_CorPar * VGeo ) ) / ( 1.0_DP + ( DelTimeX2 * xyz_CorPar )**2 )
    end if

!!$    xyz_TempA  = xyz_TempB  + xyz_DTempDtPhy  * 2.0d0 * DelTime
    xyz_TempA = xyz_PotTempB + ( xyz_DPotTempDtAdv + xyz_DTempDtPhy / xyz_Exner ) * DelTimeX2
    xyz_TempA = xyz_TempA * xyz_Exner

    xyzf_QMixA = xyzf_QMixB + ( xyzf_DQMixDtAdv + xyzf_DQMixDtPhy ) * DelTimeX2
    xyzf_QMixA = max( xyzf_QMixA, 0.0_DP )


  end subroutine DynamicsPhysicsOnly
Subroutine :

This procedure input/output NAMELIST#dynamics_physicsonly_nml .

[Source]

  subroutine DynamicsPhysicsOnlyInit

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

    ! ����å®��°è¨­å®�
    ! Physical constants settings
    !
    use constants, only: Omega
                              ! $ \Omega $ [s-1].
                              ! ��転���.
                              ! Angular velocity

    ! 座æ����¼ã�¿è¨­å®�
    ! Axes data settings
    !
    use axesset, only : y_Lat

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

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

    ! 1 次å��è¨�ç®�����å­�������¼ã���£ã�����£ã�¢ã�¸ã�¥ã�¼ã��
    ! Utility module for dynamics for 1-D calculation
    !
    use dynamics_1d_utils, only : Dynamics1DUtilsInit


    ! 宣�� ; Declaration statements
    !

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

!!$    integer:: i               ! çµ�åº��¹å�������� DO ���¼ã�����業å���
!!$                              ! Work variables for DO loop in longitude
    integer:: j               ! ç·�º¦�¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in latitude
    integer:: k


    ! NAMELIST å¤��°ç¾¤
    ! NAMELIST group name
    !
    namelist /dynamics_physicsonly_nml/ FlagDynExp, UGeo, VGeo, WMagnitude, WHeight, WTimeInit
          !
          ! �����������¤ã���¤ã��������������ç¶� "surface_flux_bulk#SurfFluxInit" 
          ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������. 
          !
          ! Refer to source codes in the initialization procedure
          ! "surface_flux_bulk#SurfFluxInit" for the default values. 
          !

    ! ���� ; Executable statement
    !


    if ( dynamics_physicsonly_inited ) return


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

    UGeo = 0.0_DP
    VGeo = 0.0_DP

    WMagnitude = 0.0_DP
    WHeight    = 0.0_DP
!!$    WMagnitude = - 0.005_DP
!!$    WHeight    =   1000.0_DP
    WTimeInit  = 0.0_DP

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

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


    allocate( xyz_CorPar(0:imax-1, 1:jmax, 1:kmax) )

    do k = 1, kmax
      do j = 1, jmax
        xyz_CorPar(:,j,k) = 2.0_DP * Omega * sin( y_Lat(j) )
      end do
    end do

    ! 1 次å��è¨�ç®�����å­�������¼ã���£ã�����£ã�¢ã�¸ã�¥ã�¼ã��
    ! Utility module for dynamics for 1-D calculation
    !
    call Dynamics1DUtilsInit


!!$    ! ���¹ã�������¼ã�¿å�ºå�����������¸ã����°ç�»é��
!!$    ! Register of variables for history data output
!!$    !
!!$    call HistoryAutoAddVariable( 'TauX', &
!!$      & (/ 'lon ', 'lat ', 'time' /), &
!!$      & 'surface stress(x)  ', 'N m-2' )
!!$
!!$    call HistoryAutoAddVariable( 'TauY', &
!!$      & (/ 'lon ', 'lat ', 'time' /), &
!!$      & 'surface stress(y)  ', 'N m-2' )
!!$
!!$    call HistoryAutoAddVariable( 'Sens', &
!!$      & (/ 'lon ', 'lat ', 'time' /), &
!!$      & 'sensible heat flux', 'W m-2' )
!!$
!!$    call HistoryAutoAddVariable( 'EVap', &
!!$      & (/ 'lon ', 'lat ', 'time' /), &
!!$      & 'latent heat flux  ', 'W m-2' )

    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '  FlagDynExp = %b', l = (/ FlagDynExp /) )
    call MessageNotify( 'M', module_name, '  UGeo = %f', d = (/ UGeo /) )
    call MessageNotify( 'M', module_name, '  VGeo = %f', d = (/ VGeo /) )
    call MessageNotify( 'M', module_name, '  WMagnitude = %f', d = (/ WMagnitude /) )
    call MessageNotify( 'M', module_name, '  WHeight    = %f', d = (/ WHeight    /) )
    call MessageNotify( 'M', module_name, '  WTimeInit  = %f', d = (/ WTimeInit  /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    dynamics_physicsonly_inited = .true.

  end subroutine DynamicsPhysicsOnlyInit

Private Instance methods

FlagDynExp
Variable :
FlagDynExp :logical , save
UGeo
Variable :
UGeo :real(DP) , save
VGeo
Variable :
VGeo :real(DP) , save
WHeight
Variable :
WHeight :real(DP) , save
WMagnitude
Variable :
WMagnitude :real(DP) , save
WTimeInit
Variable :
WTimeInit :real(DP) , save
dynamics_physicsonly_inited
Variable :
dynamics_physicsonly_inited = .false. :logical, save
: ����設������. Initialization flag
module_name
Constant :
module_name = ‘dynamics_physicsonly :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: dynamics_physicsonly.f90,v 1.7 2015/01/31 06:16:26 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version
xyz_CorPar
Variable :
xyz_CorPar(:,:,:) :real(DP), allocatable, save