I am trying to implement a python-type in operator that checks whether a 1D array contains a certain element. In principle I got this to work, but I'm having trouble covering both types of arrays that I want to work with, namely fixed-size arrays and allocatable arrays. Below I have a code that almost does what I want:
MODULE operator_in
IMPLICIT NONE
INTERFACE OPERATOR(.IN.)
MODULE PROCEDURE in_integer_list
! MODULE PROCEDURE in_integer_list_alloc
END INTERFACE OPERATOR(.IN.)
CONTAINS
FUNCTION in_integer_list(key, list) RESULT(res)
IMPLICIT NONE
INTEGER, INTENT(IN) :: key
INTEGER, INTENT(IN) :: list(:)
LOGICAL :: res
INTEGER :: ii
res = .FALSE.
DO ii = 1,SIZE(list)
IF (key == list(ii)) THEN
res = .TRUE.
RETURN
END IF
END DO
END FUNCTION in_integer_list
FUNCTION in_integer_list_alloc(key, list) RESULT(res)
IMPLICIT NONE
INTEGER, INTENT(IN) :: key
INTEGER, ALLOCATABLE, INTENT(IN) :: list(:)
LOGICAL :: res
IF (ALLOCATED(list)) THEN
res = in_integer_list(key, list)
ELSE
res = .FALSE.
END IF
END FUNCTION in_integer_list_alloc
END MODULE operator_in
PROGRAM test
USE operator_in
INTEGER :: list1(5) = (/1, 4, 6, 3, 8/)
INTEGER, ALLOCATABLE :: list2(:), list3(:)
INTEGER :: ii
ALLOCATE(list2(7))
list2(:) = (/8,7,6,5,4,2,1/)
DO ii = 1,5
IF (ii .IN. list1) THEN
WRITE (*,'(I3,A,5I3)') ii, ' is in ', list1
END IF
IF (ii .IN. list2) THEN
WRITE (*,'(I0.3,A,7I3)') ii, ' is in ', list2
END IF
! IF (ii .IN. list3) THEN
! WRITE (*,'(I3,A,7I3)') ii, ' is in ', list3
! END IF
END DO
END PROGRAM test
As is, the code produces the following output:
1 is in 1 4 6 3 8
1 is in 8 7 6 5 4 2 1
2 is in 8 7 6 5 4 2 1
3 is in 1 4 6 3 8
4 is in 1 4 6 3 8
4 is in 8 7 6 5 4 2 1
5 is in 8 7 6 5 4 2 1
However, if I un-comment the last three lines,
IF (ii .IN. list3) THEN
WRITE (*,'(I0.3,A,7I3)') ii, ' is in ', list3
END IF
the code crashes with a segmentation fault, because list3 is not allocated:
Program received signal SIGSEGV: Segmentation fault - invalid memory reference.
Backtrace for this error:
#0 0x10925ebe4
#1 0x10925e306
#2 0x7fff5e878b5c
#3 0x1092547da
#4 0x109254bc5
#5 0x109254cce
Segmentation fault: 11
I tried to fix this by writing a second function (in_integer_list_alloc) that allows for allocatable arrays, but declaring both functions in my interface:
INTERFACE OPERATOR(.IN.)
MODULE PROCEDURE in_integer_list
MODULE PROCEDURE in_integer_list_alloc
END INTERFACE OPERATOR(.IN.)
gives me an ambiguity error:
FUNCTION in_integer_list(key, list) RESULT(res)
1
user-defined_operator.f90:27:2:
FUNCTION in_integer_list_alloc(key, list) RESULT(res)
2
Error: Ambiguous interfaces in operator interface 'in' for 'in_integer_list' at (1) and 'in_integer_list_alloc' at (2)
And if I comment out the first procedure in the interface:
INTERFACE OPERATOR(.IN.)
! MODULE PROCEDURE in_integer_list
MODULE PROCEDURE in_integer_list_alloc
END INTERFACE OPERATOR(.IN.)
I of course get problems with the fixed-size array, list1:
IF (ii .IN. list1) THEN
1
Error: Operands of user operator 'in' at (1) are INTEGER(4)/INTEGER(4)
So: Is there a clever way to achieve what I want or at least get a proper error message when the code crashes because the passed array is not allocated?
ANYintrinsic subprogram. Why would you not expect a segfault? Your program references an unallocated allocatable array.IF(ALLOCATED(...))line, which is causing the actual problems.if (allocated(list3))in the main program around the if-block that involveslist3. Your operator is equivalent to writingif (in_integer_list_alloc(key, list3)). Here, you are referencing an unallocated allocatable array. Fortran does not allow that. As for the ambiguous interface, Fortran resolves the interface based on TKR (type, kind, rank). Other attributes do not matter.