Class axis_type_mod
In: src/shared/axis/axis_type.f90

end

Methods

Included Modules

type_mod gt4_history dc_trace

Public Instance methods

attrs(:) :type(GT_HISTORY_ATTR), intent(inout)
: end begin
 In/Out

begin

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

[Source]

  subroutine axis_attrs_init1(attrs)
  !
  !==== Dependency
  !

                                                                 !=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 axis_attrs_init1
attrs :type(GT_HISTORY_ATTR), intent(inout)
: end begin
 In/Out

begin

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

[Source]

  subroutine axis_attrs_init0(attrs)
  !
  !==== Dependency
  !

                                                                 !=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 axis_attrs_init0
from(:) :type(AXISINFO), intent(in)
: end begin
 Input
to(:) :type(AXISINFO), intent(out)
: Output

begin

Copy AXISINFO data (for 1 dimensional data)

[Source]

  subroutine axis_type_copy1(from, to)
  !
  !==== Dependency
  !

                                                                 !=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 axis_type_copy1
from :type(AXISINFO), intent(in)
: end begin
 Input
to :type(AXISINFO), intent(out)
: Output

Copy AXISINFO data (for 0 dimensional data)

[Source]

  subroutine axis_type_copy0(from, to)
  !
  !==== Dependency
  !

                                                                 !=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 ( associated(from%attrs) ) then
       allocate( to%attrs(size(from%attrs(:))) )
       call axis_attrs_copy(from%attrs(:), to%attrs(:))
    else
       if ( associated(to%attrs) ) then
          deallocate( to%attrs )
       endif
    endif

    call EndSub(subname)
  end subroutine axis_type_copy0

[Validate]