Creating an identical array of different type in subroutines

First up, hi!
I’m new here and to Fortran. I started my physics degree last year and felt this to be the right time to start learning a proper compiled programming language, and Fortran seemed cool half because of how old it is, and half because, well, I liked the structure when I tried it. (I like old things, by the way.)
Anyway, preliminaries aside, I’m trying to write a subroutine to normalize and convert a real array to an integer array. The problem is that the real array going into the subroutine won’t always be of the same dimensions, so I don’t know how to declare the integer array. Here’s the code I have:

subroutine prepare(realarray, integerarray)
        implicit none

        real, intent(in) :: realarray(:,:)
        integer(2), intent(out) :: integerarray(:)

        allocate(integerarray, mold=realarray)
        integerarray = nint((2**15) * realarray / maxval(realarray))

end subroutine

The error that pops up is on the allocate command.

Type of entity at (1) (integerarray) is type incompatible with source-expr at (2) (realarray).

Alternatively, upon trying

allocate(integerarray(shape(realarray)))

what I get is

Rank-mismatch in array reference

Could anyone suggest how to bypass this?
Thanks in advance!

3 Likes

There are several issues here, but I’ll mention that the Fortran may be “old”, but it has been transformed several times over the years, most recently in 2018.

Now to your code. Here are some issues I see.

  1. integerarray is rank 1 (1-dimensional) while realarray is rank 2. You can’t allocate a rank 1 array to the shape of a rank 2 array. That may be the source of the “type incompatible” message you saw, though the compiler I used gave a different error.
  2. integerarray is not given the allocatable attribute, so you’re not allowed to allocate it.

I could also comment that using an explicit kind of (2) is not best-practice. You might explore my thoughts on this at Doctor Fortran in “It Takes All KINDs” - Doctor Fortran (stevelionel.com)

It is not clear to me what you want to happen here with the different ranks. Can you show us a small example (table or text) of the results you’re looking for?

3 Likes

Thanks for the answer. Just to clarify, by old I meant the legacy that Fortran has. It inspires me that something is so long lasting.
I added the allocatable tag, and matched the rank, but the error still persists. The idea is basically to take a real array which may be one-dimensional or two-dimensional, such as

1.0 2.0
1.2 1.8
1.4 1.6
1.6 1.4
1.8 1.2
2.0 1.0

and convert it to an integer array after multiplying it by something large enough so that the differences aren’t lost in the rounding off. In that case it should look something like

16383 32768
.
.
.
32768 16384.

However, this may also have to be done with arrays of one dimension.
Also, I will read up on the kinds and clean that up.

The key here is that, at least in the current language, you’ll need separate implementations for the 1D and 2D cases. A method that works is to define a generic interface, with two specific procedures, one for a 1D interface and one for a 2D. The program calls the generic name, and the compiler figures out which one you want.

Fortran 2018 adds a feature called “deferred rank” where you declare the procedure argument (called “dummy argument” in Fortran) with dimension(..). This can accept an array of any dimension, or a scalar. You must then use a select rank construct to separate out the various ranks and do whatever is needed. I think that for your purposes, the generic interface is better.

In the worked example I show below, I’ve also eliminated the explicit allocate as it is not needed - in an assignment to an allocatable array it will be automatically (re)allocated to the shape of the value being assigned (but the ranks must still match.)

Look this over and feel free to ask further questions.

    module WF_Mod
    implicit none
    
    interface Prepare ! Declares generic interface
        module procedure Prepare1D
        module procedure Prepare2D
    end interface
    
    contains
    
    subroutine Prepare1D (realarray, integerarray)
    real, intent(in) :: realarray (:)
    integer, allocatable, intent(out) :: integerarray(:)
    
    ! Automatically allocates integerarray to the correct shape
    integerarray = nint((2**15) * realarray / maxval(realarray))
    end subroutine Prepare1D
    
    subroutine Prepare2D (realarray, integerarray)
    real, intent(in) :: realarray (:,:)
    integer, allocatable, intent(out) :: integerarray(:,:)
    
    ! Automatically allocates integerarray to the correct shape
    integerarray = nint((2**15) * realarray / maxval(realarray))
    end subroutine Prepare2D 
    
    end module WF_Mod

    program WhiteFang
    use WF_mod
    implicit none
    
    real :: ra(6,2)
    integer, allocatable :: ia(:,:)
    
    ra = reshape([1.0,2.0,1.2,1.8,1.4,1.6,1.6,1.4,1.8,1.2,2.0,1.0],shape(ra))
    call Prepare(ra,ia)
    print '(I6,1X,I6)', ia

    end program WhiteFang
5 Likes

Hi! Thanks for the example. I just have one question.
When I define an interface, how does the program choose which subroutine of the interface should be called?

With a generic interface, the compiler matches the number of arguments and the type, kind, and rank (TKR) of the actual arguments with the possible sets of dummy arguments. That means that those sets of dummy arguments must be distinct somehow in order for that process to work.

In your example, you can use the NINT() intrinsic function to convert from a real array to an integer array. That works because that function is elemental, meaning that it works for both scalars and arrays. All of the intrinsic conversion routines, INT(), NINT(), REAL(), CMPLX(), FLOOR(), ABS(), etc. are elemental, so you can convert from and to all of those types and kinds. If for some reason the intrinsic functions are not sufficient, then you can write your own elemental functions and do your own special purpose conversions. As @sblionel shows above, the conversion, creation, allocation, and assignment of the array result can be done on a single statement, so there is hardly any need for a subroutine or function to do this; thus you don’t really need to worry about TKR resolutions unless you choose to.

1 Like

To add to what @RonShepard said - you might be wondering what happens if you define two or more specific procedures in your generic interface that have the same number and TKR so that they’re ambiguous. The standard says you can’t do that, and compilers will give you an error if you do.

Here’s an aspect of this that often trips people up. Is this an ambiguous interface?

interface gen
  subroutine gen1 (a,b)
  integer :: a
  real :: b
  end subroutine gen1
  subroutine gen2 (b,a)
  real :: b
  integer :: a
  end subroutine gen2
end interface

The answer is “Yes”, because the compiler can’t disambiguate call gen (a=3,b=4.0).

OPTIONAL arguments can also mess up disambiguation.

1 Like