Class initial_data
In: prepare_data/initial_data_primitive.F90

初期値データ提供

Prepare initial data

初期値データのサンプルを提供します.

現在は以下のデータを提供します.

  • Small Disturbance of Temperature
    • 風速: 0 [m/s], 地表面気圧: 1.0e+5 [Pa],
    • 温度: 250 [K] に微小擾乱を加えたもの
  • [AGCM 5.3]{www.gfd-dennou.org/library/agcm5} Default
    • 風速: 0 [m/s], 地表面気圧: 1.0e+5 [Pa],
    • 温度: 250 [K] に微小擾乱を加えたもの

Prepare sample data of initial data (restart data)

Now, following data are provided.

  • Small Disturbance of Temperature
    • Velocity: 0 [m/s], Surface pressure: 1.0e+5 [Pa].
    • Temperature: 250 [K] and perturbation
  • [AGCM 5.3]{www.gfd-dennou.org/library/agcm5} Default
    • Velocity: 0 [m/s], Surface pressure: 1.0e+5 [Pa].
    • Temperature: 250 [K] and perturbation

Procedures List

SetInitData :初期値データ取得
———— :————
SetInitData :Get initial data

NAMELIST

NAMELIST#initial_data_nml

Methods

Included Modules

gridset dc_types dc_message axesset dc_string namelist_util dc_iounit constants

Public Instance methods

Pattern
Variable :
Pattern :character(STRING), save, public
: 初期値データのパターン. 以下のパターンを選択可能.

Initial data pattern Available patterns are as follows.

  • "Small Disturbance of Temperature" (default value)
  • "AGCM 5.3 Default"
  • "Sugiyama et al. (2008)"
PsAvr
Variable :
PsAvr :real(DP), save, public
: $ bar{p_s} $ . 地表面気圧平均値. Mean surface pressure
Subroutine :
xyz_U(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ u $ . 東西風速. Eastward wind
xyz_V(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ v $ . 南北風速. Northward wind
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ T $ . 温度. Temperature
xy_Ps(0:imax-1, 1:jmax) :real(DP), intent(out)
: $ p_s $ . 地表面気圧. Surface pressure

初期値データのサンプルを提供します.

Prepare sample data of initial data

[Source]

  subroutine SetInitData( xyz_U, xyz_V, xyz_Temp, xy_Ps )
    !
    ! 初期値データのサンプルを提供します. 
    ! 
    ! Prepare sample data of initial data
    !

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

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: x_Lon, y_Lat, z_Sigma
                              ! $ \sigma $ レベル (整数). 
                              ! Full $ \sigma $ level

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

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(out):: xyz_U  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u $ .   東西風速. Eastward wind
    real(DP), intent(out):: xyz_V  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v $ .   南北風速. Northward wind
    real(DP), intent(out):: xyz_Temp  (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ .   温度. Temperature
    real(DP), intent(out):: xy_Ps (0:imax-1, 1:jmax)
                              ! $ p_s $ . 地表面気圧. Surface pressure

    ! 作業変数
    ! Work variables
    !
    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

    ! 実行文 ; Executable statement

    if ( .not. initial_data_inited ) call InitDataInit

    ! 微小な温度擾乱のある静止場
    ! Stationary field with small disturbance of temperature
    !
    select case ( LChar( trim(Pattern) ) )
    case ( 'small disturbance of temperature' )
      xyz_U    = 0.0_DP
      xyz_V    = 0.0_DP
      xyz_Temp = TempAvr
      xy_Ps    = PsAvr

      ! 温度に擾乱を与える
      ! Add perturbation to temperature
      !
      do k = 1, kmax
        do j = 1, jmax
          do i = 0, imax - 1
            xyz_Temp(i,j,k) = xyz_Temp(i,j,k) + 0.1_DP * sin ( x_Lon(i) * y_Lat(j) ) - 0.1_DP * ( 1.0_DP - z_Sigma(k) )
          end do
        end do
      end do

      ! 東西風速を与える
      ! Add eastward wind
      !
      do j = 1, jmax
        xyz_U(:,j,:) = Ueq * cos(y_Lat(j))
      end do

    ! AGCM5.3 のデフォルト初期値
    ! AGCM5.3 default initial values
    !
    case ( 'agcm 5.3 default' )
      xyz_U    = 0.0_DP
      xyz_V    = 0.0_DP
      xyz_Temp = TempAvr
      xy_Ps    = PsAvr

      ! 温度に擾乱を与える
      ! Add perturbation to temperature
      !
      do k = 1, kmax
        do j = 1, jmax
          do i = 0, imax - 1
            xyz_Temp(i,j,k) = xyz_Temp(i,j,k) + 0.1_DP * sin ( real( ( i + 1 ) * ( jmax - j + 1 ) * ( kmax - k ), DP ) / real( imax * jmax * kmax, DP ) * 10.0_DP )
          end do
        end do
      end do

      ! 東西風速を与える
      ! Add eastward wind
      !
      do j = 1, jmax
        xyz_U(:,j,:) = Ueq * cos(y_Lat(j))
      end do
    end select

  end subroutine SetInitData
TempAvr
Variable :
TempAvr :real(DP), save, public
: $ bar{T} $ . 温度平均値. Mean temperature
Ueq
Variable :
Ueq :real(DP), save, public
: $ u_{eq} $ . 赤道上の東西風速. Eastward wind on the equator
initial_data_inited
Variable :
initial_data_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag

Private Instance methods

Subroutine :

依存モジュールの初期化チェック

Check initialization of dependency modules

[Source]

  subroutine InitCheck
    !
    ! 依存モジュールの初期化チェック
    !
    ! Check initialization of dependency modules

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

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

    ! 格子点設定
    ! Grid points settings
    !
    use gridset, only: gridset_inited

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: constants_inited

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: axesset_inited


    ! 実行文 ; Executable statement

    if ( .not. namelist_util_inited ) call MessageNotify( 'E', module_name, '"namelist_util" module is not initialized.' )

    if ( .not. gridset_inited ) call MessageNotify( 'E', module_name, '"gridset" module is not initialized.' )

    if ( .not. constants_inited ) call MessageNotify( 'E', module_name, '"constants" module is not initialized.' )

    if ( .not. axesset_inited ) call MessageNotify( 'E', module_name, '"axesset" module is not initialized.' )

  end subroutine InitCheck
Subroutine :

This procedure input/output NAMELIST#initial_data_nml .

[Source]

  subroutine InitDataInit

    ! モジュール引用 ; 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

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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    integer:: unit_nml        ! NAMELIST ファイルオープン用装置番号. 
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 読み込み時の IOSTAT. 
                              ! IOSTAT of NAMELIST read

    ! NAMELIST 変数群
    ! NAMELIST group name
    !
    namelist /initial_data_nml/ Pattern, TempAvr, PsAvr, Ueq
          !
          ! デフォルト値については初期化手続 "initial_data#InitDataInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "initial_data#InitDataInit" for the default values. 
          !


    ! 実行文 ; Executable statement

    if ( initial_data_inited ) return
    call InitCheck

    ! デフォルト値の設定 (まずは Pattern のみ)
    ! Default values settings (At first, "Pattern" only)
    !
    Pattern = 'Small Disturbance of Temperature'
    !Pattern = 'AGCM 5.3 Default'

    ! NAMELIST の読み込み (まずは Pattern のみ)
    ! NAMELIST is input (At first, "Pattern" only)
    !
    if ( trim(namelist_filename) /= '' ) then
      call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in)

      rewind( unit_nml )
      read( unit_nml, nml = initial_data_nml, iostat = iostat_nml )     ! (out)
      close( unit_nml )

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

    ! デフォルト値の設定
    ! Default values settings
    !
    select case ( LChar( trim(Pattern) ) )
    case ( 'small disturbance of temperature' )
      TempAvr = 250.0_DP
      PsAvr   = 1.0e+5_DP
      Ueq     = 0.0_DP
    case ( 'agcm 5.3 default' )
      TempAvr = 250.0_DP
      PsAvr   = 1.0e+5_DP
      Ueq     = 0.0_DP
    case default
      call MessageNotify( 'E', module_name, 'Pattern=<%c> is invalid.', c1 = trim(Pattern) )
    end select

    ! 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 = initial_data_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, '  Pattern = %c', c1 = trim(Pattern) )
    call MessageNotify( 'M', module_name, '  TempAvr = %f', d = (/ TempAvr  /) )
    call MessageNotify( 'M', module_name, '  PsAvr   = %f', d = (/ PsAvr  /) )
    call MessageNotify( 'M', module_name, '  Ueq     = %f', d = (/ Ueq  /) )
    call MessageNotify( 'M', module_name, '' )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    initial_data_inited = .true.
  end subroutine InitDataInit
module_name
Constant :
module_name = ‘initial_data :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: initial_data_primitive.F90,v 1.1.1.1 2010-08-17 05:24:50 takepiro Exp $’ :character(*), parameter
: モジュールのバージョン Module version