数组的属性和属性#
merge#
名称#
merge(3) - [ARRAY:CONSTRUCTION] Merge variables
Synopsis#
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.
Characteristics#
a kind designated as ** may be any supported kind for the type
tsource May be of any type, including user-defined.
fsource Shall be of the same type and type parameters as tsource.
mask shall be of type logical.
The result will by of the same type and type parameters as tsource.
说明#
The elemental function merge(3) selects values from two arrays or scalars according to a logical mask. The result is equal to an element of tsource where the corresponding element of mask is .true., or an element of fsource when it is .false. .
支持多维数组。
请注意,merge(3) 的参数表达式不需要短路,因此(例如)如果数组 x 在标准下面的语句中包含零值,则防止产生浮点除以零;因为 1.0/x 可以在掩码用于选择要保留的值之前针对 x 的所有值进行评估:
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
应为 logical 类型。
请注意,(当前)character 值必须具有相同的长度。
结果#
The result is built from an element of tsource if mask is .true. and from fsource otherwise.
Because tsource and fsource are required to have the same type and type parameters (for both the declared and dynamic types), the result is polymorphic if and only if both tsource and fsource are polymorphic.
示例#
示例程序:
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) packs an array into an array of rank one
spread(3) is used to add a dimension and replicate data
unpack(3) scatters the elements of a vector
transpose(3) - Transpose an array of rank two
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
pack#
名称#
pack(3) - [ARRAY:CONSTRUCTION] Pack an array into an array of rank one
Synopsis#
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(*)
Characteristics#
array is an array of any type
mask a logical scalar as well as an array conformable with array.
vector is of the same kind and type as array and of rank one
the returned value is of the same kind and type as array
说明#
pack(3) stores the elements of array in an array of rank one.
The beginning of the resulting array is made up of elements whose mask equals .true.. Afterwards, remaining positions are filled with elements taken from vector
选项#
- 数组
The data from this array is used to fill the resulting vector
- mask
the logical mask must be the same size as array or, alternatively, it may be a logical scalar.
- 向量
an array of the same type as array and of rank one. If present, the number of elements in vector shall be equal to or greater than the number of true elements in mask. If mask is scalar, the number of elements in vector shall be equal to or greater than the number of elements in array.
vector shall have at least as many elements as there are in array.
结果#
The result is an array of rank one and the same type as that of array. If vector is present, the result size is that of vector, the number of .true. values in mask otherwise.
If mask is scalar with the value .true., in which case the result size is the size of 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 intrinsic descriptions (license: MIT) @urbanjost
spread#
名称#
spread(3) - [ARRAY:CONSTRUCTION] Add a dimension and replicate data
Synopsis#
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
Characteristics#
source is a scalar or array of any type.
dim is an integer scalar
ncopies is an integer scalar
说明#
spread(3) replicates a source array along a specified dimension dim. The copy is repeated ncopies times.
So to add additional rows to a matrix dim=1 would be used, but to add additional rows dim=2 would be used, for example.
If source is scalar, the size of the resulting vector is ncopies and each element of the result has a value equal to source.
选项#
- 资源
a scalar or array of any type and a rank less than fifteen.
- 暗淡
The additional dimension value in the range from 1 to n+1, where n equals the rank of source.
- n份
the number of copies of the original data to generate
结果#
结果是一个与 source 类型相同的数组,排名为 n+1,其中 n 等于 source 的排名。
示例#
示例程序:
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
另见#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
unpack#
名称#
unpack(3) - [ARRAY:CONSTRUCTION] Scatter the elements of a vector into an array using a mask
Synopsis#
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(..)
Characteristics#
vector is a rank-one array of any type
mask is a logical array
field is the same type and type parameters as VECTOR conformable with mask.
结果是一个类型和类型参数与 vector 相同且形状与 mask 相同的数组。
说明#
unpack(3) scatters the elements of vector into a copy of an array field of any rank using .true. values from mask in array element order to specify placement of the vector values.
So a copy of field is generated with select elements replaced with values from vector. This allows for complex replacement patterns that would be difficult when using array syntax or multiple assignment statements, particularly when the replacements are conditional.
选项#
- 向量
New values to place into specified locations in field. It shall have at least as many elements as mask has .true. values.
- mask
Shall be an array that specifies which values in field are to be replaced with values from vector.
- 场地
The input array to be altered.
结果#
The element of the result that corresponds to the ith true element of mask, in array element order, has the value vector(i) for i = 1, 2, …, t, where t is the number of true values in mask. Each other element has a value equal to **field* if field is scalar or to the corresponding element of **field if it is an array.
The resulting array corresponds to field with .true. elements of mask replaced by values from vector in array element order.
示例#
通过 unpack,可以将特定值“Scattered”到数组中的特定位置
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
另见#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
allocated#
名称#
allocated(3) - [ARRAY:INQUIRY] Allocation status of an allocatable entity
Synopsis#
result = allocated(array|scalar)
logical function allocated(array,scalar)
type(TYPE(kind=**)),allocatable,optional :: array(..)
type(TYPE(kind=**)),allocatable,optional :: scalar
Characteristics#
a kind designated as ** may be any supported kind for the type
array may be any allocatable array object of any type.
scalar may be any allocatable scalar of any type.
the result is a default logical scalar
说明#
allocated(3) checks the allocation status of both arrays and scalars.
At least one and only one of array or scalar must be specified.
选项#
- entity
the allocatable object to test.
结果#
If the argument is allocated then the result is .true.; otherwise, it returns .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. allocatable scalar entities were added in Fortran 2003.
另见#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
is_contiguous#
名称#
is_contiguous(3) - [ARRAY:INQUIRY] Test if object is contiguous
Synopsis#
result = is_contiguous(array)
logical function is_contiguous(array)
type(TYPE(kind=**)),intent(in) :: array
Characteristics#
a kind designated as ** may be any supported kind for the type
array may be of any type. It shall be an array or assumed-rank. If it is a pointer it shall be associated.
the result is a default logical scalar
说明#
is_contiguous(3) returns .true. if and only if an object is contiguous.
一个对象是连续的,如果它是
(1) 具有 CONTIGUOUS 属性的对象,
(2) 非假定形状的非指针整个数组,
(3) 一个假定形状的数组,它是与连续数组关联的参数,
(4) 由 ALLOCATE 语句分配的数组,
(5) 与连续目标关联的指针,或
(6) 一个非零大小的数组部分,前提是
(a) 它的基础对象是连续的,
(b) 它没有向量下标,
(c) 该部分的元素,按数组元素顺序,是按数组元素顺序连续的基本对象元素的子集,
(d) 如果数组是字符类型并且出现子字符串范围,则子字符串范围指定父字符串的所有字符,
(e) 只有其最后的部分引用具有非零等级,并且
(f) 它不是复数类型数组的实部或虚部。
如果对象是数组子对象,则对象不连续,并且
该对象有两个或多个元素,
数组元素顺序中对象的元素在基础对象的元素中不连续,
该对象不是长度为零的字符类型,并且
该对象不是派生类型,除了零大小的数组之外没有任何最终组件,并且
字符的长度为零。
任何其它对象是否连续取决于处理器。
选项#
- 数组
An array of any type to be tested for being contiguous. If it is a pointer it shall be associated.
结果#
The result has the value .true. if array is contiguous, and .false. otherwise.
示例#
示例程序:
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
See also#
fortran-lang intrinsic descriptions
lbound#
名称#
lbound(3) - [ARRAY:INQUIRY] Lower dimension bounds of an array
Synopsis#
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
Characteristics#
array shall be assumed-rank or an array, of any type. It cannot be an unallocated allocatable array or a pointer that is not associated.
dim shall be a scalar integer. The corresponding actual argument shall not be an optional dummy argument, a disassociated pointer, or an unallocated allocatable.
kind an integer initialization expression indicating the kind parameter of the result.
The return value is of type integer and of kind kind. If kind is absent, the return value is of default integer kind. The result is scalar if dim is present; otherwise, the result is an array of rank one and size n, where n is the rank of array.
a kind designated as ** may be any supported kind for the type
说明#
result(3) returns the lower bounds of an array, or a single lower bound along the dim dimension.
选项#
- 数组
应为任何类型的数组。
- 暗淡
Shall be a scalar integer. If dim is absent, the result is an array of the upper bounds of array.
- 种类
一个 integer 初始化表达式,指示结果的种类参数。
结果#
If dim is absent, the result is an array of the lower bounds of array.
If dim is present, the result is a scalar corresponding to the lower bound of the array along that dimension. If array is an expression rather than a whole array or array structure component, or if it has a zero extent along the relevant dimension, the lower bound is taken to be 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 , with KIND argument - Fortran 2003
另见#
Array inquiry:#
State Inquiry:#
allocated(3) - Status of an allocatable entity
is_contiguous(3) - Test if object is contiguous
Kind Inquiry:#
kind(3) - Kind of an entity
Bit Inquiry:#
storage_size(3) - Storage size in bits
bit_size(3) - Bit size inquiry function
btest(3) - Tests a bit of an integer value.
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
rank#
名称#
rank(3) - [ARRAY:INQUIRY] Rank of a data object
Synopsis#
result = rank(a)
integer function rank(a)
type(TYPE(kind=**)),intent(in) :: a(..)
Characteristics#
a can be of any type TYPE and rank.
a kind designated as ** may be any supported kind for the type
说明#
rank(3) returns the rank of a scalar or array data object.
The rank of an array is the number of dimensions it has (zero for a scalar).
选项#
a is the data object to query the dimensionality of. The rank returned may be from 0 to 16.
The argument a may be any data object type, including an assumed-rank array.
结果#
For arrays, their rank is returned; for scalars zero is returned.
示例#
示例程序:
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
标准#
See also#
Array inquiry:#
State Inquiry:#
allocated(3) - Status of an allocatable entity
is_contiguous(3) - Test if object is contiguous
Kind Inquiry:#
kind(3) - Kind of an entity
Bit Inquiry:#
storage_size(3) - Storage size in bits
bit_size(3) - Bit size inquiry function
btest(3) - Tests a bit of an integer value.
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
#
shape#
名称#
shape(3) - [ARRAY:INQUIRY] Determine the shape of an array or scalar
Synopsis#
result = shape( source [,kind] )
integer(kind=KIND) function shape( source, KIND )
type(TYPE(kind=**)),intent(in) :: source(..)
integer(kind=**),intent(in),optional :: KIND
Characteristics#
a kind designated as ** may be any supported kind for the type
source is an array or scalar of any type. If source is a pointer it must be associated and allocatable arrays must be allocated. It shall not be an assumed-size array.
KIND is a constant integer initialization expression.
the result is an integer array of rank one with size equal to the rank of source of the kind specified by KIND if KIND is present, otherwise it has the default integer kind.
说明#
shape(3) queries the shape of an array.
选项#
- 资源
an array or scalar of any type. If source is a pointer it must be associated and allocatable arrays must be allocated.
- 种类
indicates the kind parameter of the result.
结果#
An integer array of rank one with as many elements as source has dimensions.
The elements of the resulting array correspond to the extent of source along the respective dimensions.
If source is a scalar, the result is an empty array (a rank-one array of size zero).
示例#
示例程序:
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 ; with KIND argument Fortran 2003
另见#
Array inquiry:#
State Inquiry:#
allocated(3) - Status of an allocatable entity
is_contiguous(3) - Test if object is contiguous
Kind Inquiry:#
kind(3) - Kind of an entity
Bit Inquiry:#
storage_size(3) - Storage size in bits
bit_size(3) - Bit size inquiry function
btest(3) - Tests a bit of an integer value.
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
size#
名称#
size(3) - [ARRAY:INQUIRY] Determine the size of an array or extent of one dimension
Synopsis#
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
Characteristics#
array is an assumed-rank array or array of any type and associated kind.
If array is a pointer it must be associated and allocatable arrays must be allocated.
dim is an integer scalar
kind is a scalar integer constant expression.
the result is an integer scalar of kind KIND. If KIND is absent a integer of default kind is returned.
a kind designated as ** may be any supported kind for the type
说明#
size(3) returns the total number of elements in an array, or if dim is specified returns the number of elements along that dimension.
size(3) determines the extent of array along a specified dimension dim, or the total number of elements in array if dim is absent.
选项#
- 数组
the array to measure the number of elements of. If **array* is an assumed-size array, dim shall be present with a value less than the rank of **array**.
- 暗淡
a value shall be in the range from 1 to n, where n equals the rank of array.
If not present the total number of elements of the entire array are returned.
- 种类
一个 integer 初始化表达式,指示结果的种类参数。
If absent the kind type parameter of the returned value is that of default integer type.
The kind must allow for the magnitude returned by size or results are undefined.
If kind is absent, the return value is of default integer kind.
结果#
If dim is not present array is assumed-rank, the result has a value equal to PRODUCT(SHAPE(ARRAY,KIND)). Otherwise, the result has a value equal to the total number of elements of array.
If dim is present the number of elements along that dimension are returned, except that if ARRAY is assumed-rank and associated with an assumed-size array and DIM is present with a value equal to the rank of array, the value is -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_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 , with kind argument - Fortran 2003
另见#
Array inquiry:#
State Inquiry:#
allocated(3) - Status of an allocatable entity
is_contiguous(3) - Test if object is contiguous
Kind Inquiry:#
kind(3) - Kind of an entity
Bit Inquiry:#
storage_size(3) - Storage size in bits
bit_size(3) - Bit size inquiry function
btest(3) - Tests a bit of an integer value.
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
ubound#
名称#
ubound(3) - [ARRAY:INQUIRY] Upper dimension bounds of an array
Synopsis#
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
Characteristics#
array shall be assumed-rank or an array, of any type. It cannot be an unallocated allocatable array or a pointer that is not associated.
dim shall be a scalar integer. The corresponding actual argument shall not be an optional dummy argument, a disassociated pointer, or an unallocated allocatable.
kind an integer initialization expression indicating the kind parameter of the result.
The return value is of type integer and of kind kind. If kind is absent, the return value is of default integer kind. The result is scalar if dim is present; otherwise, the result is an array of rank one and size n, where n is the rank of array.
a kind designated as ** may be any supported kind for the type
说明#
ubound(3) returns the upper bounds of an array, or a single upper bound along the dim dimension.
选项#
- 数组
The assumed-rank or array of any type whose upper bounds are to be determined. If allocatable it must be allocated; if a pointer it must be associated. If an assumed-size array, dim must be present.
- 暗淡
a specific dimension of array to determine the bounds of. If dim is absent, the result is an array of the upper bounds of array. dim is required if array is an assumed-size array, and in that case must be less than or equal to the rank of array.
- 种类
indicates the kind parameter of the result. If absent, an integer of the default kind is returned.
结果#
返回值的类型是 integer 和种类 kind。如果 kind 不存在,则返回值为默认整数类型。
If dim is absent, the result is an array of the upper bounds of each dimension of the array.
如果存在 dim,则结果是一个标量,对应于沿该维度的数组的上限。
如果 array 是一个表达式而不是整个数组或数组结构组件,或者如果它沿相关维度的范围为零,则上限被视为沿相关维度的元素数。
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_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 , with KIND argument Fortran 2003
另见#
Array inquiry:#
State Inquiry:#
allocated(3) - Status of an allocatable entity
is_contiguous(3) - Test if object is contiguous
Kind Inquiry:#
kind(3) - Kind of an entity
Bit Inquiry:#
storage_size(3) - Storage size in bits
bit_size(3) - Bit size inquiry function
btest(3) - Tests a bit of an integer value.
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
maxloc#
名称#
maxloc(3) - [ARRAY:LOCATION] 数组中最大值的位置
Synopsis#
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(..)
Characteristics#
a kind designated as ** may be any supported kind for the type
NUMERIC designates any intrinsic numeric type and kind.
说明#
maxloc(3) determines the location of the element in the array with the maximum value, or, if the dim argument is supplied, determines the locations of the maximum element along each row of the array in the dim direction.
If mask is present, only the elements for which mask is .true. are considered. If more than one element in the array has the maximum value, the location returned is that of the first such element in array element order.
If the array has zero size, or all of the elements of mask are .false., then the result is an array of zeroes. Similarly, if dim is supplied and all of the elements of mask along a given row are zero, the result value for that row is zero.
选项#
- 数组
应为 integer、real 或 character 类型的数组。
- 暗淡
(可选)应为 integer 类型的标量,其值介于 1 和 array 的秩之间(含)。它可能不是可选的虚拟参数。
- mask
应该是 logical 类型的数组,并且符合 array。
结果#
如果 dim 不存在,则结果是一个秩为 1 的数组,其长度等于 array 的阶。如果存在 dim,则结果是一个秩比 array 的秩小 1 的数组,其大小对应于 array 的大小dim 尺寸已删除。如果存在 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
另见#
findloc(3) - Location of first element of ARRAY identified by MASK along dimension DIM matching a target
minloc(3) - Location of the minimum value within an array
fortran-lang intrinsic descriptions
minloc#
名称#
minloc(3) - [ARRAY:LOCATION] 数组中最小值的位置
Synopsis#
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(..)
Characteristics#
a kind designated as ** may be any supported kind for the type
NUMERIC is any numeric type and kind.
说明#
minloc(3) determines the location of the element in the array with the minimum value, or, if the dim argument is supplied, determines the locations of the minimum element along each row of the array in the dim direction.
If mask is present, only the elements for which mask is true. are considered.
If more than one element in the array has the minimum value, the location returned is that of the first such element in array element order.
If the array has zero size, or all of the elements of mask are .false., then the result is an array of zeroes. Similarly, if dim is supplied and all of the elements of mask along a given row are zero, the result value for that row is zero.
选项#
- 数组
应为 integer、real 或 character 类型的数组。
- 暗淡
(可选)应为 integer 类型的标量,其值介于 1 和 array 的秩之间(含)。它可能不是可选的虚拟参数。
- mask
应该是 logical 类型的数组,并且符合 array。
结果#
如果 dim 不存在,则结果是一个秩为 1 的数组,其长度等于 array 的阶。如果存在 dim,则结果是一个秩比 array 的秩小 1 的数组,其大小对应于 array 的大小dim 尺寸已删除。如果存在 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
另见#
findloc(3) - Location of first element of ARRAY identified by MASK along dimension DIM matching a target
maxloc(3) - Location of the maximum value within an array
minloc(3) - Location of the minimum value within an array
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
findloc#
名称#
findloc(3) - [ARRAY:LOCATION] Location of first element of ARRAY identified by MASK along dimension DIM matching a target value
Synopsis#
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
Characteristics#
array is an array of any intrinsic type.
value shall be scalar but in type conformance with array, as specified for the operator == or the operator .EQV..
dim an integer corresponding to a dimension of array. The corresponding actual argument shall not be an optional dummy argument.
mask is logical and shall be conformable with array.
kind a scalar integer initialization expression (ie. a constant)
back a logical scalar.
the result is integer of default kind or kind kind if the kind argument is present. If dim does not appear, the result is an array of rank one and of size equal to the rank of array; otherwise, the result is an array of the same rank and shape as array reduced by the dimension dim.
NOTE: a kind designated as ** may be any supported kind for the type
说明#
findloc(3) returns the location of the first element of array identified by mask along dimension dim having a value equal to value.
If both array and value are of type logical, the comparison is performed with the .eqv. operator; otherwise, the comparison is performed with the == operator. If the value of the comparison is .true., that element of array matches value.
If only one element matches value, that element’s subscripts are returned. Otherwise, if more than one element matches value and back is absent or present with the value .false., the element whose subscripts are returned is the first such element, taken in array element order. If back is present with the value .true., the element whose subscripts are returned is the last such element, taken in array element order.
选项#
- 数组
应该是一个内置类型的数组。
- value
shall be scalar and in type conformance with array.
- 暗淡
shall be an integer scalar with a value in the range 1 <= DIM <= n, where n is the rank of array. The corresponding actual argument shall not be an optional dummy argument.
- mask
(可选)应为逻辑类型并且应符合array。
- 种类
(可选)应为标量整数初始化表达式。
- back
(可选)应为逻辑标量。
结果#
kind is present, the kind type parameter is that specified by the value of kind; otherwise the kind type parameter is that of default integer type. If dim does not appear, the result is an array of rank one and of size equal to the rank of array; otherwise, the result is of rank n - 1 and shape
[d1, d2, . . ., dDIM-1, dDIM+1, . . ., dn ]
有
[d1, d2, . . ., dn ]
是 array 的形状。
结果#
案例(i): findloc (array, value) 的结果是一个秩为一的数组,其元素值是 array 的一个元素的下标值,其值匹配 价值。如果存在这样的值,则返回的第 i 个下标位于 1 到 ei 的范围内,其中 ei 是 array 的第 i 个维度的范围。如果没有元素匹配 value 或 array 的大小为零,则结果的所有元素都为零。
案例(ii): findloc (array, value, mask = mask)的结果是一个秩一数组,其元素值是array的一个元素的下标值,对应mask的一个真实元素,其值匹配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
另见#
maxloc(3) - Location of the maximum value within an array
minloc(3) - Location of the minimum value within an array
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
transpose#
名称#
transpose(3) - [ARRAY:MANIPULATION] Transpose an array of rank two
Synopsis#
result = transpose(matrix)
function transpose(matrix)
type(TYPE(kind=KIND) :: transpose(N,M)
type(TYPE(kind=KIND),intent(in) :: matrix(M,N)
Characteristics#
matrix is an array of any type with a rank of two.
The result will be the same type and kind as matrix and the reversed shape of the input array
说明#
transpose(3) transposes an array of rank two.
An array is transposed by interchanging the rows and columns of the given matrix. That is, element (i,j) of the result has the value of element (j,i) of the input for all (i,j).
选项#
- 矩阵
The array to transpose
结果#
The transpose of the input array. The result has the same type as matrix, and has shape [ m, n ] if matrix has shape [ n, m ].
示例#
示例程序:
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
See also#
merge(3) - Merge variables
pack(3) - Pack an array into an array of rank one
spread(3) - Add a dimension and replicate data
unpack(3) - Scatter the elements of a vector
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
all#
名称#
all(3) - [ARRAY:REDUCTION] Determines if all the values are true
Synopsis#
result = all(mask [,dim])
function all(mask ,dim)
logical(kind=KIND),intent(in) :: mask(..)
integer,intent(in),optional :: dim
logical(kind=KIND) :: all(..)
Characteristics#
mask is a logical array
dim is an integer
the result is a logical array if dim is supplied, otherwise it is a logical scalar. It has the same characteristics as mask
说明#
all(3) determines if all the values are true in mask in the array along dimension dim if dim is specified; otherwise all elements are tested together.
This testing type is called a logical conjunction of elements of mask along dimension dim.
The mask is generally a logical expression, allowing for comparing arrays and many other common operations.
选项#
- mask
the logical array to be tested for all elements being .true.
- 暗淡
dim indicates the direction through the elements of mask to group elements for testing.
dim has a value that lies between one and the rank of mask.
The corresponding actual argument shall not be an optional dummy argument.
If dim is not present all elements are tested and a single scalar value is returned.
结果#
If dim is not present all(mask) is .true. if all elements of mask are .true.. It also is .true. if mask has zero size; otherwise, it is .false. .
If the rank of mask is one, then all(mask, dim) is equivalent to all(mask).
If the rank of mask is greater than one and dim is present then all(mask,dim) returns an array with the rank (number of dimensions) of mask minus 1. The shape is determined from the shape of mask where the dim dimension is elided. A value is returned for each set of elements along the dim dimension.
示例#
示例程序:
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
另见#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
any#
名称#
any(3) - [ARRAY:REDUCTION] Determines if any of the values in the logical array are .true.
Synopsis#
result = any(mask [,dim])
function any(mask, dim)
logical(kind=KIND),intent(in) :: mask(..)
integer,intent(in),optional :: dim
logical(kind=KIND) :: any(..)
Characteristics#
mask is a logical array
dim is a scalar integer
the result is a logical array if dim is supplied, otherwise it is a logical scalar.
说明#
any(3) determines if any of the values in the logical array mask along dimension dim are .true..
选项#
- mask
an array of logical expressions or values to be tested in groups or in total for a .true. value.
- 暗淡
a whole number value that lies between one and rank(mask) that indicates to return an array of values along the indicated dimension instead of a scalar answer.
结果#
any(mask) 返回 logical 类型的标量值,其 kind 类型参数与 mask 的 kind 类型参数相同。如果 dim 存在,则 any(mask, dim) 返回一个维度为 mask - 1 的数组。形状由 mask 决定,其中第 dim 维被省略。
any(mask) is .true. if any element of mask is .true.; otherwise, it is .false.. It also is .false. if mask has zero size.
If the rank of mask is one, then any(mask, dim) is equivalent to any(mask). If the rank is greater than one, then any(mask, dim) is determined by applying any(mask) to the array sections.
示例#
示例程序:
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
另见#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
count#
名称#
count(3) - [ARRAY:REDUCTION] Count true values in an array
Synopsis#
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
Characteristics#
a kind designated as ** may be any supported kind for the type
mask is a logical array of any shape and kind.
If dim is present, the result is an array with the specified rank removed.
KIND is a scalar integer constant expression valid as an integer kind
The return value is of default integer type unless kind is specified to declare the kind of the result.
说明#
count(3) counts the number of .true. elements in a logical mask, or, if the dim argument is supplied, counts the number of elements along each row of the array in the dim direction. If the array has zero size or all of the elements of mask are false, then the result is 0.
选项#
- mask
an array to count the number of .true. values in
- 暗淡
specifies to remove this dimension from the result and produce an array of counts of .true. values along the removed dimension. If not present, the result is a scalar count of the true elements in mask the value must be in the range 1 <= dim <= n, where n is the rank(number of dimensions) of mask.
The corresponding actual argument shall not be an optional dummy argument, a disassociated pointer, or an unallocated allocatable.
- 种类
一个 integer 初始化表达式,指示结果的种类参数。
结果#
The return value is the number of .true. values in mask if dim is not present.
If dim is present, the result is an array with a rank one less than the rank of the input array mask, and a size corresponding to the shape of array with the dim dimension removed, with the remaining elements containing the number of .true. elements along the removed dimension.
示例#
示例程序:
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 , with KIND argument - Fortran 2003
另见#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
maxval#
名称#
maxval(3) - [ARRAY:REDUCTION] Determines the maximum value in an array or row
Synopsis#
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(..)
Characteristics#
a kind designated as ** may be any supported kind for the type
NUMERIC designates any numeric type and kind.
说明#
maxval(3) determines the maximum value of the elements in an array value, or, if the dim argument is supplied, determines the maximum value along each row of the array in the dim direction. If mask is present, only the elements for which mask is .true. are considered. If the array has zero size, or all of the elements of mask are .false., then the result is the most negative number of the type and kind of array if array is numeric, or a string of nulls if array is of character type.
选项#
- 数组
应为 integer、real 或 character 类型的数组。
- 暗淡
(可选)应为 integer 类型的标量,其值介于 1 和 array 的秩之间(含)。它可能不是可选的虚拟参数。
- mask
(optional) 应为 logical 类型的数组,并与 array 一致。
结果#
如果 dim 不存在,或者 array 的维度为 1,则结果为标量。如果存在 dim,则结果是一个维度比 array 的维度小 1 的数组,其大小对应于删除 array 的第dim 维。在所有情况下,结果的类型和种类都与 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 intrinsic descriptions
minval#
名称#
minval(3) - [ARRAY:REDUCTION] Minimum value of an array
Synopsis#
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(..)
Characteristics#
a kind designated as ** may be any supported kind for the type
NUMERIC is any numeric type and kind.
说明#
minval(3) determines the minimum value of the elements in an array value, or, if the dim argument is supplied, determines the minimum value along each row of the array in the dim direction.
If mask is present, only the elements for which mask is .true. are considered.
If the array has zero size, or all of the elements of mask are .false., then the result is huge(array) if array is numeric, or a string of char(len=255) characters if array is of character type.
选项#
- 数组
应为 integer、real 或 character 类型的数组。
- 暗淡
(可选)应为 integer 类型的标量,其值介于 1 和 ARRAY 的维度之间(含)。它可能不是可选的虚参。
- mask
应该是 logical 类型的数组,并且符合 array。
结果#
如果 dim 不存在,或者 array 的维度为 1,则结果为标量。
如果 dim 不存在,或者 array 的维度为 1,则结果为标量。如果存在 dim,则结果是一个维度比 array 的维度小 1 的数组,其大小对应于删除 array 的第dim 维。在所有情况下,结果的类型和种类都与 array 相同。
示例#
示例程序:
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 intrinsic descriptions (license: MIT) @urbanjost
product#
名称#
product(3) - [ARRAY:REDUCTION] Product of array elements
Synopsis#
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(..)
Characteristics#
a kind designated as ** may be any supported kind for the type
NUMERIC is any numeric type and kind.
说明#
product(3) multiplies together all the selected elements of array, or along dimension dim if the corresponding element in mask is .true..
如果 dim 不存在,则返回一个标量,其中包含 array 中所有元素的乘积。 (注意零大小的 array 返回 1)。
当 dim 存在时,如果掩码数组的维度为 1(即是向量),则结果是标量。否则,维度为 n-1 的数组,其中 n 等于 array 的维度,形状类似于删除 array 的第dim 维。
选项#
- 数组
应为 integer、real 或 complex 类型的数组。
- 暗淡
应该是 integer 类型的标量,其值在 1 到 n 的范围内,其中 n 等于 array 的维度。
- mask
应为 logical 类型,并且可以是标量或与 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 intrinsic descriptions (license: MIT) @urbanjost
sum#
名称#
sum(3) - [ARRAY:REDUCTION] Sum the elements of an array
Synopsis#
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(..)
Characteristics#
a kind designated as ** may be any supported kind for the type
array may be of any numeric type - integer, real or complex.
dim is an integer
mask is logical and conformable with array.
The result is of the same type and kind as array. It is scalar if dim is not present or array is a vector, else it is an array.
说明#
sum(3) adds the elements of array.
When only array is specified all elements are summed, but groups of sums may be returned along the dimension specified by dim and/or elements to add may be selected by a logical mask.
No method is designated for how the sum is conducted, so whether or not accumulated error is compensated for is processor-dependent.
选项#
- 数组
an array containing the elements to add
- 暗淡
a value in the range from 1 to n, where n equals the rank (the number of dimensions) of array. dim designates the dimension along which to create sums. When absent a scalar sum of the elements optionally selected by mask is returned.
- mask
an array of the same shape as array that designates which elements to add. If absent all elements are used in the sum(s).
结果#
If dim is absent, a scalar with the sum of all selected elements in array is returned. Otherwise, an array of rank n-1, where n equals the rank of array, and a shape similar to that of array with dimension dim dropped is returned. Since a vector has a rank of one, the result is a scalar (if n==1, n-1 is zero; and a rank of zero means a scalar).
示例#
示例程序:
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) - Determines if all the values are true
any(3) - Determines if any of the values in the logical array are true.
count(3) - Count true values in an array
maxval(3) - Determines the maximum value in an array
minval(3) - Minimum value of an array
product(3) - Product of array elements
merge(3) - Merge variables
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
reshape#
名称#
reshape(3) - [ARRAY:RESHAPE] Function to reshape an array
Synopsis#
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(:)
Characteristics#
source is an array of any type
shape defines a Fortran shape and therefore an integer vector (of rank one) of constant size of up to 16 non-negative values.
pad is the same type as source
order is the same shape as shape
结果是一个形状为 shape 的数组,其类型与 source 相同。
a kind designated as ** may be any supported kind for the type
说明#
reshape constructs an array of arbitrary shape shape using the elements from source and possibly pad to fill it.
If necessary, the new array may be padded with elements from pad or permuted as defined by order.
Among many other uses, reshape can be used to reorder a Fortran array to match C array ordering before the array is passed from Fortran to a C procedure.
选项#
- 资源
an array containing the elements to be copied to the result. there must be enough elements in the source to fill the new shape if pad is omitted or has size zero. Expressed in 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
This is the shape of the new array being generated. Being by definition a shape; all elements are either positive integers or zero, the size but be 1 or greater, it may have up to 16 elements but must be of constant fixed size and rank one.
- pad
used to fill in extra values if the result array is larger than source. It will be used repeatedly after all the elements of source have been placed in the result until the result has all elements assigned.
If it is absent or is a zero-sized array, you can only make source into another array of the same size as source or smaller.
- order
used to insert elements in the result in an order other than the normal Fortran array element order, in which the first dimension varies fastest.
By definition of ranks the values have to be a permutation of the numbers from 1 to n, where n is the rank of shape.
the elements of source and pad are placed into the result in order; changing the left-most rank most rapidly by default. To change the order by which the elements are placed in the result use order.
结果#
The result is an array of shape shape with the same type and type parameters as source. It is first filled with the values of elements of source, with the remainder filled with repeated copies of pad until all elements are filled. The new array may be smaller than 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 intrinsic descriptions (license: MIT) @urbanjost