Fortran Select Type with arrays [duplicate] - select

My question is, "Can a select type block be used to distinguish real :: realInput from real :: realArrayInput(:)?" It's clear how select type may be used to distinguish derived types, but becomes less clear to me how (or whether) it may be used on intrinsic types.
In Mad Libs form, can the blanks be filled in below to distinguish between the inputs above:
select type (input)
type is (real)
print *, "I caught the realInput"
type is (___________)
print *, "I caught the realArrayInput"
end select
I've found some related posts that did not quite contain the answer I was hoping for:
Select Type Issues
Determining Variable Type

No. input is either declared as an array or a scalar, even when it is polymorphic (and even when it is unlimited polymorphic).
The recent further interoperability with C TS (which may be part of F201X) introduced the concept of assumed rank and the RANK intrinsic, which may do what you want. But there are many limitations around what can be done with assumed rank objects. And regardless of that SELECT TYPE still only works on type. The syntax of the select type construct simply doesn't permit specification of rank in the type guard statements.
Obviously depending on what it is that you actually want to do (?) ... and beyond generic interfaces mentioned by others, a way to have objects that can be either array or scalar in current Fortran (there are other possibilities) is to use derived type wrappers that are an extension of a common parent type. You then use a polymorphic object declared as the parent type (or you can use an unlimited polymorphic object) to refer to an object of the relevant derived type.
TYPE :: parent
END TYPE parent
TYPE, EXTENDS(parent) :: scalar_wrapper
REAL :: scalar_component
END TYPE scalar_wrapper
TYPE, EXTENDS(parent) :: array_wrapper
REAL :: array_component(10)
END TYPE array_wrapper
...
SUBROUTINE what_am_i(object)
! Note that object is scalar, but that doesn't tell us
! the rank of the components of the dynamic type of object.
CLASS(parent), INTENT(IN) :: object
!****
SELECT TYPE (object)
TYPE IS (scalar_wrapper)
PRINT "('I am a scalar with value ',G0)", &
object%scalar_component
TYPE IS (array_wrapper)
PRINT "('I am an array with values ',*(G0,:,','))", &
object%array_component
CLASS DEFAULT
PRINT "('I am not sure what I am.')"
END SELECT
END SUBROUTINE what_am_i

Just to combine IanH's anwser and M.S.B's comment and explain more in detail: You can not use the select type construct to distinguish between real scalars and real arrays as they only differ in their dimension, but not in their type. When you declare your variable input, you already decide 'for ever', whether it has or it has not the dimension attribute:
class(*) :: input_scalar
class(*), dimension(10) :: input_array
Whichever value the variable takes later (or to whichever object it points to, if it is a pointer), it can not represent something with a dimensionality (rank) different from the one in its declaration.
On the other hand, you could for example use the interface construct (or generic in type bound procedures) to distinguish between objects of the same type but different ranks. The example below demonstrates that for scalar and rank one integer and real arrays.
module testmod
implicit none
interface typetest
module procedure typetest0, typetest1
end interface typetest
contains
subroutine typetest0(object)
class(*), intent(in) :: object
select type(object)
type is (real)
print *, "real scalar"
type is (integer)
print *, "integer scalar"
end select
end subroutine typetest0
subroutine typetest1(object)
class(*), dimension(:), intent(in) :: object
select type(object)
type is (real)
print *, "real array"
type is (integer)
print *, "integer array"
end select
end subroutine typetest1
end module testmod
program test
use testmod
implicit none
integer :: ii
integer, dimension(10) :: iarray
call typetest(ii) ! invokes typetest0
call typetest(iarray) ! invokes typetest1
end program test

Related

Problem with Ambiguous interfaces with gfortan

I have a situation similar to the following code snipped (saved in test.f90):
module interfaces_mod
private
public :: interf
interface interf
module procedure interf1
module procedure interf2
end interface
contains
subroutine interf1(&
numbers,&
num_numbers,&
dense_ranks&
)
Implicit None
integer, dimension(:), intent(in) :: numbers
integer, intent(in) :: num_numbers
integer, dimension(:), intent(out), optional :: dense_ranks
end subroutine interf1
subroutine interf2(&
degeneracies,&
numbers,&
num_numbers,&
dense_ranks&
)
Implicit None
Integer, dimension(:), intent(inout) :: degeneracies
integer, dimension(:), intent(in) :: numbers
integer, intent(in) :: num_numbers
Integer, dimension(:), intent(out), optional :: dense_ranks
end subroutine interf2
end module interfaces_mod
The module therefore defines a generic interfaces with two possible realizations.
This snipped can be compiled using ifort with
ifort -c -o "test.o" "test.f90"
to create a module.
However trying to compile the same code with gfortran:
gfortran -c -o "test.o" "test.f90"
leads to the error:
15 | subroutine interf1(&
| 1
......
32 | subroutine interf2(&
| 2
Error: Ambiguous interfaces in generic interface 'interf' for ‘interf1’ at (1) and ‘interf2’ at (2)
Now looking at the dummy parameters of the realizations, interf1 is called with
an Integer array followed by an Integer and an optional Integer array.
interf2 instead is called with two Integer arrays followed by an Integer and an optional
Integer array.
So I dont understand where the ambiguity is coming from, and why ifort can compile this snipped and gfortran is not able to compile it.
gfortran version is 9.3.0,
ifort version is 19.0.5.281
Your procedures do not meet the rules for having the same generic identifier, and gfortran is entitled to reject the generic.
The constraint to consider is C1514 of Fortran 2018. Let's take a detailed look. There are no dummy procedures or passed-object dummy arguments, so we're down to (1) and (4) of that constraint. One of these conditions must pass.
For (1):
We have one scalar argument in each procedure, called num_numbers in each. The scalar argument cannot be used to disambiguate.
In interf1 we have a (1a) score of 1 for the two array dummy arguments, whereas the (1b) score for each is 3. For interf2 the (1a) scores are 2 for the three array dummy, whereas the (1b) score for each is also 2.
(1) is not met.
For (4):
No dummy argument in one procedure is distinguishable from that with the same name in the other.
interf1 does not have a dummy argument with name not appearing in interf2.
interf2 has name-disambiguating argument degeneracies at position 1 while its first position-disambiguating argument is at position 2.
(4) is not met.
Although (4) is not met, it is easy to modify the procedure definitions such that it is: move degeneracies later in the argument list.
There's an important note in the Fortran standard itself, before you try to work out exactly how to create an ambiguous reference:
These rules are sufficient to ensure that references to procedures that meet them are unambiguous, but there remain examples that fail to meet these rules but which can be shown to be unambiguous [...] The rules
to cover all cases are too complicated to be useful.

Fortran polymorphism in pointers

I am trying to use pointers to create links between objects. Using Fortran and here is the code piece:
module base_pars_module
type,abstract,public :: base_pars
end type
end module
module test_parameters_module
use base_pars_module
type, extends(base_pars) :: test_pars
contains
procedure :: whoami
end type
contains
function whoami(this) result(iostat)
class( test_pars) :: this
write(*,*) 'i am a derived type child of base_pars'
end type
end module
module base_mask_module
use base_pars module
type, abstract , public :: base_mask
class(base_pars),pointer :: parameters
end type
end module
module test_mask_module
use base_mask_module
implicit none
type, extends(base_mask) :: test_mask
end type
end module
program driver
type(test_pars) , target :: par_Test
type(test_mask) :: mask_test
iostat= par_test%whoami()
mask_test%parameters=>par_test
iostat=mask_test%parameters%whoami()
end program
parameters at base_mask_module is a pointer with base_pars class. I would like to use this pointer to refer par_test object which is test_pars type that extends base_pars type. So the pointer and the target has the same class. But when I compile this it gives an error:
driver.f90:17.37:
iostat=mask_test%parameters%whoami()
1
Error: 'whoami' at (1) is not a member of the 'base_pars' structure
Is it a bug or am i doing something wrong?
When you have polymorphism like this there are two things to consider about an object: its dynamic type and its declared type. The parameters component of test_mask (base_mask) is declared as
class(base_pars),pointer :: parameters
Such a component therefore has declared type base_pars.
Come the pointer assignment
mask_test%parameters=>par_test
mask_test%parameters has dynamic type the same as par_test: test_pars. It's of declared type base_pars, though, and it's the declared type that is important when we care about its components and bindings. base_pars indeed has no whoami.
You need, then, something which has declared type par_test. Without changing the definitions of the derived types you can do this with the select type construct.
select type (pars => mask_test%parameters)
class is (par_test)
iostat=pars%whoami() ! pars of declared type par_test associated with mask_test%parameters
end select
That said, things get pretty tedious quite quickly with this approach. Always using select type, distinguishing between numerous extending types, will be quite a bind. An alternative would be to ensure that the declared type base_pars has a binding whoami. Instead of changing the main program as above, we alter the module base_pars_module:
module base_par_modules
implicit none ! Encourage good practice
type,abstract,public :: base_pars
contains
procedure(whoami_if), deferred :: whoami
end type
interface
integer function whoami_if(this)
import base_pars ! Recall we're in a different scope from the module
class(base_pars) this
end function
end interface
end module
So, we've a deferred binding in base_pars that is later over-ridden by a binding in the extending type test_pars. mask_test%parameters%whoami() in the main program is then a valid and the function called is that offered by the dynamic type of parameters.
Both approaches here address the problem with the binding of the declared type of parameters. Which best suits your real-world problem depends on your overall design.
If you know that your hierarchy of types will all have enough in common with the base type (that is, all will offer a whoami binding) then it makes sense to go for this second approach. Use the first approach rather when you have odd special cases, which I'd suggest should be rare.

Interfaces in Fortran

I stumbled over a particular problem with interfaces while debugging some code, where a called subroutine has a dummy argument of rank 2 but an actual argument of rank 1. The resulting difference in the arguments resulted in an invalid read.
To reproduce I created a small program (ignore the comments ! <> for now):
PROGRAM ptest
USE mtest ! <>
IMPLICIT NONE
REAL, ALLOCATABLE, DIMENSION(:) :: field
INTEGER :: n
REAL :: s
n = 10
ALLOCATE(field(n))
CALL RANDOM_NUMBER(field)
CALL stest(n, field, s)
WRITE(*,*) s
DEALLOCATE(field)
END PROGRAM
and a module
MODULE mtest ! <>
IMPLICIT NONE ! <>
CONTAINS ! <>
SUBROUTINE stest(n, field, erg)
INTEGER :: n
REAL, DIMENSION(n,n) :: field
REAL :: erg
erg = SUM(field)
END SUBROUTINE
END MODULE ! <>
As far as I understand, this subroutine gets an automatic (explicit?) interface from being placed in the module. The problem is, that the actual field has length 10, while the subroutine sums a field of length 10x10=100 which is clearly visible in valgrind as an invalid read.
Then I tested this same code without the module, i.e. all lines marked with ! <> got removed/commented. As a result, gfortran's -Wimplicit-interface threw a warning, but the code worked as before.
So my question is: What is the best way, to deal with such a situation? Should I always place a generic interface à la
INTERFACE stest
MODULE PROCEDURE stest
END INTERFACE
in the module? Or should I replace the definition of field with an deferred-shape array (i.e. REAL, ALLOCATABLE, DIMENSION(:,:) :: field)?
EDIT: To be more precise on my question, I don't want to solve this particular problem, but want to know, what to do, to get a better diagnostic output from the compiler.
E.g. the given code doesn't give an error message and does, in principle, produce a segmentation fault (though, the code doesn't notice it). Placing a generic interface produces at least an error, complaining, that no matching definition for stest is found, which is also not really helpful, especially in the case, where you don't have the source code. Only a deferred-shape array resulted in an understandable error message (rank mismatch).
And this is, were I'm wondering, why the automatic module interface doesn't give a similar warning/error message.
The compiler cannot warn you, because the code is legal! You just pass wrong n and a non-square number of points. For explicit shape arrays you are responsible for correct dimensions. Consider
ALLOCATE(field(1000))
CALL stest(10, field, s)
this code will work although the number of elements of the actual and dummy arguments is not the same. Maybe suggest to gfortran developers to check whether the dummy argument is not larger, but I am not sure how difficult that is.
The generic interface causes the compiler to check the TKR rules. No sequence association of arrays of different rank is allowed and the compilation will fail. Therefore it will disable all legal uses of passing arrays of different rank to explicit shape and assumed size dummy arguments and limit your possibilities.
What is the solution? Use explicit shape arrays for situations they are good for and use assumed shape arrays otherwise (possibly with the contiguous attribute). The generic interface might help too, but changes the semantics and limits the possible use.

checking for self-assignment in fortran overloaded assignment

I am trying to implement a polynomial class with fortran 2003, with overloaded arithmetic operations and assignments. The derived type maintains allocatable list of term definitions and coefficients, like this
type polynomial
private
type(monomial),dimension(:),allocatable :: term
double precision,dimension(:),allocatable :: coef
integer :: nterms=0
contains
...
end type polynomial
interface assignment(=)
module procedure :: polynomial_assignment
end interface
...
contains
elemental subroutine polyn_assignment(lhs,rhs)
implicit none
type(polynomial),intent(???) :: lhs
type(polynomial),intent(in) :: rhs
...
I had to make it elemental because this is intended to be used as matrices of polynomials. That does work, for the most cases at least. However, I somehow got myself into concerns about self-assignment here. One can simply check the pointers to see if things are the same in C++, but it doesn't seem to be an option in Fortran. However the compiler do detect the self-assignment and gave me a warning. (gfortran 4.9.0)
When I have intent(out) for lhs, the allocatable entries for both lhs and rhs appeared to be deallocated on entry to the subroutine, which made sense since they were both p, and an intent(out) argument would first be finalized.
Then I tried to avoid the deallocation with an intent(inout), and check self-assignment by modifying one field in the lhs output
elemental subroutine polyn_assignment(lhs,rhs)
implicit none
type(polynomial),intent(inout) :: lhs
type(polynomial),intent(in) :: rhs
lhs%nterms=rhs%nterms-5
if(lhs%nterms==rhs%nterms)then
lhs%nterms=rhs%nterms+5
return
end if
lhs%nterms=rhs%nterms
Well, now this is what surprised me. When i do
p=p
It didn't make the test and proceeded, giving me a polynomial with 0 terms but no memory violations. Confused, I printed lhs%nterms and rhs%nterms inside the assignment, only to find that they are different!
What is even more confusing is that when I did the same thing with
call polyn_assignment(p,p)
It works perfectly and detected that both arguments are the same. I am puzzled how an interface of a subroutine can run differently from the subroutine itself.
Is there something special about assignment in Fortran 2003 that I've missed?
(First time to ask a question here. Please correct me if i didn't do it right.)
If you have a statement a = b that invokes defined assignment via a subroutine sub, the assignment statement is equivalent to call sub(a, (b)). Note the parentheses - the right hand side argument is the result of evaluating a parenthesised expression and is therefore not conceptually the same object as b. See F2008 12.4.3.4.3 for details.
Consequently, a = a is equivalent to call sub(a, (a)). The two arguments are not aliased. It is different from call sub(a,a), the latter may (depending on the specifics of the internals of sub, including dummy argument attributes) break Fortran's argument aliasing rules (e.g. in your example, a statement such as call polyn_subroutine(a,a) is illegal).

Array valued function to be called from type definition

While writing a library to read image values, I have the following problem:
I defined a new type called realimage. Within this type a function is referenced, which returns an array as a result.
module typedefinition
implicit none
type realimage
integer :: byteorder = 0
contains
procedure :: initialize => initializereal
procedure :: pxvalues => pxvaluesreal ! Array valued function
end type realimage
contains
function pxvaluesreal(this, x, y) result(val)
implicit none
type(realimage) this
real val(5)
integer :: x, y
...
end function
end module
Compiling the module with gfortran and calling the function with image1%pxvalues(x,y), I always get the following error message:
main.f95: In function ‘testtype’:
main.f95:15: internal compiler error
If I directly call the function in the main program (pxvaluesreal(image1,x,y)), everything works fine.
Is it possible to define the array dimension in the type definition in order to tell the compiler, which are the dimesions of the return value of the function?
Internal compiler errors are always due to a compiler bug. If you are using a recent version of gfortran you should consider reviewing their list of open bugs and perhaps filing a bug report.
Beyond that - your code is not standard compliant - the passed object 'this' must be polymorphic (declare it with CLASS rather than TYPE). Otherwise your specification of the size of the array function result is correct - when you reference the pxvalues binding the compiler knows that the size of the function result is 5 as it 'knows' the interface of the specific procedure pxvaluesreal that the binding is associated with.