配列のプロパティと属性#

merge#

名前#

merge(3) - [ARRAY:CONSTRUCTION] 変数のマージ

概要#

    result = merge(tsource, fsource, mask)
     elemental type(TYPE(kind=KIND)) function merge(tsource,fsource,mask)

      type(TYPE(kind=KIND)),intent(in) :: tsource
      type(TYPE(kind=KIND)),intent(in) :: fsource
      logical(kind=**),intent(in)   :: mask
      mask** : Shall be of type logical.

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • tsource ユーザー定義を含む任意の型です。

  • fsource tsource と同じ型および型パラメーターである必要があります。

  • mask 論理型である必要があります。

  • 結果は、tsource と同じ型および型パラメーターになります。

説明#

要素関数 merge(3) は、論理マスクに従って 2 つの配列またはスカラーから値を選択します。結果は、mask の対応する要素が .true. の場合、tsource の要素と等しくなり、.false. の場合は fsource の要素となります。

多次元配列がサポートされています。

merge(3) の引数式は、短絡処理が要求されないことに注意してください。(例として)配列 x が以下のステートメントでゼロ値を含む場合、標準では浮動小数点のゼロ除算が発生するのを防ぎません。マスクを使用して保持する値を選択する前に、1.0/xx のすべての値に対して評価される可能性があるためです。

      y = merge( 1.0/x, 0.0, x /= 0.0 )

コンパイラは短絡処理を実行したり、無限大を生成したりすることもできるため、多くのプログラミング環境では機能する可能性がありますが、推奨されません。

このような場合、代わりに where コンストラクトを使用してマスクされた代入を使用できます。

      where(x .ne. 0.0)
         y = 1.0/x
      elsewhere
         y = 0.0
      endwhere

より分かりにくい

      merge(1.0/merge(x,1.0,x /= 0.0), 0.0, x /= 0.0)

オプション#

  • tsource

    ユーザー定義を含む任意の型です。

  • fsource

    tsource と同じ型および型パラメーターである必要があります。

  • mask

    論理型である必要があります。

(現在) 文字値は同じ長さである必要があります。

結果#

結果は、mask.true. の場合は tsource の要素から、それ以外の場合は fsource から構築されます。

tsourcefsource は同じ型と型パラメーターを持つ必要があるため(宣言された型と動的型の両方)、tsourcefsource の両方が多態性の場合は、結果も多態性になります。

#

サンプルプログラム

program demo_merge
implicit none
integer :: tvals(2,3), fvals(2,3), answer(2,3)
logical :: mask(2,3)
integer :: i
integer :: k
logical :: chooseleft

   ! Works with scalars
   k=5
   write(*,*)merge (1.0, 0.0, k > 0)
   k=-2
   write(*,*)merge (1.0, 0.0, k > 0)

   ! set up some simple arrays that all conform to the
   ! same shape
   tvals(1,:)=[  10, -60,  50 ]
   tvals(2,:)=[ -20,  40, -60 ]

   fvals(1,:)=[ 0, 3, 2 ]
   fvals(2,:)=[ 7, 4, 8 ]

   mask(1,:)=[ .true.,  .false., .true. ]
   mask(2,:)=[ .false., .false., .true. ]

   ! lets use the mask of specific values
   write(*,*)'mask of logicals'
   answer=merge( tvals, fvals, mask )
   call printme()

   ! more typically the mask is an expression
   write(*, *)'highest values'
   answer=merge( tvals, fvals, tvals > fvals )
   call printme()

   write(*, *)'lowest values'
   answer=merge( tvals, fvals, tvals < fvals )
   call printme()

   write(*, *)'zero out negative values'
   answer=merge( tvals, 0, tvals < 0)
   call printme()

   write(*, *)'binary choice'
   chooseleft=.false.
   write(*, '(3i4)')merge([1,2,3],[10,20,30],chooseleft)
   chooseleft=.true.
   write(*, '(3i4)')merge([1,2,3],[10,20,30],chooseleft)

contains

subroutine printme()
      write(*, '(3i4)')(answer(i, :), i=1, size(answer, dim=1))
end subroutine printme

end program demo_merge

期待される結果

 >     mask of logicals
 >      10   3  50
 >       7   4 -60
 >     highest values
 >      10   3  50
 >       7  40   8
 >     lowest values
 >       0 -60   2
 >     -20   4 -60
 >     zero out negative values
 >       0 -60   0
 >     -20   0 -60
 >     binary choice
 >      10  20  30
 >       1   2   3

標準#

Fortran 95

関連項目#

  • pack(3) は配列をランク1の配列にパックします。

  • spread(3) は次元を追加し、データを複製するために使用されます。

  • unpack(3) はベクトルの要素を散乱させます。

  • transpose(3) - ランク2の配列を転置します。

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

pack#

名前#

pack(3) - [ARRAY:CONSTRUCTION] 配列をランク1の配列にパックする

概要#

    result = pack( array, mask [,vector] )
     TYPE(kind=KIND) function pack(array,mask,vector)

      TYPE(kind=KIND),option(in) :: array(..)
      logical  :: mask(..)
      TYPE(kind=KIND),option(in),optional :: vector(*)

特性#

  • array は任意の型の配列です。

  • mask 論理スカラー、および array と適合する配列。

  • vectorarray と同じ種類と型で、ランク1です。

  • 戻り値は array と同じ種類と型です。

説明#

pack(3) は array の要素をランク1の配列に格納します。

結果の配列の先頭は、mask.true. と等しい要素で構成されます。その後、残りの位置は vector から取得された要素で埋められます。

オプション#

  • array

    この配列のデータを使用して、結果のベクトルを埋めます。

  • mask

    論理マスクは array と同じサイズである必要があります。または、論理スカラーにすることもできます。

  • vector

    array と同じ型でランク1の配列。存在する場合、vector の要素数は mask の true 要素数以上である必要があります。mask がスカラーの場合、vector の要素数は array の要素数以上である必要があります。

vectorarray に含まれる要素数以上の要素を持つ必要があります。

結果#

結果は、ランク1の配列であり、array と同じ型です。vector が存在する場合、結果のサイズは vector のサイズです。そうでない場合は mask.true. の値の数です。

mask が値 .true. のスカラーの場合、結果のサイズは array のサイズになります。

#

サンプルプログラム

program demo_pack
implicit none
integer, allocatable :: m(:)
character(len=10) :: c(4)

 ! gathering nonzero elements from an array:
   m = [ 1, 0, 0, 0, 5, 0 ]
   write(*, fmt="(*(i0, ' '))") pack(m, m /= 0)

 ! Gathering nonzero elements from an array and appending elements
 ! from VECTOR till the size of the mask array (or array size if the
 ! mask is scalar):
   m = [ 1, 0, 0, 2 ]
   write(*, fmt="(*(i0, ' '))") pack(m, m /= 0, [ 0, 0, 3, 4 ])
   write(*, fmt="(*(i0, ' '))") pack(m, m /= 0 )

 ! select strings whose second character is "a"
   c = [ character(len=10) :: 'ape', 'bat', 'cat', 'dog']
   write(*, fmt="(*(g0, ' '))") pack(c, c(:)(2:2) == 'a' )

end program demo_pack

結果

 > 1 5
 > 1 2 3 4
 > 1 2
 > bat        cat

標準#

Fortran 95

関連項目#

merge(3)spread(3)unpack(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

spread#

名前#

spread(3) - [ARRAY:CONSTRUCTION] 次元を追加してデータを複製する

概要#

    result = spread(source, dim, ncopies)
     TYPE(kind=KIND) function spread(source, dim, ncopies)

      TYPE(kind=KIND)             :: source(..)
      integer(kind=**),intent(in) :: dim
      integer(kind=**),intent(in) :: ncopies

特性#

  • source は任意の型のスカラーまたは配列です。

  • dim は整数スカラーです。

  • ncopies は整数スカラーです。

説明#

spread(3) は、指定された次元 dim に沿って source 配列を複製します。コピーは ncopies 回繰り返されます。

したがって、行列に追加の行を追加するには dim=1 を使用しますが、追加の列を追加するには dim=2 を使用します。

source がスカラーの場合、結果のベクトルのサイズは ncopies であり、結果の各要素の値は source と等しくなります。

オプション#

  • source

    任意の型のスカラーまたは配列であり、ランクは15未満です。

  • dim

    1 から n+1 の範囲の追加次元値(ここで nsource のランクです)。

  • ncopies

    生成する元のデータのコピー数

結果#

結果は、source と同じ型の配列であり、ランクは n+1 です(ここで nsource のランクです)。

#

サンプルプログラム

program demo_spread
implicit none

integer a1(4,3), a2(3,4), v(4), s

   write(*,'(a)' ) &
   'TEST SPREAD(3)                                      ', &
   '  SPREAD(3) is a FORTRAN90 function which replicates', &
   '  an array by adding a dimension.                   ', &
   ' '

   s = 99
   call printi('suppose we have a scalar S',s)

   write(*,*) 'to add a new dimension (1) of extent 4 call'
   call printi('spread( s, dim=1, ncopies=4 )',spread ( s, 1, 4 ))

   v = [ 1, 2, 3, 4 ]
   call printi(' first we will set V to',v)

   write(*,'(a)')' and then do "spread ( v, dim=2, ncopies=3 )"'
   a1 = spread ( v, dim=2, ncopies=3 )
   call printi('this adds a new dimension (2) of extent 3',a1)

   a2 = spread ( v, 1, 3 )
   call printi(' spread(v,1,3) adds a new dimension (1) of extent 3',a2)
   ! add more
   a2 = spread ( v, 1, 3 )
   call printi(' spread(v,1,3) adds a new dimension (1) of extent 3',a2)

contains
! CONVENIENCE ROUTINE; NOT DIRECTLY CONNECTED TO SPREAD(3)
subroutine printi(title,a)
use, intrinsic :: iso_fortran_env, only : stderr=>ERROR_UNIT,&
 & stdin=>INPUT_UNIT, stdout=>OUTPUT_UNIT
implicit none

!@(#) print small 2d integer scalar, vector, matrix in row-column format

character(len=*),parameter   :: all='(" ",*(g0,1x))'
character(len=*),intent(in)  :: title
character(len=20)            :: row
integer,intent(in)           :: a(..)
integer                      :: i

   write(*,all,advance='no')trim(title)
   ! select rank of input
   select rank(a)
   rank (0); write(*,'(a)')' (a scalar)'
      write(*,'(" > [ ",i0," ]")')a
   rank (1); write(*,'(a)')' (a vector)'
      ! find how many characters to use for integers
      write(row,'(i0)')ceiling(log10(real(maxval(abs(a)))))+2
      ! use this format to write a row
      row='(" > [",*(i'//trim(row)//':,","))'
      do i=1,size(a)
         write(*,fmt=row,advance='no')a(i)
         write(*,'(" ]")')
      enddo
   rank (2); write(*,'(a)')' (a matrix) '
      ! find how many characters to use for integers
      write(row,'(i0)')ceiling(log10(real(maxval(abs(a)))))+2
      ! use this format to write a row
      row='(" > [",*(i'//trim(row)//':,","))'
      do i=1,size(a,dim=1)
         write(*,fmt=row,advance='no')a(i,:)
         write(*,'(" ]")')
      enddo
   rank default
      write(stderr,*)'*printi* did not expect rank=', rank(a), &
       & 'shape=', shape(a),'size=',size(a)
      stop '*printi* unexpected rank'
   end select
   write(*,all) '>shape=',shape(a),',rank=',rank(a),',size=',size(a)
   write(*,*)

end subroutine printi

end program demo_spread

結果

   TEST SPREAD(3)
     SPREAD(3) is a FORTRAN90 function which replicates
     an array by adding a dimension.

    suppose we have a scalar S  (a scalar)
    > [ 99 ]
    >shape= ,rank= 0 ,size= 1

    to add a new dimension (1) of extent 4 call
    spread( s, dim=1, ncopies=4 )  (a vector)
    > [  99 ]
    > [  99 ]
    > [  99 ]
    > [  99 ]
    >shape= 4 ,rank= 1 ,size= 4

     first we will set V to  (a vector)
    > [  1 ]
    > [  2 ]
    > [  3 ]
    > [  4 ]
    >shape= 4 ,rank= 1 ,size= 4

    and then do "spread ( v, dim=2, ncopies=3 )"
    this adds a new dimension (2) of extent 3  (a matrix)
    > [  1,  1,  1 ]
    > [  2,  2,  2 ]
    > [  3,  3,  3 ]
    > [  4,  4,  4 ]
    >shape= 4 3 ,rank= 2 ,size= 12

     spread(v,dim=1,ncopies=3) adds a new dimension (1) (a matrix)
    > [  1,  2,  3,  4 ]
    > [  1,  2,  3,  4 ]
    > [  1,  2,  3,  4 ]
    >shape= 3 4 ,rank= 2 ,size= 12

標準#

Fortran 95

関連項目#

merge(3)pack(3)unpack(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

unpack#

名前#

unpack(3) - [ARRAY:CONSTRUCTION] マスクを使用してベクトルの要素を配列に分散する

概要#

    result = unpack(vector, mask, field)
     type(TYPE(kind=KIND)) unpack(vector, mask, field)

      type(TYPE(kind=KIND)),intent(in) :: vector(:)
      logical,intent(in)               :: mask(..)
      type(TYPE(kind=KIND)),intent(in) :: field(..)

特性#

  • vector は任意の型のランク1配列です。

  • mask は論理配列です。

  • field は、mask と適合するvector と同じ型および型パラメータです。

  • 結果は、vector と同じ型および型パラメータを持ち、mask と同じ形状の配列です。

説明#

unpack(3) は、任意のランクの配列fieldのコピーにvectorの要素を分散します。配列要素の順序でmask.true.値を使用して、vector値の配置を指定します。

そのため、fieldのコピーが生成され、選択された要素がvectorの値に置き換えられます。これにより、配列構文または複数の代入文を使用する場合、特に置換が条件付きの場合に困難となる複雑な置換パターンが可能になります。

オプション#

  • vector

    fieldの指定された場所に配置する新しい値。mask.true.値を持つ数以上の要素を持つ必要があります。

  • mask

    fieldのどの値をvectorの値で置き換えるかを指定する配列である必要があります。

  • field

    変更される入力配列。

結果#

結果の要素のうち、配列要素の順序でmaskの第i番目の真の要素に対応する要素は、tがmaskの真の値の数である場合、i = 1, 2, …, tに対してvector(i)の値を持ちます。その他の各要素の値は、**field*がスカラーの場合は**field*と等しく、配列の場合は**field*の対応する要素と等しくなります。

結果の配列は、配列要素の順序でvectorからの値でmask.true.要素が置き換えられたfieldに対応します。

#

特定の値は、以下を使用して配列の特定の位置に「分散」させることができます。

                       1 0 0
    If M is the array  0 1 0
                       0 0 1

    V is the array [1, 2, 3],
                               . T .
    and Q is the logical mask  T . .
                               . . T
    where "T" represents true and "." represents false, then the result of

    UNPACK (V, MASK = Q, FIELD = M) has the value

      1 2 0
      1 1 0
      0 0 3

    and the result of UNPACK (V, MASK = Q, FIELD = 0) has the value

      0 2 0
      1 0 0
      0 0 3

サンプルプログラム

program demo_unpack
implicit none
logical,parameter :: T=.true., F=.false.

integer :: vector(2)  = [1,1]

! mask and field must conform
integer,parameter :: r=2, c=2
logical :: mask(r,c)  = reshape([ T,F,F,T ],[2,2])
integer :: field(r,c) = 0, unity(2,2)

   ! basic usage
   unity = unpack( vector, mask, field )
   call print_matrix_int('unity=', unity)

   ! if FIELD is a scalar it is used to fill all the elements
   ! not assigned to by the vector and mask.
   call print_matrix_int('scalar field',         &
   & unpack(                                     &
   & vector=[ 1, 2, 3, 4 ],                      &
   & mask=reshape([ T,F,T,F,F,F,T,F,T ], [3,3]), &
   & field=0) )

contains

   subroutine print_matrix_int(title,arr)
   ! convenience routine:
   ! just prints small integer arrays in row-column format
   implicit none
   character(len=*),intent(in)  :: title
   integer,intent(in)           :: arr(:,:)
   integer                      :: i
   character(len=:),allocatable :: biggest

      write(*,*)trim(title)
      ! make buffer to write integer into
      biggest='           '
      ! find how many characters to use for integers
      write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
      ! use this format to write a row
      biggest='("  [",*(i'//trim(biggest)//':,","))'
      ! print one row of array at a time
      do i=1,size(arr,dim=1)
         write(*,fmt=biggest,advance='no')arr(i,:)
         write(*,'(" ]")')
      enddo
   end subroutine print_matrix_int

end program demo_unpack

結果

   > unity=
   >  [ 1, 0 ]
   >  [ 0, 1 ]
   > scalar field
   >  [  1,  0,  3 ]
   >  [  0,  0,  0 ]
   >  [  2,  0,  4 ]

標準#

Fortran 95

参照#

merge(3)pack(3)spread(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

allocated#

名前#

allocated(3) - [ARRAY:INQUIRY] 割り当て可能なエンティティの割り当て状態

概要#

    result = allocated(array|scalar)
     logical function allocated(array,scalar)

      type(TYPE(kind=**)),allocatable,optional :: array(..)
      type(TYPE(kind=**)),allocatable,optional :: scalar

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • array は、任意の型の割り当て可能な配列オブジェクトです。

  • scalar は、任意の型の割り当て可能なスカラーです。

  • 結果はデフォルトの論理スカラーです。

説明#

allocated(3) は、配列とスカラーの両方の割り当て状態をチェックします。

arrayまたはscalarの少なくとも1つのみを指定する必要があります。

オプション#

  • entity

    テストする割り当て可能オブジェクト。

結果#

引数が割り当てられている場合、結果は.true.になります。それ以外の場合は、.false.を返します。

#

サンプルプログラム

program demo_allocated
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=sp), allocatable :: x(:)
character(len=256) :: message
integer :: istat
  ! basics
   if( allocated(x)) then
       write(*,*)'do things if allocated'
   else
       write(*,*)'do things if not allocated'
   endif

   ! if already allocated, deallocate
   if ( allocated(x) ) deallocate(x,STAT=istat, ERRMSG=message )
   if(istat.ne.0)then
      write(*,*)trim(message)
      stop
   endif

   ! only if not allocated, allocate
   if ( .not. allocated(x) ) allocate(x(20))

  ! allocation and intent(out)
   call intentout(x)
   write(*,*)'note it is deallocated!',allocated(x)

   contains

   subroutine intentout(arr)
   ! note that if arr has intent(out) and is allocatable,
   ! arr is deallocated on entry
   real(kind=sp),intent(out),allocatable :: arr(:)
       write(*,*)'note it was allocated in calling program',allocated(arr)
   end subroutine intentout

end program demo_allocated

結果

 >  do things if not allocated
 >  note it was allocated in calling program F
 >  note it is deallocated! F

標準#

Fortran 95。割り当て可能なスカラーエンティティはFortran 2003で追加されました。

参照#

move_alloc(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

is_contiguous#

名前#

is_contiguous(3) - [ARRAY:INQUIRY] オブジェクトが連続しているかどうかをテストする

概要#

    result = is_contiguous(array)
     logical function is_contiguous(array)

      type(TYPE(kind=**)),intent(in) :: array

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • array は任意の型です。配列または仮ランクである必要があります。ポインタの場合は、関連付けられている必要があります。

  • 結果はデフォルトの論理スカラーです。

説明#

is_contiguous(3) は、オブジェクトが連続している場合にのみ.true.を返します。

オブジェクトは、次の場合に連続しています。

  • (1) CONTIGUOUS属性を持つオブジェクト

  • (2) 仮形状ではないノンポインタ全体配列

  • (3) 連続している配列と引数関連付けされている仮形状配列

  • (4) ALLOCATE文によって割り当てられた配列

  • (5) 連続したターゲットに関連付けられているポインタ

  • (6) 次の条件を満たすゼロ以外のサイズの配列セクション

    • (a) 基底オブジェクトが連続している

    • (b) ベクトル添字を持たない

    • (c) 配列要素の順序でセクションの要素は、配列要素の順序で連続している基底オブジェクト要素のサブセットである

    • (d) 配列が文字型であり、部分文字列範囲が表示される場合、部分文字列範囲は親文字列のすべての文字を指定する

    • (e) 最終の部分参照のみがゼロ以外のランクを持つ

    • (f) 複素数型の配列の実数部または虚数部ではない

オブジェクトは、配列サブオブジェクトであり、次の場合に連続していません。

  • オブジェクトは2つ以上の要素を持つ

  • 配列要素の順序でのオブジェクトの要素は、基底オブジェクトの要素で連続していない

  • オブジェクトは長さゼロの文字型ではない

  • オブジェクトは、長さゼロの配列と長さゼロの文字以外の究極のコンポーネントを持たない派生型ではない

他のオブジェクトが連続しているかどうかは、プロセッサ依存です。

オプション#

  • array

    連続しているかどうかをテストする任意の型の配列。ポインタの場合は、関連付けられている必要があります。

結果#

arrayが連続している場合は.true.、それ以外の場合は.false.という値になります。

#

サンプルプログラム

program demo_is_contiguous
implicit none
intrinsic is_contiguous
real, DIMENSION (1000, 1000), TARGET :: A
real, DIMENSION (:, :), POINTER       :: IN, OUT
   IN => A              ! Associate IN with target A
   OUT => A(1:1000:2,:) ! Associate OUT with subset of target A
   !
   write(*,*)'IN is ',IS_CONTIGUOUS(IN)
   write(*,*)'OUT is ',IS_CONTIGUOUS(OUT)
   !
end program demo_is_contiguous

結果

    IN is  T
    OUT is  F

標準#

Fortran 2008

参照#

****(3)

fortran-lang組み込み記述

lbound#

名前#

lbound(3) - [ARRAY:INQUIRY] 配列の下限次元境界

概要#

    result = lbound(array [,dim] [,kind] )
     elemental TYPE(kind=KIND) function lbound(array,dim,kind)

      TYPE(kind=KIND),intent(in)           :: array(..)
      integer(kind=**),intent(in),optional :: dim
      integer(kind=**),intent(in),optional :: kind

特性#

  • array は、任意の型の仮ランクまたは配列である必要があります。未割り当ての割り当て可能配列または関連付けられていないポインタにすることはできません。

  • dim はスカラー整数である必要があります。対応する実際の引数は、オプションのダミー引数、関連付け解除されたポインタ、または未割り当ての割り当て可能にすることはできません。

  • kind 結果の型パラメータを示す整数初期化式。

  • 戻り値は、型が整数で、kindがkindです。kindが省略されている場合、戻り値はデフォルトの整数kindになります。dimが存在する場合はスカラーになり、それ以外の場合はランクが1でサイズがnの配列になります(nはarrayのランク)。

  • **として指定された種類は、型でサポートされている任意の種類です。**

説明#

result(3) は、配列の下限境界、またはdim次元沿いの単一の下限境界を返します。

オプション#

  • array

    任意の型の配列である必要があります。

  • dim

    スカラー整数である必要があります。dimが存在しない場合、結果はarrayの上限境界の配列になります。

  • kind

    結果の型パラメータを示す整数初期化式。

結果#

dimが存在しない場合、結果はarrayの下限境界の配列です。

dimが存在する場合、結果は、その次元沿いの配列の下限境界に対応するスカラーです。arrayが全体配列または配列構造体コンポーネントではなく式である場合、または関連する次元で範囲がゼロの場合、下限境界は1と見なされます。

NOTE1

If **array** is assumed-rank and has rank zero, **dim** cannot be
present since it cannot satisfy the requirement **1 <= dim <= 0**.

#

私の意見では、この関数は、仮サイズ配列または明示的なインターフェースのない関数では使用すべきではありません。インターフェースが定義されていない場合、エラーが発生する可能性があります。

サンプルプログラム

! program demo_lbound
module m_bounds
implicit none
 contains
    subroutine msub(arr)
       !!integer,intent(in) :: arr(*)  ! cannot be assumed-size array
       integer,intent(in) :: arr(:)
       write(*,*)'MSUB: LOWER=',lbound(arr), &
       & 'UPPER=',ubound(arr), &
       & 'SIZE=',size(arr)
    end subroutine msub
 end module m_bounds

 program demo_lbound
 use m_bounds, only : msub
 implicit none
 interface
    subroutine esub(arr)
    integer,intent(in) :: arr(:)
    end subroutine esub
 end interface
 integer :: arr(-10:10)
    write(*,*)'MAIN: LOWER=',lbound(arr), &
    & 'UPPER=',ubound(arr), &
    & 'SIZE=',size(arr)
    call csub()
    call msub(arr)
    call esub(arr)
 contains
subroutine csub
   write(*,*)'CSUB: LOWER=',lbound(arr), &
   & 'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
end subroutine csub
end

 subroutine esub(arr)
 implicit none
 integer,intent(in) :: arr(:)
    ! WARNING: IF CALLED WITHOUT AN EXPLICIT INTERFACE
    ! THIS WILL GIVE UNDEFINED ANSWERS (like 0,0,0)
    write(*,*)'ESUB: LOWER=',lbound(arr), &
    & 'UPPER=',ubound(arr), &
    & 'SIZE=',size(arr)
 end subroutine esub

!end program demo_lbound

結果

   MAIN: LOWER=         -10 UPPER=          10 SIZE=          21
   CSUB: LOWER=         -10 UPPER=          10 SIZE=          21
   MSUB: LOWER=           1 UPPER=          21 SIZE=          21
   ESUB: LOWER=           1 UPPER=          21 SIZE=          21

標準#

Fortran 95、KIND引数付き - Fortran 2003

参照#

配列照会:#

  • size(3) - 配列のサイズを決定する

  • rank(3) - データオブジェクトのランク

  • shape(3) - 配列の形状を決定する

  • ubound(3) - 配列の上限次元境界

co_ubound(3)co_lbound(3)

状態照会:#

  • allocated(3) - 割り当て可能なエンティティの状態

  • is_contiguous(3) - オブジェクトが連続しているかどうかをテストします

種類照会:#

  • kind(3) - エンティティの種類

ビット照会:#

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

ランク#

名前#

rank(3) - [配列:照会] データオブジェクトのランク

要約#

    result = rank(a)
     integer function rank(a)

      type(TYPE(kind=**)),intent(in) :: a(..)

特性#

  • a は、任意の種類TYPEとランクのデータオブジェクトです。

  • **として指定された種類は、型でサポートされている任意の種類です。**

説明#

rank(3) は、スカラーまたは配列データオブジェクトのランクを返します。

配列のランクは、それが持つ次元の数です(スカラーの場合はゼロ)。

オプション#

  • a は、次元数を問い合わせるデータオブジェクトです。返されるランクは0〜16です。

    引数a は、仮ランク配列を含む任意のデータオブジェクト型にすることができます。

結果#

配列の場合、そのランクが返され、スカラーの場合はゼロが返されます。

#

サンプルプログラム

program demo_rank
implicit none

! a bunch of data objects to query
integer           :: a
real, allocatable :: b(:,:)
real, pointer     :: c(:)
complex           :: d

! make up a type
type mytype
   integer :: int
   real :: float
   character :: char
end type mytype
type(mytype) :: any_thing(1,2,3,4,5)

  ! basics
   print *, 'rank of scalar a=',rank(a)
   ! you can query this array even though it is not allocated
   print *, 'rank of matrix b=',rank(b)
   print *, 'rank of vector pointer c=',rank(c)
   print *, 'rank of complex scalar d=',rank(d)

  ! you can query any type, not just intrinsics
   print *, 'rank of any arbitrary type=',rank(any_thing)

  ! an assumed-rank object may be queried
   call query_int(10)
   call query_int([20,30])
   call query_int( reshape([40,50,60,70],[2,2]) )

  ! you can even query an unlimited polymorphic entity
   call query_anything(10.0)
   call query_anything([.true.,.false.])
   call query_anything( reshape([40.0,50.0,60.0,70.0],[2,2]) )

contains

subroutine query_int(data_object)
! It is hard to do much with something dimensioned
! name(..) if not calling C except inside of a
! SELECT_RANK construct but one thing you can
! do is call the inquiry functions ...
integer,intent(in) :: data_object(..)
character(len=*),parameter :: all='(*(g0,1x))'

   if(rank(data_object).eq.0)then
      print all,&
      & 'passed a scalar to an assumed rank,  &
      & rank=',rank(data_object)
   else
      print all,&
      & 'passed an array to an assumed rank,  &
      & rank=',rank(data_object)
   endif

end subroutine query_int

subroutine query_anything(data_object)
class(*),intent(in) ::data_object(..)
character(len=*),parameter :: all='(*(g0,1x))'
  if(rank(data_object).eq.0)then
    print all,&
    &'passed a scalar to an unlimited polymorphic rank=', &
    & rank(data_object)
  else
    print all,&
    & 'passed an array to an unlimited polymorphic, rank=', &
    & rank(data_object)
  endif
end subroutine query_anything

end program demo_rank

結果

    rank of scalar a=           0
    rank of matrix b=           2
    rank of vector pointer c=           1
    rank of complex scalar d=           0
    rank of any arbitrary type=           5
   passed a scalar to an assumed rank,   rank= 0
   passed an array to an assumed rank,   rank= 1
   passed an array to an assumed rank,   rank= 2
   passed a scalar to an unlimited polymorphic rank= 0
   passed an array to an unlimited polymorphic, rank= 1
   passed an array to an unlimited polymorphic, rank= 2

標準#

参照#

配列照会:#

  • size(3) - 配列のサイズを決定する

  • rank(3) - データオブジェクトのランク

  • shape(3) - 配列の形状を決定する

  • ubound(3) - 配列の上限次元境界

  • lbound(3) - 配列の下限次元境界

状態照会:#

  • allocated(3) - 割り当て可能なエンティティの状態

  • is_contiguous(3) - オブジェクトが連続しているかどうかをテストします

種類照会:#

  • kind(3) - エンティティの種類

ビット照会:#

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

#

shape#

名前#

shape(3) - [配列:照会] 配列またはスカラーの形状を決定します

要約#

  result = shape( source [,kind] )
   integer(kind=KIND) function shape( source, KIND )

    type(TYPE(kind=**)),intent(in)       :: source(..)
    integer(kind=**),intent(in),optional :: KIND

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • source は、任意の型の配列またはスカラーです。source がポインタの場合、関連付けられていなければならず、割り当て可能な配列は割り当てられていなければなりません。仮サイズ配列であってはなりません。

  • KIND は、定数整数初期化式です。

  • 結果は、KIND が存在する場合は、KIND で指定された種類のサイズがsource のランクに等しいランク1の整数配列です。存在しない場合は、デフォルトの整数型になります。

説明#

shape(3) は、配列の形状を問い合わせます。

オプション#

  • source

    任意の型の配列またはスカラー。source がポインタの場合、関連付けられていなければならず、割り当て可能な配列は割り当てられていなければなりません。

  • kind

    結果の種類パラメータを示します。

結果#

source が持つ次元と同じ数の要素を持つランク1の整数配列。

結果配列の要素は、それぞれの次元に対するsource の範囲に対応します。

source がスカラーの場合、結果は空の配列(サイズゼロのランク1配列)です。

#

サンプルプログラム

program demo_shape
implicit none
character(len=*),parameter :: all='(*(g0,1x))'
integer, dimension(-1:1, -1:2) :: a
   print all, 'shape of array=',shape(a)
   print all, 'shape of constant=',shape(42)
   print all, 'size of shape of constant=',size(shape(42))
   print all, 'ubound of array=',ubound(a)
   print all, 'lbound of array=',lbound(a)
end program demo_shape

結果

   shape of array= 3 4
   shape of constant=
   size of shape of constant= 0
   ubound of array= 1 2
   lbound of array= -1 -1

標準#

Fortran 95; KIND引数付き - Fortran 2003

参照#

配列照会:#

  • size(3) - 配列のサイズを決定する

  • rank(3) - データオブジェクトのランク

  • ubound(3) - 配列の上限次元境界

  • lbound(3) - 配列の下限次元境界

状態照会:#

  • allocated(3) - 割り当て可能なエンティティの状態

  • is_contiguous(3) - オブジェクトが連続しているかどうかをテストします

種類照会:#

  • kind(3) - エンティティの種類

ビット照会:#

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

size#

名前#

size(3) - [配列:照会] 配列のサイズまたは1次元の範囲を決定します

要約#

    result = size(array [,dim] [,kind])
     integer(kind=KIND) function size(array,dim,kind)

      type(TYPE(kind=KIND),intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      integer(kind=**),intent(in),optional :: KIND

特性#

  • array は、任意の型と関連付けられた種類の仮ランク配列または配列です。

    array がポインタの場合、関連付けられていなければならず、割り当て可能な配列は割り当てられていなければなりません。

  • dim は整数スカラーです

  • kind はスカラー整数定数式です。

  • 結果は、KIND の種類の整数スカラーです。KIND がない場合は、デフォルトの種類の整数が返されます。

  • **として指定された種類は、型でサポートされている任意の種類です。**

説明#

size(3) は、配列の要素の総数を返します。dim が指定されている場合は、その次元方向の要素数を返します。

size(3) は、指定された次元dim に沿ったarray の範囲、またはdim がない場合はarray の要素の総数を決定します。

オプション#

  • array

    要素数を測定する配列。**array* が仮サイズ配列の場合、**dim** は、**array** のランクより小さい値で存在する必要があります。

  • dim

    値は1〜nの範囲内にある必要があります。ここでnは**array** のランクに等しくなります。

    存在しない場合は、配列全体の要素の総数が返されます。

  • kind

    結果の型パラメータを示す整数初期化式。

    存在しない場合は、返される値の種類型パラメータはデフォルトの整数型になります。

    size で返される大きさに対して、kind は許容可能でなければなりません。そうでない場合、結果は未定義です。

    kind がない場合、戻り値はデフォルトの整数型です。

結果#

dim が存在しない場合、array が仮ランクの場合、結果はPRODUCT(SHAPE(ARRAY,KIND)) に等しい値を持ちます。それ以外の場合、結果はarray の要素の総数に等しい値を持ちます。

dim が存在する場合、その次元方向の要素数が返されます。ただし、ARRAYが仮ランクであり、仮サイズ配列に関連付けられており、DIMがarray のランクに等しい値で存在する場合は、値は-1になります。

注記1

array が仮ランクであり、ランクがゼロの場合、1 <= DIM <= 0 という要件を満たすことができないため、dim は存在できません。

.

#

サンプルプログラム

program demo_size
implicit none
integer :: arr(0:2,-5:5)
   write(*,*)'SIZE of simple two-dimensional array'
   write(*,*)'SIZE(arr)       :total count of elements:',size(arr)
   write(*,*)'SIZE(arr,DIM=1) :number of rows         :',size(arr,dim=1)
   write(*,*)'SIZE(arr,DIM=2) :number of columns      :',size(arr,dim=2)

   ! pass the same array to a procedure that passes the value two
   ! different ways
   call interfaced(arr,arr)
contains

subroutine interfaced(arr1,arr2)
! notice the difference in the array specification
! for arr1 and arr2.
integer,intent(in) :: arr1(:,:)
integer,intent(in) :: arr2(2,*)
   !
   write(*,*)'interfaced assumed-shape array'
   write(*,*)'SIZE(arr1)        :',size(arr1)
   write(*,*)'SIZE(arr1,DIM=1)  :',size(arr1,dim=1)
   write(*,*)'SIZE(arr1,DIM=2)  :',size(arr1,dim=2)

!  write(*,*)'SIZE(arr2)        :',size(arr2)
   write(*,*)'SIZE(arr2,DIM=1)  :',size(arr2,dim=1)
!
! CANNOT DETERMINE SIZE OF ASSUMED SIZE ARRAY LAST DIMENSION
!  write(*,*)'SIZE(arr2,DIM=2)  :',size(arr2,dim=2)

end subroutine interfaced

end program demo_size

結果

    SIZE of simple two-dimensional array
    SIZE(arr)       :total count of elements:          33
    SIZE(arr,DIM=1) :number of rows         :           3
    SIZE(arr,DIM=2) :number of columns      :          11
    interfaced assumed-shape array
    SIZE(arr1)        :          33
    SIZE(arr1,DIM=1)  :           3
    SIZE(arr1,DIM=2)  :          11
    SIZE(arr2,DIM=1)  :           2

標準#

Fortran 95、kind 引数付き - Fortran 2003

参照#

配列照会:#

  • size(3) - 配列のサイズを決定する

  • rank(3) - データオブジェクトのランク

  • shape(3) - 配列の形状を決定する

  • ubound(3) - 配列の上限次元境界

  • lbound(3) - 配列の下限次元境界

状態照会:#

  • allocated(3) - 割り当て可能なエンティティの状態

  • is_contiguous(3) - オブジェクトが連続しているかどうかをテストします

種類照会:#

  • kind(3) - エンティティの種類

ビット照会:#

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

ubound#

名前#

ubound(3) - [配列:照会] 配列の上限次元境界

要約#

    result = ubound(array [,dim] [,kind] )
     elemental TYPE(kind=KIND) function ubound(array,dim,kind)

      TYPE(kind=KIND),intent(in)           :: array
      integer(kind=**),intent(in),optional :: dim
      integer(kind=**),intent(in),optional :: kind

特性#

  • array は、任意の型の仮ランクまたは配列である必要があります。未割り当ての割り当て可能配列または関連付けられていないポインタにすることはできません。

  • dim はスカラー整数である必要があります。対応する実際の引数は、オプションのダミー引数、関連付け解除されたポインタ、または未割り当ての割り当て可能にすることはできません。

  • kind 結果の型パラメータを示す整数初期化式。

  • 戻り値は、型が整数で、kindがkindです。kindが省略されている場合、戻り値はデフォルトの整数kindになります。dimが存在する場合はスカラーになり、それ以外の場合はランクが1でサイズがnの配列になります(nはarrayのランク)。

  • **として指定された種類は、型でサポートされている任意の種類です。**

説明#

ubound(3) は、配列の上限境界、またはdim 次元に沿った単一の上限境界を返します。

オプション#

  • array

    上限境界を決定する任意の型の仮ランク配列または配列。割り当て可能な場合は割り当てられていなければならず、ポインタの場合は関連付けられていなければなりません。仮サイズ配列の場合、dim は存在する必要があります。

  • dim

    境界を決定するarray の特定の次元。dim がない場合、結果はarray の上限境界の配列です。array が仮サイズ配列の場合、dim は必要であり、その場合はarray のランク以下でなければなりません。

  • kind

    結果の種類パラメータを示します。存在しない場合は、デフォルトの種類の整数が返されます。

結果#

戻り値は、整数型で、kind の種類です。kind がない場合、戻り値はデフォルトの整数型です。

dim がない場合、結果はarray の各次元の上限境界の配列です。

dim が存在する場合、結果は、その次元方向の配列の上限境界に対応するスカラーです。

array が、配列全体または配列構造体のコンポーネントではなく式である場合、または関連する次元方向に範囲がゼロの場合、上限境界は関連する次元方向の要素数と見なされます。

注記1 ARRAYが仮ランクであり、ランクがゼロの場合、1 <= DIM <= 0 という要件を満たすことができないため、DIMは存在できません。

#

この関数は、仮サイズ配列または明示的なインターフェースのない関数では使用しないでください。インターフェースが定義されていない場合、エラーが発生する可能性があります。

サンプルプログラム

! program demo_ubound
module m2_bounds
implicit none

contains

subroutine msub(arr)
!!integer,intent(in) :: arr(*)  ! cannot be assumed-size array
integer,intent(in) :: arr(:)
   write(*,*)'MSUB: LOWER=',lbound(arr),'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
end subroutine msub

end module m2_bounds
!
program demo_ubound
use m2_bounds, only : msub
implicit none
interface
   subroutine esub(arr)
   integer,intent(in) :: arr(:)
   end subroutine esub
end interface
integer :: arr(-10:10)
   write(*,*)'MAIN: LOWER=',lbound(arr),'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
   call csub()
   call msub(arr)
   call esub(arr)
contains
subroutine csub
   write(*,*)'CSUB: LOWER=',lbound(arr),'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
end subroutine csub

end

subroutine esub(arr)
implicit none
integer,intent(in) :: arr(:)
   ! WARNING: IF CALLED WITHOUT AN EXPLICIT INTERFACE
   ! THIS WILL GIVE UNDEFINED ANSWERS (like 0,0,0)
   write(*,*)'ESUB: LOWER=',lbound(arr),'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
end subroutine esub
!end program demo_ubound

結果

 >  MAIN: LOWER=         -10 UPPER=          10 SIZE=          21
 >  CSUB: LOWER=         -10 UPPER=          10 SIZE=          21
 >  MSUB: LOWER=           1 UPPER=          21 SIZE=          21
 >  ESUB: LOWER=           1 UPPER=          21 SIZE=          21

標準#

Fortran 95、KIND引数付き - Fortran 2003

参照#

配列照会:#

  • size(3) - 配列のサイズを決定する

  • rank(3) - データオブジェクトのランク

  • shape(3) - 配列の形状を決定する

  • lbound(3) - 配列の下限次元境界

co_ubound(3)co_lbound(3)

状態照会:#

  • allocated(3) - 割り当て可能なエンティティの状態

  • is_contiguous(3) - オブジェクトが連続しているかどうかをテストします

種類照会:#

  • kind(3) - エンティティの種類

ビット照会:#

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

maxloc#

名前#

maxloc(3) - [配列:位置] 配列内の最大値の位置

要約#

    result = maxloc(array [,mask]) | maxloc(array [,dim] [,mask])
     NUMERIC function maxloc(array, dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • NUMERIC は、任意の組み込み数値型と種類を示します。

説明#

maxloc(3) は、配列内で最大値を持つ要素の位置を決定します。dim 引数が提供されている場合は、dim 方向の配列の各行に沿った最大要素の位置を決定します。

mask が存在する場合、mask が `.true.` である要素のみが考慮されます。配列内に最大値を持つ要素が複数ある場合、配列要素の順序で最初に現れる要素の位置が返されます。

配列のサイズがゼロの場合、または mask のすべての要素が `.false.` の場合、結果はゼロの配列になります。同様に、dim が指定され、特定の行に沿った mask のすべての要素がゼロの場合、その行の結果値はゼロになります。

オプション#

  • array

    整数実数、または文字型の配列である必要があります。

  • dim

    (オプション) 整数型のスカラーで、値は 1 以上 array の階数以下である必要があります。オプションのダミー引数にすることはできません。

  • mask

    論理型の配列で、array と適合する必要があります。

結果#

dim が存在しない場合、結果は、array の階数に等しい長さの階数 1 の配列です。dim が存在する場合、結果は、array の階数より 1 つ低い階数の配列で、dim 次元を除いた array のサイズに対応するサイズになります。dim が存在し、array の階数が 1 の場合、結果はスカラーです。いずれの場合も、結果はデフォルトの整数型になります。

返される値は、配列の先頭からのオフセットへの参照であり、配列の添字が 1 から始まらない場合、必ずしも添字値ではありません。

#

サンプルプログラム

program demo_maxloc
implicit none
integer      :: ii
integer,save :: i(-3:3)=[(abs(abs(ii)-50),ii=-3,3)]
integer,save :: ints(3,5)= reshape([&
   1,  2,  3,  4,  5, &
   10, 20, 30, 40, 50, &
   11, 22, 33, 44, 55  &
],shape(ints),order=[2,1])

    write(*,*) maxloc(ints)
    write(*,*) maxloc(ints,dim=1)
    write(*,*) maxloc(ints,dim=2)
    ! when array bounds do not start with one remember MAXLOC(3) returns
    ! the offset relative to the lower bound-1 of the location of the
    ! maximum value, not the subscript of the maximum value. When the
    ! lower bound of the array is one, these values are the same. In
    ! other words, MAXLOC(3) returns the subscript of the value assuming
    ! the first subscript of the array is one no matter what the lower
    ! bound of the subscript actually is.
    write(*,'(g0,1x,g0)') (ii,i(ii),ii=lbound(i,dim=1),ubound(i,dim=1))
    write(*,*)maxloc(i)

end program demo_maxloc

結果

 >     3       5
 >     3       3       3       3       3
 >     5       5       5
 >  -3 47
 >  -2 48
 >  -1 49
 >  0 50
 >  1 49
 >  2 48
 >  3 47

標準#

Fortran 95

参照#

fortran-lang組み込み記述

minloc#

名前#

minloc(3) - [ARRAY:LOCATION] 配列内の最小値の位置

概要#

    result = minloc(array [,mask]) | minloc(array [,dim] [,mask])
     NUMERIC function minloc(array, dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • NUMERIC は任意の数値型と種類です。

説明#

minloc(3) は、配列内で最小値を持つ要素の位置を決定します。または、dim 引数が指定されている場合、dim 方向の配列の各行に沿った最小要素の位置を決定します。

mask が存在する場合、masktrue. である要素のみが考慮されます。

配列内に最小値を持つ要素が複数ある場合、配列要素の順序で最初に現れる要素の位置が返されます。

配列のサイズがゼロの場合、または mask のすべての要素が .false. の場合、結果はゼロの配列になります。同様に、dim が指定され、特定の行に沿った mask のすべての要素がゼロの場合、その行の結果値はゼロになります。

オプション#

  • array

    整数実数、または文字型の配列である必要があります。

  • dim

    (オプション) 整数型のスカラーで、値は 1 以上 array の階数以下である必要があります。オプションのダミー引数にすることはできません。

  • mask

    論理型の配列で、array と適合する必要があります。

結果#

dim が存在しない場合、結果は、array の階数に等しい長さの階数 1 の配列です。dim が存在する場合、結果は、array の階数より 1 つ低い階数の配列で、dim 次元を除いた array のサイズに対応するサイズになります。dim が存在し、array の階数が 1 の場合、結果はスカラーです。いずれの場合も、結果はデフォルトの整数型になります。

#

サンプルプログラム

program demo_minloc
implicit none
integer,save :: ints(3,5)= reshape([&
   4, 10,  1,  7, 13, &
   9, 15,  6, 12,  3, &
  14,  5, 11,  2,  8  &
],shape(ints),order=[2,1])
   write(*,*) minloc(ints)
   write(*,*) minloc(ints,dim=1)
   write(*,*) minloc(ints,dim=2)
   ! where in each column is the smallest number .gt. 10 ?
   write(*,*) minloc(ints,dim=2,mask=ints.gt.10)
   ! a one-dimensional array with dim=1 explicitly listed returns a scalar
   write(*,*) minloc(pack(ints,.true.),dim=1) ! scalar
end program demo_minloc

結果

 >        1       3
 >        1       3       1       3       2
 >        3       5       4
 >        5       4       3
 >        7

標準#

Fortran 95

参照#

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

findloc#

名前#

findloc(3) - [ARRAY:LOCATION] ターゲット値と一致する次元 DIM に沿って MASK によって識別される ARRAY の最初の要素の位置

概要#

    result = findloc (array, value, dim [,mask] [,kind] [,back]) |
             findloc (array, value [,mask] [,kind] [,back])
     function findloc (array, value, dim, mask, kind, back)

      type TYPE(kind=KIND),intent(in)      :: array(..)
      type TYPE(kind=KIND),intent(in)      :: value
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)
      integer(kind=**),intent(in),optional :: kind
      logical(kind=**),intent(in),optional :: back

特性#

  • array は任意の組込み型の配列です。

  • value はスカラーでなければなりませんが、演算子 == または演算子 .EQV. で指定されているように、array と型互換性がある必要があります。

  • dim は、array の次元に対応する整数です。対応する実引数は、オプションのダミー引数であってはなりません。

  • mask は論理型であり、array と適合する必要があります。

  • kind はスカラー整数初期化式(つまり、定数)です。

  • back は論理型スカラーです。

  • 結果は、kind 引数が存在する場合は kind kind のデフォルトの種類または種類の整数です。dim が表示されない場合、結果はランク 1 の配列であり、サイズは array のランクに等しくなります。それ以外の場合は、結果は array と同じランクと形状の配列であり、次元 dim によって削減されます。

注記: **として指定された種類は、型に対してサポートされている種類です。

説明#

findloc(3) は、value と等しい値を持つ次元 dim に沿って mask によって識別される array の最初の要素の位置を返します。

arrayvalue の両方が論理型の場合、比較は .eqv. 演算子を使用して実行されます。それ以外の場合は、比較は == 演算子を使用して実行されます。比較の結果が .true. の場合、array のその要素は value と一致します。

value と一致する要素が 1 つしかない場合、その要素の添字が返されます。そうでない場合、複数の要素が value と一致し、back が存在しないか、値が .false. である場合、返される添字を持つ要素は、配列要素の順序で最初に現れる要素です。back が値 .true. で存在する場合、返される添字を持つ要素は、配列要素の順序で最後に現れる要素です。

オプション#

  • array

    組込み型の配列である必要があります。

  • value

    スカラーで、array と型互換性がある必要があります。

  • dim

    1 <= DIM <= n の範囲内の整数スカラーである必要があります。ここで、n は array のランクです。対応する実引数は、オプションのダミー引数であってはなりません。

  • mask

    (オプション) 論理型で、array と適合する必要があります。

  • kind

    (オプション) スカラー整数初期化式である必要があります。

  • back

    (オプション) 論理型スカラーである必要があります。

結果#

kind が存在する場合、kind 型パラメーターは kind の値によって指定されたものです。それ以外の場合は、kind 型パラメーターはデフォルトの整数型のものです。dim が表示されない場合、結果はランク 1 の配列であり、サイズは array のランクに等しくなります。それ以外の場合は、ランク n - 1 と形状になります。

   [d1, d2, . . ., dDIM-1, dDIM+1, . . ., dn ]

ここで

   [d1, d2, . . ., dn ]

array の形状です。

結果#

  • ケース (i): findloc (array, value) の結果は、ランク 1 の配列であり、その要素値は、値が value と一致する array の要素の添字の値です。そのような値がある場合、返される i 番目の添字は、1 から ei の範囲にあり、ここで ei は array の i 番目の次元の範囲です。要素が value と一致しない場合、または array のサイズがゼロの場合、結果のすべての要素はゼロになります。

  • ケース (ii): findloc (array, value, mask = mask) の結果は、ランク 1 の配列であり、その要素値は、mask の真の要素に対応する array の要素の添字の値であり、その値は value と一致します。そのような値がある場合、返される i 番目の添字は、1 から ei の範囲にあり、ここで ei は array の i 番目の次元の範囲です。要素が value と一致しない場合、array のサイズがゼロの場合、または mask のすべての要素の値が false の場合、結果のすべての要素はゼロになります。

#

サンプルプログラム

program demo_findloc
logical,parameter :: T=.true., F=.false.
integer,allocatable :: ibox(:,:)
logical,allocatable :: mask(:,:)
  ! basics
   ! the first element matching the value is returned AS AN ARRAY
   call printi('== 6',findloc ([2, 6, 4, 6], value = 6))
   call printi('== 6',findloc ([2, 6, 4, 6], value = 6,back=.true.))
   ! the first element matching the value is returned AS A SCALAR
   call printi('== 6',findloc ([2, 6, 4, 6], value = 6,dim=1))
   call printi('== 6',findloc ([2, 6, 4, 6], value = 6,back=.true.,dim=1))

   ibox=reshape([ 0,-5,  7, 7, &
                  3, 4, -1, 2, &
                  1, 5,  6, 7] ,shape=[3,4],order=[2,1])

   mask=reshape([ T, T, F, T, &
                  T, T, F, T, &
                  T, T, F, T] ,shape=[3,4],order=[2,1])

   call printi('array is', ibox )
   call printl('mask  is', mask )
   print *, 'so for == 7 and back=.false.'
   call printi('so for == 7 the address of the element is', &
           & findloc (ibox, 7, mask = mask) )
   print *, 'so for == 7 and back=.true.'
   call printi('so for == 7 the address of the element is', &
           & findloc (ibox, 7, mask = mask, back=.true.) )

   print *,'This is independent of declared lower bounds for the array'

   print *, ' using dim=N'
   ibox=reshape([ 1,  2, -9,  &
                  2,  2,  6 ] ,shape=[2,3],order=[2,1])

   call printi('array is', ibox )
   ! has the value [2, 1, 0] and
   call printi('',findloc (ibox, value = 2, dim = 1) )
   ! has the value [2, 1].
   call printi('',findloc (ibox, value = 2, dim = 2) )
contains
! GENERIC ROUTINES TO PRINT MATRICES
subroutine printl(title,a)
implicit none
!@(#) print small 2d logical scalar, vector, matrix in row-column format
character(len=*),intent(in)  :: title
logical,intent(in)           :: a(..)

character(len=*),parameter   :: row='(" > [ ",*(l1:,","))'
character(len=*),parameter   :: all='(" ",*(g0,1x))'
logical,allocatable          :: b(:,:)
integer                      :: i
   write(*,all,advance='no')trim(title)
   ! copy everything to a matrix to keep code simple
   select rank(a)
   rank (0); write(*,'(a)')' (a scalar)'; b=reshape([a],[1,1])
   rank (1); write(*,'(a)')' (a vector)'; b=reshape(a,[size(a),1])
   rank (2); write(*,'(a)')' (a matrix)'; b=a
   rank default; stop '*printl* unexpected rank'
   end select
   do i=1,size(b,dim=1)
      write(*,fmt=row,advance='no')b(i,:)
      write(*,'(" ]")')
   enddo
   write(*,all) '>shape=',shape(a),',rank=',rank(a),',size=',size(a)
   write(*,*)
end subroutine printl

subroutine printi(title,a)
implicit none
!@(#) print small 2d integer scalar, vector, matrix in row-column format
character(len=*),intent(in)  :: title
integer,intent(in)           :: a(..)
character(len=*),parameter   :: all='(" ",*(g0,1x))'
character(len=20)            :: row
integer,allocatable          :: b(:,:)
integer                      :: i
   write(*,all,advance='no')trim(title)
   ! copy everything to a matrix to keep code simple
   select rank(a)
   rank (0); write(*,'(a)')' (a scalar)'; b=reshape([a],[1,1])
   rank (1); write(*,'(a)')' (a vector)'; b=reshape(a,[size(a),1])
   rank (2); write(*,'(a)')' (a matrix)'; b=a
   rank default; stop '*printi* unexpected rank'
   end select
   ! find how many characters to use for integers
   write(row,'(i0)')ceiling(log10(real(maxval(abs(b)))))+2
   ! use this format to write a row
   row='(" > [",*(i'//trim(row)//':,","))'
   do i=1,size(b,dim=1)
      write(*,fmt=row,advance='no')b(i,:)
      write(*,'(" ]")')
   enddo
   write(*,all) '>shape=',shape(a),',rank=',rank(a),',size=',size(a)
   write(*,*)
end subroutine printi
end program demo_findloc

結果

 >  == 6  (a vector)
 >  > [  2 ]
 >  >shape= 1 ,rank= 1 ,size= 1
 >
 >  == 6  (a vector)
 >  > [  4 ]
 >  >shape= 1 ,rank= 1 ,size= 1
 >
 >  == 6  (a scalar)
 >  > [  2 ]
 >  >shape= ,rank= 0 ,size= 1
 >
 >  == 6  (a scalar)
 >  > [  4 ]
 >  >shape= ,rank= 0 ,size= 1
 >
 >  array is  (a matrix)
 >  > [  0, -5,  7,  7 ]
 >  > [  3,  4, -1,  2 ]
 >  > [  1,  5,  6,  7 ]
 >  >shape= 3 4 ,rank= 2 ,size= 12
 >
 >  mask  is  (a matrix)
 >  > [ T,T,F,T ]
 >  > [ T,T,F,T ]
 >  > [ T,T,F,T ]
 >  >shape= 3 4 ,rank= 2 ,size= 12
 >
 >  so for == 7 and back=.false.
 >  so for == 7 the address of the element is  (a vector)
 >  > [  1 ]
 >  > [  4 ]
 >  >shape= 2 ,rank= 1 ,size= 2
 >
 >  so for == 7 and back=.true.
 >  so for == 7 the address of the element is  (a vector)
 >  > [  3 ]
 >  > [  4 ]
 >  >shape= 2 ,rank= 1 ,size= 2
 >
 >  This is independent of declared lower bounds for the array
 >   using dim=N
 >  array is  (a matrix)
 >  > [  1,  2, -9 ]
 >  > [  2,  2,  6 ]
 >  >shape= 2 3 ,rank= 2 ,size= 6
 >
 >    (a vector)
 >  > [  2 ]
 >  > [  1 ]
 >  > [  0 ]
 >  >shape= 3 ,rank= 1 ,size= 3
 >
 >    (a vector)
 >  > [  2 ]
 >  > [  1 ]
 >  >shape= 2 ,rank= 1 ,size= 2
 >

標準#

Fortran 95

参照#

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

transpose#

名前#

transpose(3) - [ARRAY:MANIPULATION] 階数 2 の配列の転置

概要#

    result = transpose(matrix)
     function transpose(matrix)

      type(TYPE(kind=KIND)            :: transpose(N,M)
      type(TYPE(kind=KIND),intent(in) :: matrix(M,N)

特性#

  • matrix は、階数 2 の任意の型の配列です。

  • 結果は、matrix と同じ型と種類になり、入力配列の形状が反転します。

説明#

transpose(3) は、階数 2 の配列を転置します。

配列は、指定された行列の行と列を入れ替えることによって転置されます。つまり、結果の要素 (i,j) は、すべての (i,j) について、入力の要素 (j,i) の値を持ちます。

オプション#

  • matrix

    転置する配列

結果#

入力配列の転置。結果は matrix と同じ型を持ち、matrix の形状が [n, m] の場合、形状 [m, n] を持ちます。

#

サンプルプログラム

program demo_transpose
implicit none
integer,save :: xx(3,5)= reshape([&
    1,  2,  3,  4,  5,    &
   10, 20, 30, 40, 50,    &
   11, 22, 33, 44, -1055  &
 ],shape(xx),order=[2,1])

call print_matrix_int('xx array:',xx)
call print_matrix_int('xx array transposed:',transpose(xx))

contains

subroutine print_matrix_int(title,arr)
! print small 2d integer arrays in row-column format
implicit none
character(len=*),intent(in)  :: title
integer,intent(in)           :: arr(:,:)
integer                      :: i
character(len=:),allocatable :: biggest
   write(*,*)trim(title)  ! print title
   biggest='           '  ! make buffer to write integer into
   ! find how many characters to use for integers
   write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
   ! use this format to write a row
   biggest='(" > [",*(i'//trim(biggest)//':,","))'
   ! print one row of array at a time
   do i=1,size(arr,dim=1)
      write(*,fmt=biggest,advance='no')arr(i,:)
      write(*,'(" ]")')
   enddo
end subroutine print_matrix_int

end program demo_transpose

結果

    xx array:
    > [     1,     2,     3,     4,     5 ]
    > [    10,    20,    30,    40,    50 ]
    > [    11,    22,    33,    44, -1055 ]
    xx array transposed:
    > [     1,    10,    11 ]
    > [     2,    20,    22 ]
    > [     3,    30,    33 ]
    > [     4,    40,    44 ]
    > [     5,    50, -1055 ]

標準#

Fortran 95

参照#

  • merge(3) - 変数のマージ

  • pack(3) - 配列を階数 1 の配列にパック

  • spread(3) - 次元を追加してデータを複製

  • unpack(3) - ベクトルの要素を散らす

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

all#

名前#

all(3) - [ARRAY:REDUCTION] すべての値が真であるかどうかを判定する

概要#

   result = all(mask [,dim])
     function all(mask ,dim)

      logical(kind=KIND),intent(in) :: mask(..)
      integer,intent(in),optional   :: dim
      logical(kind=KIND)            :: all(..)

特性#

  • mask は *論理型* 配列です。

  • dim は *整数型* です。

  • dim が指定されている場合、結果は論理型配列になります。指定されていない場合は論理型スカラーになります。mask と同じ特性を持ちます。

説明#

all(3) は、dim が指定されている場合は、配列のdim次元方向に沿ってmask内のすべての値が真であるかどうかを判定します。指定されていない場合は、すべての要素がまとめてテストされます。

このテストの種類は、dim次元方向に沿ったmaskの要素の論理積と呼ばれます。

maskは一般的に*論理型*式であり、配列の比較やその他の多くの一般的な演算を可能にします。

オプション#

  • mask

    すべての要素が*.true.*であるかどうかテストされる論理型配列。

  • dim

    dim は、テスト対象の要素をグループ化するmaskの要素を通る方向を示します。

    dim の値は、1 と mask の階数(次元数)の間にある必要があります。

    対応する実引数は、オプションの仮引数であってはなりません。

    dim が存在しない場合、すべての要素がテストされ、単一のスカラー値が返されます。

結果#

  1. dim が存在しない場合、mask のすべての要素が*.true.*であれば、all(mask) は*.true.*になります。mask のサイズがゼロの場合も*.true.*になり、それ以外の場合は*.false.*になります。

  2. mask の階数が1の場合、all(mask, dim)all(mask) と同等です。

  3. mask の階数が1より大きく、dim が存在する場合、all(mask,dim) は、階数がmaskより1つ少ない配列を返します。形状は、dim次元が省略されたmaskの形状から決定されます。dim次元方向の各要素の集合に対して値が返されます。

#

サンプルプログラム

program demo_all
implicit none
logical,parameter :: T=.true., F=.false.
logical bool
  ! basic usage
   ! is everything true?
   bool = all([ T,T,T ])
   bool = all([ T,F,T ])
   print *, bool

  ! by a dimension
   ARRAYS: block
   integer :: a(2,3), b(2,3)
    ! set everything to one except one value in b
    a = 1
    b = 1
    b(2,2) = 2
    ! now compare those two arrays
    print *,'entire array :', all(a ==  b )
    print *,'compare columns:', all(a ==  b, dim=1)
    print *,'compare rows:', all(a ==  b, dim=2)
  end block ARRAYS

end program demo_all

結果

 >  T
 >  F
 >  entire array : F
 >  compare columns: T F T
 >  compare rows: T F

標準#

Fortran 95

参照#

any(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

any#

名前#

any(3) - [ARRAY:REDUCTION] 論理型配列内の値のいずれかが*.true.*であるかどうかを判定する

概要#

    result = any(mask [,dim])
     function any(mask, dim)

      logical(kind=KIND),intent(in) :: mask(..)
      integer,intent(in),optional   :: dim
      logical(kind=KIND)            :: any(..)

特性#

  • mask は *論理型* 配列です。

  • dim はスカラー整数です。

  • dim が指定されている場合、結果は論理型配列になります。指定されていない場合は論理型スカラーになります。

説明#

any(3) は、論理型配列mask内のdim次元方向に沿った値のいずれかが*.true.*であるかどうかを判定します。

オプション#

  • mask

    グループ単位または全体で*.true.*の値についてテストされる論理型式または値の配列。

  • dim

    スカラー値を返すのではなく、指定された次元方向に沿った値の配列を返すことを示す、1とrank(mask)の間にある整数値。

結果#

any(mask) は、型がmaskの型パラメーターと同じ論理型のスカラー値を返します。dim が存在する場合、any(mask, dim) は、階数がmaskより1つ少ない配列を返します。形状は、dim次元が省略されたmaskの形状から決定されます。

  1. any(mask) は、mask のいずれかの要素が *.true.* の場合 *.true.* を返し、それ以外の場合は *.false.* を返します。mask のサイズがゼロの場合も *.false.* を返します。

  2. mask の階数が1の場合、any(mask, dim)any(mask) と同等です。階数が1より大きい場合、any(mask, dim) は配列セクションに any(mask) を適用することで決定されます。

#

サンプルプログラム

program demo_any
implicit none
logical,parameter :: T=.true., F=.false.
integer           :: a(2,3), b(2,3)
logical           :: bool
  ! basic usage
   bool = any([F,F,T,F])
   print *,bool
   bool = any([F,F,F,F])
   print *,bool
  ! fill two integer arrays with values for testing
   a = 1
   b = 1
   b(:,2) = 2
   b(:,3) = 3
  ! using any(3) with logical expressions you can compare two arrays
  ! in a myriad of ways
   ! first, print where elements of b are bigger than in a
   call printl( 'first print b > a             ', b > a         )
   ! now use any() to test
   call printl( 'any true values?  any(b > a)  ', any(b > a )   )
   call printl( 'again by columns? any(b > a,1)', any(b > a, 1) )
   call printl( 'again by rows?    any(b > a,2)', any(b > a, 2) )
contains
! CONVENIENCE ROUTINE. this is not specific to ANY()
subroutine printl(title,a)
use, intrinsic :: iso_fortran_env, only : &
 & stderr=>ERROR_UNIT,&
 & stdin=>INPUT_UNIT,&
 & stdout=>OUTPUT_UNIT
implicit none

!@(#) print small 2d logical scalar, vector, or matrix

character(len=*),parameter   :: all='(*(g0,1x))'
character(len=*),parameter   :: row='(" > [ ",*(l1:,","))'
character(len=*),intent(in)  :: title
logical,intent(in)           :: a(..)
integer                      :: i
   write(*,*)
   write(*,all,advance='no')trim(title),&
    & ' : shape=',shape(a),',rank=',rank(a),',size=',size(a)
   ! get size and shape of input
   select rank(a)
   rank (0); write(*,'(a)')'(a scalar)'
      write(*,fmt=row,advance='no')a
      write(*,'(" ]")')
   rank (1); write(*,'(a)')'(a vector)'
      do i=1,size(a)
         write(*,fmt=row,advance='no')a(i)
         write(*,'(" ]")')
      enddo
   rank (2); write(*,'(a)')'(a matrix) '
      do i=1,size(a,dim=1)
         write(*,fmt=row,advance='no')a(i,:)
         write(*,'(" ]")')
      enddo
   rank default
      write(stderr,*)'*printl* did not expect rank=', rank(a), &
       & 'shape=', shape(a),'size=',size(a)
      stop '*printl* unexpected rank'
   end select

end subroutine printl

end program demo_any

結果

 >  T
 >  F
 >
 > first print b > a : shape=23,rank=2,size=6(a matrix)
 >  > [ F,T,T ]
 >  > [ F,T,T ]
 >
 > any true values?  any(b > a) : shape=,rank=0,size=1(a scalar)
 >  > [ T ]
 >
 > again by columns? any(b > a,1) : shape=3,rank=1,size=3(a vector)
 >  > [ F ]
 >  > [ T ]
 >  > [ T ]
 >
 > again by rows?    any(b > a,2) : shape=2,rank=1,size=2(a vector)
 >  > [ T ]
 >  > [ T ]

標準#

Fortran 95

参照#

all(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

count#

名前#

count(3) - [ARRAY:REDUCTION] 配列内の真の値を数える

概要#

    result = count(mask [,dim] [,kind] )
     integer(kind=KIND) function count(mask, dim, KIND )

      logical(kind=**),intent(in) :: mask(..)
      integer(kind=**),intent(in),optional :: dim
      integer(kind=**),intent(in),optional :: KIND

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • mask は任意の形状と種類の*論理型*配列です。

  • dim が存在する場合、結果は指定された階数が削除された配列になります。

  • KIND は、*整数型*の種類として有効なスカラー整数定数式です。

  • kind が指定されて結果の種類が宣言されていない限り、戻り値はデフォルトの*整数型*になります。

説明#

count(3) は、論理型mask内の*.true.*要素の数を数えます。または、dim引数が指定されている場合、dim方向の配列の各行の要素の数を数えます。配列のサイズがゼロの場合、またはmaskのすべての要素が偽の場合、結果は0になります。

オプション#

  • mask

    *.true.*値の数を数える配列

  • dim

    この次元を結果から削除し、削除された次元方向に沿った*.true.*値の数の配列を生成することを指定します。存在しない場合、結果はmask内の真の要素のスカラーカウントになります。値は1 <= dim <= nの範囲内にある必要があります。ここで、nはmaskの階数(次元数)です。

    対応する実引数は、オプションの仮引数、関連付けられていないポインター、または割り当てられていない割り当て可能変数であってはなりません。

  • kind

    結果の型パラメータを示す整数初期化式。

結果#

dimが存在しない場合、戻り値はmask内の*.true.*値の数です。

dim が存在する場合、結果は入力配列maskの階数より1つ少ない階数の配列であり、dim次元が削除されたarrayの形状に対応するサイズを持ちます。残りの要素には、削除された次元方向に沿った*.true.*要素の数が含まれます。

#

サンプルプログラム

   program demo_count
   implicit none
   character(len=*),parameter :: ints='(*(i2,1x))'
   ! two arrays and a mask all with the same shape
   integer, dimension(2,3) :: a, b
   logical, dimension(2,3) :: mymask
   integer :: i
   integer :: c(2,3,4)

   print *,'the numeric arrays we will compare'
   a = reshape( [ 1, 2, 3, 4, 5, 6 ], [ 2, 3 ])
   b = reshape( [ 0, 7, 3, 4, 5, 8 ], [ 2, 3 ])
   c = reshape( [( i,i=1,24)], [ 2, 3 ,4])
   print '(3i3)', a(1,:)
   print '(3i3)', a(2,:)
   print *
   print '(3i3)', b(1,:)
   print '(3i3)', b(2,:)
   !
   ! basic calls
   print *, 'count a few basic things creating a mask from an expression'
   print *, 'count a>b',count(a>b)
   print *, 'count b<a',count(a<b)
   print *, 'count b==a',count(a==b)
   print *, 'check sum = ',count(a>b) + &
                         & count(a<b) + &
                         & count(a==b).eq.size(a)
   !
   ! The common usage is just getting a count, but if you want
   ! to specify the DIM argument and get back reduced arrays
   ! of counts this is easier to visualize if we look at a mask.
   print *, 'make a mask identifying unequal elements ...'
   mymask = a.ne.b
   print *, 'the mask generated from a.ne.b'
   print '(3l3)', mymask(1,:)
   print '(3l3)', mymask(2,:)
   !
   print *,'count total and along rows and columns ...'
   !
   print '(a)', 'number of elements not equal'
   print '(a)', '(ie. total true elements in the mask)'
   print '(3i3)', count(mymask)
   !
   print '(a)', 'count of elements not equal in each column'
   print '(a)', '(ie. total true elements in each column)'
   print '(3i3)', count(mymask, dim=1)
   !
   print '(a)', 'count of elements not equal in each row'
   print '(a)', '(ie. total true elements in each row)'
   print '(3i3)', count(mymask, dim=2)
   !
   ! working with rank=3 ...
   print *, 'lets try this with c(2,3,4)'
   print *,'  taking the result of the modulo   '
   print *,'   z=1      z=2      z=3      z=4   '
   print *,'  1 3 0 || 2 4 1 || 3 0 2 || 4 1 3 |'
   print *,'  2 4 1 || 3 0 2 || 4 1 3 || 0 2 4 |'
   print *,'                                    '
   print *,'  would result in the mask ..       '
   print *,'  F F T || F F F || F T F || F F F |'
   print *,'  F F F || F T F || F F F || T F F |'
   print *,'                                    '
   print *,' the total number of .true.values is'
   print ints, count(modulo(c,5).eq.0)
   call printi('counting up along a row and removing rows',&
   count(modulo(c,5).eq.0,dim=1))
   call printi('counting up along a column and removing columns',&
   count(modulo(c,5).eq.0,dim=2))
   call printi('counting up along a depth and removing depths',&
   count(modulo(c,5).eq.0,dim=3))
   !
   contains
   !
   ! CONVENIENCE ROUTINE FOR PRINTING SMALL INTEGER MATRICES
   subroutine printi(title,arr)
   implicit none
   !
   !@(#) print small 2d integer arrays in row-column format
   !
   character(len=*),parameter :: all='(*(g0,1x))' ! a handy format
   character(len=*),intent(in)  :: title
   integer,intent(in)           :: arr(:,:)
   integer                      :: i
   character(len=:),allocatable :: biggest
      !
      print all
      print all, trim(title),':(',shape(arr),')'  ! print title
      biggest='           '  ! make buffer to write integer into
      ! find how many characters to use for integers
      write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
      ! use this format to write a row
      biggest='(" > [",*(i'//trim(biggest)//':,","))'
      ! print one row of array at a time
      do i=1,size(arr,dim=1)
         write(*,fmt=biggest,advance='no')arr(i,:)
         write(*,'(" ]")')
      enddo
      !
   end subroutine printi
   end program demo_count

結果

 >   the numeric arrays we will compare
 >    1  3  5
 >    2  4  6
 >
 >    0  3  5
 >    7  4  8
 >   count a few basic things creating a mask from an expression
 >   count a>b           1
 >   count b<a           2
 >   count b==a           3
 >   check sum =  T
 >   make a mask identifying unequal elements ...
 >   the mask generated from a.ne.b
 >    T  F  F
 >    T  F  T
 >   count total and along rows and columns ...
 >  number of elements not equal
 >  (ie. total true elements in the mask)
 >    3
 >  count of elements not equal in each column
 >  (ie. total true elements in each column)
 >    2  0  1
 >  count of elements not equal in each row
 >  (ie. total true elements in each row)
 >    1  2
 >   lets try this with c(2,3,4)
 >     taking the result of the modulo
 >      z=1      z=2      z=3      z=4
 >     1 3 0 || 2 4 1 || 3 0 2 || 4 1 3 |
 >     2 4 1 || 3 0 2 || 4 1 3 || 0 2 4 |
 >
 >     would result in the mask ..
 >     F F T || F F F || F T F || F F F |
 >     F F F || F T F || F F F || T F F |
 >
 >    the total number of .true.values is
 >   4
 >
 >  counting up along a row and removing rows :( 3 4 )
 >   > [ 0, 0, 0, 1 ]
 >   > [ 0, 1, 1, 0 ]
 >   > [ 1, 0, 0, 0 ]
 >
 >  counting up along a column and removing columns :( 2 4 )
 >   > [ 1, 0, 1, 0 ]
 >   > [ 0, 1, 0, 1 ]
 >
 >  counting up along a depth and removing depths :( 2 3 )
 >   > [ 0, 1, 1 ]
 >   > [ 1, 1, 0 ]

標準#

Fortran 95、KIND引数付き - Fortran 2003

参照#

any(3)all(3)sum(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

maxval#

名前#

maxval(3) - [ARRAY:REDUCTION] 配列または行内の最大値を決定する

概要#

    result = maxval(array [,mask]) | maxval(array [,dim] [,mask])
     NUMERIC function maxval(array ,dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • NUMERIC は任意の数値型および種類を指定します。

説明#

maxval(3) は、配列値内の要素の最大値を決定します。または、dim引数が指定されている場合、dim方向の配列の各行に沿った最大値を決定します。maskが存在する場合、maskが*.true.*である要素のみが考慮されます。配列のサイズがゼロの場合、またはmaskのすべての要素が*.false.*の場合、結果は、arrayが数値型の場合はその型と種類で最も小さい数、arrayが文字型の場合はヌルの文字列になります。

オプション#

  • array

    整数実数、または文字型の配列である必要があります。

  • dim

    (オプション) 整数型のスカラーで、値は 1 以上 array の階数以下である必要があります。オプションのダミー引数にすることはできません。

  • mask

    (オプション) *論理型*の配列であり、arrayと適合する必要があります。

結果#

dim が存在しない場合、または array の階数が 1 の場合、結果はスカラーです。dim が存在する場合、結果は、階数が array より 1 つ少なく、サイズが dim 次元が削除された array のサイズに対応する配列です。いずれの場合も、結果は array と同じ型および種類になります。

#

サンプルプログラム

program demo_maxval
implicit none
integer,save :: ints(3,5)= reshape([&
   1,  2,  3,  4,  5, &
  10, 20, 30, 40, 50, &
  11, 22, 33, 44, 55  &
],shape(ints),order=[2,1])

   write(*,*) maxval(ints)
   write(*,*) maxval(ints,dim=1)
   write(*,*) maxval(ints,dim=2)
   ! find biggest number less than 30 with mask
   write(*,*) maxval(ints,mask=ints.lt.30)
end program demo_maxval

結果

 >  55
 >  11     22     33     44     55
 >   5     50     55
 >  22

標準#

Fortran 95

参照#

maxloc(3)minloc(3)minval(3)max(3)min(3)

fortran-lang組み込み記述

minval#

名前#

minval(3) - [ARRAY:REDUCTION] 配列の最小値

概要#

    result = minval(array, [mask]) | minval(array [,dim] [,mask])
     NUMERIC function minval(array, dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • NUMERIC は任意の数値型と種類です。

説明#

minval(3) は、配列値内の要素の最小値を決定します。または、dim引数が指定されている場合、dim方向の配列の各行に沿った最小値を決定します。

maskが存在する場合、maskが*.true.*である要素のみが考慮されます。

配列のサイズがゼロの場合、またはmaskのすべての要素が*.false.*の場合、結果は、arrayが数値型の場合はhuge(array)arrayが文字型の場合はchar(len=255)文字の文字列になります。

オプション#

  • array

    整数実数、または文字型の配列である必要があります。

  • dim

    (オプション) 整数型のスカラーでなければなりません。値は1からARRAYのランクまでの間でなければなりません。オプションのダミー引数であってはなりません。

  • mask

    論理型の配列で、array と適合する必要があります。

結果#

dimが省略されている場合、またはarrayのランクが1の場合、結果はスカラーになります。

dimが存在する場合、結果はarrayのランクより1つ少ないランクの配列になり、サイズはdim次元が削除されたarrayのサイズに対応します。いずれの場合も、結果はarrayと同じ型とkindになります。

#

サンプルプログラム

program demo_minval
implicit none
integer :: i
character(len=*),parameter :: g='(3x,*(g0,1x))'

integer,save :: ints(3,5)= reshape([&
       1,  -2,   3,   4,   5,  &
      10,  20, -30,  40,  50,  &
      11,  22,  33, -44,  55  &
],shape(ints),order=[2,1])

integer,save :: box(3,5,2)

   box(:,:,1)=ints
   box(:,:,2)=-ints

   write(*,*)'Given the array'
   write(*,'(1x,*(g4.4,1x))') &
   & (ints(i,:),new_line('a'),i=1,size(ints,dim=1))

   write(*,*)'What is the smallest element in the array?'
   write(*,g) minval(ints),'at <',minloc(ints),'>'

   write(*,*)'What is the smallest element in each column?'
   write(*,g) minval(ints,dim=1)

   write(*,*)'What is the smallest element in each row?'
   write(*,g) minval(ints,dim=2)

   ! notice the shape of the output has less columns
   ! than the input in this case
   write(*,*)'What is the smallest element in each column,'
   write(*,*)'considering only those elements that are'
   write(*,*)'greater than zero?'
   write(*,g) minval(ints, dim=1, mask = ints > 0)

   write(*,*)&
   & 'if everything is false a zero-sized array is NOT returned'
   write(*,*) minval(ints, dim=1, mask = .false.)
   write(*,*)'even for a zero-sized input'
   write(*,g) minval([integer ::], dim=1, mask = .false.)

   write(*,*)'a scalar answer for everything false is huge()'
   write(*,g) minval(ints, mask = .false.)
   write(*,g) minval([integer ::], mask = .false.)

   write(*,*)'some calls with three dimensions'
   write(*,g) minval(box, mask = .true. )
   write(*,g) minval(box, dim=1, mask = .true. )

   write(*,g) minval(box, dim=2, mask = .true. )
   write(*,g) 'shape of answer is ', &
   & shape(minval(box, dim=2, mask = .true. ))

end program demo_minval

結果

 > Given the array
 >    1   -2    3    4    5
 >   10   20  -30   40   50
 >   11   22   33  -44   55
 >
 > What is the smallest element in the array?
 >   -44 at < 3 4 >
 > What is the smallest element in each column?
 >   1 -2 -30 -44 5
 > What is the smallest element in each row?
 >   -2 -30 -44
 > What is the smallest element in each column,
 > considering only those elements that are
 > greater than zero?
 >   1 20 3 4 5
 > if everything is false a zero-sized array is NOT returned
 >  2147483647  2147483647  2147483647  2147483647  2147483647
 > even for a zero-sized input
 >   2147483647
 > a scalar answer for everything false is huge()
 >   2147483647
 >   2147483647
 > some calls with three dimensions
 >   -55
 >   1 -2 -30 -44 5 -11 -22 -33 -40 -55
 >   -2 -30 -44 -5 -50 -55
 >   shape of answer is  3 2

標準#

Fortran 95

参照#

min(3)minloc(3) maxloc(3)maxval(3)min(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

product#

名前#

product(3) - [ARRAY:REDUCTION] 配列要素の積

概要#

    result = product(array [,dim] [,mask])
     NUMERIC function product(array, dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • NUMERIC は任意の数値型と種類です。

説明#

product(3) は、arrayの選択されたすべての要素を掛け合わせます。または、maskの対応する要素が.true.の場合、次元dimに沿って掛け合わせます。

dimが省略されている場合、arrayのすべての要素の積を持つスカラーが返されます。(ゼロサイズのarray1を返します。)

dimが存在する場合、マスクされた配列の次元が1(つまり、ベクトル)の場合、結果はスカラーになります。それ以外の場合は、ランクがn-1(ここでnarrayのランク)の配列になり、次元dimが削除されたarrayに似た形状になります。

オプション#

  • array

    整数型、実数型、または複素数型の配列でなければなりません。

  • dim

    整数型のスカラーでなければなりません。値の範囲は1からnで、narrayのランクです。

  • mask

    論理型でなければなりません。スカラーまたはarrayと同じ形状の配列のいずれかです。

結果#

結果はarrayと同じ型になります。

#

サンプルプログラム

program demo_product
implicit none
character(len=*),parameter :: all='(*(g0,1x))' ! a handy format
character(len=1),parameter :: nl=new_line('a')

NO_DIM: block
!    If DIM is not specified, the result is the product of all the
!    selected array elements.
integer :: i,n, p1, p2
integer,allocatable :: array(:)
   ! all elements are selected by default
   do n=1,10
      print all, 'factorial of ',n,' is ', product([(real(i),i=1,n)])
   enddo

   ! using a mask
   array=[10,12,13,15,20,25,30]
   p1=product(array, mask=mod(array, 2)==1) ! only odd elements
   p2=product(array, mask=mod(array, 2)/=1) ! only even elements
   print all, nl,'product of all elements',product(array) ! all elements
   print all, ' odd * even =',nl,p1,'*',p2,'=',p1*p2

   ! NOTE: If ARRAY is a zero-sized array, the result is equal to one
   print all
   print all, 'zero-sized array=>',product([integer :: ])
   ! NOTE: If nothing in the mask is true, this also results in a null
   !       array
   print all, 'all elements have a false mask=>', &
            & product(array,mask=.false.)

endblock NO_DIM

WITH_DIM: block
integer :: rect(2,3)
integer :: box(2,3,4)

!  lets fill a few arrays
   rect = reshape([ &
     1, 2, 3,       &
     4, 5, 6        &
   ],shape(rect),order=[2,1])
   call print_matrix_int('rect',rect)

!  Find the product of each column in RECT.
   print all, 'product of columns=',product(rect, dim = 1)

! Find the product of each row in RECT.
   print all, 'product of rows=',product(rect, dim = 2)

! now lets try a box
   box(:,:,1)=rect
   box(:,:,2)=rect*(+10)
   box(:,:,3)=rect*(-10)
   box(:,:,4)=rect*2
   ! lets look at the values
   call print_matrix_int('box 1',box(:,:,1))
   call print_matrix_int('box 2',box(:,:,2))
   call print_matrix_int('box 3',box(:,:,3))
   call print_matrix_int('box 4',box(:,:,4))

   ! remember without dim= even a box produces a scalar
   print all, 'no dim gives a scalar',product(real(box))

   ! only one plane has negative values, so note all the "1" values
   ! for vectors with no elements
   call print_matrix_int('negative values', &
   & product(box,mask=box < 0,dim=1))

!   If DIM is specified and ARRAY has rank greater than one, the
!   result is a new array in which dimension DIM has been eliminated.

   ! pick a dimension to multiply though
   call print_matrix_int('dim=1',product(box,dim=1))

   call print_matrix_int('dim=2',product(box,dim=2))

   call print_matrix_int('dim=3',product(box,dim=3))

endblock WITH_DIM

contains

   subroutine print_matrix_int(title,arr)
   implicit none

   !@(#) print small 2d integer arrays in row-column format

   character(len=*),intent(in)  :: title
   integer,intent(in)           :: arr(:,:)
   integer                      :: i
   character(len=:),allocatable :: biggest

      print all
      print all, trim(title),':(',shape(arr),')'  ! print title
      biggest='           '  ! make buffer to write integer into
      ! find how many characters to use for integers
      write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
      ! use this format to write a row
      biggest='(" > [",*(i'//trim(biggest)//':,","))'
      ! print one row of array at a time
      do i=1,size(arr,dim=1)
         write(*,fmt=biggest,advance='no')arr(i,:)
         write(*,'(" ]")')
      enddo

   end subroutine print_matrix_int

end program demo_product

結果

factorial of  1  is  1.000000
factorial of  2  is  2.000000
factorial of  3  is  6.000000
factorial of  4  is  24.00000
factorial of  5  is  120.0000
factorial of  6  is  720.0000
factorial of  7  is  5040.000
factorial of  8  is  40320.00
factorial of  9  is  362880.0
factorial of  10  is  3628800.

 product of all elements 351000000
 odd * even =
 4875 * 72000 = 351000000

zero-sized array=> 1
all elements have a false mask=> 1

rect :( 2 3 )
 > [  1,  2,  3 ]
 > [  4,  5,  6 ]
product of columns= 4 10 18
product of rows= 6 120

box 1 :( 2 3 )
 > [  1,  2,  3 ]
 > [  4,  5,  6 ]

box 2 :( 2 3 )
 > [  10,  20,  30 ]
 > [  40,  50,  60 ]

box 3 :( 2 3 )
 > [ -10, -20, -30 ]
 > [ -40, -50, -60 ]

box 4 :( 2 3 )
 > [   2,   4,   6 ]
 > [   8,  10,  12 ]
no dim gives a scalar .1719927E+26

negative values :( 3 4 )
 > [     1,     1,   400,     1 ]
 > [     1,     1,  1000,     1 ]
 > [     1,     1,  1800,     1 ]

dim=1 :( 3 4 )
 > [     4,   400,   400,    16 ]
 > [    10,  1000,  1000,    40 ]
 > [    18,  1800,  1800,    72 ]

dim=2 :( 2 4 )
 > [       6,    6000,   -6000,      48 ]
 > [     120,  120000, -120000,     960 ]

dim=3 :( 2 3 )
 > [    -200,   -3200,  -16200 ]
 > [  -51200, -125000, -259200 ]

標準#

Fortran 95

参照#

sum(3)、要素ごとの乗算はアスタリスク文字を使用して直接行われます。

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

sum#

名前#

sum(3) - [ARRAY:REDUCTION] 配列の要素の合計

概要#

   result = sum(array [,dim[,mask]] | [mask] )
     TYPE(kind=KIND) function sum(array, dim, mask)

      TYPE(kind=KIND),intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • **として指定された種類は、型でサポートされている任意の種類です。**

  • arrayは、整数型、実数型、または複素数のいずれかの数値型にすることができます。

  • dim は *整数型* です。

  • maskは論理型であり、arrayと適合性があります。

  • 結果はarrayと同じ型とkindになります。dimが存在しない場合、またはarrayがベクトルの場合はスカラーです。それ以外の場合は配列です。

説明#

sum(3) はarrayの要素を加算します。

arrayのみが指定されている場合、すべての要素が合計されますが、dimで指定された次元ごとに合計のグループが返される場合があり、論理マスクによって加算する要素を選択できます。

合計の実行方法については、指定された方法はありません。そのため、累積誤差が補償されるかどうかはプロセッサ依存です。

オプション#

  • array

    加算する要素を含む配列

  • dim

    1からnまでの範囲の値で、nはarrayのランク(次元の数)に等しくなります。dimは、合計を作成する次元を指定します。省略された場合は、maskによってオプションで選択された要素のスカラー合計が返されます。

  • mask

    arrayと同じ形状の配列で、加算する要素を指定します。省略された場合は、すべての要素が合計に使用されます。

結果#

dimが省略されている場合、arrayの選択されたすべての要素の合計を持つスカラーが返されます。それ以外の場合は、ランクがn-1(ここでnはarrayのランク)の配列になり、次元dimが削除されたarrayに似た形状になります。ベクトルのランクは1であるため、結果はスカラーになります(n==1の場合、n-1はゼロです。ランクがゼロはスカラーを意味します)。

#

サンプルプログラム

program demo_sum
implicit none
integer :: vector(5) , matrix(3,4), box(5,6,7)

   vector = [ 1, 2, -3, 4, 5 ]

   matrix(1,:)=[  -1,   2,    -3,   4    ]
   matrix(2,:)=[  10,   -20,  30,   -40  ]
   matrix(3,:)=[  100,  200, -300,  400  ]

   box=11

  ! basics
   print *, 'sum all elements:',sum(vector)
   print *, 'real :',sum([11.0,-5.0,20.0])
   print *, 'complex :',sum([(1.1,-3.3),(4.0,5.0),(8.0,-6.0)])
  ! with MASK option
   print *, 'sum odd elements:',sum(vector, mask=mod(vector, 2)==1)
   print *, 'sum positive values:', sum(vector, mask=vector>0)

   call printi('the input array', matrix )
   call printi('sum of all elements in matrix', sum(matrix) )
   call printi('sum of positive elements', sum(matrix,matrix>=0) )
  ! along dimensions
   call printi('sum along rows', sum(matrix,dim=1) )
   call printi('sum along columns', sum(matrix,dim=2) )
   call printi('sum of a vector is always a scalar', sum(vector,dim=1) )
   call printi('sum of a volume by row', sum(box,dim=1) )
   call printi('sum of a volume by column', sum(box,dim=2) )
   call printi('sum of a volume by depth', sum(box,dim=3) )

contains
! CONVENIENCE ROUTINE; NOT DIRECTLY CONNECTED TO SPREAD(3)
subroutine printi(title,a)
use, intrinsic :: iso_fortran_env, only : stderr=>ERROR_UNIT,&
 & stdin=>INPUT_UNIT, stdout=>OUTPUT_UNIT
implicit none

!@(#) print small 2d integer scalar, vector, matrix in row-column format

character(len=*),intent(in)  :: title
integer,intent(in)           :: a(..)

character(len=*),parameter   :: all='(" ",*(g0,1x))'
character(len=20)            :: row
integer,allocatable          :: b(:,:)
integer                      :: i
   write(*,all,advance='no')trim(title)
   ! copy everything to a matrix to keep code simple
   select rank(a)
   rank (0); write(*,'(a)')' (a scalar)'; b=reshape([a],[1,1])
   rank (1); write(*,'(a)')' (a vector)'; b=reshape(a,[size(a),1])
   rank (2); write(*,'(a)')' (a matrix)'; b=a
   rank default; stop '*printi* unexpected rank'
   end select
   ! find how many characters to use for integers
   write(row,'(i0)')ceiling(log10(real(maxval(abs(b)))))+2
   ! use this format to write a row
   row='(" > [",*(i'//trim(row)//':,","))'
   do i=1,size(b,dim=1)
      write(*,fmt=row,advance='no')b(i,:)
      write(*,'(" ]")')
   enddo
   write(*,all) '>shape=',shape(a),',rank=',rank(a),',size=',size(a)
   write(*,*)
end subroutine printi
end program demo_sum

結果

    sum all elements:           9
    real :   26.00000
    complex : (13.10000,-4.300000)
    sum odd elements:           6
    sum positive values:          12
    the input array  (a matrix)
    > [   -1,    2,   -3,    4 ]
    > [   10,  -20,   30,  -40 ]
    > [  100,  200, -300,  400 ]
    >shape= 3 4 ,rank= 2 ,size= 12

    sum of all elements in matrix  (a scalar)
    > [  382 ]
    >shape= ,rank= 0 ,size= 1

    sum of positive elements  (a scalar)
    > [  746 ]
    >shape= ,rank= 0 ,size= 1

    sum along rows  (a vector)
    > [  109 ]
    > [  182 ]
    > [ -273 ]
    > [  364 ]
    >shape= 4 ,rank= 1 ,size= 4

    sum along columns  (a vector)
    > [    2 ]
    > [  -20 ]
    > [  400 ]
    >shape= 3 ,rank= 1 ,size= 3

    sum of a vector is always a scalar  (a scalar)
    > [  9 ]
    >shape= ,rank= 0 ,size= 1

    sum of a volume by row  (a matrix)
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    >shape= 6 7 ,rank= 2 ,size= 42

    sum of a volume by column  (a matrix)
    > [  66,  66,  66,  66,  66,  66,  66 ]
    > [  66,  66,  66,  66,  66,  66,  66 ]
    > [  66,  66,  66,  66,  66,  66,  66 ]
    > [  66,  66,  66,  66,  66,  66,  66 ]
    > [  66,  66,  66,  66,  66,  66,  66 ]
    >shape= 5 7 ,rank= 2 ,size= 35

    sum of a volume by depth  (a matrix)
    > [  77,  77,  77,  77,  77,  77 ]
    > [  77,  77,  77,  77,  77,  77 ]
    > [  77,  77,  77,  77,  77,  77 ]
    > [  77,  77,  77,  77,  77,  77 ]
    > [  77,  77,  77,  77,  77,  77 ]
    >shape= 5 6 ,rank= 2 ,size= 30

標準#

Fortran 95

参照#

  • all(3) - すべての値がtrueかどうかを判定します

  • any(3) - 論理配列の値のいずれかがtrueかどうかを判定します。

  • count(3) - 配列内のtrueの値をカウントします

  • maxval(3) - 配列内の最大値を決定します

  • minval(3) - 配列の最小値

  • product(3) - 配列要素の積

  • merge(3) - 変数のマージ

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost

reshape#

名前#

reshape(3) - [ARRAY:RESHAPE] 配列の形状を変更する関数

概要#

    result = reshape( source, shape [,pad] [,order] )
     type(TYPE(kind=KIND) function reshape

      type(TYPE(kind=KIND),intent(in)          :: source(..)
      integer(kind=**),intent(in)              :: shape(:)
      type(TYPE(kind=KIND),intent(in),optional :: pad(..)
      integer(kind=**),intent(in),optional     :: order(:)

特性#

  • sourceは任意の型の配列です

  • shapeはFortranの形状を定義し、そのため最大16個の非負の値を持つ定数の大きさの整数ベクトル(ランク1)です。

  • padsourceと同じ型です

  • ordershapeと同じ形状です

  • 結果はshapeの形状で、sourceと同じ型の配列です。

  • **として指定された種類は、型でサポートされている任意の種類です。**

説明#

reshapeは、sourceの要素と場合によってはpadを使用して、任意の形状shapeの配列を作成します。

必要に応じて、新しい配列はpadの要素でパディングするか、orderで定義されたように並べ替えることができます。

reshapeは、他の多くの用途の中でも、配列がFortranからCプロシージャに渡される前に、Fortran配列の順序をC配列の順序に合わせるために使用できます。

オプション#

  • source

    結果にコピーされる要素を含む配列。padが省略されているかサイズがゼロの場合、新しい形状を埋めるのに十分な要素がsourceに含まれている必要があります。Fortranでは…

   if(.not.present(pad))then
      if(size(source) < product(shape))then
        stop 'not enough elements in the old array to fill the new one'
      endif
   endif
  • shape

    これは生成される新しい配列の形状です。定義上、形状であるため、すべての要素は正の整数またはゼロであり、サイズは1以上でなければなりません。最大16個の要素を持つことができますが、定数の固定サイズとランク1でなければなりません。

  • pad

    結果配列がsourceより大きい場合に追加の値を埋めるために使用されます。sourceのすべての要素が結果に配置された後、結果がすべての要素が割り当てられるまで繰り返し使用されます。

    省略されているか、サイズがゼロの配列の場合、sourcesourceと同じサイズまたはそれ以下のサイズの別の配列にすることしかできません。

  • order

    最初の次元が最も速く変化する通常のFortran配列要素の順序とは異なる順序で、結果に要素を挿入するために使用されます。

    ランクの定義により、値は1からnまでの数値の順列でなければなりません。ここで、nはshapeのランクです。

    sourceとpadの要素は、デフォルトでは最も左側のランクを最も速く変更して、順序付けられて結果に配置されます。結果に要素が配置される順序を変更するには、orderを使用します。

結果#

結果は、shapeの形状で、sourceと同じ型と型パラメータを持つ配列です。まず、sourceの要素の値で塗りつぶされ、残りはpadの繰り返しコピーで塗りつぶされて、すべての要素が塗りつぶされるまで続きます。新しい配列はsourceより小さくなる可能性があります。

#

サンプルプログラム

program demo_reshape
implicit none
! notice the use of "shape(box)" on the RHS
integer :: box(3,4)=reshape([1,2,3,4,5,6,7,8,9,10,11,12],shape(box))
integer,allocatable :: v(:,:)
integer :: rc(2)
   ! basics0
    ! what is the current shape of the array?
    call printi('shape of box is ',box)
    ! change the shape
    call printi('reshaped ',reshape(box,[2,6]))
    call printi('reshaped ',reshape(box,[4,3]))

   ! fill in row column order using order
    v=reshape([1,2,3,4,10,20,30,40,100,200,300,400],[1,12])
    call printi('here is some data to shape',v)
    call printi('normally fills columns first ',reshape([v],[3,4]))
    call printi('fill rows first', reshape([v],[3,4],order=[2,1]))

    ! if we take the data and put in back in filling
    ! rows first instead of columns, and flipping the
    ! height and width of the box we not only fill in
    ! a vector using row-column order we actually
    ! transpose it.
    rc(2:1:-1)=shape(box)
    ! copy the data in changing column number fastest
    v=reshape(box,rc,order=[2,1])
    call printi('reshaped and reordered',v)
    ! of course we could have just done a transpose
    call printi('transposed',transpose(box))

   ! making the result bigger than source using pad
    v=reshape(box,rc*2,pad=[-1,-2,-3],order=[2,1])
    call printi('bigger and padded and reordered',v)
contains

subroutine printi(title,arr)
implicit none

!@(#) print small 2d integer arrays in row-column format

character(len=*),parameter :: all='(*(g0,1x))' ! a handy format
character(len=*),intent(in)  :: title
integer,intent(in)           :: arr(:,:)
integer                      :: i
character(len=:),allocatable :: biggest

   print all
   print all, trim(title),':(',shape(arr),')'  ! print title
   biggest='           '  ! make buffer to write integer into
   ! find how many characters to use for integers
   write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
   ! use this format to write a row
   biggest='(" > [",*(i'//trim(biggest)//':,","))'
   ! print one row of array at a time
   do i=1,size(arr,dim=1)
      write(*,fmt=biggest,advance='no')arr(i,:)
      write(*,'(" ]")')
   enddo

end subroutine printi

end program demo_reshape

結果

   shape of box is :( 3 4 )
    > [   1,   4,   7,  10 ]
    > [   2,   5,   8,  11 ]
    > [   3,   6,   9,  12 ]

   reshaped :( 2 6 )
    > [   1,   3,   5,   7,   9,  11 ]
    > [   2,   4,   6,   8,  10,  12 ]

   reshaped :( 4 3 )
    > [   1,   5,   9 ]
    > [   2,   6,  10 ]
    > [   3,   7,  11 ]
    > [   4,   8,  12 ]

   here is some data to shape :( 1 12 )
    > [   1,   2,   3,   4,  10,  20,  30,  40, 100, 200, 300, 400 ]

   normally fills columns first :( 3 4 )
    > [    1,    4,   30,  200 ]
    > [    2,   10,   40,  300 ]
    > [    3,   20,  100,  400 ]

   fill rows first :( 3 4 )
    > [    1,    2,    3,    4 ]
    > [   10,   20,   30,   40 ]
    > [  100,  200,  300,  400 ]

   reshaped and reordered :( 4 3 )
    > [   1,   2,   3 ]
    > [   4,   5,   6 ]
    > [   7,   8,   9 ]
    > [  10,  11,  12 ]

   transposed :( 4 3 )
    > [   1,   2,   3 ]
    > [   4,   5,   6 ]
    > [   7,   8,   9 ]
    > [  10,  11,  12 ]

   bigger and padded and reordered :( 8 6 )
    > [   1,   2,   3,   4,   5,   6 ]
    > [   7,   8,   9,  10,  11,  12 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]

標準#

Fortran 95

参照#

shape(3)pack(3)transpose(3)

fortran-lang 固有関数の説明 (ライセンス: MIT) @urbanjost