historyautoputaxis.f90

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

座標データの設定

Settings of data of axes.

Authors:Yasuhiro MORIKAWA
Version:$Id: historyautoputaxis.f90,v 1.1 2009-05-10 12:19:17 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_types

Public Instance methods

Subroutine :
dim :character(*), intent(in)
: 座標の名称.

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

Name of axis.

Note that this value must be set as "dims" of "HistoryAutoCreate".

array(:) :real(DP), intent(in)
: 座標データ

データ型は整数, 単精度実数型, 倍精度実数型のどれでもかまいません. ただし, ファイルへ出力される際には, HistoryAutoCreate の xtypes で指定した データ型へ変換されます.

Data of axis

Integer, single or double precision are acceptable as data type. Note that when this is output to a file, data type is converted into "xtypes" specified in "HistoryAutoCreate"

座標データを設定します.

Set data of an axis.

[Source]

  subroutine HistoryAutoPutAxisDouble( dim, array )
    !
    ! 座標データを設定します. 
    !
    ! Set data of an axis. 
    !

    use gtool_historyauto_internal, only: initialized, numdims, data_axes, gthst_axes
    use gtool_history, only: HistoryAxisInquire, HistoryAxisAddAttr, HistoryVarinfoCreate
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, GT_EARGSIZEMISMATCH, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_types, only: DP, STRING, TOKEN

    implicit none
    character(*), intent(in):: dim
                              ! 座標の名称. 
                              !
                              ! ただし, ここで指定するもの
                              ! は, HistoryAutoCreate の *dims*
                              ! 既に指定されていなければなりません.
                              !
                              ! Name of axis. 
                              !
                              ! Note that this value must be set 
                              ! as "dims" of "HistoryAutoCreate". 
                              !
    real(DP), intent(in):: array(:)
                              ! 座標データ
                              !
                              ! データ型は整数, 単精度実数型, 
                              ! 倍精度実数型のどれでもかまいません. 
                              ! ただし, ファイルへ出力される際には, 
                              ! HistoryAutoCreate の *xtypes* で指定した
                              ! データ型へ変換されます. 
                              ! 
                              ! Data of axis
                              !
                              ! Integer, single or double precision are 
                              ! acceptable as data type. 
                              ! Note that when this is output to a file, 
                              ! data type is converted into "xtypes" 
                              ! specified in "HistoryAutoCreate"
                              ! 

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoPutAxisDouble"
  continue
    call BeginSub(subname, 'dim=<%c>', c1=trim(dim) )
    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(dim) == trim(name) ) then
        data_axes(i) % a_axis = array
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = dim

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoPutAxisDouble
Subroutine :
dim :character(*), intent(in)
: 座標の名称.

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

Name of axis.

Note that this value must be set as "dims" of "HistoryAutoCreate".

array(:) :integer, intent(in)
: 座標データ

データ型は整数, 単精度実数型, 倍精度実数型のどれでもかまいません. ただし, ファイルへ出力される際には, HistoryAutoCreate の xtypes で指定した データ型へ変換されます.

Data of axis

Integer, single or double precision are acceptable as data type. Note that when this is output to a file, data type is converted into "xtypes" specified in "HistoryAutoCreate"

座標データを設定します.

Set data of an axis.

[Source]

  subroutine HistoryAutoPutAxisInt( dim, array )
    !
    ! 座標データを設定します. 
    !
    ! Set data of an axis. 
    !

    use gtool_historyauto_internal, only: initialized, numdims, data_axes, gthst_axes
    use gtool_history, only: HistoryAxisInquire, HistoryAxisAddAttr, HistoryVarinfoCreate
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, GT_EARGSIZEMISMATCH, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_types, only: DP, STRING, TOKEN

    implicit none
    character(*), intent(in):: dim
                              ! 座標の名称. 
                              !
                              ! ただし, ここで指定するもの
                              ! は, HistoryAutoCreate の *dims*
                              ! 既に指定されていなければなりません.
                              !
                              ! Name of axis. 
                              !
                              ! Note that this value must be set 
                              ! as "dims" of "HistoryAutoCreate". 
                              !
    integer, intent(in):: array(:)
                              ! 座標データ
                              !
                              ! データ型は整数, 単精度実数型, 
                              ! 倍精度実数型のどれでもかまいません. 
                              ! ただし, ファイルへ出力される際には, 
                              ! HistoryAutoCreate の *xtypes* で指定した
                              ! データ型へ変換されます. 
                              ! 
                              ! Data of axis
                              !
                              ! Integer, single or double precision are 
                              ! acceptable as data type. 
                              ! Note that when this is output to a file, 
                              ! data type is converted into "xtypes" 
                              ! specified in "HistoryAutoCreate"
                              ! 

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoPutAxisInt"
  continue
    call BeginSub(subname, 'dim=<%c>', c1=trim(dim) )
    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(dim) == trim(name) ) then
        data_axes(i) % a_axis = array
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = dim

999 continue
    call StoreError(stat, subname, cause_c = cause_c)
    call EndSub(subname)
  end subroutine HistoryAutoPutAxisInt
Subroutine :
dim :character(*), intent(in)
: 座標の名称.

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

Name of axis.

Note that this value must be set as "dims" of "HistoryAutoCreate".

array(:) :real, intent(in)
: 座標データ

データ型は整数, 単精度実数型, 倍精度実数型のどれでもかまいません. ただし, ファイルへ出力される際には, HistoryAutoCreate の xtypes で指定した データ型へ変換されます.

Data of axis

Integer, single or double precision are acceptable as data type. Note that when this is output to a file, data type is converted into "xtypes" specified in "HistoryAutoCreate"

座標データを設定します.

Set data of an axis.

[Source]

  subroutine HistoryAutoPutAxisReal( dim, array )
    !
    ! 座標データを設定します. 
    !
    ! Set data of an axis. 
    !

    use gtool_historyauto_internal, only: initialized, numdims, data_axes, gthst_axes
    use gtool_history, only: HistoryAxisInquire, HistoryAxisAddAttr, HistoryVarinfoCreate
    use dc_trace, only: BeginSub, EndSub
    use dc_error, only: StoreError, DC_NOERR, GT_EARGSIZEMISMATCH, HST_ENOAXISNAME, DC_ENOTINIT
    use dc_types, only: DP, STRING, TOKEN

    implicit none
    character(*), intent(in):: dim
                              ! 座標の名称. 
                              !
                              ! ただし, ここで指定するもの
                              ! は, HistoryAutoCreate の *dims*
                              ! 既に指定されていなければなりません.
                              !
                              ! Name of axis. 
                              !
                              ! Note that this value must be set 
                              ! as "dims" of "HistoryAutoCreate". 
                              !
    real, intent(in):: array(:)
                              ! 座標データ
                              !
                              ! データ型は整数, 単精度実数型, 
                              ! 倍精度実数型のどれでもかまいません. 
                              ! ただし, ファイルへ出力される際には, 
                              ! HistoryAutoCreate の *xtypes* で指定した
                              ! データ型へ変換されます. 
                              ! 
                              ! Data of axis
                              !
                              ! Integer, single or double precision are 
                              ! acceptable as data type. 
                              ! Note that when this is output to a file, 
                              ! data type is converted into "xtypes" 
                              ! specified in "HistoryAutoCreate"
                              ! 

    character(STRING):: name
    integer:: stat, i
    character(STRING):: cause_c
    character(*), parameter:: subname = "HistoryAutoPutAxisReal"
  continue
    call BeginSub(subname, 'dim=<%c>', c1=trim(dim) )
    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(dim) == trim(name) ) then
        data_axes(i) % a_axis = array
        goto 999
      end if
    end do

    stat = HST_ENOAXISNAME
    cause_c = dim

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