stdlib_array
moduleModule for index manipulation and array handling tasks.
trueloc
Experimental
Turn a logical mask into an index array by selecting all true values.
Provides similar functionality like the built-in where
or the intrinsic procedures merge
and pack
when working with logical mask.
The built-in / intrinsics are usually preferable to trueloc
, unless the access to the index array is required.
loc =
trueloc (array[, lbound])
Pure function.
array
: List of default logical arrays. This argument is intent(in)
.
lbound
: Lower bound of the array to index. This argument is optional
and intent(in)
.
Returns an array of default integer size, with a maximum length of size(array)
elements.
program example_trueloc
use stdlib_array, only: trueloc
implicit none
real, allocatable :: array(:)
allocate (array(500))
call random_number(array)
array(trueloc(array > 0.5)) = 0.0
end program example_trueloc
falseloc
Experimental
Turn a logical mask into an index array by selecting all false values.
Provides similar functionality like the built-in where
or the intrinsic procedures merge
and pack
when working with logical mask.
The built-in / intrinsics are usually preferable to falseloc
, unless the access to the index array is required.
loc =
falseloc (array[, lbound])
Pure function.
array
: List of default logical arrays. This argument is intent(in)
.
lbound
: Lower bound of the array to index. This argument is optional
and intent(in)
.
Returns an array of default integer size, with a maximum length of size(array)
elements.
program example_falseloc
use stdlib_array, only: falseloc
implicit none
real, allocatable :: array(:)
allocate (array(-200:200))
call random_number(array)
array(falseloc(array < 0.5, lbound(array, 1))) = 0.0
end program example_falseloc