| Class | set_1d_profile | 
| In: | prepare_data/set_1d_profile.f90 | 
| Subroutine : | |
| xyz_Press(0:imax-1,1:jmax,1:kmax) : | real(DP), intent(in ) | 
| xyz_Temp(0:imax-1,1:jmax,1:kmax) : | real(DP), intent(out) | 
| xyz_QVap(0:imax-1,1:jmax,1:kmax) : | real(DP), intent(out) | 
  subroutine Set1DProfileAtm( xyz_Press, xyz_Temp, xyz_QVap )
    real(DP), intent(in ) :: xyz_Press(0:imax-1,1:jmax,1:kmax)
    real(DP), intent(out) :: xyz_Temp (0:imax-1,1:jmax,1:kmax)
    real(DP), intent(out) :: xyz_QVap (0:imax-1,1:jmax,1:kmax)
    !
    ! local variables
    !
    real(DP), allocatable :: a_InLogQH2O(:)
    ! 初期化確認
    ! Initialization check
    !
    if ( .not. set_1d_profile_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if
    call Set1DProfileInterpolate( Inkmax, a_InPress, a_InTemp, xyz_Press, xyz_Temp )
    allocate( a_InLogQH2O( Inkmax ) )
    a_InLogQH2O = log( a_InQH2O )
    call Set1DProfileInterpolate( Inkmax, a_InPress, a_InLogQH2O, xyz_Press, xyz_QVap )
    xyz_QVap(:,:,:) = exp( xyz_QVap(:,:,:) )
    deallocate( a_InLogQH2O )
  end subroutine Set1DProfileAtm
          | Subroutine : | 
This procedure input/output NAMELIST#set_1d_profile_nml .
  subroutine Set1DProfileInit
    ! ファイル入出力補助
    ! File I/O support
    !
    use dc_iounit, only: FileOpen
    ! gtool データ入力
    ! Gtool data input
    !
    use gtool_history, only: HistoryGet, HistoryGetAttr
    ! NetCDF のラッパープログラム
    ! NetCDF wrapper
    !
    use netcdf_wrapper, only : NWInqDimLen
    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid
    ! 宣言文 ; Declaration statements
    !
    logical :: flag_mpi_init
    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_1d_profile_nml/ InFileName
          !
          ! デフォルト値については初期化手続 "set_1d_profile#Set1DProfileInit"
          ! のソースコードを参照のこと.
          !
          ! Refer to source codes in the initialization procedure
          ! "set_1d_profile#Set1DProfileInit" for the default values.
          !
    if ( set_1d_profile_inited ) return
    ! デフォルト値の設定
    ! Default values settings
    !
!!$    InFileName = 'data.nc'
    InFileName = ''
    ! 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 = set_1d_profile_nml, iostat = iostat_nml )             ! (out)
      close( unit_nml )
      call NmlutilMsg( iostat_nml, module_name ) ! (in)
    end if
    if ( InFileName /= '' ) then
      call NWInqDimLen( InFileName, 'plev', Inkmax )
      allocate( a_InPress( Inkmax ) )
      allocate( a_InTemp ( Inkmax ) )
      allocate( a_InQH2O ( Inkmax ) )
      allocate( a_InQO3  ( Inkmax ) )
      flag_mpi_init = .true.
      call HistoryGet( InFileName, 'plev', a_InPress, flag_mpi_split = flag_mpi_init )
      call HistoryGet( InFileName, 'Temp', a_InTemp, flag_mpi_split = flag_mpi_init )
      call HistoryGet( InFileName, 'QH2O', a_InQH2O, flag_mpi_split = flag_mpi_init )
      call HistoryGet( InFileName, 'QO3', a_InQO3, flag_mpi_split = flag_mpi_init )
    end if
    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'InFileName = %c', c1 = trim(InFileName) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )
    set_1d_profile_inited = .true.
  end subroutine Set1DProfileInit
          | Subroutine : | |
| xyz_Press(0:imax-1,1:jmax,1:kmax) : | real(DP), intent(in ) | 
| xyz_QO3(0:imax-1,1:jmax,1:kmax) : | real(DP), intent(out) | 
  subroutine Set1DProfileO3( xyz_Press, xyz_QO3 )
    real(DP), intent(in ) :: xyz_Press(0:imax-1,1:jmax,1:kmax)
    real(DP), intent(out) :: xyz_QO3  (0:imax-1,1:jmax,1:kmax)
    !
    ! local variables
    !
    real(DP), allocatable :: a_InLogQO3(:)
    ! 初期化確認
    ! Initialization check
    !
    if ( .not. set_1d_profile_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if
    allocate( a_InLogQO3( Inkmax ) )
    a_InLogQO3 = log( a_InQO3 )
    call Set1DProfileInterpolate( Inkmax, a_InPress, a_InLogQO3, xyz_Press, xyz_QO3 )
    xyz_QO3(:,:,:) = exp( xyz_QO3(:,:,:) )
    deallocate( a_InLogQO3 )
  end subroutine Set1DProfileO3
          | Subroutine : | |
| xy_Ps(0:imax-1,1:jmax) : | real(DP), intent(out) | 
  subroutine Set1DProfilePs( xy_Ps )
    real(DP), intent(out) :: xy_Ps(0:imax-1,1:jmax)
    !
    ! local variables
    !
    ! 初期化確認
    ! Initialization check
    !
    if ( .not. set_1d_profile_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if
    xy_Ps = a_InPress(1)
  end subroutine Set1DProfilePs
          | Subroutine : | |
| xy_SurfTemp(0:imax-1,1:jmax) : | real(DP), intent(out) | 
  subroutine Set1DProfileSurfTemp( xy_SurfTemp )
    real(DP), intent(out) :: xy_SurfTemp(0:imax-1,1:jmax)
    !
    ! local variables
    !
    ! 初期化確認
    ! Initialization check
    !
    if ( .not. set_1d_profile_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if
    xy_SurfTemp = a_InTemp(1)
  end subroutine Set1DProfileSurfTemp
          | Subroutine : | |
| NLev : | integer , intent(in ) | 
| a_Press(1:NLev) : | real(DP), intent(in ) | 
| a_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) | 
  subroutine Set1DProfileInterpolate( NLev, a_Press, a_Array, xyz_Press, xyz_Array )
    integer , intent(in ) :: NLev
    real(DP), intent(in ) :: a_Press  (1:NLev)
    real(DP), intent(in ) :: a_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 :: i
    integer :: j
    integer :: k
    integer :: kk
    ! 初期化確認
    ! Initialization check
    !
    if ( .not. set_1d_profile_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if
    ! Old code to be deleted
!!$    do k = 1, kmax
!!$      if( xyz_Press(0,1,k) <= a_Press(NLev) ) then
!!$        xyz_Array(0,1,k) = a_Array(NLev)
!!$      else
!!$        search_loop : do kk = 2, Inkmax
!!$          if( a_Press( kk ) < xyz_Press(0,1,k) ) exit search_loop
!!$        end do search_loop
!!$        if( kk > NLev ) &
!!$          stop 'Unexpected error in setting temperature profile'
!!$        xyz_Array(0,1,k) =                                  &
!!$          &   ( a_Array( kk ) - a_Array( kk-1 ) )           &
!!$          & / ( log( a_Press( kk )    / a_Press( kk-1 ) ) ) &
!!$          & * ( log( xyz_Press(0,1,k) / a_Press( kk-1 ) ) ) &
!!$          & + a_Array( kk-1 )
!!$      end if
!!$    end do
!!$
!!$    do k = 1, kmax
!!$      xyz_Array(:,:,k) = xyz_Array(0,1,k)
!!$    end do
    do k = 1, kmax
      do j = 1, jmax
        do i = 0, imax-1
          if( xyz_Press(i,j,k) <= a_Press(NLev) ) then
            xyz_Array(i,j,k) = a_Array(NLev)
          else
            search_loop : do kk = 2, Inkmax
              if( a_Press( kk ) < xyz_Press(i,j,k) ) exit search_loop
            end do search_loop
            if( kk > NLev ) stop 'Unexpected error in setting temperature profile'
            xyz_Array(i,j,k) = ( a_Array( kk ) - a_Array( kk-1 ) ) / ( log( a_Press( kk )    / a_Press( kk-1 ) ) ) * ( log( xyz_Press(i,j,k) / a_Press( kk-1 ) ) ) + a_Array( kk-1 )
          end if
        end do
      end do
    end do
  end subroutine Set1DProfileInterpolate
          | Constant : | |||
| module_name = ‘set_1d_profile‘ : | character(*), parameter 
 | 
| Variable : | |||
| set_1d_profile_inited = .false. : | logical, save 
 | 
| Constant : | |||
| version = ’$Name: dcpam5-20120301 $’ // ’$Id: set_1d_profile.f90,v 1.4 2011-07-16 19:52:49 yot Exp $’ : | character(*), parameter 
 |