Class dynamics_1d_utils
In: dynamics/dynamics_1d_utils.f90

1 次元計算用力学過程ユーティリティモジュール

Utility module for dynamics for 1-D calculation

Note that Japanese and English are described in parallel.

Methods

Included Modules

dc_types gridset dc_message

Public Instance methods

Subroutine :

[Source]

  subroutine Dynamics1DUtilsInit

    ! 文字列操作
    ! Character handling
    !
!!$    use dc_string, only: toChar

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

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


    ! 宣言文 ; 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 /set_TWPICE_profile_nml/ &
!!$      & InFileNameSounding, &
!!$      & InFileNameForcing
          !
          ! デフォルト値については初期化手続 "set_GATE_profile#SetGATEProfileInit"
          ! のソースコードを参照のこと.
          !
          ! Refer to source codes in the initialization procedure
          ! "set_GATE_profile#SetGATEProfileInit" for the default values.
          !

    ! デフォルト値の設定
    ! 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 = set_TWPICE_profile_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, 'InFileNameSounding = %c', c1 = trim(InFileNameSounding) )
!!$    call MessageNotify( 'M', module_name, 'InFileNameForcing  = %c', c1 = trim(InFileNameForcing ) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )


    dynamics_1d_utils_inited = .true.


  end subroutine Dynamics1DUtilsInit
Subroutine :
xyz_W(0:imax-1,1:jmax,1:kmax) :real(DP), intent(in )
xyz_Height(0:imax-1,1:jmax,1:kmax) :real(DP), intent(in )
xyz_Array(0:imax-1,1:jmax,1:kmax) :real(DP), intent(in )
xyz_VAdv(0:imax-1,1:jmax,1:kmax) :real(DP), intent(out)

[Source]

  subroutine Dynamics1DUtilsVerAdv( xyz_W, xyz_Height, xyz_Array, xyz_VAdv )

    ! モジュール引用 ; USE statements
    !

    real(DP), intent(in ) :: xyz_W     (0:imax-1,1:jmax,1:kmax)
    real(DP), intent(in ) :: xyz_Height(0:imax-1,1:jmax,1:kmax)
    real(DP), intent(in ) :: xyz_Array (0:imax-1,1:jmax,1:kmax)
    real(DP), intent(out) :: xyz_VAdv  (0:imax-1,1:jmax,1:kmax)


    !
    ! local variables
    !
    integer :: i
    integer :: j
    integer :: k
    integer :: kp
    integer :: kn


    ! 初期化確認
    ! Initialization check
    !
    if ( .not. dynamics_1d_utils_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    do k = 1, kmax

      do j = 1, jmax
        do i = 0, imax-1

!!$          kp = max( k - 1, 1    )
!!$          kn = min( k + 1, kmax )
          if ( xyz_W(i,j,k) >= 0.0_DP ) then
            kp = max( k - 1, 1    )
            kn = kp + 1
          else
            kn = min( k + 1, kmax )
            kp = kn - 1
          end if
          xyz_VAdv(i,j,k) = - xyz_W(i,j,k) * ( xyz_Array (i,j,kn) - xyz_Array (i,j,kp) ) / ( xyz_Height(i,j,kn) - xyz_Height(i,j,kp) )
        end do
      end do

    end do

  end subroutine Dynamics1DUtilsVerAdv
Subroutine :
NLev :integer , intent(in )
z_Press(1:NLev) :real(DP), intent(in )
z_Array(1:NLev) :real(DP), intent(in )
xyz_Press(0:imax-1,1:jmax,1:kmax) :real(DP), intent(in )
xyz_Array(0:imax-1,1:jmax,1:kmax) :real(DP), intent(out)

[Source]

  subroutine Dynamics1DUtilsVerInterp( NLev, z_Press, z_Array, xyz_Press, xyz_Array )

    integer , intent(in ) :: NLev
    real(DP), intent(in ) :: z_Press  (1:NLev)
    real(DP), intent(in ) :: z_Array  (1:NLev)
    real(DP), intent(in ) :: xyz_Press(0:imax-1,1:jmax,1:kmax)
    real(DP), intent(out) :: xyz_Array(0:imax-1,1:jmax,1:kmax)


    !
    ! local variables
    !
    integer  :: k
    integer  :: kk


    ! 初期化確認
    ! Initiarization check
    !
    if ( .not. dynamics_1d_utils_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    do k = 1, kmax
      if( xyz_Press(0,1,k) <= z_Press(NLev) ) then
        xyz_Array(0,1,k) = z_Array(NLev)
      else
        search_loop : do kk = 2, NLev
          if( z_Press( kk ) < xyz_Press(0,1,k) ) exit search_loop
        end do search_loop
        if( kk > NLev ) stop 'Unexpected error in setting vertical profile'
        xyz_Array(0,1,k) = ( z_Array( kk ) - z_Array( kk-1 ) ) / ( log( z_Press( kk )    / z_Press( kk-1 ) ) ) * ( log( xyz_Press(0,1,k) / z_Press( kk-1 ) ) ) + z_Array( kk-1 )
      end if
    end do

    do k = 1, kmax
      xyz_Array(:,:,k) = xyz_Array(0,1,k)
    end do


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

Private Instance methods

Subroutine :

[Source]

  subroutine Dynamics1DUtilsFinalize


    ! 宣言文 ; Declaration statements
    !



    dynamics_1d_utils_inited = .false.


  end subroutine Dynamics1DUtilsFinalize
module_name
Constant :
module_name = ‘dynamics_1d_utils :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: dynamics_1d_utils.f90,v 1.1 2015/01/31 06:16:26 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version