Properties and attributes of arrays#
merge#
Name#
merge(3) - [ARRAY CONSTRUCTION] Merge variables
Syntax#
result = merge(tsource, fsource, mask)
Description#
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. .
Multi-dimensional arrays are supported.
Note that argument expressions to merge(3) are not required to be short-circuited so (as an example) if the array x contains zero values in the statement below the standard does not prevent floating point divide by zero being generated; as 1.0/x may be evaluated for all values of x before the mask is used to select which value to retain:
y = merge( 1.0/x, 0.0, x /= 0.0 )
Note the compiler is also free to short-circuit or to generate an infinity so this may work in many programming environments but is not recommended.
For cases like this one may instead use masked assignment via the where construct:
where(x .ne. 0.0)
y = 1.0/x
elsewhere
y = 0.0
endwhere
instead of the more obscure
merge(1.0/merge(x,1.0,x /= 0.0), 0.0, x /= 0.0)
Arguments#
- 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.
Note that (currently) character values must be of the same length.
Returns#
The result is of the same type and type parameters as tsource. For any element the result is tsource if mask is true and fsource otherwise.
Examples#
The value of
merge (1.0, 0.0, k > 0)
is 1.0 for K=5 and 0.0 for K=-2.
program demo_merge
implicit none
integer :: tvals(2,3), fvals(2,3), answer(2,3)
logical :: mask(2,3)
integer :: i
logical :: chooseleft
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. ]
write(*,*)'mask of logicals'
answer=merge( tvals, fvals, mask )
call printme()
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
Expected Results:
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
Standard#
Fortran 95 and later
See Also#
pack(3), unpack(3), pack(3), spread(3), unpack(3)
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
pack#
Name#
pack(3) - [ARRAY CONSTRUCTION] Pack an array into an array of rank one
Syntax#
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(*)
where TYPE(kind=KIND) may be any type, where array and vector and the returned value must by of the same type. mask may be a scalar as well an an array.
Description#
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, positions are filled with elements taken from vector.
Arguments#
- array
Shall be an array of any type.
- mask
Shall be an array of type logical and of the same size as array. Alternatively, it may be a logical scalar.
- vector
(Optional) shall be 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.
Returns#
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.
Examples#
Sample program:
program demo_pack
implicit none
call test1()
call test2()
call test3()
contains
!
subroutine test1()
! gathering nonzero elements from an array:
integer :: m(6)
m = [ 1, 0, 0, 0, 5, 0 ]
write(*, fmt="(*(i0, ' '))") pack(m, m /= 0) ! "1 5"
end subroutine test1
!
subroutine test2()
! 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):
integer :: m(4)
m = [ 1, 0, 0, 2 ]
write(*, fmt="(*(i0, ' '))") pack(m, m /= 0, [ 0, 0, 3, 4 ])
end subroutine test2
!
subroutine test3()
! select strings whose second character is "a"
character(len=10) :: m(4)
m = [ character(len=10) :: 'ape', 'bat', 'cat', 'dog']
write(*, fmt="(*(g0, ' '))") pack(m, m(:)(2:2) == 'a' )
end subroutine test3
!
end program demo_pack
Results:
1 5
1 2 3 4
bat cat
Standard#
Fortran 95 and later
See Also#
unpack(3), merge(3), pack(3), spread(3), unpack(3)
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
spread#
Name#
spread(3) - [ARRAY CONSTRUCTION] Add a dimension to an array
Syntax#
result = spread(source, dim, ncopies)
TYPE(kind=KIND) function spread(source, dim, ncopies)
TYPE(kind=KIND) :: source(..)
integer,intent(in) :: dim
integer,intent(in) :: ncopies
Description#
Replicates a source array ncopies times along a specified dimension dim.
If SOURCE is scalar, the shape of the result is (MAX (NCOPIES, 0)). and each element of the result has a value equal to SOURCE.
Arguments#
- source
Shall be a scalar or an array of any type and a rank less than fifteen.
- dim
Shall be a scalar of type integer with a value in the range from 1 to n+1, where n equals the rank of source.
- ncopies
Shall be a scalar of type integer.
Returns#
The result is an array of the same type as source and has rank n+1 where n equals the rank of source.
Examples#
Sample program:
program demo_spread
implicit none
integer :: a = 1, b(2) = [ 1, 2 ]
write(*,*) spread(a, 1, 2) ! "1 1"
write(*,*) spread(b, 1, 2) ! "1 1 2 2"
end program demo_spread
program example_spread
! Author:
! John Burkardt, 03 July 2006
implicit none
!
integer ( kind = 4 ) a1(4,3)
integer ( kind = 4 ) a2(3,4)
integer i
integer ( kind = 4 ) s
integer ( kind = 4 ) v(4)
!
write ( *, '(a)' ) ' '
write ( *, '(a)' ) 'TEST_SPREAD'
write ( *, '(a)' ) ' SPREAD is a FORTRAN90 function which replicates'
write ( *, '(a)' ) ' an array by adding a dimension.'
write ( *, '(a)' ) ' '
!
s = 99
!
write ( *, '(a,i6)' ) ' Suppose we have a scalar S = ', s
write ( *, '(a)' ) ' '
!
v = spread ( s, 1, 4 )
!
write ( *, '(a)' ) ' V = spread ( s, 1, 4 )'
write ( *, '(a)' ) ' '
write ( *, '(a)' ) ' adds a new dimension (1) of extent 4'
write ( *, '(a)' ) ' '
write ( *, '(4i6)' ) v(1:4)
write ( *, '(a)' ) ' '
write ( *, '(a)' ) ' Now first reset V to (1,2,3,4)'
v = [ 1, 2, 3, 4 ]
!
a1 = spread ( v, 2, 3 )
!
write ( *, '(a)' ) ' '
write ( *, '(a)' ) ' A1 = spread ( v, 2, 3 )'
write ( *, '(a)' ) ' '
write ( *, '(a)' ) ' adds a new dimension (2) of extent 3'
write ( *, '(a)' ) ' '
do i = 1, 4
write ( *, '(3i6)' ) a1(i,1:3)
end do
!
a2 = spread ( v, 1, 3 )
!
write ( *, '(a)' ) ' '
write ( *, '(a)' ) ' A2 = spread ( v, 1, 3 )'
write ( *, '(a)' ) ' '
write ( *, '(a)' ) ' adds a new dimension (1) of extent 3'
write ( *, '(a)' ) ' '
do i = 1, 3
write ( *, '(4i6)' ) a2(i,1:4)
end do
end program example_spread
Standard#
Fortran 95 and later
See Also#
pack(3), unpack(3), merge(3), pack(3), unpack(3)
####### fortran-lang intrinsic descriptions
unpack#
Name#
unpack(3) - [ARRAY CONSTRUCTION] Store the elements of a vector in an array of higher rank
Syntax#
result = unpack(vector, mask, field)
Description#
Store the elements of vector in an array of higher rank.
Arguments#
- vector
Shall be an array of any type and rank one. It shall have at least as many elements as mask has .true. values.
- mask
Shall be an array of type logical.
- field
Shall be of the same type as vector and have the same shape as mask.
Returns#
The resulting array corresponds to field with .true. elements of mask replaced by values from vector in array element order.
Examples#
Sample program:
program demo_unpack
implicit none
integer :: vector(2) = [1,1]
logical :: mask(4) = [ .true., .false., .false., .true. ]
integer :: field(2,2) = 0, unity(2,2)
! result: unity matrix
unity = unpack(vector, reshape(mask, [2,2]), field)
write(*,*)unity,size(unity),shape(unity)
end program demo_unpack
Results:
1 0 0 1 4
2 2
Standard#
Fortran 95 and later
See Also#
pack(3), merge(3), pack(3), spread(3), unpack(3)
####### fortran-lang intrinsic descriptions