Class axis_type_mod
In: axis/axis_type.f90

    Copyright (C) GFD Dennou Club, 2005. All rights reserved.

                                                                 !=begin

Module axis_type_mod

  * Developers: Morikawa Yasuhiro
  * Version: $Id: axis_type.f90,v 1.8 2005/01/19 08:52:24 morikawa Exp $
  * Tag Name: $Name:  $
  * Change History:

Overview

This module provide derived types including all information about Axes data, and utility to treat the derived type variables. 座標軸に関する全ての情報を包括する構造体、 およびその構造体変数を扱うためのユーティリティを提供する。

Error Handling

Known Bugs

Note

Future Plans

                                                                 !=end

Methods

Included Modules

type_mod gt4_history type_mod dc_trace type_mod dc_trace type_mod gt4_history dc_trace type_mod gt4_history dc_trace type_mod gt4_history dc_trace

Public Instance methods

begin

Copy AXISATTR (in gt4f90io) data (for 1 dimensional data)

[Source]

subroutine axis_attrs_copy (from, to)

  !
  !==== Dependency
  !
    use type_mod, only: STRING, INTKIND
    use gt4_history, only: GT_HISTORY_ATTR
    use dc_trace, only: BeginSub, EndSub, DbgMessage
                                                                 !=end
    implicit none
                                                                 !=begin
    !==== Input
    !
    type(GT_HISTORY_ATTR), intent(in)  :: from(:)
    !==== Output
    !
    type(GT_HISTORY_ATTR), intent(out) :: to(:)
                                                                 !=end
    integer(INTKIND)                   :: i
    character(STRING), parameter:: subname = "axis_attrs_copy"
  continue

    call BeginSub(subname)

    call DbgMessage('size(from)=<%d>, size(to)=<%d>, So copy <%d> times.', &
         &       i=(/ size(from), size(to), min(size(from),size(to)) /) )

    do i = 1, min( size(from), size(to) )
       call DbgMessage('from(%d) [attrname=<%c> '                // &
            & 'attrtype=<%c> array=<%b> cvalue=<%c>  '        // &
            & 'ivalue=<%d> rvalue=<%r> dvalue=<%f> '          // &
            & 'iarray(1:%d)=<%d, ...> '                       // &
            & 'rarray(1:%d)=<%r, ...> darray(1:%d)=<%f, ...>'  , &
            & c1=trim( from(i)%attrname )                      , &
            & c2=trim( from(i)%attrtype )                      , &
            & c3=trim( from(i)%cvalue )                        , &
            & i=(/ i, from(i)%ivalue                           , &
            &      size(from(i)%iarray)                        , &
            &      from(i)%iarray                              , &
            &      size(from(i)%rarray)                        , &
            &      size(from(i)%darray)                          &
            &   /)                                             , &
            & r=(/from(i)%rvalue, from(i)%rarray/)    , &
            & d=(/from(i)%dvalue, from(i)%darray/)    , &
            & l=(/from(i)%lvalue/)                      )

       allocate(  to(i)%iarray( size(from(i)%iarray) )  )
       allocate(  to(i)%rarray( size(from(i)%rarray) )  )
       allocate(  to(i)%darray( size(from(i)%darray) )  )

       to(i)%attrname  = from(i)%attrname 
       to(i)%attrtype  = from(i)%attrtype 
       to(i)%array     = from(i)%array    
       to(i)%cvalue    = from(i)%cvalue   
       to(i)%ivalue    = from(i)%ivalue   
       to(i)%rvalue    = from(i)%rvalue   
       to(i)%dvalue    = from(i)%dvalue   
       to(i)%lvalue    = from(i)%lvalue   
       to(i)%iarray(:) = from(i)%iarray(:)
       to(i)%rarray(:) = from(i)%rarray(:)
       to(i)%darray(:) = from(i)%darray(:)
    enddo

    call EndSub(subname)

end subroutine

begin

Initialize AXISATTR (in gt4f90io) data (for 0 dimensional data)

[Source]

subroutine axis_attrs_init0 (attrs)

  !
  !==== Dependency
  !
    use type_mod, only: STRING, INTKIND
    use gt4_history, only: GT_HISTORY_ATTR
    use dc_trace, only: BeginSub, EndSub, DbgMessage
                                                                 !=end
    implicit none
                                                                 !=begin
    !==== In/Out
    !
    type(GT_HISTORY_ATTR), intent(inout):: attrs
                                                                 !=end
    character(STRING), parameter:: subname = "axis_attrs_init0"
  continue

    call BeginSub(subname)

    allocate(  attrs%iarray( 1 )  )
    allocate(  attrs%rarray( 1 )  )
    allocate(  attrs%darray( 1 )  )

    attrs%attrname  = ''     
    attrs%attrtype  = ''     
    attrs%array     = .false.
    attrs%cvalue    = ''     
    attrs%ivalue    = 0      
    attrs%rvalue    = 0.0    
    attrs%dvalue    = 0.0d0  
    attrs%lvalue    = .false.
    attrs%iarray(:) = 0      
    attrs%rarray(:) = 0.0    
    attrs%darray(:) = 0.0d0  

    call DbgMessage('Initialize attrs [attrname=<%c> '        // &
         & 'attrtype=<%c> array=<%b> cvalue=<%c>  '        // &
         & 'ivalue=<%d> rvalue=<%r> dvalue=<%f> '          // &
         & 'iarray(1:%d)=<%d, ...> '                       // &
         & 'rarray(1:%d)=<%r, ...> darray(1:%d)=<%f, ...>'  , &
         & c1=trim( attrs%attrname )                        , &
         & c2=trim( attrs%attrtype )                        , &
         & c3=trim( attrs%cvalue )                          , &
         & i=(/ attrs%ivalue                                , &
         &      size(attrs%iarray)                          , &
         &      attrs%iarray                                , &
         &      size(attrs%rarray)                          , &
         &      size(attrs%darray)                            &
         &   /)                                             , &
         & r=(/attrs%rvalue, attrs%rarray/)                 , &
         & d=(/attrs%dvalue, attrs%darray/)                 , &
         & l=(/attrs%lvalue/)                      )

    call EndSub(subname)

end subroutine

begin

Initialize AXISATTR (in gt4f90io) data (for 1 dimensional data)

[Source]

subroutine axis_attrs_init1 (attrs)

  !
  !==== Dependency
  !
    use type_mod, only: STRING, INTKIND
    use gt4_history, only: GT_HISTORY_ATTR
    use dc_trace, only: BeginSub, EndSub, DbgMessage
                                                                 !=end
    implicit none
                                                                 !=begin
    !==== In/Out
    !
    type(GT_HISTORY_ATTR), intent(inout):: attrs(:)
                                                                 !=end
    integer(INTKIND)                    :: i
    character(STRING), parameter:: subname = "axis_attrs_init1"
  continue

    call BeginSub(subname)

    call DbgMessage('size(attrs)=<%d>' , i=(/size(attrs)/) )

    do i = 1, size(attrs)
       call axis_attrs_init(attrs(i))
    enddo

    call EndSub(subname)

end subroutine

begin

Procedure Interface

Copy AXISINFO data (for 0 dimensional data)

[Source]

subroutine axis_type_copy0 (from, to)

  !
  !==== Dependency
  !
    use type_mod, only: STRING
    use dc_trace, only: BeginSub, EndSub
                                                                 !=end
    implicit none
                                                                 !=begin
    !==== Input
    !
    type(AXISINFO), intent(in)  :: from
    !
    !==== Output
    type(AXISINFO), intent(out) :: to
                                                                 !=end
    character(STRING), parameter:: subname = "axis_type_copy0"
  continue

    call BeginSub(subname)
    to%axisinfo%name     = from%axisinfo%name
    to%axisinfo%length   = from%axisinfo%length
    to%axisinfo%longname = from%axisinfo%longname
    to%axisinfo%units    = from%axisinfo%units
    to%axisinfo%xtype    = from%axisinfo%xtype
    to%stored   = from%stored
    allocate( to%a_Dim(size(from%a_Dim)) )
    to%a_Dim(:) = from%a_Dim(:)

    if ( allocated(from%attrs) ) then
       allocate( to%attrs(size(from%attrs(:))) )
       call axis_attrs_copy(from%attrs(:), to%attrs(:))
    else
       if ( allocated(to%attrs) ) then
          deallocate( to%attrs )
       endif
    endif

    call EndSub(subname)

end subroutine

begin

Copy AXISINFO data (for 1 dimensional data)

[Source]

subroutine axis_type_copy1 (from, to)

  !
  !==== Dependency
  !
    use type_mod, only: STRING, INTKIND
    use dc_trace, only: BeginSub, EndSub
                                                                 !=end
    implicit none
                                                                 !=begin
    !==== Input
    !
    type(AXISINFO), intent(in)  :: from(:)
    !==== Output
    !
    type(AXISINFO), intent(out) :: to(:)
                                                                 !=end
    integer(INTKIND)            :: i
    character(STRING), parameter:: subname = "axis_type_copy1"
  continue
    call BeginSub(subname)

    do i = 1, min( size(from), size(to) )
       call axis_type_copy( from(i), to(i) )
    enddo

    call EndSub(subname)

end subroutine

[Validate]