Class intavr_operate
In: util/intavr_operate.F90

積分と平均の操作

Operation for integral and average

Note that Japanese and English are described in parallel.

積分で用いる座標重みを考慮した積分や平均操作のための関数を提供します. SPMODEL ライブラリ の w_integral_module.f90 を参考に作成しました.

Functions for integral or average operation with weight for integration are provided This program is created referring to "w_integral_module.f90" in SPMODEL library

Procedures List

IntLonLat_xy :緯度経度積分
!$ ! y_IntLon_xy, IntLon_x :経度積分
!$ ! ya_IntLon_xya :経度積分 (多層用)
!$ ! x_IntLat_xy, IntLat_y :緯度積分
!$ ! xa_IntLat_xya :緯度積分 (多層用)
!$ ! AvrLonLat_xy :緯度経度平均
!$ ! y_AvrLon_xy, AvrLon_x :経度平均
!$ ! ya_AvrLon_xya :経度平均 (多層用)
!$ ! x_AvrLat_xy, AvrLat_y :緯度平均
!$ ! xa_AvrLat_xya :緯度平均 (多層用)
——————— :———————
y_IntLon_xy, IntLon_x :Meridional integral
!$ ! ya_IntLon_xya :Meridional integral (for multi layer)
!$ ! x_IntLat_xy, IntLat_y :Zonal integral
!$ ! xa_IntLat_xya :Zonal integral (for multi layer)
!$ ! AvrLonLat_xy :Zonal and meridional average
!$ ! y_AvrLon_xy, AvrLon_x :Meridional average
!$ ! ya_AvrLon_xya :Meridional average (for multi layer)
!$ ! x_AvrLat_xy, AvrLat_y :Zonal average
!$ ! xa_AvrLat_xya :Zonal average (for multi layer)

Methods

Included Modules

axesset gridset dc_types dc_message mpi_wrapper constants

Public Instance methods

Function :
IntLonLat_xy :real(DP)
xy_Data(0:imax-1, 1:jmax) :real(DP), intent(in)

2 次元緯度経度格子点データの全領域積分(1 層用).

実際には格子点データ各点毎に x_Lon_Weight, y_Lat_Weight を掛けた 総和を計算している.

Global integration of 2-dimensional (latitude and longitude) grid data.

Practically, the sum total of grid data is calculated by multiplying in each grid "x_Lon_Weight" and "y_Lat_Weight".

[Source]

  function IntLonLat_xy( xy_Data )
    !
    ! 2 次元緯度経度格子点データの全領域積分(1 層用). 
    !
    ! 実際には格子点データ各点毎に x_Lon_Weight, y_Lat_Weight を掛けた
    ! 総和を計算している. 
    !
    ! Global integration of 2-dimensional (latitude and longitude)
    ! grid data.
    !
    ! Practically, the sum total of grid data is calculated
    ! by multiplying in each grid "x_Lon_Weight" and "y_Lat_Weight".
    !

    real(DP), intent(in) :: xy_Data (0:imax-1, 1:jmax)
    real(DP)             :: IntLonLat_xy

    ! 実行文 ; Executable statement
    !

    ! Old one to be deleted
!!$    IntLonLat_xy = IntLon_x( x_IntLat_xy( xy_Data ) )

    IntLonLat_xy = IntLat_y( y_IntLon_xy( xy_Data ) )

  end function IntLonLat_xy
intavr_operate_inited
Variable :
intavr_operate_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
    !

    ! 格子点設定
    ! 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. 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 :

intavr_operate モジュールの初期化を行います. NAMELIST#intavr_operate_nml の読み込みはこの手続きで行われます.

"intavr_operate" module is initialized. "NAMELIST#intavr_operate_nml" is loaded in this procedure.

[Source]

  subroutine IntAvrOprInit
    !
    ! intavr_operate モジュールの初期化を行います. 
    ! NAMELIST#intavr_operate_nml の読み込みはこの手続きで行われます. 
    !
    ! "intavr_operate" module is initialized. 
    ! "NAMELIST#intavr_operate_nml" is loaded in this procedure. 
    !

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

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

    ! 実行文 ; Executable statement
    !

    if ( intavr_operate_inited ) return
    call InitCheck

    ! デフォルト値の設定
    ! 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 = intavr_operate_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) )
    intavr_operate_inited = .true.
  end subroutine IntAvrOprInit
Function :
IntLat_y :real(DP)
y_Data(1:jmax) :real(DP), intent(in)

1 次元緯度格子点データの緯度方向積分(1 層用).

実際には格子点データ各点毎に y_Lat_Weight を掛けた 総和を計算している.

Meridonal integration of 1-dimensional (latitude) grid data.

Practically, the sum total of grid data is calculated by multiplying in each grid "y_Lat_Weight".

[Source]

  function IntLat_y( y_Data )
    !
    ! 1 次元緯度格子点データの緯度方向積分(1 層用). 
    !
    ! 実際には格子点データ各点毎に y_Lat_Weight を掛けた
    ! 総和を計算している. 
    !
    ! Meridonal integration of 1-dimensional (latitude)
    ! grid data.
    !
    ! Practically, the sum total of grid data is calculated
    ! by multiplying in each grid "y_Lat_Weight".
    !
    real(DP), intent(in) :: y_Data (1:jmax)
    real(DP)             :: IntLat_y

    ! 作業変数
    ! Work variables
    !

    ! 実行文 ; Executable statement
    !
    IntLat_y = sum( y_Data * y_Lat_Weight )

  end function IntLat_y
Function :
IntLat_y :real(DP)
y_Data(1:jmax) :real(DP), intent(in)

1 次元緯度経度格子点データの全領域平均(1 層用).

Global mean of 2-dimensional (latitude and longitude) grid data.

[Source]

  function IntLat_y( y_Data )
    !
    ! 1 次元緯度経度格子点データの全領域平均(1 層用). 
    !
    ! Global mean of 2-dimensional (latitude and longitude)
    ! grid data.
    !

    ! MPI
    !
    use mpi_wrapper, only: nprocs, myrank, MPIWrapperISend, MPIWrapperIRecv, MPIWrapperWait

    ! 格子点数・最大波数設定
    ! Number of grid points and maximum truncated wavenumber settings
    !
    use gridset, only: a_jmax, jmax_max

    real(DP), intent(in) :: y_Data (1:jmax)
    real(DP)             :: IntLat_y


    ! Local variable
    !
    real(DP), allocatable :: a_SendBuf (:)
    real(DP), allocatable :: aa_RecvBuf(:,:)
    integer , allocatable :: a_iReqSend(:)
    integer , allocatable :: a_iReqRecv(:)

    integer               :: j
    integer               :: n


    ! 実行文 ; Executable statement
    !


    allocate( a_SendBuf (1:jmax_max) )
    allocate( aa_RecvBuf(1:jmax_max,0:nprocs-1) )
    allocate( a_iReqSend(0:nprocs-1) )
    allocate( a_iReqRecv(0:nprocs-1) )

    do j = 1, jmax
      a_SendBuf(j) = y_Data(j) * y_Lat_Weight(j)
    end do
    do j = jmax+1, jmax_max
      a_SendBuf(j) = -1.0d0
    end do

    do n = 0, nprocs-1
      if ( n == myrank ) then
        do j = 1, jmax
          aa_RecvBuf(:,n) = a_SendBuf
        end do
      else
        call MPIWrapperISend( n, jmax_max, a_SendBuf      , a_iReqSend(n) )
        call MPIWrapperIRecv( n, jmax_max, aa_RecvBuf(:,n), a_iReqRecv(n) )
      end if
    end do
    do n = 0, nprocs-1
      if ( n == myrank ) cycle
      call MPIWrapperWait( a_iReqSend(n) )
      call MPIWrapperWait( a_iReqRecv(n) )
    end do


    IntLat_y = 0.0d0
    do n = nprocs-1, 0, -1
      do j = 1, a_jmax(n) / 2
        IntLat_y = IntLat_y + aa_RecvBuf(j,n)
      end do
    end do
    do n = 0, nprocs-1
      do j = a_jmax(n) / 2 + 1, a_jmax(n)
        IntLat_y = IntLat_y + aa_RecvBuf(j,n)
      end do
    end do


    deallocate( a_SendBuf  )
    deallocate( aa_RecvBuf )
    deallocate( a_iReqSend )
    deallocate( a_iReqRecv )


  end function IntLat_y
module_name
Constant :
module_name = ‘intavr_operate :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: intavr_operate.F90,v 1.1.1.1 2010-08-17 05:24:51 takepiro Exp $’ :character(*), parameter
: モジュールのバージョン Module version
Function :
y_IntLon_xy(1:jmax) :real(DP)
xy_Data(0:imax-1, 1:jmax) :real(DP), intent(in)

2 次元緯度経度格子点データの経度方向積分(1 層用).

実際には格子点データ各点毎に x_Lon_Weight を掛けた 総和を計算している.

Zonal integration of 2-dimensional (latitude and longitude) grid data.

Practically, the sum total of grid data is calculated by multiplying in each grid "x_Lon_Weight".

[Source]

  function y_IntLon_xy( xy_Data )
    !
    ! 2 次元緯度経度格子点データの経度方向積分(1 層用). 
    !
    ! 実際には格子点データ各点毎に x_Lon_Weight を掛けた
    ! 総和を計算している. 
    !
    ! Zonal integration of 2-dimensional (latitude and longitude)
    ! grid data.
    !
    ! Practically, the sum total of grid data is calculated
    ! by multiplying in each grid "x_Lon_Weight".
    !

    real(DP), intent(in) :: xy_Data (0:imax-1, 1:jmax)
    real(DP)             :: y_IntLon_xy (1:jmax)

    ! 作業変数
    ! Work variables
    !
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitudinal direction
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitudinal direction

    ! 実行文 ; Executable statement
    !

    y_IntLon_xy = 0.0_DP
    do j = 1, jmax
      do i = 0, imax - 1
        y_IntLon_xy(j) = y_IntLon_xy(j) + xy_Data (i,j) * x_Lon_Weight(i)
      end do
    end do

  end function y_IntLon_xy