| Path: | dc_utils/dcstringputline.f90 | 
| Last Update: | Fri Mar 20 18:09:52 +0900 2009 | 
| Subroutine : | |
| array(:) : | real(DP), intent(in) | 
| lbounds(1) : | integer, intent(in), optional | 
| ubounds(1) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineDouble1( array, lbounds, ubounds, unit, indent, sd )
                                        
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real(DP), intent(in):: array(:)
  integer, intent(in), optional:: lbounds(1)
  integer, intent(in), optional:: ubounds(1)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(1), ubound_nums(1)
  character(STRING):: size_str, sd_str
  real(DP):: max_value, min_value
  real(DP), allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = array
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<DP-ARRAY:: @size=%c, @max=%f, @min=%f, @avg=%r%c>', d = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineDouble1
          | Subroutine : | |
| array(:,:) : | real(DP), intent(in) | 
| lbounds(2) : | integer, intent(in), optional | 
| ubounds(2) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineDouble2( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real(DP), intent(in):: array(:,:)
  integer, intent(in), optional:: lbounds(2)
  integer, intent(in), optional:: ubounds(2)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(2), ubound_nums(2)
  character(STRING):: size_str, sd_str
  real(DP):: max_value, min_value
  real(DP), allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<DP-ARRAY:: @size=%c, @max=%f, @min=%f, @avg=%r%c>', d = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineDouble2
          | Subroutine : | |
| array(:,:,:) : | real(DP), intent(in) | 
| lbounds(3) : | integer, intent(in), optional | 
| ubounds(3) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineDouble3( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real(DP), intent(in):: array(:,:,:)
  integer, intent(in), optional:: lbounds(3)
  integer, intent(in), optional:: ubounds(3)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(3), ubound_nums(3)
  character(STRING):: size_str, sd_str
  real(DP):: max_value, min_value
  real(DP), allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<DP-ARRAY:: @size=%c, @max=%f, @min=%f, @avg=%r%c>', d = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineDouble3
          | Subroutine : | |
| array(:,:,:,:) : | real(DP), intent(in) | 
| lbounds(4) : | integer, intent(in), optional | 
| ubounds(4) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineDouble4( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real(DP), intent(in):: array(:,:,:,:)
  integer, intent(in), optional:: lbounds(4)
  integer, intent(in), optional:: ubounds(4)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(4), ubound_nums(4)
  character(STRING):: size_str, sd_str
  real(DP):: max_value, min_value
  real(DP), allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<DP-ARRAY:: @size=%c, @max=%f, @min=%f, @avg=%r%c>', d = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineDouble4
          | Subroutine : | |
| array(:,:,:,:,:) : | real(DP), intent(in) | 
| lbounds(5) : | integer, intent(in), optional | 
| ubounds(5) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineDouble5( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real(DP), intent(in):: array(:,:,:,:,:)
  integer, intent(in), optional:: lbounds(5)
  integer, intent(in), optional:: ubounds(5)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(5), ubound_nums(5)
  character(STRING):: size_str, sd_str
  real(DP):: max_value, min_value
  real(DP), allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<DP-ARRAY:: @size=%c, @max=%f, @min=%f, @avg=%r%c>', d = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineDouble5
          | Subroutine : | |
| array(:,:,:,:,:,:) : | real(DP), intent(in) | 
| lbounds(6) : | integer, intent(in), optional | 
| ubounds(6) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineDouble6( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real(DP), intent(in):: array(:,:,:,:,:,:)
  integer, intent(in), optional:: lbounds(6)
  integer, intent(in), optional:: ubounds(6)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(6), ubound_nums(6)
  character(STRING):: size_str, sd_str
  real(DP):: max_value, min_value
  real(DP), allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
    lbound_nums(6) = lbound( array, 6 )
    ubound_nums(6) = ubound( array, 6 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(6)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(6)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<DP-ARRAY:: @size=%c, @max=%f, @min=%f, @avg=%r%c>', d = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineDouble6
          | Subroutine : | |
| array(:,:,:,:,:,:,:) : | real(DP), intent(in) | 
| lbounds(7) : | integer, intent(in), optional | 
| ubounds(7) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineDouble7( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real(DP), intent(in):: array(:,:,:,:,:,:,:)
  integer, intent(in), optional:: lbounds(7)
  integer, intent(in), optional:: ubounds(7)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(7), ubound_nums(7)
  character(STRING):: size_str, sd_str
  real(DP):: max_value, min_value
  real(DP), allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
    lbound_nums(6) = lbound( array, 6 )
    ubound_nums(6) = ubound( array, 6 )
                    
    lbound_nums(7) = lbound( array, 7 )
    ubound_nums(7) = ubound( array, 7 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(6)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(6)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(7)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(7)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<DP-ARRAY:: @size=%c, @max=%f, @min=%f, @avg=%r%c>', d = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineDouble7
          | Subroutine : | |
| array(:) : | integer, intent(in) | 
| lbounds(1) : | integer, intent(in), optional | 
| ubounds(1) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
数値型配列の要約を以下のように印字します. avg は平均値, sd は標準偏差です. 標準偏差は, 論理型オプショナル引数 sd に真を与えたときのみ 表示します.
Summary of numerical array is printed as follows. "avg" is average value, "sd" is standard deviation. Standard deviation is displayed only when .true. is set to logical optional argument "sd".
#<INT-ARRAY:: @size=(1:3), @max=3, @min=1, @avg=2. @sd=0.816496611> #<SP-ARRAY:: @size=(1:1), @max=0., @min=0., @avg=0. @sd=0.> #<DP-ARRAY:: @size=(1:3,1:3,1:3), @max=20., @min=7., @avg=13.5 @sd=3.29140282>
array には整数, 単精度実数, 倍精度実数の配列 (1 〜 7) を 与えます. 配列添字の下限と上限を表示したい場合には, 以下のように lbounds と ubounds を指定します. これらを指定しない場合には, 表示される配列添字は 1:<配列サイズ> となります.
Integer, single precision, and double precision array (1 — 7) is given to array. In order to print the upper bound and the lower bound for subscript of array, specify lbounds and ubounds as follows. Otherwise, 1:<size of array> is printed as subscript of array.
  program putline_test
    use dc_string, only: PutLine
    real:: rarray(-2:2, -3:3)
    rarray(-2:0, -3:0) = -1.0
    rarray(-2:0, 1:3) = -2.0
    rarray(1:2, -3:0) = 1.0
    rarray(1:2, 1:3) = 2.0
    call PutLine ( rarray, &
      & lbounds = lbound(rarray), ubounds = ubound(rarray) )
  end program putline_test
unit には印字する装置番号を指定します. デフォルトは標準出力です. indent には字下げのための空白を与えます.
Unit number for print is specified to unit. Default is standard output. Blank for indent is specified to indent.
subroutine PutLineInt1( array, lbounds, ubounds, unit, indent, sd )
                                          !
  ! 数値型配列の要約を以下のように印字します. 
  ! avg は平均値, sd は標準偏差です. 
  ! 標準偏差は, 論理型オプショナル引数 sd に真を与えたときのみ
  ! 表示します. 
  !
  ! Summary of numerical array is printed as follows.
  ! "avg" is average value, "sd" is standard deviation.
  ! Standard deviation is displayed only when .true. is set to 
  ! logical optional argument "sd". 
  !
  !   #<INT-ARRAY:: @size=(1:3), @max=3, @min=1, @avg=2. @sd=0.816496611>
  !   #<SP-ARRAY:: @size=(1:1), @max=0., @min=0., @avg=0. @sd=0.>
  !   #<DP-ARRAY:: @size=(1:3,1:3,1:3), @max=20., @min=7., @avg=13.5 @sd=3.29140282>
  !
  ! *array* には整数, 単精度実数, 倍精度実数の配列 (1 〜 7) を
  ! 与えます. 配列添字の下限と上限を表示したい場合には, 
  ! 以下のように *lbounds* と *ubounds* を指定します. 
  ! これらを指定しない場合には, 
  ! 表示される配列添字は 1:<配列サイズ> となります.
  ! 
  ! Integer, single precision, and double precision array 
  ! (1 -- 7) is given to *array*. 
  ! In order to print the upper bound and the lower bound 
  ! for subscript of array, 
  ! specify *lbounds* and *ubounds* as follows. 
  ! Otherwise, 1:<size of array> is printed as subscript of array.
  ! 
  !   program putline_test
  !     use dc_string, only: PutLine
  !     real:: rarray(-2:2, -3:3)
  !   
  !     rarray(-2:0, -3:0) = -1.0
  !     rarray(-2:0, 1:3) = -2.0
  !     rarray(1:2, -3:0) = 1.0
  !     rarray(1:2, 1:3) = 2.0
  !     call PutLine ( rarray, & 
  !       & lbounds = lbound(rarray), ubounds = ubound(rarray) )
  !   end program putline_test
  !
  ! *unit* には印字する装置番号を指定します. デフォルトは標準出力です.
  ! *indent* には字下げのための空白を与えます.
  !
  ! Unit number for print is specified to *unit*. Default is standard output.
  ! Blank for indent is specified to *indent*.
  !
                    
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  integer, intent(in):: array(:)
  integer, intent(in), optional:: lbounds(1)
  integer, intent(in), optional:: ubounds(1)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(1), ubound_nums(1)
  character(STRING):: size_str, sd_str
  integer:: max_value, min_value
  integer, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = array
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<INT-ARRAY:: @size=%c, @max=%d, @min=%d, @avg=%r%c>', i = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineInt1
          | Subroutine : | |
| array(:,:) : | integer, intent(in) | 
| lbounds(2) : | integer, intent(in), optional | 
| ubounds(2) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineInt2( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  integer, intent(in):: array(:,:)
  integer, intent(in), optional:: lbounds(2)
  integer, intent(in), optional:: ubounds(2)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(2), ubound_nums(2)
  character(STRING):: size_str, sd_str
  integer:: max_value, min_value
  integer, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<INT-ARRAY:: @size=%c, @max=%d, @min=%d, @avg=%r%c>', i = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineInt2
          | Subroutine : | |
| array(:,:,:) : | integer, intent(in) | 
| lbounds(3) : | integer, intent(in), optional | 
| ubounds(3) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineInt3( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  integer, intent(in):: array(:,:,:)
  integer, intent(in), optional:: lbounds(3)
  integer, intent(in), optional:: ubounds(3)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(3), ubound_nums(3)
  character(STRING):: size_str, sd_str
  integer:: max_value, min_value
  integer, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<INT-ARRAY:: @size=%c, @max=%d, @min=%d, @avg=%r%c>', i = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineInt3
          | Subroutine : | |
| array(:,:,:,:) : | integer, intent(in) | 
| lbounds(4) : | integer, intent(in), optional | 
| ubounds(4) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineInt4( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  integer, intent(in):: array(:,:,:,:)
  integer, intent(in), optional:: lbounds(4)
  integer, intent(in), optional:: ubounds(4)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(4), ubound_nums(4)
  character(STRING):: size_str, sd_str
  integer:: max_value, min_value
  integer, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<INT-ARRAY:: @size=%c, @max=%d, @min=%d, @avg=%r%c>', i = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineInt4
          | Subroutine : | |
| array(:,:,:,:,:) : | integer, intent(in) | 
| lbounds(5) : | integer, intent(in), optional | 
| ubounds(5) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineInt5( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  integer, intent(in):: array(:,:,:,:,:)
  integer, intent(in), optional:: lbounds(5)
  integer, intent(in), optional:: ubounds(5)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(5), ubound_nums(5)
  character(STRING):: size_str, sd_str
  integer:: max_value, min_value
  integer, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<INT-ARRAY:: @size=%c, @max=%d, @min=%d, @avg=%r%c>', i = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineInt5
          | Subroutine : | |
| array(:,:,:,:,:,:) : | integer, intent(in) | 
| lbounds(6) : | integer, intent(in), optional | 
| ubounds(6) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineInt6( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  integer, intent(in):: array(:,:,:,:,:,:)
  integer, intent(in), optional:: lbounds(6)
  integer, intent(in), optional:: ubounds(6)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(6), ubound_nums(6)
  character(STRING):: size_str, sd_str
  integer:: max_value, min_value
  integer, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
    lbound_nums(6) = lbound( array, 6 )
    ubound_nums(6) = ubound( array, 6 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(6)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(6)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<INT-ARRAY:: @size=%c, @max=%d, @min=%d, @avg=%r%c>', i = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineInt6
          | Subroutine : | |
| array(:,:,:,:,:,:,:) : | integer, intent(in) | 
| lbounds(7) : | integer, intent(in), optional | 
| ubounds(7) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineInt7( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  integer, intent(in):: array(:,:,:,:,:,:,:)
  integer, intent(in), optional:: lbounds(7)
  integer, intent(in), optional:: ubounds(7)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(7), ubound_nums(7)
  character(STRING):: size_str, sd_str
  integer:: max_value, min_value
  integer, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
    lbound_nums(6) = lbound( array, 6 )
    ubound_nums(6) = ubound( array, 6 )
                    
    lbound_nums(7) = lbound( array, 7 )
    ubound_nums(7) = ubound( array, 7 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(6)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(6)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(7)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(7)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<INT-ARRAY:: @size=%c, @max=%d, @min=%d, @avg=%r%c>', i = (/max_value, min_value/), r = (/avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineInt7
          | Subroutine : | |
| array(:) : | real, intent(in) | 
| lbounds(1) : | integer, intent(in), optional | 
| ubounds(1) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineReal1( array, lbounds, ubounds, unit, indent, sd )
                                        
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real, intent(in):: array(:)
  integer, intent(in), optional:: lbounds(1)
  integer, intent(in), optional:: ubounds(1)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(1), ubound_nums(1)
  character(STRING):: size_str, sd_str
  real:: max_value, min_value
  real, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = array
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<SP-ARRAY:: @size=%c, @max=%r, @min=%r, @avg=%r%c>', r = (/max_value, min_value, avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineReal1
          | Subroutine : | |
| array(:,:) : | real, intent(in) | 
| lbounds(2) : | integer, intent(in), optional | 
| ubounds(2) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineReal2( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real, intent(in):: array(:,:)
  integer, intent(in), optional:: lbounds(2)
  integer, intent(in), optional:: ubounds(2)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(2), ubound_nums(2)
  character(STRING):: size_str, sd_str
  real:: max_value, min_value
  real, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<SP-ARRAY:: @size=%c, @max=%r, @min=%r, @avg=%r%c>', r = (/max_value, min_value, avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineReal2
          | Subroutine : | |
| array(:,:,:) : | real, intent(in) | 
| lbounds(3) : | integer, intent(in), optional | 
| ubounds(3) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineReal3( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real, intent(in):: array(:,:,:)
  integer, intent(in), optional:: lbounds(3)
  integer, intent(in), optional:: ubounds(3)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(3), ubound_nums(3)
  character(STRING):: size_str, sd_str
  real:: max_value, min_value
  real, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<SP-ARRAY:: @size=%c, @max=%r, @min=%r, @avg=%r%c>', r = (/max_value, min_value, avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineReal3
          | Subroutine : | |
| array(:,:,:,:) : | real, intent(in) | 
| lbounds(4) : | integer, intent(in), optional | 
| ubounds(4) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineReal4( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real, intent(in):: array(:,:,:,:)
  integer, intent(in), optional:: lbounds(4)
  integer, intent(in), optional:: ubounds(4)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(4), ubound_nums(4)
  character(STRING):: size_str, sd_str
  real:: max_value, min_value
  real, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<SP-ARRAY:: @size=%c, @max=%r, @min=%r, @avg=%r%c>', r = (/max_value, min_value, avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineReal4
          | Subroutine : | |
| array(:,:,:,:,:) : | real, intent(in) | 
| lbounds(5) : | integer, intent(in), optional | 
| ubounds(5) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineReal5( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real, intent(in):: array(:,:,:,:,:)
  integer, intent(in), optional:: lbounds(5)
  integer, intent(in), optional:: ubounds(5)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(5), ubound_nums(5)
  character(STRING):: size_str, sd_str
  real:: max_value, min_value
  real, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<SP-ARRAY:: @size=%c, @max=%r, @min=%r, @avg=%r%c>', r = (/max_value, min_value, avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineReal5
          | Subroutine : | |
| array(:,:,:,:,:,:) : | real, intent(in) | 
| lbounds(6) : | integer, intent(in), optional | 
| ubounds(6) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineReal6( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real, intent(in):: array(:,:,:,:,:,:)
  integer, intent(in), optional:: lbounds(6)
  integer, intent(in), optional:: ubounds(6)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(6), ubound_nums(6)
  character(STRING):: size_str, sd_str
  real:: max_value, min_value
  real, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
    lbound_nums(6) = lbound( array, 6 )
    ubound_nums(6) = ubound( array, 6 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(6)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(6)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<SP-ARRAY:: @size=%c, @max=%r, @min=%r, @avg=%r%c>', r = (/max_value, min_value, avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineReal6
          | Subroutine : | |
| array(:,:,:,:,:,:,:) : | real, intent(in) | 
| lbounds(7) : | integer, intent(in), optional | 
| ubounds(7) : | integer, intent(in), optional | 
| unit : | integer, intent(in), optional | 
| indent : | character(*), intent(in), optional | 
| sd : | logical, intent(in), optional | 
subroutine PutLineReal7( array, lbounds, ubounds, unit, indent, sd )
                    
  use dc_types, only: DP, STRING, STDOUT
  use dc_string, only: toChar
  use dc_string, only: Printf, CPrintf
  use dc_present, only: present_and_true
  implicit none
  real, intent(in):: array(:,:,:,:,:,:,:)
  integer, intent(in), optional:: lbounds(7)
  integer, intent(in), optional:: ubounds(7)
  integer, intent(in), optional:: unit
  character(*), intent(in), optional:: indent
  logical, intent(in), optional:: sd
  integer:: out_unit
  integer:: indent_len
  character(STRING):: indent_str
  integer:: i
  integer:: alldim_size, lbound_nums(7), ubound_nums(7)
  character(STRING):: size_str, sd_str
  real:: max_value, min_value
  real, allocatable:: array_packed(:)
  real:: avg_value, variance_value, sd_value
continue
  !-----------------------------------------------------------------
  !  オプショナル引数のチェック
  !  Check optional arguments
  !-----------------------------------------------------------------
  if ( present(unit) ) then
    out_unit = unit
  else
    out_unit = STDOUT
  end if
  indent_len = 0
  indent_str = ''
  if ( present(indent) ) then
    if (len(indent) /= 0) then
      indent_len = len(indent)
      indent_str(1:indent_len) = indent
    end if
  end if
  !-------------------------------------------------------------------
  !  配列サイズ
  !  Array size
  !-------------------------------------------------------------------
  if ( present(lbounds) .and. present(ubounds) ) then
    lbound_nums = lbounds
    ubound_nums = ubounds
  else
                        lbound_nums(1) = lbound( array, 1 )
    ubound_nums(1) = ubound( array, 1 )
                    
    lbound_nums(2) = lbound( array, 2 )
    ubound_nums(2) = ubound( array, 2 )
                    
    lbound_nums(3) = lbound( array, 3 )
    ubound_nums(3) = ubound( array, 3 )
                    
    lbound_nums(4) = lbound( array, 4 )
    ubound_nums(4) = ubound( array, 4 )
                    
    lbound_nums(5) = lbound( array, 5 )
    ubound_nums(5) = ubound( array, 5 )
                    
    lbound_nums(6) = lbound( array, 6 )
    ubound_nums(6) = ubound( array, 6 )
                    
    lbound_nums(7) = lbound( array, 7 )
    ubound_nums(7) = ubound( array, 7 )
                    
  end if
  size_str = '('
  size_str = trim(size_str) // trim(toChar(lbound_nums(1))) // ':'
  size_str = trim(size_str) // trim(toChar(ubound_nums(1)))
                      size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(2)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(2)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(3)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(3)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(4)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(4)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(5)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(5)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(6)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(6)))
                    
  size_str = trim(size_str) // ',' // trim(toChar(lbound_nums(7)))
  size_str = trim(size_str) // ':' // trim(toChar(ubound_nums(7)))
                    
  size_str = trim(size_str) // ')'
  !-------------------------------------------------------------------
  !  最大値
  !  Maximum value
  !-------------------------------------------------------------------
  max_value = maxval(array)
  !-------------------------------------------------------------------
  !  最小値
  !  Minimum value
  !-------------------------------------------------------------------
  min_value = minval(array)
  !-------------------------------------------------------------------
  !  平均値
  !  Average value
  !-------------------------------------------------------------------
  alldim_size = size(array)
  avg_value = sum(array) / real(alldim_size)
  !-------------------------------------------------------------------
  !  標準偏差
  !  Standard deviation
  !-------------------------------------------------------------------
  sd_value = 0.0
  variance_value = 0.0
  sd_str = ''
  if ( present_and_true( sd ) ) then
    if ( alldim_size > 1 ) then
      if (allocated(array_packed)) then
        deallocate(array_packed)
      end if
      allocate( array_packed(alldim_size) )
                            array_packed = pack(array, .true.)
                      
      do i = 1, alldim_size
        variance_value = variance_value + (array_packed(i) - avg_value) * (array_packed(i) - avg_value)
      end do
      variance_value = variance_value / real(alldim_size)
      sd_value = sqrt( variance_value )
      sd_str = CPrintf ( ' @sd=%r', r = (/ sd_value /) )
    end if
  end if
  !-------------------------------------------------------------------
  !  印字
  !  Print
  !-------------------------------------------------------------------
  call Printf(out_unit, indent_str(1:indent_len) // '#<SP-ARRAY:: @size=%c, @max=%r, @min=%r, @avg=%r%c>', r = (/max_value, min_value, avg_value/), c1 = trim(size_str), c2 = trim(sd_str) )
end subroutine PutLineReal7