Class read_time_series
In: io/read_time_series.f90

��ç³»å�����¼ã�¿ã����¿è¾¼��

Reading time series

Note that Japanese and English are described in parallel.

海表�¢æ¸©åº�, O3 ���������ç³»å�����¼ã�¿ã�� NetCDF ���¡ã�¤ã������読ã�¿è¾¼��.

Reading time series data, such as sea surface temperature, O3, and so on, from NetCDF file.

Procedures List

!$ ! GroundFileGet :�°è¡¨�¢ã���¼ã�¿ã���¡ã�¤ã�����¥å��

!$ !—

!$ ! GroundFileOpen :�°è¡¨�¢ã���¼ã�¿ã���¡ã�¤ã�������¼ã����
!$ ! GroundFileOutput :�°è¡¨�¢ã���¼ã�¿ã���¡ã�¤ã���¸ã�����¼ã�¿å�ºå��
!$ ! GroundFileClose :�°è¡¨�¢ã���¼ã�¿ã���¡ã�¤ã�������­ã�¼ã��

++

———— :————
!$ ! GroundFileGet :Input ground data file

!$ !—

!$ ! GroundFileOpen :Open ground data file
!$ ! GroundFileOutput :Data output to ground data file
!$ ! GroundFileClose :Close ground data file

++

NAMELIST

!$ ! NAMELIST#ground_file_io_nml

Methods

Included Modules

dc_types dc_message gridset gtool_history dc_string dc_calendar timeset netcdf_wrapper dc_iounit namelist_util

Public Instance methods

Subroutine :

This procedure input/output NAMELIST#read_time_series_nml .

[Source]

  subroutine ReadTimeSeriesInit

    ! ���¡ã�¤ã���¥å�ºå��è£���
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! NAMELIST ���¡ã�¤ã���¥å�����¢ã�������¼ã���£ã������
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid

    ! ���»ç���
    ! Time control
    !
    use timeset, only: InitialDate

    ! 宣�� ; 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 /read_time_series_nml/ FlagYearCyclic
          !
          ! �����������¤ã���¤ã��������������ç¶� "read_time_series#ReadTimeSeriesInit"
          ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������.
          !
          ! Refer to source codes in the initialization procedure
          ! "read_time_series#ReadTimeSeriesInit" for the default values.
          !

    if ( read_time_series_inited ) return


    ! �����������¤ã��¨­å®�
    ! Default values settings
    !

    FlagYearCyclic = .true.

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

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


    ! Initialzation
    !
    NumMaxStruct = 0


    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'FlagYearCyclic = %b', l = (/ FlagYearCyclic /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )


    read_time_series_inited = .true.


  end subroutine ReadTimeSeriesInit
SetValuesFromTimeSeriesWrapper( Keyword, FileName, VarName, Var )
Subroutine :
Keyword :character(*), intent(in )
FileName :character(*), intent(in )
: ���¡ã�¤ã����. File name
VarName :character(*), intent(in )
: å¤��°å��. Variable name
Var :real(DP) , intent(inout)
: �°è¡¨�¢æ¸©åº�. Surface temperature

Alias for SetValFromTimeSeriesWrapper0D

SetValuesFromTimeSeriesWrapper( Keyword, FileName, VarName, xy_Var )
Subroutine :
Keyword :character(*), intent(in )
FileName :character(*), intent(in )
: ���¡ã�¤ã����. File name
VarName :character(*), intent(in )
: å¤��°å��. Variable name
xy_Var(0:imax-1, 1:jmax) :real(DP) , intent(inout)
: �°è¡¨�¢æ¸©åº�. Surface temperature

Alias for SetValFromTimeSeriesWrapper2D

SetValuesFromTimeSeriesWrapper( Keyword, FileName, VarName, xyz_Press, xyz_Var, FlagLogVLev, FlagLog, FlagPositiveDef )
Subroutine :
Keyword :character(*), intent(in )
FileName :character(*), intent(in )
: ���¡ã�¤ã����. File name
VarName :character(*), intent(in )
: å¤��°å��. Variable name
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP) , intent(in )
: �°è¡¨�¢æ¸©åº�. Surface temperature
xyz_Var(0:imax-1, 1:jmax, 1:kmax) :real(DP) , intent(inout)
: �°è¡¨�¢æ¸©åº�. Surface temperature
FlagLogVLev :logical , intent(in )
FlagLog :logical , intent(in )
FlagPositiveDef :logical , intent(in )

Alias for SetValFromTimeSeriesWrapper3D

Private Instance methods

FlagYearCyclic
Variable :
FlagYearCyclic = .true. :logical, save
Subroutine :
FileName :character(*), intent(in )
DateString :character(*), intent(in )
Yr :integer , intent(out)
Mon :integer , intent(out)
Day :integer , intent(out)
Hr :integer , intent(out)
Min :integer , intent(out)
Sec :real(DP) , intent(out)

[Source]

  subroutine InterpretTimeUnitString( FileName, DateString, Yr, Mon, Day, Hr, Min, Sec )

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! 宣�� ; Declaration statements
    !
    implicit none

    character(*), intent(in ) :: FileName
    character(*), intent(in ) :: DateString
    integer     , intent(out) :: Yr
    integer     , intent(out) :: Mon
    integer     , intent(out) :: Day
    integer     , intent(out) :: Hr
    integer     , intent(out) :: Min
    real(DP)    , intent(out) :: Sec


    ! �業��
    ! Work variables
    !
    integer :: StrLen
    integer :: l
    integer :: ll

    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if

    StrLen = len_trim( DateString )

    ! format of the DateString has to be "... since YYYY/MM/DD HH:MM:SS".

    search_since : do ll = 1, StrLen-5+1
      if ( DateString(ll:ll+5-1) == "since" ) exit search_since
    end do search_since
    if ( ll > StrLen-5+1 ) then
      call MessageNotify( 'E', module_name, 'Unable to find "since" in %c.', c1 = trim(FileName) )
    end if
    !
    l = ll + 5
    !
    if ( DateString(l:l) /= " " ) then
      call MessageNotify( 'E', module_name, 'Unable to find a space after "since" in %c.', c1 = trim(FileName) )
    end if
    !
    l = l + 1
    !
    search_yr : do ll = l, StrLen
      if ( DateString(ll:ll) == "-" ) exit search_yr
    end do search_yr
    if ( ll > StrLen ) then
      call MessageNotify( 'E', module_name, 'Unable to find "-" between year and month in %c.', c1 = trim(FileName) )
    end if
    read( DateString(l:ll-1), * ) Yr
    !
    l = ll + 1
    !
    search_mon : do ll = l, StrLen
      if ( DateString(ll:ll) == "-" ) exit search_mon
    end do search_mon
    if ( ll > StrLen ) then
      call MessageNotify( 'E', module_name, 'Unable to find "-" between month and day in %c.', c1 = trim(FileName) )
    end if
    read( DateString(l:ll-1), * ) Mon
    !
    l = ll + 1
    !
    search_day : do ll = l, StrLen
      if ( DateString(ll:ll) == " " ) exit search_day
    end do search_day
    if ( ll > StrLen ) then
      call MessageNotify( 'E', module_name, 'Unable to find a space between day and hour in %c.', c1 = trim(FileName) )
    end if
    read( DateString(l:ll-1), * ) Day
    !
    l = ll
    !
    if ( DateString(l:l) /= " " ) then
      call MessageNotify( 'E', module_name, 'Unable to confirm a space between day and hour in %c.', c1 = trim(FileName) )
    end if
    !
    l = l + 1
    !
    search_hr : do ll = l, StrLen
      if ( DateString(ll:ll) == ":" ) exit search_hr
    end do search_hr
    if ( ll > StrLen ) then
      call MessageNotify( 'E', module_name, 'Unable to find ":" between hour and minute in %c.', c1 = trim(FileName) )
    end if
    read( DateString(l:ll-1), * ) Hr
    !
    l = ll + 1
    !
    search_min : do ll = l, StrLen
      if ( DateString(ll:ll) == ":" ) exit search_min
    end do search_min
    if ( ll > StrLen ) then
      call MessageNotify( 'E', module_name, 'Unable to find ":" between minute and second in %c.', c1 = trim(FileName) )
    end if
    read( DateString(l:ll-1), * ) Min
    !
    l = ll + 1
    !
    search_sec : do ll = l, StrLen
      if ( ( DateString(ll:ll) == " " ) .or. ( DateString(ll:ll) == "." ) ) exit search_sec
    end do search_sec
!!$    if ( ll > StrLen ) then
!!$      call MessageNotify( 'E', module_name, 'Unable to find end of second in %c.', c1 = trim(FileName) )
!!$    end if
    read( DateString(l:ll-1), * ) Sec


  end subroutine InterpretTimeUnitString
NumMaxStruct
Variable :
NumMaxStruct :integer, save
NumMaxStructArr
Constant :
NumMaxStructArr = 25 :integer, parameter
Subroutine :
Keyword :character(*), intent(in )
: Keyword
Index :integer , intent(out)
: Index

[Source]

  subroutine SetValFromTimeSeriesFindIndex( Keyword, Index )


    ! 宣�� ; Declaration statements
    !
    implicit none

    character(*), intent(in ):: Keyword
                              ! 
                              ! Keyword
    integer     , intent(out):: Index
                              ! 
                              ! Index

    integer :: l


    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    ! Search index of a_TSDataInfo with Keyword

    Index = 0

    search_index : do l = 1, NumMaxStruct
      if ( a_TSDataInfo( l ) % Keyword == Keyword ) then
        Index = l
        exit search_index
      end if
    end do search_index

    ! If an element of a_TSDataInfo with Keyword cannot be found, a new 
    ! element will be used. 
    if ( Index == 0 ) then
      NumMaxStruct = NumMaxStruct + 1
      Index        = NumMaxStruct
      a_TSDataInfo( Index ) % Keyword = Keyword
    end if


    if ( Index > NumMaxStructArr ) then
      call MessageNotify( 'E', module_name, 'Index is greater than NumMaxStructArr.' )
    end if


  end subroutine SetValFromTimeSeriesFindIndex
Subroutine :
Keyword :character(*), intent(in )
FileName :character(*), intent(in )
: ���¡ã�¤ã����. File name
VarName :character(*), intent(in )
: å¤��°å��. Variable name
Var :real(DP) , intent(inout)
: �°è¡¨�¢æ¸©åº�. Surface temperature

[Source]

  subroutine SetValFromTimeSeriesWrapper0D( Keyword, FileName, VarName, Var )


    ! 宣�� ; Declaration statements
    !
    implicit none

    character(*), intent(in   ):: Keyword
    character(*), intent(in   ):: FileName
                              ! ���¡ã�¤ã����. 
                              ! File name
    character(*), intent(in   ):: VarName
                              ! å¤��°å��. 
                              ! Variable name
    real(DP)    , intent(inout):: Var
                              ! �°è¡¨�¢æ¸©åº�. 
                              ! Surface temperature


    integer :: Index


    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    call SetValFromTimeSeriesFindIndex( Keyword, Index )
    call SetValuesFromTimeSeries( a_TSDataInfo( Index ), FileName, VarName, Var = Var )


  end subroutine SetValFromTimeSeriesWrapper0D
Subroutine :
Keyword :character(*), intent(in )
FileName :character(*), intent(in )
: ���¡ã�¤ã����. File name
VarName :character(*), intent(in )
: å¤��°å��. Variable name
xy_Var(0:imax-1, 1:jmax) :real(DP) , intent(inout)
: �°è¡¨�¢æ¸©åº�. Surface temperature

[Source]

  subroutine SetValFromTimeSeriesWrapper2D( Keyword, FileName, VarName, xy_Var )


    ! 宣�� ; Declaration statements
    !
    implicit none

    character(*), intent(in   ):: Keyword
    character(*), intent(in   ):: FileName
                              ! ���¡ã�¤ã����. 
                              ! File name
    character(*), intent(in   ):: VarName
                              ! å¤��°å��. 
                              ! Variable name
    real(DP)    , intent(inout):: xy_Var(0:imax-1, 1:jmax)
                              ! �°è¡¨�¢æ¸©åº�. 
                              ! Surface temperature


    integer :: Index


    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    call SetValFromTimeSeriesFindIndex( Keyword, Index )
    call SetValuesFromTimeSeries( a_TSDataInfo( Index ), FileName, VarName, xy_Var = xy_Var )


  end subroutine SetValFromTimeSeriesWrapper2D
Subroutine :
Keyword :character(*), intent(in )
FileName :character(*), intent(in )
: ���¡ã�¤ã����. File name
VarName :character(*), intent(in )
: å¤��°å��. Variable name
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP) , intent(in )
: �°è¡¨�¢æ¸©åº�. Surface temperature
xyz_Var(0:imax-1, 1:jmax, 1:kmax) :real(DP) , intent(inout)
: �°è¡¨�¢æ¸©åº�. Surface temperature
FlagLogVLev :logical , intent(in )
FlagLog :logical , intent(in )
FlagPositiveDef :logical , intent(in )

[Source]

  subroutine SetValFromTimeSeriesWrapper3D( Keyword, FileName, VarName, xyz_Press, xyz_Var, FlagLogVLev, FlagLog, FlagPositiveDef )


    ! 宣�� ; Declaration statements
    !
    implicit none

    character(*), intent(in   ):: Keyword
    character(*), intent(in   ):: FileName
                              ! ���¡ã�¤ã����. 
                              ! File name
    character(*), intent(in   ):: VarName
                              ! å¤��°å��. 
                              ! Variable name
    real(DP)    , intent(in   ):: xyz_Press(0:imax-1, 1:jmax, 1:kmax)
                              ! �°è¡¨�¢æ¸©åº�. 
                              ! Surface temperature
    real(DP)    , intent(inout):: xyz_Var(0:imax-1, 1:jmax, 1:kmax)
                              ! �°è¡¨�¢æ¸©åº�. 
                              ! Surface temperature
    logical     , intent(in   ):: FlagLogVLev
    logical     , intent(in   ):: FlagLog
    logical     , intent(in   ):: FlagPositiveDef


    integer :: Index


    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    call SetValFromTimeSeriesFindIndex( Keyword, Index )
    call SetValuesFromTimeSeries( a_TSDataInfo(Index), FileName, VarName, xyz_Press = xyz_Press, xyz_Var = xyz_Var, FlagLogVLev     = FlagLogVLev, FlagLog         = FlagLog, FlagPositiveDef = FlagPositiveDef )



  end subroutine SetValFromTimeSeriesWrapper3D
Subroutine :
TSDataInfo :type(time_series_data), intent(inout)
FileName :character(*) , intent(in )
: ���¡ã�¤ã����. File name
VarName :character(*) , intent(in )
: å¤��°å��. Variable name
xyz_Press(0:imax-1, 1:jmax, 1:kmax) :real(DP) , optional, intent(in )
: 3 次�����. 3D array
Var :real(DP) , optional, intent(inout)
: 2 次�����. 2D array
xy_Var(0:imax-1, 1:jmax) :real(DP) , optional, intent(inout)
: 2 次�����. 2D array
xyz_Var(0:imax-1, 1:jmax, 1:kmax) :real(DP) , optional, intent(inout)
: 3 次�����. 3D array
FlagLogVLev :logical , optional, intent(in )
FlagLog :logical , optional, intent(in )
FlagPositiveDef :logical , optional, intent(in )

�°è¡¨�¢ã����������¼ã�¿ã��設å����¾ã��. xy_SurfTemp 以å�����������¼ã�°ã���������¿è¨­å®������¾ã��.

Get various data on ground. Arguments excluding "xy_SurfTemp" are configured at first only.

[Source]

  subroutine SetValuesFromTimeSeries( TSDataInfo, FileName, VarName, xyz_Press, Var, xy_Var, xyz_Var, FlagLogVLev, FlagLog, FlagPositiveDef )
    !
    ! �°è¡¨�¢ã����������¼ã�¿ã��設å����¾ã��. 
    ! xy_SurfTemp 以å�����������¼ã�°ã���������¿è¨­å®������¾ã��. 
    !
    ! Get various data on ground. 
    ! Arguments excluding "xy_SurfTemp" are configured at first only. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! gtool4 ���¼ã�¿å�¥å��
    ! Gtool4 data input
    !
    use gtool_history, only: HistoryGet

    ! ��������
    ! Character handling
    !
    use dc_string, only: toChar

    ! �¥ä������³æ���»ã������±ã��
    ! Date and time handler
    !
    use dc_calendar, only: DCCalDateEvalSecOfYear

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimeN, InitialDate

    ! 宣�� ; Declaration statements
    !
    implicit none

    type(time_series_data), intent(inout):: TSDataInfo
    character(*)          , intent(in   ):: FileName
                              ! ���¡ã�¤ã����. 
                              ! File name
    character(*)          , intent(in   ):: VarName
                              ! å¤��°å��. 
                              ! Variable name
    real(DP)    , optional, intent(in   ):: xyz_Press(0:imax-1, 1:jmax, 1:kmax)
                              ! 3 次�����. 
                              ! 3D array
    real(DP)    , optional, intent(inout):: Var
                              ! 2 次�����. 
                              ! 2D array
    real(DP)    , optional, intent(inout):: xy_Var (0:imax-1, 1:jmax)
                              ! 2 次�����. 
                              ! 2D array
    real(DP)    , optional, intent(inout):: xyz_Var(0:imax-1, 1:jmax, 1:kmax)
                              ! 3 次�����. 
                              ! 3D array
    logical     , optional, intent(in   ):: FlagLogVLev
    logical     , optional, intent(in   ):: FlagLog
    logical     , optional, intent(in   ):: FlagPositiveDef

    ! �業��
    ! Work variables
    !
    real(DP):: CurrentTimeInSec
    integer :: tindex

!!$    real(DP):: xyza_VarInterpolated(0:imax-1, 1:jmax, 1:kmax, 2)

    logical :: FlagReadData

    integer :: t


    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    if ( ( .not. present( Var ) ) .and. ( .not. present( xy_Var ) ) .and. ( .not. present( xyz_Var ) ) ) then
      call MessageNotify( 'E', module_name, 'Var or xy_Var or xyz_Var have to be given.' )
    end if

    if ( ( present( Var ) ) .and. ( present( xy_Var ) ) ) then
      call MessageNotify( 'E', module_name, 'Both Var and xy_Var are not given.' )
    end if

    if ( ( present( xy_Var ) ) .and. ( present( xyz_Var ) ) ) then
      call MessageNotify( 'E', module_name, 'Both xy_Var and xyz_Var are not given.' )
    end if

    if ( ( present( xyz_Var ) ) .and. ( present( Var ) ) ) then
      call MessageNotify( 'E', module_name, 'Both xyz_Var and Var are not be given.' )
    end if

    if ( ( present( xyz_Var ) ) .and. ( .not. present( xyz_Press ) ) ) then
      call MessageNotify( 'E', module_name, 'xyz_Press has to be given, when xyz_Var is given.' )
    end if

    ! ���� ; Executable statement
    !
    if ( .not. associated( TSDataInfo % a_time ) ) then
      if ( present( Var ) ) then
        call StructureInit( FileName, VarName, 0, TSDataInfo )
      else if ( present( xy_Var ) ) then
        call StructureInit( FileName, VarName, 2, TSDataInfo )
      else
        call StructureInit( FileName, VarName, 3, TSDataInfo )
      end if
    end if


    ! Update values of time paying attention to leap year
    ! This is not used, because this causes error when FlagYearCyclic = .true..
    !
!!$    call UpdateTime(     &
!!$      & TSDataInfo             & ! (inout)
!!$      & )


    if ( TSDataInfo % tmax >= 2 ) then

      if ( FlagYearCyclic ) then
        CurrentTimeInSec = DCCalDateEvalSecOfYear( TimeN, date = InitialDate )
      else
        CurrentTimeInSec = TimeN + TSDataInfo%TimeFromOriginToInitialDate
      end if

!!$      write( 6, * ) TSDataInfo%a_time(TSDataInfo%a_tindex(1)), &
!!$        & SecOfYear, TSDataInfo%a_time(TSDataInfo%a_tindex(2))


      ! Check whether the data have to be read or not
      if ( ( CurrentTimeInSec <  TSDataInfo%a_time(TSDataInfo%a_tindex(1)) ) .or. ( CurrentTimeInSec >= TSDataInfo%a_time(TSDataInfo%a_tindex(2)) ) ) then
        FlagReadData = .true.
      else
        FlagReadData = .false.
      end if
      if ( .not. FlagYearCyclic ) then
        if ( ( CurrentTimeInSec <  TSDataInfo%a_time(1)               ) .or. ( CurrentTimeInSec >= TSDataInfo%a_time(TSDataInfo%tmax) ) ) then
          FlagReadData = .false.
          CurrentTimeInSec = max( CurrentTimeInSec, TSDataInfo%a_time(1) )
          CurrentTimeInSec = min( CurrentTimeInSec, TSDataInfo%a_time(TSDataInfo%tmax) )
        end if
      end if

      if ( FlagReadData ) then
!!$      if ( ( CurrentTimeInSec <   TSDataInfo%a_time(TSDataInfo%a_tindex(1)) ) .or. &
!!$        &  ( CurrentTimeInSec >=  TSDataInfo%a_time(TSDataInfo%a_tindex(2)) ) ) then

        TSDataInfo % a_tindex(1) = 0
        TSDataInfo % a_tindex(2) = 1
        do t = 1, TSDataInfo%tmax
          if ( TSDataInfo % a_time(t) <= CurrentTimeInSec ) then
            TSDataInfo % a_tindex(1) = t
            TSDataInfo % a_tindex(2) = t+1
          end if
        end do

!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) 'in if', TSDataInfo % a_tindex(1), TSDataInfo % a_tindex(2)
!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) '##############################################'
!!$        write( 6, * ) '##############################################'

        ! set time index
        if ( FlagYearCyclic ) then
          tindex = TSDataInfo % a_tindex(1)
          if ( tindex == 0 ) then
            tindex = TSDataInfo % tmax
          else if ( tindex == TSDataInfo % tmax + 1 ) then
            tindex = 1
          else
            tindex = tindex
          end if
        else
          tindex = TSDataInfo % a_tindex(1)
          tindex = min( max( tindex, 1 ), TSDataInfo % tmax )
        end if


        if ( present( Var ) ) then
          call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(0,1,1,1), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
        else if ( present( xy_Var ) ) then
          call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,1,1), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
        else
          call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,:,1), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
        end if

        ! set time index
        if ( FlagYearCyclic ) then
          tindex = TSDataInfo % a_tindex(2)
          if ( tindex == 0 ) then
            tindex = TSDataInfo % tmax
          else if ( tindex == TSDataInfo % tmax + 1 ) then
            tindex = 1
          else
            tindex = tindex
          end if
        else
          tindex = TSDataInfo % a_tindex(2)
          tindex = min( max( tindex, 1 ), TSDataInfo % tmax )
        end if

        if ( present( Var ) ) then
          call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(0,1,1,2), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
        else if ( present( xy_Var ) ) then
          call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,1,2), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
        else
          call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,:,2), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
        end if

      end if

      if ( present( Var ) ) then
        Var = ( TSDataInfo%xyza_SavedData(0,1,1,2) - TSDataInfo%xyza_SavedData(0,1,1,1)  ) / ( TSDataInfo%a_time(TSDataInfo%a_tindex(2)) - TSDataInfo%a_time(TSDataInfo%a_tindex(1))  ) * ( CurrentTimeInSec - TSDataInfo%a_time(TSDataInfo%a_tindex(1))  ) + TSDataInfo%xyza_SavedData(0,1,1,1)
      else if ( present( xy_Var ) ) then
        xy_Var = ( TSDataInfo%xyza_SavedData(:,:,1,2) - TSDataInfo%xyza_SavedData(:,:,1,1)  ) / ( TSDataInfo%a_time(TSDataInfo%a_tindex(2)) - TSDataInfo%a_time(TSDataInfo%a_tindex(1))  ) * ( CurrentTimeInSec - TSDataInfo%a_time(TSDataInfo%a_tindex(1))  ) + TSDataInfo%xyza_SavedData(:,:,1,1)
      else
        TSDataInfo%xyz_VarTimeInterpolated = ( TSDataInfo%xyza_SavedData(:,:,:,2) - TSDataInfo%xyza_SavedData(:,:,:,1)  ) / ( TSDataInfo%a_time(TSDataInfo%a_tindex(2)) - TSDataInfo%a_time(TSDataInfo%a_tindex(1))  ) * ( CurrentTimeInSec - TSDataInfo%a_time(TSDataInfo%a_tindex(1))  ) + TSDataInfo%xyza_SavedData(:,:,:,1)

        call VerticalInterpolation( TSDataInfo%NVLevels, TSDataInfo%z_VLevels, TSDataInfo%xyz_VarTimeInterpolated, xyz_Press, xyz_Var, FlagLogVLev, FlagLog, FlagPositiveDef )
      end if

    else

      if ( present( Var ) ) then
        Var = TSDataInfo%xyza_SavedData(0,1,1,1)
      else if ( present( xy_Var ) ) then
        xy_Var = TSDataInfo%xyza_SavedData(:,:,1,1)
      else
        call VerticalInterpolation( TSDataInfo%NVLevels, TSDataInfo%z_VLevels, TSDataInfo%xyza_SavedData(:,:,:,1), xyz_Press, xyz_Var, FlagLogVLev, FlagLog, FlagPositiveDef )
      end if

    end if


  end subroutine SetValuesFromTimeSeries
Subroutine :
FileName :character(*) , intent(in )
: ���¡ã�¤ã����. File name
VarName :character(*) , intent(in )
: å¤��°å��. Variable name
NDims :integer , intent(in )
: ����以å�����°ã�����. Number of dimensions except for time dimension
TSDataInfo :type(time_series_data), intent(inout)

[Source]

  subroutine StructureInit( FileName, VarName, NDims, TSDataInfo )

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! gtool4 ���¼ã�¿å�¥å��
    ! Gtool4 data input
    !
    use gtool_history, only: HistoryGet, HistoryGetPointer

    ! ��������
    ! Character handling
    !
    use dc_string, only: toChar

    ! �����¥æ��������±ã��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DC_CAL_DATE, DCCalInquire, DCCalDateEvalSecOfYear, DCCalDateCreate, DCCalDateDifference

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimeN, InitialDate

    ! NetCDF wrapper
    !
    use netcdf_wrapper, only: NWGetAtt, NWInqDimLen


    ! 宣�� ; Declaration statements
    !
    implicit none

    character(*)          , intent(in   ):: FileName
                              ! ���¡ã�¤ã����. 
                              ! File name
    character(*)          , intent(in   ):: VarName
                              ! å¤��°å��. 
                              ! Variable name
    integer               , intent(in   ):: NDims
                              ! ����以å�����°ã�����. 
                              ! Number of dimensions except for time dimension
    type(time_series_data), intent(inout):: TSDataInfo


    ! �業��
    ! Work variables
    !
    real(DP)         :: CurrentTimeInSec
!!$    real(DP), pointer:: a_time(:)
    integer          :: tindex
    integer          :: t

    character(STRING):: VLevelName

    character(STRING):: attchar

    integer:: hour_in_day, min_in_hour, day_in_year
    integer, pointer:: day_in_month_ptr(:) => null()
    real(DP):: sec_in_min, sec_in_day


    type(DC_CAL_DATE), save :: DataOriginDate
                              ! ���¼ã�¿æ�¥æ���ºæ�
                              ! Origin date of data
    integer  :: DataOriginYr
    integer  :: DataOriginMon
    integer  :: DataOriginDay
    integer  :: DataOriginHr
    integer  :: DataOriginMin
    real(DP) :: DataOriginSec


    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


!!$    nullify( a_time )


    call DCCalInquire( day_in_month_ptr = day_in_month_ptr , hour_in_day      = hour_in_day  , min_in_hour      = min_in_hour  , sec_in_min       = sec_in_min )         ! (out)
    day_in_year = sum( day_in_month_ptr )
    deallocate( day_in_month_ptr )
    sec_in_day  = hour_in_day * min_in_hour * sec_in_min


    TSDataInfo % FileName = FileName
    TSDataInfo % VarName  = VarName
    TSDataInfo % NDims    = NDims


    if ( TSDataInfo % NDims == 0 ) then
      TSDataInfo % NVLevels = 1
    else if ( TSDataInfo % NDims == 2 ) then
      TSDataInfo % NVLevels = 1
    else
      VLevelName = "plev"

      call HistoryGetPointer( TSDataInfo%FileName, VLevelName, TSDataInfo % z_VLevels, flag_mpi_split = flag_mpi_split )
      TSDataInfo % NVLevels = size( TSDataInfo % z_Vlevels )
    end if


    call NWInqDimLen( TSDataInfo%FileName, 'time', TSDataInfo%tmax )


    if ( ( FlagYearCyclic ) .or. ( TSDataInfo % tmax < 2 ) ) then
      ! case in which the data are cyclic

      TSDataInfo % TimeFromOriginToInitialDate = 0.0_DP

    else
      ! case in which the data are not cyclic

      call NWGetAtt( TSDataInfo%FileName, 'time', 'units', AttChar )

      call InterpretTimeUnitString( TSDataInfo%FileName, AttChar, DataOriginYr, DataOriginMon, DataOriginDay, DataOriginHr, DataOriginMin, DataOriginSec )

      ! Check time from data origin to start time of integration
      !
      call DCCalDateCreate( year       = DataOriginYr, month      = DataOriginMon, day        = DataOriginDay, hour       = DataOriginHr  , min        = DataOriginMin, sec        = DataOriginSec, date       = DataOriginDate )
      TSDataInfo % TimeFromOriginToInitialDate = DCCalDateDifference( DataOriginDate, InitialDate )

      call MessageNotify( 'M', module_name, 'Origin time for a variable %c is %d/%d/%d %d:%d:%f.', c1 = trim(TSDataInfo%VarName), i = (/ DataOriginYr, DataOriginMon, DataOriginDay, DataOriginHr, DataOriginMin /), d = (/ DataOriginSec /) )
      call MessageNotify( 'M', module_name, 'Time from origin to initial date is %f s.', d = (/ TSDataInfo % TimeFromOriginToInitialDate /) )

    end if



    !-----
!!$    call HistoryGetPointer(               &
!!$      & TSDataInfo%FileName,              &
!!$      & 'time',                           &
!!$      & a_time,                           &
!!$      & flag_mpi_split = flag_mpi_split   &
!!$      & )
!!$    TSDataInfo % tmax = size( a_time )
!!$
!!$    call NWGetAtt( TSDataInfo%FileName, 'time', 'units', attchar )
!!$    if ( ( attchar(1:3) == 'day' ) .or. &
!!$      &  ( attchar(1:3) == 'DAY' ) .or. &
!!$      &  ( attchar(1:3) == 'Day' ) ) then
!!$      a_time = a_time * DAY_SECONDS
!!$    else
!!$      call MessageNotify( 'E', module_name, 'Unit of time, %c, is not supported.', c1 = trim(attchar) )
!!$    end if
    !-----


    if ( TSDataInfo % tmax >= 2 ) then

      if ( FlagYearCyclic ) then
        CurrentTimeInSec = DCCalDateEvalSecOfYear( TimeN, date = InitialDate )
      else
        CurrentTimeInSec = TimeN + TSDataInfo%TimeFromOriginToInitialDate
      end if

      !-----
!!$      allocate( TSDataInfo % a_time(0:TSDataInfo%tmax+1) )
!!$      TSDataInfo % a_time(0) = - ( YEAR_DAYS * DAY_SECONDS - a_time(TSDataInfo%tmax) )
!!$      do t = 1, TSDataInfo%tmax
!!$        TSDataInfo % a_time(t) = a_time(t)
!!$      end do
!!$      TSDataInfo % a_time(TSDataInfo%tmax+1) = YEAR_DAYS * DAY_SECONDS + a_time(1)
!!$      deallocate( a_time )
      !-----


      allocate( TSDataInfo % a_time(0:TSDataInfo%tmax+1) )
      call HistoryGet( TSDataInfo%FileName, 'time', TSDataInfo%a_time(1:TSDataInfo%tmax), flag_mpi_split = flag_mpi_split )
      call NWGetAtt( TSDataInfo%FileName, 'time', 'units', attchar )

      if ( ( attchar(1:3) == 'day' ) .or. ( attchar(1:3) == 'DAY' ) .or. ( attchar(1:3) == 'Day' ) ) then

        ! convert unit of time from day to sec
        TSDataInfo%a_time(1:TSDataInfo%tmax) = TSDataInfo%a_time(1:TSDataInfo%tmax) * sec_in_day
      else
        call MessageNotify( 'E', module_name, 'Unit of time, %c, is not supported.', c1 = trim(attchar) )
      end if

      ! set time in hallo regions
      if ( FlagYearCyclic ) then
        TSDataInfo % a_time(0                ) = - ( day_in_year * sec_in_day - TSDataInfo % a_time(TSDataInfo%tmax) )
        TSDataInfo % a_time(TSDataInfo%tmax+1) = day_in_year * sec_in_day + TSDataInfo % a_time(1              )
      else
        TSDataInfo % a_time(0                ) = TSDataInfo % a_time(1                ) - 1.0_DP

        TSDataInfo % a_time(TSDataInfo%tmax+1) = TSDataInfo % a_time(TSDataInfo%tmax  ) + 1.0_DP
      end if


      allocate( TSDataInfo % a_tindex(1:2) )
      allocate( TSDataInfo % xyza_SavedData(0:imax-1,1:jmax,1:TSDataInfo%NVLevels,1:2) )

      TSDataInfo % a_tindex(1) = 0
      TSDataInfo % a_tindex(2) = 1
      do t = 1, TSDataInfo%tmax
        if ( TSDataInfo % a_time(t) <= CurrentTimeInSec ) then
          TSDataInfo % a_tindex(1) = t
          TSDataInfo % a_tindex(2) = t+1
        end if
      end do

      ! set time index
      if ( FlagYearCyclic ) then
        tindex = TSDataInfo % a_tindex(1)
        if ( tindex == 0 ) then
          tindex = TSDataInfo % tmax
        else if ( tindex == TSDataInfo % tmax + 1 ) then
          tindex = 1
        else
          tindex = tindex
        end if
      else
        tindex = TSDataInfo % a_tindex(1)
        tindex = min( max( tindex, 1 ), TSDataInfo % tmax )
      end if


      if ( TSDataInfo % NDims == 0 ) then
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(0,1,1,1), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
      else if ( TSDataInfo % NDims == 2 ) then
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,1,1), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
      else
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,:,1), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
      end if

      ! set time index
      if ( FlagYearCyclic ) then
        tindex = TSDataInfo % a_tindex(2)
        if ( tindex == 0 ) then
          tindex = TSDataInfo % tmax
        else if ( tindex == TSDataInfo % tmax + 1 ) then
          tindex = 1
        else
          tindex = tindex
        end if
      else
        tindex = TSDataInfo % a_tindex(2)
        tindex = min( max( tindex, 1 ), TSDataInfo % tmax )
      end if

      if ( TSDataInfo % NDims == 0 ) then
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(0,1,1,2), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
      else if ( TSDataInfo % NDims == 2 ) then
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,1,2), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
      else
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,:,2), range = 'time=^'//toChar(tindex), flag_mpi_split = flag_mpi_split )
      end if

      allocate( TSDataInfo%xyz_VarTimeInterpolated(0:imax-1, 1:jmax, 1:TSDataInfo%NVLevels) )

    else

      !-----
!!$      allocate( TSDataInfo % a_time(TSDataInfo%tmax) )
!!$      do t = 1, TSDataInfo%tmax
!!$        TSDataInfo % a_time(t) = a_time(t)
!!$      end do
      !-----


      allocate( TSDataInfo % a_time(TSDataInfo%tmax) )
      call HistoryGet( TSDataInfo%FileName, 'time', TSDataInfo%a_time(1:TSDataInfo%tmax), flag_mpi_split = flag_mpi_split )
      call NWGetAtt( TSDataInfo%FileName, 'time', 'units', attchar )
      if ( ( attchar(1:3) == 'day' ) .or. ( attchar(1:3) == 'DAY' ) .or. ( attchar(1:3) == 'Day' ) ) then
        ! convert unit of time from day to sec
        TSDataInfo%a_time(1:TSDataInfo%tmax) = TSDataInfo%a_time(1:TSDataInfo%tmax) * sec_in_day
      else
        call MessageNotify( 'E', module_name, 'Unit of time, %c, is not supported.', c1 = trim(attchar) )
      end if

      allocate( TSDataInfo % a_tindex(1:1) )
      allocate( TSDataInfo % xyza_SavedData(0:imax-1,1:jmax,1:TSDataInfo%NVLevels,1:1) )

      TSDataInfo % a_tindex(1) = 1

      if ( TSDataInfo % NDims == 0 ) then
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(0,1,1,1), range = 'time=^'//toChar(TSDataInfo%a_tindex(1)), flag_mpi_split = flag_mpi_split )
      else if ( TSDataInfo % NDims == 2 ) then
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,1,1), range = 'time=^'//toChar(TSDataInfo%a_tindex(1)), flag_mpi_split = flag_mpi_split )
      else
        call HistoryGet( TSDataInfo%FileName, TSDataInfo%VarName, TSDataInfo%xyza_SavedData(:,:,:,1), range = 'time=^'//toChar(TSDataInfo%a_tindex(1)), flag_mpi_split = flag_mpi_split )
      end if

    end if


  end subroutine StructureInit
Subroutine :
TSDataInfo :type(time_series_data), intent(inout)

[Source]

  subroutine UpdateTime( TSDataInfo )

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! �����¥æ��������±ã��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DC_CAL_DATE             ! �¥æ����è¡�憗�������¼ã�¿å��.
                                ! Data type for date and time

    ! �¥ä������³æ���»ã������±ã��
    ! Date and time handler
    !
    use dc_calendar, only: DCCalInquire, DCCalDateCreate, DCCalDateInquire, DCCalDateChkLeapYear

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimeN, InitialDate

    ! 宣�� ; Declaration statements
    !
    implicit none

    type(time_series_data), intent(inout):: TSDataInfo


    ! �業��
    ! Work variables
    !
    integer           :: hour_in_day, min_in_hour, day_in_year
    integer, pointer  :: day_in_month_ptr(:) => null()
    real(DP)          :: sec_in_min, sec_in_day

    integer           :: year
    type(DC_CAL_DATE) :: PreYearDate


    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    if ( TSDataInfo % tmax >= 2 ) then

      call DCCalInquire( day_in_month_ptr = day_in_month_ptr , hour_in_day      = hour_in_day  , min_in_hour      = min_in_hour  , sec_in_min       = sec_in_min )         ! (out)
      day_in_year = sum( day_in_month_ptr )
      deallocate( day_in_month_ptr )
      sec_in_day  = hour_in_day * min_in_hour * sec_in_min


      ! Set TSDataInfo % a_time(0)
      !

      call DCCalDateInquire( year       = year, elapse_sec = TimeN, date       = InitialDate )
      call DCCalDateCreate( year       = year - 1, month      = 1, day        = 1, hour       = 0, min        = 0, sec        = 0.0_DP, date       = PreYearDate )

      if ( DCCalDateChkLeapYear( 0.0_DP, PreYearDate ) ) then
        TSDataInfo % a_time(0                ) = - ( ( day_in_year + 1 ) * sec_in_day - TSDataInfo % a_time(TSDataInfo%tmax) )
      else
        TSDataInfo % a_time(0                ) = - (   day_in_year       * sec_in_day - TSDataInfo % a_time(TSDataInfo%tmax) )
      end if


      ! Set TSDataInfo % a_time(TSDataInfo%tmax+1)
      !

      if ( DCCalDateChkLeapYear( TimeN, InitialDate ) ) then
        TSDataInfo % a_time(TSDataInfo%tmax+1) = ( day_in_year + 1 ) * sec_in_day + TSDataInfo % a_time(1              )
      else
        TSDataInfo % a_time(TSDataInfo%tmax+1) = day_in_year       * sec_in_day + TSDataInfo % a_time(1              )
      end if


    end if


  end subroutine UpdateTime
Subroutine :
NVLevels :integer , intent(in )
z_VLevelsIn(1:NVLevels) :real(DP), intent(in )
xyz_VarIn(0:imax-1, 1:jmax, 1:NVLevels) :real(DP), intent(in )
xyz_VarOut(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
FlagLogVLev :logical , intent(in ), optional
FlagLog :logical , intent(in ), optional
FlagPositiveDef :logical , intent(in ), optional

[Source]

  subroutine VerticalInterpolation( NVLevels, z_VLevelsIn, xyz_VarIn, xyz_VLevelsOut, xyz_VarOut, FlagLogVLev, FlagLog, FlagPositiveDef )

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! 宣�� ; Declaration statements
    !
    implicit none

    integer , intent(in ):: NVLevels
    real(DP), intent(in ):: z_VLevelsIn(1:NVLevels)
    real(DP), intent(in ):: xyz_VarIn  (0:imax-1, 1:jmax, 1:NVLevels)
    real(DP), intent(in ):: xyz_VlevelsOut(0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(out):: xyz_VarOut    (0:imax-1, 1:jmax, 1:kmax)
    logical , intent(in ), optional:: FlagLogVLev
    logical , intent(in ), optional:: FlagLog
    logical , intent(in ), optional:: FlagPositiveDef


    ! �業��
    ! Work variables
    !
    logical:: FlagLogVLevLV
    logical:: FlagLogLV
    logical:: FlagPositiveDefLV
    integer:: i
    integer:: j
    integer:: k
    integer:: kk
    integer:: xyz_kk(0:imax-1, 1:jmax, 1:kmax)


    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. read_time_series_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if

    ! Check order of vertical levels
    !
    if ( z_VlevelsIn(1) < z_VlevelsIn(2) ) then
      call MessageNotify( 'E', module_name, 'The order of vertical levels is inappropriate.' )
    end if


    ! Flags are checked
    !
    if ( present( FlagLogVLev ) ) then
      FlagLogVLevLV = FlagLogVLev
    else
      FlagLogVLevLV = .false.
    end if
    if ( present( FlagLog ) ) then
      FlagLogLV = FlagLog
    else
      FlagLogLV = .false.
    end if
    if ( present( FlagPositiveDef ) ) then
      FlagPositiveDefLV = FlagPositiveDef
    else
      FlagPositiveDefLV = .false.
    end if


    xyz_kk = 1

    do kk = 1, NVLevels-1

      do k = 1, kmax
        do j = 1, jmax
          do i = 0, imax-1
            if ( xyz_VLevelsOut(i,j,k) < z_VLevelsIn(kk) ) then
              xyz_kk(i,j,k) = kk
            end if
          end do
        end do
      end do

    end do


    if ( FlagLogVLevLV ) then

      if ( FlagLogLV ) then
        ! log-log

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

!!$          if ( xyz_VLevelsOut(i,j,k) > z_VLevelsIn(1) ) then
!!$            xyz_VarOut(i,j,k) = xyz_VarIn(i,j,1)
!!$
!!$!          else if ( xyz_VLevelsOut(i,j,k) < z_VLevelsIn(NVLevels) ) then
!!$!            call MessageNotify( 'E', module_name, 'Vertical level is out of given range.' )
!!$!!            xyz_VarOut(i,j,k) = 0.0d0
!!$
!!$          else
!!$
!!$            xyz_VarOut(i,j,k) = &
!!$              &   ( xyz_VarIn(i,j,xyz_kk(i,j,k)+1)     - xyz_VarIn(i,j,xyz_kk(i,j,k)) ) &
!!$              & / log( z_VLevelsIn   (xyz_kk(i,j,k)+1) / z_VLevelsIn(xyz_kk(i,j,k))   ) &
!!$              & * log( xyz_VLevelsOut(i,j,k)           / z_VLevelsIn(xyz_kk(i,j,k))   ) &
!!$              & + xyz_VarIn(i,j,xyz_kk(i,j,k))
!!$
!!$          end if


              xyz_VarOut(i,j,k) = log(   ( xyz_VarIn(i,j,xyz_kk(i,j,k)+1) + 1.0d-100 ) / ( xyz_VarIn(i,j,xyz_kk(i,j,k)  ) + 1.0d-100 )  ) / log(   z_VLevelsIn   (xyz_kk(i,j,k)+1) / z_VLevelsIn(xyz_kk(i,j,k))      ) * log(   xyz_VLevelsOut(i,j,k) / z_VLevelsIn(xyz_kk(i,j,k))      ) + log( xyz_VarIn(i,j,xyz_kk(i,j,k)) + 1.0d-100 )
              xyz_VarOut(i,j,k) = exp( xyz_VarOut(i,j,k) )

            end do
          end do
        end do

      else
        ! log-linear

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

              xyz_VarOut(i,j,k) = (   xyz_VarIn(i,j,xyz_kk(i,j,k)+1) - xyz_VarIn(i,j,xyz_kk(i,j,k)  )     ) / log(   z_VLevelsIn   (xyz_kk(i,j,k)+1) / z_VLevelsIn(xyz_kk(i,j,k))      ) * log(   xyz_VLevelsOut(i,j,k) / z_VLevelsIn(xyz_kk(i,j,k))      ) + xyz_VarIn(i,j,xyz_kk(i,j,k))

            end do
          end do
        end do

      end if

    else

      if ( FlagLogLV ) then
        ! linear-log

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

              xyz_VarOut(i,j,k) = log(   ( xyz_VarIn(i,j,xyz_kk(i,j,k)+1) + 1.0d-100 ) / ( xyz_VarIn(i,j,xyz_kk(i,j,k)  ) + 1.0d-100 )  ) / (   z_VLevelsIn(xyz_kk(i,j,k)+1) - z_VLevelsIn(xyz_kk(i,j,k)  )    ) * (   xyz_VLevelsOut(i,j,k) - z_VLevelsIn(xyz_kk(i,j,k))      ) + log( xyz_VarIn(i,j,xyz_kk(i,j,k)) + 1.0d-100 )
              xyz_VarOut(i,j,k) = exp( xyz_VarOut(i,j,k) )

            end do
          end do
        end do

      else
        ! linear-linear

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

              xyz_VarOut(i,j,k) = (   xyz_VarIn(i,j,xyz_kk(i,j,k)+1) - xyz_VarIn(i,j,xyz_kk(i,j,k)  ) ) / (   z_VLevelsIn(xyz_kk(i,j,k)+1) - z_VLevelsIn(xyz_kk(i,j,k)  )   ) * (   xyz_VLevelsOut(i,j,k) - z_VLevelsIn(xyz_kk(i,j,k))     ) + xyz_VarIn(i,j,xyz_kk(i,j,k))

            end do
          end do
        end do

      end if

    end if


    if ( FlagPositiveDefLV ) then

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

            if ( xyz_VarOut(i,j,k) < 0.0_DP ) then
              xyz_VarOut(i,j,k) = 0.0_DP
            end if

          end do
        end do
      end do

    end if


!!$    i = 0
!!$    j = jmax / 2
!!$    do k = 1, NVLevels
!!$      write( 92, * ) z_VLevelsIn(k), xyz_VarIn(i,j,k)
!!$    end do
!!$    write( 92, * )
!!$    call flush( 92 )
!!$    do k = 1, kmax
!!$      write( 93, * ) xyz_VLevelsOut(i,j,k), xyz_VarOut(i,j,k)
!!$    end do
!!$    write( 93, * )
!!$    call flush( 93 )
!!$    stop


  end subroutine VerticalInterpolation
a_TSDataInfo
Variable :
a_TSDataInfo( NumMaxStructArr ) :type(time_series_data), save
flag_mpi_split
Variable :
flag_mpi_split = .true. :logical, save
module_name
Constant :
module_name = ‘read_time_series_from_file‘ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
read_time_series_inited
Variable :
read_time_series_inited = .false. :logical, save
: ����設������. Initialization flag
time_series_data
Derived Type :
Keyword :character(STRING)
: Keyword
FileName :character(STRING)
: ���¡ã�¤ã����. File name
VarName :character(STRING)
: å¤��°å��. Variable name
NDims :integer
tmax :integer
NVLevels :integer
z_VLevels(:) :real(DP), pointer
a_time(:) :real(DP), pointer
a_tindex(:) :integer , pointer
xyza_SavedData(:,:,:,:) :real(DP), pointer
xyz_VarTimeInterpolated(:,:,:) :real(DP), pointer
TimeFromOriginToInitialDate :real(DP)
version
Constant :
version = ’$Name: $’ // ’$Id: read_time_series.f90,v 1.19 2015/01/29 12:02:29 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version