Class surface_data
In: prepare_data/surface_data_primitive.f90

地表面データ提供

Prepare surface data

Note that Japanese and English are described in parallel.

GCM で用いる地表面データを生成します. 現在は暫定的に Hosaka et al. (1998) の SST 分布を与えます.

Surface data for GCM is generated. Now, SST profile in Hosaka et al. (1998) is provided tentatively.

Procedures List

SetSurfData :地表面データの取得
———— :————
SetSurfData :Set surface data

NAMELIST

NAMELIST#surface_data_nml

Methods

Included Modules

gridset dc_types dc_message axesset constants dc_string namelist_util dc_iounit

Public Instance methods

Subroutine :
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(out), optional
: 地表面温度. Surface temperature
xy_SurfRoughLength(0:imax-1, 1:jmax) :real(DP), intent(out), optional
: 地表粗度長. Surface rough length
xy_SurfHeatCapacity(0:imax-1, 1:jmax) :real(DP), intent(out), optional
: 地表熱容量. Surface heat capacity
xy_GroundTempFlux(0:imax-1, 1:jmax) :real(DP), intent(out), optional
: 地中熱フラックス. Ground temperature flux
xy_SurfCond(0:imax-1, 1:jmax) :integer , intent(out), optional
: 地表状態 (0: 固定, 1: 可変) . Surface condition (0: fixed, 1: variable)

GCM 用の地表面データを返します.

Return surface data for GCM.

[Source]

  subroutine SetSurfData( xy_SurfTemp, xy_SurfRoughLength, xy_SurfHeatCapacity, xy_GroundTempFlux, xy_SurfCond )
    !
    ! GCM 用の地表面データを返します.
    !
    ! Return surface data for GCM.
    !

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

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: y_Lat                 ! $ \varphi $ [rad.] . 緯度. Latitude

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: PI                    ! $ \pi $ .
                              ! 円周率.  Circular constant

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

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(out), optional:: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度. 
                              ! Surface temperature
    real(DP), intent(out), optional:: xy_SurfRoughLength (0:imax-1, 1:jmax)
                              ! 地表粗度長. 
                              ! Surface rough length
    real(DP), intent(out), optional:: xy_SurfHeatCapacity (0:imax-1, 1:jmax)
                              ! 地表熱容量. 
                              ! Surface heat capacity
    real(DP), intent(out), optional:: xy_GroundTempFlux (0:imax-1, 1:jmax)
                              ! 地中熱フラックス. 
                              ! Ground temperature flux
    integer , intent(out), optional:: xy_SurfCond (0:imax-1, 1:jmax)
                              ! 地表状態 (0: 固定, 1: 可変) . 
                              ! Surface condition (0: fixed, 1: variable)

    ! 作業変数
    ! 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. surface_data_inited ) call SurfDataInit

    select case ( LChar( trim(Pattern) ) )

    case ( 'homogeneous' )
      ! SST 一様
      ! SST is homogeneous
      !

      if ( present(xy_SurfTemp        ) ) xy_SurfTemp         = SurfTemp
      if ( present(xy_SurfRoughLength ) ) xy_SurfRoughLength  = RoughLength
      if ( present(xy_SurfHeatCapacity) ) xy_SurfHeatCapacity = HeatCapacity
      if ( present(xy_GroundTempFlux  ) ) xy_GroundTempFlux   = TempFlux
      if ( present(xy_SurfCond        ) ) xy_SurfCond         = SurfCond

    case ( 'hosaka et al. (1998)' )
      ! Hosaka et al. (1998) において用いられた SST
      ! SST used in Hosaka et al. (1998)
      !

      if ( present(xy_SurfRoughLength ) ) xy_SurfRoughLength  = RoughLength
      if ( present(xy_SurfHeatCapacity) ) xy_SurfHeatCapacity = HeatCapacity
      if ( present(xy_GroundTempFlux  ) ) xy_GroundTempFlux   = TempFlux
      if ( present(xy_SurfCond        ) ) xy_SurfCond         = SurfCond

      if ( present( xy_SurfTemp ) ) then
        call Hosakaetal98SST( xy_SurfTemp )
      end if

    case ( 'nh01_control' )
      ! Neale and Hoskins (2001) の Control experiment において用いられた SST
      ! SST used for Control experiment by Neale and Hoskins (2001)
      !

      if ( present(xy_SurfRoughLength ) ) xy_SurfRoughLength  = RoughLength
      if ( present(xy_SurfHeatCapacity) ) xy_SurfHeatCapacity = HeatCapacity
      if ( present(xy_GroundTempFlux  ) ) xy_GroundTempFlux   = TempFlux
      if ( present(xy_SurfCond        ) ) xy_SurfCond         = SurfCond

      if ( present( xy_SurfTemp ) ) then
        call NH01SST( 'control', xy_SurfTemp )
      end if

    case default
      call MessageNotify( 'E', module_name, 'Pattern=<%c> is invalid.', c1 = trim(Pattern) )
    end select

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

Private Instance methods

HeatCapacity
Variable :
HeatCapacity :real(DP), save
: 地表熱容量. Surface heat capacity
Subroutine :
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(out)
: 地表面温度. Surface temperature

GCM 用の地表面データを返します.

Return surface data for GCM.

[Source]

  subroutine Hosakaetal98SST( xy_SurfTemp )
    !
    ! GCM 用の地表面データを返します.
    !
    ! Return surface data for GCM.
    !

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

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: y_Lat                 ! $ \varphi $ [rad.] . 緯度. Latitude

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: PI                    ! $ \pi $ .
                              ! 円周率.  Circular constant

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

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(out) :: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度. 
                              ! Surface temperature

    ! 作業変数 (Hosaka et al. (1998))
    ! Work variables (Hosaka et al. (1998))
    !
    real(DP):: TempEq         ! 赤道上 (正確には LatCenter 上) での温度.
                              ! Temperature on the equator 
                              ! (on LatCenter, to be exact)
    real(DP):: LatCenter      ! 温度最高の緯度. 
                              ! Latitude on which temperature is maximum.
    real(DP):: LatFlatWidth   ! 温度が平坦化される緯度幅. 
                              ! Latitude width in which temperature is flattened
    integer:: jp
    integer:: jm

    real(DP):: LatA, Alpha, Beta, Gamma

    real(DP):: Phi1, AlphaBeta4, Phi, LatAPlus, LatAMinus
    real(DP):: SurfTempMx

    ! 作業変数
    ! 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. surface_data_inited ) call SurfDataInit

    ! Hosaka et al. (1998) において用いられた SST
    ! SST used in Hosaka et al. (1998)
    !

!!$    TempEq       = SurfTemp
    TempEq       = 302.0_DP
    LatCenter    =   0.0_DP
    LatFlatWidth =   7.0_DP

    LatA         =  30.0_DP
    Alpha        =  60.0_DP
    Beta         =  32.0_DP
    Gamma        =   0.0_DP

    Phi1 = abs( LatA * PI / 180.0_DP )
    AlphaBeta4  = 2.0_DP *( Phi1**3 ) * ( Beta / Alpha )

    do j = 1, jmax
      Phi = abs( y_Lat(j) - LatCenter * PI / 180.0_DP )
      xy_SurfTemp (:,j) = TempEq - Alpha / 2.0_DP * ( Phi - max( sqrt( Phi1**2 + AlphaBeta4 ) - sqrt( ( Phi - Phi1 )**2 + AlphaBeta4 ), 0.0_DP ) ) + Gamma * ( Phi**3 )
    end do

    ! 中心 LatCenter +/- LatFlatWidth の間を平坦に
    ! Flatten between LatCenter +/- LatFlatWidth
    !
    if ( LatFlatWidth < 0.0_DP ) then
      LatFlatWidth = - LatFlatWidth
    end if
    LatAPlus = ( LatCenter + LatFlatWidth ) * PI / 180.0_DP
    LatAMinus = ( LatCenter - LatFlatWidth ) * PI / 180.0_DP

    jp = 1
    jm = jmax
    do j = 1, jmax
      if ( y_Lat(j) <= LatAPlus ) then
        jp = j
        if ( j == jmax ) jp = jp - 1
      end if
      if ( y_Lat(j) < LatAMinus ) then
        jm = j
        if ( j == jmax ) jm = jm - 1
      end if
    end do

    if ( jmax /= 1 ) then
      SurfTempMx = (   xy_SurfTemp(1,jm) * ( y_Lat(jm+1) - LatAMinus ) + xy_SurfTemp(1,jm+1) * ( LatAMinus - y_Lat(jm) ) ) / ( y_Lat(jm+1) - y_Lat(jm) )

      xy_SurfTemp(:,jm+1:jp) = SurfTempMx
    end if


  end subroutine Hosakaetal98SST
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 :recursive
SSTType :character(len=*), intent(in )
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP) , intent(inout)
: 地表面温度. Surface temperature

Set SST described by Neale and Hoskins (2001)

[Source]

  recursive subroutine NH01SST( SSTType, xy_SurfTemp )
    !
    ! Set SST described by Neale and Hoskins (2001)
    !

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

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: x_Lon, y_Lat                 ! $ \varphi $ [rad.] . 緯度. Latitude

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: PI                    ! $ \pi $ .
                              ! 円周率.  Circular constant

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

    ! 宣言文 ; Declaration statements
    !
    implicit none
    character(len=*), intent(in   ) :: SSTType
    real(DP)        , intent(inout) :: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度.
                              ! Surface temperature

    ! 作業変数
    ! Work variables
    !
    real(DP) :: Temp0         ! Zero degree Celsius
                              ! Latitude width in which temperature is flattened
    real(DP) :: xy_SurfTempTmp1 (0:imax-1, 1:jmax)
    real(DP) :: xy_SurfTempTmp2 (0:imax-1, 1:jmax)

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

    Temp0 = 273.15d0

    if ( SSTType == 'control' ) then
      ! Neale and Hoskins (2001) の control experiment において用いられた SST
      ! SST used for control experiment by Neale and Hoskins (2001)
      !

      do j = 1, jmax
        if ( abs( y_Lat(j) ) < PI / 3.0d0 ) then
          xy_SurfTemp(:,j) = 27.0d0 * ( 1.0d0 - sin( 3.0d0 * y_Lat(j) / 2.0d0 )**2 )
        else
          xy_SurfTemp(:,j) = 0.0d0
        end if
      end do
      xy_SurfTemp = xy_SurfTemp + Temp0


    else if ( SSTType == 'peaked' ) then
      ! Neale and Hoskins (2001) の Peaked experiment において用いられた SST
      ! SST used for Peaked experiment by Neale and Hoskins (2001)
      !

      do j = 1, jmax
        if ( abs( y_Lat(j) ) < PI / 3.0d0 ) then
          xy_SurfTemp(:,j) = 27.0d0 * ( 1.0d0 - 3.0d0 * abs( y_Lat(j) ) / PI )
        else
          xy_SurfTemp(:,j) = 0.0d0
        end if
      end do
      xy_SurfTemp = xy_SurfTemp + Temp0

    else if ( SSTType == 'flat' ) then
      ! Neale and Hoskins (2001) の Flat experiment において用いられた SST
      ! SST used for Flat experiment by Neale and Hoskins (2001)
      !

      do j = 1, jmax
        if ( abs( y_Lat(j) ) < PI / 3.0d0 ) then
          xy_SurfTemp(:,j) = 27.0d0 * ( 1.0d0 - sin( 3.0d0 * y_Lat(j) / 2.0d0 )**4 )
        else
          xy_SurfTemp(:,j) = 0.0d0
        end if
      end do
      xy_SurfTemp = xy_SurfTemp + Temp0

    else if ( SSTType == 'control-5n' ) then
      ! Neale and Hoskins (2001) の Control-5N experiment において用いられた SST
      ! SST used for Control-5N experiment by Neale and Hoskins (2001)
      !

      do j = 1, jmax
        if ( y_Lat(j) < - PI / 3.0d0 ) then
          xy_SurfTemp(:,j) = 0.0d0
        else if ( y_Lat(j) < PI / 36.0d0 ) then
          xy_SurfTemp(:,j) = 27.0d0 * ( 1.0d0 - sin( 90.0d0/65.0d0 * ( y_Lat(j) - PI/36.0d0 ) )**2 )
        else if ( y_Lat(j) < PI / 3.0d0 ) then
          xy_SurfTemp(:,j) = 27.0d0 * ( 1.0d0 - sin( 90.0d0/55.0d0 * ( y_Lat(j) - PI/36.0d0 ) )**2 )
        else
          xy_SurfTemp(:,j) = 0.0d0
        end if
      end do
      xy_SurfTemp = xy_SurfTemp + Temp0

    else if ( SSTType == 'qobs' ) then
      ! Neale and Hoskins (2001) の Qobs experiment において用いられた SST
      ! SST used for Qobs experiment by Neale and Hoskins (2001)
      !

      call NH01SST( 'control', xy_SurfTempTmp1 )
      call NH01SST( 'control', xy_SurfTempTmp2 )
      xy_SurfTemp = ( xy_SurfTempTmp1 + xy_SurfTempTmp2 ) * 0.5d0

!!$    else if ( SSTType == '1keq' ) then
!!$      ! Neale and Hoskins (2001) の 1KEQ experiment において用いられた SST
!!$      ! SST used for 1KEQ experiment by Neale and Hoskins (2001)
!!$      !
!!$
!!$      call NH01SST( &
!!$        & 'control',     & ! (in   )
!!$        & xy_SurfTemp  & ! (inout)
!!$        & )
!!$
!!$      do j = 1, jmax
!!$        do i = 1,
!!$          if ( ( abs( x_Lon(i) - PI ) < PI /  3.0d0 ) .and. &
!!$            &  ( abs( y_Lat(j)      ) < PI / 12.0d0 ) ) then
!!$            xy_SurfTemp(i,j) = xy_SurfTemp(i,j)                                 &
!!$              & + 1.0d0 * cos( PI/2.0d0 * ( x_Lon(i) - PI ) / ( PI ) )**2       &
!!$              &         * cos( PI/2.0d0 * y_Lat(j)          / ( PI ) )**2 )
!!$          end if
!!$        end do
!!$      end do

    else
      call MessageNotify( 'E', module_name, 'SSTType=<%c> is invalid.', c1 = trim(SSTType) )
    end if


  end subroutine NH01SST
Pattern
Variable :
Pattern :character(STRING), save
: 地表面データのパターン. 以下のパターンを選択可能.

Surface data pattern. Available patterns are as follows.

  • "Hosaka et al. (1998)"
  • "Homogeneous"
RoughLength
Variable :
RoughLength :real(DP), save
: 地表粗度長. Surface rough length
SurfCond
Variable :
SurfCond :integer, save
: 地表状態 (0: 固定, 1: 可変). Surface condition (0: fixed, 1: variable)
Subroutine :

This procedure input/output NAMELIST#surface_data_nml .

[Source]

  subroutine SurfDataInit

    ! モジュール引用 ; 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 /surface_data_nml/ Pattern, SurfTemp, RoughLength, HeatCapacity, TempFlux, SurfCond
          !
          ! デフォルト値については初期化手続 "surface_data#SurfDataInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "surface_data#SurfDataInit" for the default values. 
          !


    ! 実行文 ; Executable statement

    if ( surface_data_inited ) return
    call InitCheck

    ! デフォルト値の設定 (まずは Pattern のみ)
    ! Default values settings (At first, "Pattern" only)
    !
    Pattern      = 'Hosaka et al. (1998)'
    SurfTemp     = 273.15_DP
    RoughLength  = 1.0e-4_DP
    HeatCapacity = 0.0_DP
    TempFlux     = 0.0_DP
    SurfCond     = 0

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

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


    ! 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 = surface_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, '  SurfTemp     = %f', d = (/ SurfTemp     /) )
    call MessageNotify( 'M', module_name, '  RoughLength  = %f', d = (/ RoughLength  /) )
    call MessageNotify( 'M', module_name, '  HeatCapacity = %f', d = (/ HeatCapacity /) )
    call MessageNotify( 'M', module_name, '  TempFlux     = %f', d = (/ TempFlux     /) )
    call MessageNotify( 'M', module_name, '  SurfCond     = %d', i = (/ SurfCond     /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    surface_data_inited = .true.
  end subroutine SurfDataInit
SurfTemp
Variable :
SurfTemp :real(DP), save
: 地表面温度の基準値. Standard value of surface temperature
TempFlux
Variable :
TempFlux :real(DP), save
: 地中熱フラックス. Ground temperature flux
module_name
Constant :
module_name = ‘surface_data :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: surface_data_primitive.f90,v 1.1.1.1 2010-08-17 05:24:50 takepiro Exp $’ :character(*), parameter
: モジュールのバージョン Module version