2

Using code from the Fortran90 standard, is there a way to pass the name of a derived type element to a subroutine in Fortran? I'd like to do something like the following:

TYPE :: DataContainer
    REAL :: DataElementA
    REAL :: DataElementB
    REAL :: DataElementC
END TYPE DataContainer

SUBROUTINE ComplexOperation(DataMatrixParameter, DataElementName, Parameter)
    ! Parameter Typing for DataElementName?
    DataMatrixParameter%DataElementName = Parameter
END SUBROUTINE

TYPE (DataContainer), DIMENSION :: Data
CALL ComplexMatrixOperation(Data, DataElementA, 5)
CALL ComplexMatrixOperation(Data, DataElementC, 4)

So that Data%DataElementA is 5 and Data%DataElementC is 4. The DataElementName parameter could be any kind of element identifier, but I would prefer to avoid strings and case statements. Those familiar with C++ will recognize it as something directly analogous to the pointer to member feature.

My real problem is, of course, much more complex than just assigning the elements to a given value.

  • 1
    I don't understand. What do you mean by "`Data%DataElementA` is `5`", etc.? If you're just after selecting a component by a character label then there are likely other questions about that. – francescalus Dec 17 '15 at 19:56
  • @francescalus I mean that the element in question has been assigned to the given value, by following the code in the `ComplexOperation` subroutine. Can you link some of the questions you're talking about? – professional_yet_not_trackable Dec 17 '15 at 20:02
  • 1
    http://stackoverflow.com/q/23071709 could be one, but there perhaps isn't sufficient motivation in the question (so why, for example, you don't just pass `Data%DataElementA`) to be really sure. – francescalus Dec 17 '15 at 20:10
  • I don't think namelists apply, as it seems they can't be used to refer to record elements, and seem to strictly apply to read statements.This is for a more general operation that is, for the purposes of this question, isomorphic to assigning to a given parameter value. The actual details of what's going on are too complex to sanitize for posting here, and if the solution works for assignment, it should work for what I'm doing. Some of the later answers suggest a select case statement, which could be made to work, but I'd rather avoid as it requires me to duplicate the enumeration of fields. – professional_yet_not_trackable Dec 17 '15 at 20:17
  • The questions are similar in intent, but differ critically in that the other poster wants to do it specifically with a user-specified character string, whereas I'm looking for any kind of user-supplied token. The direct analogy here is the C++ pointer to member capability I mentioned. That capability could meet my need (by specifying the member name as a token known to the compiler), but not the need of the other user (who wanted to call it by a character string). I was hoping there was something similar in Fortran, but it appears that may not be the case. – professional_yet_not_trackable Dec 17 '15 at 20:32
  • 2
    There is indeed no thing to do what you. If you edit your needs into the question (I'm surely not the only Fortran user to not be sufficiently familiar with the C++ concepts) then you may get an answer building on that. [But I still don't understand why you can't just pass the component itself, rather than a redirect identifier. – francescalus Dec 17 '15 at 20:36
  • 1
    I've tried to edit the question to clarify a bit what I'm talking about. The short answer as to why I can't pass the component itself is that these methods actually operate on matrices of derived type objects, and I want it to act on all of the data elements of a certain type across that matrix. – professional_yet_not_trackable Dec 17 '15 at 21:00
  • 1
    You can also pass an array of components. Passing `Data%DataElementB` is perfectly legal. – Vladimir F Героям слава Dec 17 '15 at 22:01

3 Answers3

1

From what I can gather you want to be able to write something like

call ComplexMatrixOperation(Data, DataElementA, ...)

where Data is a matrix, so that a subroutine looking something like

subroutine ComplexMatrixOperation(matrix, selector, ...)
  type(DataContainer) matrix(:,:)
  something_magical selector

can act on the elements matrix(i,j)%DataElementA or matrix(i,j)%DataElementC depending on the selector.

That something_magical doesn't exist. However, you still have options (beyond those already answered).

As we can see that DataElementA is a scalar component we are able to reference Data%DataElementA which is an array of reals of shape that of Data.

You can, then,

call ComplexMatrixOperation(Data%DataElementA, ...)

or

call ComplexMatrixOperation(Data%DataElementC, ...)

for

subroutine ComplexMatrixOperation(matrix, ...)
  real matrix(:,:)

if we again assume that Data is of rank 2 (adjust accordingly).

francescalus
  • 30,576
  • 16
  • 61
  • 96
0

You can't do this. Your best bet is to use an array instead of named elements

TYPE :: DataContainer
    REAL, DIMENSION(3) :: DataElement
END TYPE DataContainer

and then use it with

SUBROUTINE ComplexOperation(DataMatrixParameter, DataElementIndex, Parameter)
    TYPE(DataContainer) :: DataMatrixParameter
    INTEGER, INTENT(IN) :: DataElementIndex
    REAL, INTENT(IN) :: Parameter
    DataMatrixParameter%DataElement(DataElementIndex) = Parameter
END SUBROUTINE

Maybe use named constants like

INTEGER, PARAMETER :: DataElementA=1, DataElementB=2, DataElementC=3

to be used as

CALL ComplexOperation(Data, DataElementC, 1.33)
John Alexiou
  • 28,472
  • 11
  • 77
  • 133
0

Although it is probably not possible to mimic the C++ way for using pointers to class members and also there is no native metaprogramming facility at present (except for preprocessor macros), Fortran instead has the ability to create arrays of type components efficiently without making any array temporaries (as suggested above), which might be useful for the OP's purpose. To illustrate this, here is some example code for using such component arrays:

module testmod
    implicit none
    type A_t
        integer :: u = 0, v = 0
    endtype
    type B_t
        integer :: x = 0, y = 0
        type(A_t) :: a
    endtype

contains
    subroutine setval ( elem, val )
        integer :: elem(:), val    !! assumed-shape array
        elem(:) = val
    endsubroutine

    subroutine setval_2D ( elem, val )
        integer :: elem(:,:), val    !! assumed-shape array
        elem(:,:) = val
    endsubroutine

    subroutine setval_explicit ( elem, n, val )
        integer :: n, elem( n ), val  !! explicit-shape array
        elem( 1:n ) = val
    endsubroutine
end module

program main
    use testmod
    implicit none
    type(B_t), target :: b( 2 ), bmat( 2, 2 )

    !! Pass 1D component arrays.
    call setval ( b(:)% x,     1 )
    call setval ( b(:)% y,     2 )
    call setval ( b(:)% a% u,  3 )
    call setval ( b(:)% a% v,  4 )

    print *, "b( : )% x    = ", b( : )% x
    print *, "b( : )% y    = ", b( : )% y
    print *, "b( : )% a% u = ", b( : )% a% u
    print *, "b( : )% a% v = ", b( : )% a% v
    print *, "b(1) = ", b(1)
    print *, "b(2) = ", b(2)

    !! Pass a 2D component array.
    call setval_2D ( bmat(:,:)% x, 50 )

    print *, "bmat(:,:)% x = ", bmat(:,:)% x

    !! Pass 1D component array sections.
    call setval ( bmat(:, 1)% x, 1 )
    call setval ( bmat(:, 2)% x, 2 )
    call setval ( bmat(2, :)% x, 5 )

    print *, "bmat(:,:)% x = ", bmat(:,:)% x

    !! Pass a 2D component array to an explicit-shape dummy array
    !! (in this case, copy-in/copy-out may occur).
    call setval_explicit ( bmat(:,:)% x, size(bmat), 100 )

    print *, "bmat(:,:)% x = ", bmat(:,:)% x
endprogram

with the result

 b( : )% x    =            1           1
 b( : )% y    =            2           2
 b( : )% a% u =            3           3
 b( : )% a% v =            4           4
 b(1) =            1           2           3           4
 b(2) =            1           2           3           4
 bmat(:,:)% x =           50          50          50          50
 bmat(:,:)% x =            1           5           2           5
 bmat(:,:)% x =          100         100         100         100

[Side note] It is also interesting to see how metaprogramming works in dynamic languages, e.g. with Julia (a similar thing might be possible with preprocessor macros, though).

function test( a, fieldname, val )
    @eval $a.$fieldname = $val
end

type Person
    age :: Int
    weight :: Float64
end

foo = Person( 0, 0.0 )

test( foo, :age, 100 )
test( foo, :weight, 789.0 )

@show foo.age
@show foo.weight
Community
  • 1
  • 1
roygvib
  • 7,218
  • 2
  • 19
  • 36