public subroutine UniqueValuesOfGridInteger(grid, values)
Description
return a vector of distinct values from a grid_integer
Arguments
Type |
Intent | Optional | Attributes |
|
Name |
|
type(grid_integer),
|
intent(in) |
|
|
:: |
grid |
|
integer(kind=short),
|
intent(out), |
|
ALLOCATABLE
|
:: |
values(:) |
|
Variables
Type |
Visibility | Attributes |
|
Name |
| Initial | |
integer(kind=short),
|
public |
|
:: |
count |
|
|
|
integer(kind=short),
|
public |
|
:: |
i |
= |
0 |
|
integer(kind=short),
|
public |
|
:: |
max_val |
|
|
|
integer(kind=short),
|
public |
|
:: |
min_val |
|
|
|
integer(kind=short),
|
public, |
ALLOCATABLE
|
:: |
unique(:) |
|
|
|
integer(kind=short),
|
public, |
ALLOCATABLE
|
:: |
vector(:) |
|
|
|
Source Code
SUBROUTINE UniqueValuesOfGridInteger &
!
(grid, values)
IMPLICIT NONE
!arguments with intent(in):
TYPE(grid_integer), INTENT (IN) :: grid
!arguments with intent (out):
INTEGER (KIND = short), INTENT (OUT), ALLOCATABLE :: values (:)
!Local declarations:
INTEGER (KIND = short), ALLOCATABLE :: vector (:)
INTEGER (KIND = short), ALLOCATABLE :: unique (:)
INTEGER (KIND = short) :: i = 0
INTEGER (KIND = short) :: count
INTEGER (KIND = short) :: min_val, max_val
!------------------------------------end of declarations-----------------------
! vectorize grid
CALL Grid2Vector (grid, vector)
!allocate temporary unique array
ALLOCATE ( unique ( SIZE(vector) ) )
!elaborate
min_val = MINVAL (vector) - 1
max_val = MAXVAL (vector)
DO WHILE (min_val<max_val)
i = i + 1
min_val = MINVAL (vector, mask = vector > min_val)
unique(i) = min_val
END DO
ALLOCATE ( values (i), source = unique(1:i) ) !<-- Or, just use unique(1:i)
!free memory
DEALLOCATE (vector)
DEALLOCATE (unique)
RETURN
END SUBROUTINE UniqueValuesOfGridInteger