3

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?

5
  • 1
    Looks like a lot of code to re-implement the ANY intrinsic subprogram. Why would you not expect a segfault? Your program references an unallocated allocatable array. Commented Jul 12, 2019 at 15:34
  • @events True, the integers were in that sense a bad example. I do understand why the segfaultlt happens, that's why I am trying to integrate the IF(ALLOCATED(...)) line, which is causing the actual problems. Commented Jul 12, 2019 at 15:48
  • You need to use if (allocated(list3)) in the main program around the if-block that involves list3. Your operator is equivalent to writing if (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. Commented Jul 13, 2019 at 0:17
  • 1
    The edit is not legal Fortran! The wrapper needs to be invoked ahead of the procedure implementing the operator, not within it. Commented Jul 14, 2019 at 21:11
  • @IanH Thanks for the info -- I removed the edit. With gfortran it worked well, so I assumed it would be ok. Anyway, considering your answer and my illegal edit, I think it is best to not use an operator after all and rather stay with a function... Commented Jul 22, 2019 at 10:24

2 Answers 2

3

Ideally, redesign your code such that there is no need to deal with an unallocated array. If you want to represent an empty list, use a allocated zero size array.

(An unallocated object is a better conceptual fit to "there is no list", rather than an "the list is empty". Conceptually, you should not be querying something that doesn't exist.)

If you must, you could write a single argument adapter function along the line of the following:

FUNCTION foo(arg)
  INTEGER, INTENT(IN), OPTIONAL:: arg(:)
  INTEGER, ALLOCATABLE :: foo(:)
  IF (PRESENT(arg)) THEN
    foo = arg
  ELSE
    foo = [INTEGER ::]
  END IF
END FUNCTION foo

The adapter could then be used:

 IF (item .in. foo(list)) THEN
   ...

Appropriate naming of the adapter function is left to the reader.

(The adapter has been written with the dummy argument OPTIONAL, to accommodate actual argument not present, actual argument not allocated and actual argument dissociated. This is a Fortran 2008 feature.)

Sign up to request clarification or add additional context in comments.

4 Comments

Yes, making sure in the main code that the list is indeed allocated was what I was thinking as well. One way would, of course, be to wrap the list into a user-defined type, in which case checking for the array not being allocated would be trivial.
So do I understand this correctly, if I pass an unallocated array as OPTIONAL argument arg to function foo, the code behaves as if I would not pass any argument at all?
Yes. See F2008 12.5.2.12 (F2018 15.5.2.12). Check your compiler supports this feature, otherwise you will need to make the dummy argument allocatable, and adjust the procedure's internals appropriately.
That's perfect, thank you very much. I put my adaption of you answer into an edit of the question.
1

NB: This answer has a flaw, as pointed out in the comments. I will leave it here so that other readers might avoid making the same mistake.

Being a Python user, I can also appreciate the syntactic sugar that an .in. operator could provide. That said, standard Fortran is also quite concise:

if (any(items==value)) then
    ...
endif

However, here is one way to implement .in. that should handle both fixed-size and allocatable arrays:

module operator_in
    implicit none
    interface operator(.in.)
        module procedure operatorin
    end interface operator(.in.)

    contains
    logical function operatorin(v,lst) result(found)
        implicit none
        integer, intent(in) :: v
        integer, intent(in) :: lst(:)
        integer, allocatable :: temp(:)

        found = .false.
        allocate(temp,source=lst)
        if (size(temp)>0) then
            if (any(temp == v)) found=.true.
        endif
    end function operatorin
end module operator_in

Notes: I use the allocatable temp array so that if compiled with check:all (or similar) the code will run without error messages. Also, I use any to avoid manually looping over the list of items. Try it out, it's nice.

3 Comments

Associating an unallocated array with a non-optional assumed shape argument is not permitted by the rules of the language (F2018 15.5.2.4p7). Compilers differ in their ability to diagnose programming errors like this.
This looks really good, but unfortunately at least my compiler (gfortran) cannot handle the unallocated array and I get a crash anyway, but at least now the crash is somewhat verbose...
@IanH I'll leave this answer posted with an edit to see your comment, so that others will not make the same mistake.

Your Answer

By clicking “Post Your Answer”, you agree to our terms of service and acknowledge you have read our privacy policy.

Start asking to get answers

Find the answer to your question by asking.

Ask question

Explore related questions

See similar questions with these tags.