Class history_file_io
In: io/history_file_io.F90

���¹ã�������¼ã�¿å�ºå��

History data output

Note that Japanese and English are described in parallel.

���¹ã�������¼ã�¿å�ºå����������, ���»é�²è�, �»é�²å��°ã��¡¨ç¤ºã�� çµ�äº�������è¡����¾ã��. [gtool5 ���¤ã������]{www.gfd-dennou.org/library/gtool} �� gtool_historyauto �¢ã�¸ã�¥ã�¼ã���������¾ã��.

�����¼ã�¿ã���ºå����, �¢ã�����������­ã�°ã��������������, gtool_historyauto �¢ã�¸ã�¥ã�¼ã��������ä¾������� HistoryAutoAddVariable ������ HistoryAutoPut �������¾ã��.

Methods

Included Modules

gridset dc_types dc_message fileset constants0 axesset namelist_util timeset gtool_historyauto dc_iounit dc_string

Public Instance methods

Subroutine :

���¹ã�������¼ã�¿ã���¡ã�¤ã���ºå�����äº�������è¡����¾ã��.

Terminate history data files output.

[Source]

  subroutine HistoryFileClose
    !
    ! ���¹ã�������¼ã�¿ã���¡ã�¤ã���ºå�����äº�������è¡����¾ã��. 
    !
    ! Terminate history data files output. 

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

    ! gtool4 netCDF ���¼ã�¿ã���¥å�ºå���¤ã�³ã�¿ã�¼ã���§ã�¼ã�� (大è�模ã�¢ã������)
    ! Interface of Input/Output of gtool4 netCDF data (For large models)
    !
    use gtool_historyauto, only: HistoryAutoClose

    ! 宣�� ; Declaration statements
    !
    implicit none

    ! �業��
    ! Work variables
    !

    ! ���� ; Executable statement
    !

    call HistoryAutoClose

  end subroutine HistoryFileClose
Subroutine :

history_file_io �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��.

"history_file_io" module is initialized.

[Source]

  subroutine HistoryFileOpen
    !
    ! history_file_io �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. 
    !
    !
    ! "history_file_io" module is initialized. 
    !
    !

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

    ! �ºå�����¡ã�¤ã�����ºæ������
    ! Basic information for output files
    ! 
    use fileset, only: FileTitle, FileSource, FileInstitution
                              ! ���¼ã�¿ã���¡ã�¤ã������çµ�������´ã����çµ�ç¹�/��äº�. 
                              ! Institution or person that changes data files for the last time

    ! �����»æ�°å­¦å®��°è¨­å®�
    ! Physical and mathematical constants settings
    !
    use constants0, only: PI                    ! $ \pi $.
                              ! �����. Circular constant

    ! 座æ����¼ã�¿è¨­å®�
    ! Axes data settings
    !
    use axesset, only: AxnameX  , AxnameY  , AxnameZ  , AxnameR  , AxnameSSZ, AxnameSSR, AxnameWN , AxnameT  , x_Lon, x_Lon_Weight, y_Lat, y_Lat_Weight, z_Sigma, r_Sigma, z_DelSigma, w_Number, r_SSDepth, z_SSDepth
                              ! subsurface grid at midpoint of layer

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

    ! ���»ç���
    ! Time control
    !
    use timeset, only: RestartTime, EndTime, InitialDate, DelTime               ! $ \Delta t $ [s]

    ! gtool4 netCDF ���¼ã�¿ã���¥å�ºå���¤ã�³ã�¿ã�¼ã���§ã�¼ã�� (大è�模ã�¢ã������)
    ! Interface of Input/Output of gtool4 netCDF data (For large models)
    !
    use gtool_historyauto, only: HistoryAutoCreate, HistoryAutoAddAttr, HistoryAutoAddWeight, HistoryAutoPutAxis, HistoryAutoPutAxisMPI

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

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

    ! ç¨��¥å�������¡ã��
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! æ¨�æº��ºå�����ç½����. Unit number of standard output

    ! 宣�� ; Declaration statements
    !
    implicit none

    ! �業��
    ! Work variables
    !
    logical:: flag_mpi_init

    ! ���� ; Executable statement
    !

    if ( history_file_io_inited ) return
    call InitCheck

    ! �����������¤ã��¨­å®�
    ! Default values settings
    !
    DefaultIntValue = 1.0
    DefaultIntUnit  = 'sec'
    DefaultFilePrefix = ''
!!$    DefaultIntValue = 1.0
!!$    DefaultIntUnit  = 'hrs'
!!$    DefaultFilePrefix = 'data01/'

    flag_mpi_init = .false.

    ! HistoryAutoCreate ������������
    ! Initialization by "HistoryAutoCreate"
    !
    call HistoryAutoCreate( title = trim(FileTitle) // ' history data', source = FileSource, institution = FileInstitution, dims = (/ AxnameX, AxnameY, AxnameZ, AxnameR, AxnameSSZ, AxnameSSR, AxnameWN, AxnameT /), dimsizes = (/ imax, jmax, kmax, kmax + 1, max(kslmax,1), kslmax+1, lmax, 0 /), longnames = (/ 'longitude                                       ', 'latitude                                        ', 'sigma at layer midpoints                        ', 'sigma at layer interface (half level)           ', 'depth at subsurface layer midpoints             ', 'depth at subsurface layer interface (half level)', 'subscript of spectral data                      ', 'time                                            ' /), units = (/ 'degree_east ', 'degree_north', '1           ', '1           ', 'm           ', 'm           ', '1           ', DefaultIntUnit /), xtypes = (/ 'float', 'float', 'float', 'float', 'float', 'float', 'int  ', 'float' /), origin  = RestartTime, terminus = EndTime + 2. * DelTime, interval = DefaultIntValue, #ifdef INCLUDE_TIME_ORIGIN #endif
!!$      &     slice_start  = (/ 1.0, 1.0, 1.0, 1.0, 1.0 /), & ! (in) optional
!!$      &     slice_end    = (/ 0.0, 0.0, 0.0, 0.0, 0.0 /), & ! (in) optional
!!$      &     slice_stride = (/   1,   1,   1,   1,   1 /), & ! (in) optional
!!$      &    space_average = (/ .false., .false., .false., &
!!$      &                       .false., .false. /), &        ! (in) optional
!!$      & newfile_interval = real( delta_time * 10 ), &       ! (in) optional

!!$      &  flag_mpi_gather = flag_mpi_init, &                    ! (in) optional file_prefix = DefaultFilePrefix, namelist_filename = namelist_filename )                ! (in) optional


    ! 座æ����¼ã�¿ã�¸ã����§ã��¨­å®�
    ! Attributes of axes data settings
    !
    call HistoryAutoAddAttr( varname = 'lon', attrname = 'standard_name', value = 'longitude' )                            ! (in)
    call HistoryAutoAddAttr( varname = 'lat', attrname = 'standard_name', value = 'latitude' )                             ! (in)
    call HistoryAutoAddAttr( varname = 'sig', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate' )          ! (in)
    call HistoryAutoAddAttr( varname = 'sigm', attrname = 'standard_name', value = 'atmosphere_sigma_coordinate' )          ! (in)
    call HistoryAutoAddAttr( varname = 'sig', attrname = 'positive', value = 'down' )                                 ! (in)
    call HistoryAutoAddAttr( varname = 'sigm', attrname = 'positive', value = 'down' )                                 ! (in)
    call HistoryAutoAddAttr( varname = 'ssz', attrname = 'standard_name', value = 'depth' )                                ! (in)
    call HistoryAutoAddAttr( varname = 'sszi', attrname = 'standard_name', value = 'depth' )                                ! (in)

    ! 座æ����¼ã�¿ã��¨­å®�
    ! Axes data settings
    !
    call HistoryAutoPutAxis( 'lon',  x_Lon / PI * 180.0_DP )  ! (in)
    call HistoryAutoPutAxis( 'lat',  y_Lat / PI * 180.0_DP )  ! (in)
    call HistoryAutoPutAxis( 'sig',  z_Sigma )                ! (in)
    call HistoryAutoPutAxis( 'sigm', r_Sigma )                ! (in)
    if ( kslmax == 0 ) then
      call HistoryAutoPutAxis( 'ssz',  r_SSDepth )              ! (in)
    else
      call HistoryAutoPutAxis( 'ssz',  z_SSDepth )              ! (in)
    end if
    call HistoryAutoPutAxis( 'sszi', r_SSDepth )              ! (in)
    call HistoryAutoPutAxis( 'wn',   w_Number )               ! (in)

    ! 座æ����¿ã��¨­å®�
    ! Axes weights settings
    !
    call HistoryAutoAddWeight( dim = 'lon', weight = x_Lon_Weight, units = 'radian', xtype = 'double' )  ! (in) optional
    call HistoryAutoAddWeight( dim = 'lat', weight = y_Lat_Weight, units = 'radian', xtype = 'double' )  ! (in) optional
    call HistoryAutoAddWeight( dim = 'sig', weight = z_DelSigma, xtype = 'double' )                    ! (in) optional

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

    history_file_io_inited = .true.
  end subroutine HistoryFileOpen
history_file_io_inited
Variable :
history_file_io_inited = .false. :logical, save, public
: ����設������. Initialization flag

Private Instance methods

DefaultFilePrefix
Variable :
DefaultFilePrefix :character(STRING)
: ���¹ã�������¼ã�¿ã�����¡ã�¤ã������Ž¥�­è� (������������). Prefixes of history data filenames (default value)
DefaultIntUnit
Variable :
DefaultIntUnit :character(12), save
: ���¹ã�������¼ã�¿ã���ºå����������ä½� (������������). Unit for interval of history data output (default value)
DefaultIntValue
Variable :
DefaultIntValue :real(DP), save
: ���¹ã�������¼ã�¿ã���ºå���������°å�� (������������). Numerical value for interval of history data output (default value)
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

    ! �ºå�����¡ã�¤ã�����ºæ�����±ç���
    ! Management basic information for output files
    !
    use fileset, only: fileset_inited

    ! �¼å��¹è¨­å®�
    ! Grid points settings
    !
    use gridset, only: gridset_inited

    ! 座æ����¼ã�¿è¨­å®�
    ! Axes data settings
    !
    use axesset, only: axesset_inited

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

    ! ���� ; Executable statement
    !

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

    if ( .not. fileset_inited ) call MessageNotify( 'E', module_name, '"fileset" module is not initialized.' )

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

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

    if ( .not. timeset_inited ) call MessageNotify( 'E', module_name, '"timeset" module is not initialized.' )

  end subroutine InitCheck
module_name
Constant :
module_name = ‘history_file_io :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: history_file_io.F90,v 1.9 2013/09/16 12:23:38 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version