historyautoaddattr.f90

Path: gtool/gtool_historyauto/historyautoaddattr.f90
Last Update: Sun May 10 21:19:18 +0900 2009

属性付加

Add Attributes

Authors:Yasuhiro MORIKAWA
Version:$Id: historyautoaddattr.f90,v 1.1 2009-05-10 12:19:18 morikawa Exp $
Tag Name:$Name: gtool5-20101228-1 $
Copyright:Copyright (C) GFD Dennou Club, 2008-2009. All rights reserved.
License:See COPYRIGHT

Required files

Methods

Included Modules

gtool_historyauto_internal gtool_history dc_trace dc_error dc_string dc_types

Public Instance methods

Subroutine :
varname :character(*), intent(in)
: 変数の名前.

ここで指定するものは, HistoryAutoCreate の dims , または HistoryAutoAddWeight の varname で既に指定されてい なければなりません.

Name of a variable.

This must be specified with dims in HistoryAutoCreate, or varname in "HistoryAutoAddWeight".

attrname :character(*), intent(in)
: 属性の名前. Name of an attribute.
value :character(*), intent(in)
: 属性の値. Value of an attribute.

座標変数および座標重み変数に属性を付加します. このサブルーチンを用いる前に, HistoryAutoCreate による初期設定が 必要です.

  • 座標変数については, HistoryAutoCreate の "dims" に与えられた もののみ指定可能です.
  • 座標重み変数については, HistoryAutoAddWeight で与えられた もののみ指定可能です.
  • HistoryAutoAddAttr は複数のサブルーチンの総称名です. value にはいくつかの型を与えることが可能です. 下記のサブルーチンを参照ください.

Add attributes axes or weights of axes. Initialization by "HistoryAutoCreate" is needed before use of this subroutine.

  • About axes, "dims" specified by "HistoryAutoCreate" can be specified.
  • About weights of axes, "dims" specified by "HistoryAutoAddWeight" can be specified.
  • "HistoryAutoAddAttr" is a generic name of multiple subroutines. Then some data type can be specified to "value".

[Source]

  subroutine HistoryAutoAddAttrChar0( varname, attrname, value )
    !
                        !
    ! 座標変数および座標重み変数に属性を付加します. 
    ! このサブルーチンを用いる前に, HistoryAutoCreate による初期設定が
    ! 必要です.
    ! 
    ! * 座標変数については, HistoryAutoCreate の "dims" に与えられた
    !   もののみ指定可能です. 
    !
    ! * 座標重み変数については, HistoryAutoAddWeight で与えられた
    !   もののみ指定可能です. 
    !
    ! * *HistoryAutoAddAttr* は複数のサブルーチンの総称名です. *value* 
    !   にはいくつかの型を与えることが可能です.
    !   下記のサブルーチンを参照ください.
    !
    ! Add attributes axes or weights of axes. 
    ! Initialization by "HistoryAutoCreate" is needed 
    ! before use of this subroutine. 
    ! 
    ! * About axes, "dims" specified by "HistoryAutoCreate" can be
    !   specified. 
    !
    ! * About weights of axes, "dims" specified by "HistoryAutoAddWeight" 
    !   can be specified. 
    !
    ! * "HistoryAutoAddAttr" is a generic name of multiple subroutines. 
    !   Then some data type can be specified to "value". 
    !
                    
    !
    use gtool_historyauto_internal, only: initialized, numdims, numwgts, gthst_axes, gthst_weights
    use gtool_history, only: HistoryAxisAddAttr, HistoryAxisInquire, HistoryVarinfoAddAttr, HistoryVarinfoInquire
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_string, only: toChar
    use dc_types, only: DP, STRING, TOKEN
    implicit none
    character(*), intent(in):: varname
                                                  ! 変数の名前.
                              !
                              ! ここで指定するものは,
                              ! HistoryAutoCreate の *dims* ,
                              ! または HistoryAutoAddWeight の
                              ! *varname* で既に指定されてい
                              ! なければなりません.
                              ! 
                              ! Name of a variable. 
                              !
                              ! This must be specified with *dims*
                              ! in HistoryAutoCreate, or 
                              ! *varname* in "HistoryAutoAddWeight". 
                              ! 
                    
    character(*), intent(in):: attrname
                                                  ! 属性の名前. 
                              ! Name of an attribute. 
                    
    character(*), intent(in):: value
                                                  ! 属性の値. 
                              ! Value of an attribute. 
                    

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoAddAttrChar0"
  continue
    call BeginSub(subname, 'varname=<%c> attrname=<%c>, value=<%c>', c1=trim(varname), c2=trim(attrname), c3=trim(value))
    stat = DC_NOERR
    cause_c = ""

    ! 初期設定チェック
    ! Check initialization
    !
    if ( .not. initialized ) then
      stat = DC_ENOTINIT
      cause_c = 'gtool_historyauto'
      goto 999
    end if

    do i = 1, numdims
      call HistoryAxisInquire( axis = gthst_axes(i), name = name )            ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryAxisAddAttr( axis = gthst_axes(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    do i = 1, numwgts
      call HistoryVarinfoInquire( varinfo = gthst_weights(i), name = name )                  ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryVarinfoAddAttr( varinfo = gthst_weights(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = varname

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoAddAttrChar0
Subroutine :
varname :character(*), intent(in)
attrname :character(*), intent(in)
value :real(DP), intent(in)

[Source]

  subroutine HistoryAutoAddAttrDouble0( varname, attrname, value )
    !
                    
    !
    use gtool_historyauto_internal, only: initialized, numdims, numwgts, gthst_axes, gthst_weights
    use gtool_history, only: HistoryAxisAddAttr, HistoryAxisInquire, HistoryVarinfoAddAttr, HistoryVarinfoInquire
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_string, only: toChar
    use dc_types, only: DP, STRING, TOKEN
    implicit none
    character(*), intent(in):: varname
                    
    character(*), intent(in):: attrname
                    
    real(DP), intent(in):: value
                    

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoAddAttrDouble0"
  continue
    call BeginSub(subname, 'varname=<%c> attrname=<%c>, value=<%c>', c1=trim(varname), c2=trim(attrname), c3=trim(toChar(value)))
    stat = DC_NOERR
    cause_c = ""

    ! 初期設定チェック
    ! Check initialization
    !
    if ( .not. initialized ) then
      stat = DC_ENOTINIT
      cause_c = 'gtool_historyauto'
      goto 999
    end if

    do i = 1, numdims
      call HistoryAxisInquire( axis = gthst_axes(i), name = name )            ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryAxisAddAttr( axis = gthst_axes(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    do i = 1, numwgts
      call HistoryVarinfoInquire( varinfo = gthst_weights(i), name = name )                  ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryVarinfoAddAttr( varinfo = gthst_weights(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = varname

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoAddAttrDouble0
Subroutine :
varname :character(*), intent(in)
attrname :character(*), intent(in)
value(:) :real(DP), intent(in)

[Source]

  subroutine HistoryAutoAddAttrDouble1( varname, attrname, value )
    !
                    
    !
    use gtool_historyauto_internal, only: initialized, numdims, numwgts, gthst_axes, gthst_weights
    use gtool_history, only: HistoryAxisAddAttr, HistoryAxisInquire, HistoryVarinfoAddAttr, HistoryVarinfoInquire
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_string, only: toChar
    use dc_types, only: DP, STRING, TOKEN
    implicit none
    character(*), intent(in):: varname
                    
    character(*), intent(in):: attrname
                    
    real(DP), intent(in):: value(:)
                    

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoAddAttrDouble1"
  continue
    call BeginSub(subname, 'varname=<%c> attrname=<%c>, value=<%c>', c1=trim(varname), c2=trim(attrname), c3=trim(toChar(value)))
    stat = DC_NOERR
    cause_c = ""

    ! 初期設定チェック
    ! Check initialization
    !
    if ( .not. initialized ) then
      stat = DC_ENOTINIT
      cause_c = 'gtool_historyauto'
      goto 999
    end if

    do i = 1, numdims
      call HistoryAxisInquire( axis = gthst_axes(i), name = name )            ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryAxisAddAttr( axis = gthst_axes(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    do i = 1, numwgts
      call HistoryVarinfoInquire( varinfo = gthst_weights(i), name = name )                  ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryVarinfoAddAttr( varinfo = gthst_weights(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = varname

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoAddAttrDouble1
Subroutine :
varname :character(*), intent(in)
attrname :character(*), intent(in)
value :integer, intent(in)

[Source]

  subroutine HistoryAutoAddAttrInt0( varname, attrname, value )
    !
                    
    !
    use gtool_historyauto_internal, only: initialized, numdims, numwgts, gthst_axes, gthst_weights
    use gtool_history, only: HistoryAxisAddAttr, HistoryAxisInquire, HistoryVarinfoAddAttr, HistoryVarinfoInquire
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_string, only: toChar
    use dc_types, only: DP, STRING, TOKEN
    implicit none
    character(*), intent(in):: varname
                    
    character(*), intent(in):: attrname
                    
    integer, intent(in):: value
                    

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoAddAttrInt0"
  continue
    call BeginSub(subname, 'varname=<%c> attrname=<%c>, value=<%c>', c1=trim(varname), c2=trim(attrname), c3=trim(toChar(value)))
    stat = DC_NOERR
    cause_c = ""

    ! 初期設定チェック
    ! Check initialization
    !
    if ( .not. initialized ) then
      stat = DC_ENOTINIT
      cause_c = 'gtool_historyauto'
      goto 999
    end if

    do i = 1, numdims
      call HistoryAxisInquire( axis = gthst_axes(i), name = name )            ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryAxisAddAttr( axis = gthst_axes(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    do i = 1, numwgts
      call HistoryVarinfoInquire( varinfo = gthst_weights(i), name = name )                  ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryVarinfoAddAttr( varinfo = gthst_weights(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = varname

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoAddAttrInt0
Subroutine :
varname :character(*), intent(in)
attrname :character(*), intent(in)
value(:) :integer, intent(in)

[Source]

  subroutine HistoryAutoAddAttrInt1( varname, attrname, value )
    !
                    
    !
    use gtool_historyauto_internal, only: initialized, numdims, numwgts, gthst_axes, gthst_weights
    use gtool_history, only: HistoryAxisAddAttr, HistoryAxisInquire, HistoryVarinfoAddAttr, HistoryVarinfoInquire
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_string, only: toChar
    use dc_types, only: DP, STRING, TOKEN
    implicit none
    character(*), intent(in):: varname
                    
    character(*), intent(in):: attrname
                    
    integer, intent(in):: value(:)
                    

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoAddAttrInt1"
  continue
    call BeginSub(subname, 'varname=<%c> attrname=<%c>, value=<%c>', c1=trim(varname), c2=trim(attrname), c3=trim(toChar(value)))
    stat = DC_NOERR
    cause_c = ""

    ! 初期設定チェック
    ! Check initialization
    !
    if ( .not. initialized ) then
      stat = DC_ENOTINIT
      cause_c = 'gtool_historyauto'
      goto 999
    end if

    do i = 1, numdims
      call HistoryAxisInquire( axis = gthst_axes(i), name = name )            ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryAxisAddAttr( axis = gthst_axes(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    do i = 1, numwgts
      call HistoryVarinfoInquire( varinfo = gthst_weights(i), name = name )                  ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryVarinfoAddAttr( varinfo = gthst_weights(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = varname

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoAddAttrInt1
Subroutine :
varname :character(*), intent(in)
attrname :character(*), intent(in)
value :logical, intent(in)

[Source]

  subroutine HistoryAutoAddAttrLogical0( varname, attrname, value )
    !
                    
    !
    use gtool_historyauto_internal, only: initialized, numdims, numwgts, gthst_axes, gthst_weights
    use gtool_history, only: HistoryAxisAddAttr, HistoryAxisInquire, HistoryVarinfoAddAttr, HistoryVarinfoInquire
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_string, only: toChar
    use dc_types, only: DP, STRING, TOKEN
    implicit none
    character(*), intent(in):: varname
                    
    character(*), intent(in):: attrname
                    
    logical, intent(in):: value
                    

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoAddAttrLogical0"
  continue
    call BeginSub(subname, 'varname=<%c> attrname=<%c>, value=<%c>', c1=trim(varname), c2=trim(attrname), c3=trim(toChar(value)))
    stat = DC_NOERR
    cause_c = ""

    ! 初期設定チェック
    ! Check initialization
    !
    if ( .not. initialized ) then
      stat = DC_ENOTINIT
      cause_c = 'gtool_historyauto'
      goto 999
    end if

    do i = 1, numdims
      call HistoryAxisInquire( axis = gthst_axes(i), name = name )            ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryAxisAddAttr( axis = gthst_axes(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    do i = 1, numwgts
      call HistoryVarinfoInquire( varinfo = gthst_weights(i), name = name )                  ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryVarinfoAddAttr( varinfo = gthst_weights(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = varname

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoAddAttrLogical0
Subroutine :
varname :character(*), intent(in)
attrname :character(*), intent(in)
value :real, intent(in)

[Source]

  subroutine HistoryAutoAddAttrReal0( varname, attrname, value )
    !
                    
    !
    use gtool_historyauto_internal, only: initialized, numdims, numwgts, gthst_axes, gthst_weights
    use gtool_history, only: HistoryAxisAddAttr, HistoryAxisInquire, HistoryVarinfoAddAttr, HistoryVarinfoInquire
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_string, only: toChar
    use dc_types, only: DP, STRING, TOKEN
    implicit none
    character(*), intent(in):: varname
                    
    character(*), intent(in):: attrname
                    
    real, intent(in):: value
                    

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoAddAttrReal0"
  continue
    call BeginSub(subname, 'varname=<%c> attrname=<%c>, value=<%c>', c1=trim(varname), c2=trim(attrname), c3=trim(toChar(value)))
    stat = DC_NOERR
    cause_c = ""

    ! 初期設定チェック
    ! Check initialization
    !
    if ( .not. initialized ) then
      stat = DC_ENOTINIT
      cause_c = 'gtool_historyauto'
      goto 999
    end if

    do i = 1, numdims
      call HistoryAxisInquire( axis = gthst_axes(i), name = name )            ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryAxisAddAttr( axis = gthst_axes(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    do i = 1, numwgts
      call HistoryVarinfoInquire( varinfo = gthst_weights(i), name = name )                  ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryVarinfoAddAttr( varinfo = gthst_weights(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = varname

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoAddAttrReal0
Subroutine :
varname :character(*), intent(in)
attrname :character(*), intent(in)
value(:) :real, intent(in)

[Source]

  subroutine HistoryAutoAddAttrReal1( varname, attrname, value )
    !
                    
    !
    use gtool_historyauto_internal, only: initialized, numdims, numwgts, gthst_axes, gthst_weights
    use gtool_history, only: HistoryAxisAddAttr, HistoryAxisInquire, HistoryVarinfoAddAttr, HistoryVarinfoInquire
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_string, only: toChar
    use dc_types, only: DP, STRING, TOKEN
    implicit none
    character(*), intent(in):: varname
                    
    character(*), intent(in):: attrname
                    
    real, intent(in):: value(:)
                    

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoAddAttrReal1"
  continue
    call BeginSub(subname, 'varname=<%c> attrname=<%c>, value=<%c>', c1=trim(varname), c2=trim(attrname), c3=trim(toChar(value)))
    stat = DC_NOERR
    cause_c = ""

    ! 初期設定チェック
    ! Check initialization
    !
    if ( .not. initialized ) then
      stat = DC_ENOTINIT
      cause_c = 'gtool_historyauto'
      goto 999
    end if

    do i = 1, numdims
      call HistoryAxisInquire( axis = gthst_axes(i), name = name )            ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryAxisAddAttr( axis = gthst_axes(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    do i = 1, numwgts
      call HistoryVarinfoInquire( varinfo = gthst_weights(i), name = name )                  ! (out)
      if ( trim(varname) == trim(name) ) then
        call HistoryVarinfoAddAttr( varinfo = gthst_weights(i), attrname = attrname, value = value ) ! (in)
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = varname

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoAddAttrReal1