- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
If I have a structure called fred which contains many variables, eg. x and y, is there a way to avoid keeping having to preface the variables everywhere I use them with "fred%". This used to be available in Pascal as:
with fred begin x = 555 y = 666 end
Long shot...
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The equivalent feature in Fortran is ASSOCIATE.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve Lionel (Intel) wrote:
The equivalent feature in Fortran is ASSOCIATE.
Not sure how that is supposed to work with the fred example above. I'd like to strip away the parent structure name.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Adrian F. wrote:
Quote:
Steve Lionel (Intel) wrote:
The equivalent feature in Fortran is ASSOCIATE.
Not sure how that is supposed to work with the fred example above. I'd like to strip away the parent structure name.
You can look in Modern Fortran Explained by Metcalf et al. for more details, but here is a simple example:
program p type :: t integer :: x integer :: y end type t type(t) :: foo foo%x = 1 foo%y = 2 asc: associate ( x => foo%x, y => foo%y ) print *, " foo%x = ", x print *, " foo%y = ", y end associate asc stop end program p
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The ASSOCIATE construct is similar to, but not quite the same as Pascal's WITH.
Here is what you can do in the example case that you wrote about. Note that ASSOCIATE has more features than WITH. In the example below, you may see that there are multiple associations set up, but note that the individual associations do not always have to be components of a single user defined type.
program xassoc type st integer x integer y end type type(st) fred ! fred=st(15,36) associate(x=>fred%x, y=>fred%y) write(*,*)x,y,x+y end associate end program
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
ok thanks. Two questions.
1. I see you have not declared the x and y referred to on the left hand side of the associate statements. Does the compiler just assume they are the same type as those on the right?
2. So if fred is large, then I have to have a very long associate statement at the beginning of the file. I guess this can be hidden in an include file.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Adrian F. wrote:
1. I see you have not declared the x and y referred to on the left hand side of the associate statements. Does the compiler just assume they are the same type as those on the right?
Section 8.1.3.2 of the F2008 standard says, "The associating entity assumes the declared type and type parameters of the selector.".
2. So if fred is large, then I have to have a very long associate statement at the beginning of the file. I guess this can be hidden in an include file.
At the beginning of the file? Possible, but not a good idea. I'd suggest making ASSOCIATE constructs short, because the body of the construct is seemingly easy to read, but its meaning is not knowable without knowing the associations. I think of ASSOCIATE as a limited and short-in-scope variable renaming facility.
Hiding the ASSOCIATE in an include file would make things even worse for the reader.
I tried out the example code in #5 in the VS2013 debugger, and I see some rough edges there. In the local panes I see X and Y shown twice, as if they were separate variables. (This is probably the result of an error in debug symbols generation, as described in https://software.intel.com/en-us/forums/topic/540783, and should be fixed when IFort 16.0 comes out). You have to look at the source code pane to become aware of the association. Before the construct is entered, these alias names are shown with "undefined" values. However, as of now, when execution has halted on a line within the construct, we see three copies of X and Y.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I'd also comment that hiding information on a large scale can make maintenance more difficult. Where ASSOCIATE can really help is if you have a nested structure, such as a%b%c where c is also a derived type. You can use ASSOCIATE to create an associate name for a%b%c (call it xc) and then reference xc%whatever. This also works for array references.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yes I remember all too well the pitfalls of WITH in Pascal. Just that the separator '%' in Fortran just makes the code that much more unreadable than the unobtrusive '.' So much so that I'd prefer to hide it.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Not sure what is wrong here:
program main type :: t_net integer, pointer:: nodes(:) end type t_net type(t_net) :: net associate(nodes => net%nodes) allocate(nodes(nnode)) end associate end
ifort aa.f90
Intel(R) Visual Fortran Compiler XE for applications running on IA-32, Version 14.0.2.176 Build 20140130
Copyright (C) 1985-2014 Intel Corporation. All rights reserved.
aa.f90(11): error #8306: Associate name defined in ASSOCIATE or SELECT TYPE statements doesn't have ALLOCATABLE or POINTER attribute [NODES]
allocate(nodes(nnode))
---------------^
compilation aborted for aa.f90 (code 1)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
As the message says, the associated name is never a pointer or allocatable, even if you are associating it with something that appears to be an allocatable or pointer. It is associated with the data object designated by the right hand side of the =>, rather than the things that holds the data object. Perhaps the reasoning is a bit obscure, but this approach is consistent with other aspects of the design of the language - conceptually the allocation status of net%nodes in your example is part of the value of the parent net object, not the net%nodes component itself.
On a different tack, if you are defining a particular structure from scratch, then structure constructors may be helpful.
type t integer :: x integer :: y end type t type(t) :: fred fred = t(x=555, y=666)
If, instead you are updating part of an existing object I would be tempted to write a function that used optional arguments to assist with the update:
type t integer :: x integer :: y end type t interface t procedure :: t_update end interface t function t_update(original, x, y) result(updated) type(t), intent(in) :: original integer, intent(in), optional :: x integer, intent(in), optional :: y type(t) :: updated updated = original if (present(x)) updated%x = x if (present(y)) updated%y = y end function t_update ... type(t) :: fred fred = t(555,666) ... fred = t(fred, Y=777)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
mecej4 wrote:
Quote:
Adrian F. wrote:
1. I see you have not declared the x and y referred to on the left hand side of the associate statements. Does the compiler just assume they are the same type as those on the right?
Section 8.1.3.2 of the F2008 standard says, "The associating entity assumes the declared type and type parameters of the selector.".
Ok so from IanH's reply to my blind adherence to the above standard, you can use allocatables or pointer variable types, you just can't allocate them. This works:
program main implicit none type :: t_net integer, pointer:: nodes(:) end type t_net type(t_net) :: net allocate(net%nodes(1)) call sub(net) write(*,*) net%nodes(1) end !-------------------------------------- subroutine sub(net) implicit none type :: t_net integer, pointer:: nodes(:) end type t_net type(t_net) :: net associate(nodes => net%nodes) nodes(1) = 12345 end associate return end
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Adrian F. wrote:
Ok so from IanH's reply to my blind adherence to the above standard, you can't use allocatables or pointer variable types.
You can't do things relating to the allocation status of selectors with the allocatable attribute or the pointer association status of selectors with the pointer attribute, but you can still reference them and define them through the associate name (if the selector is defined/definable). If the selector has the target attribute (which is the case for anything that a associated pointer is pointing at) then the associate name also has the target attribute, so you can associate pointers with the associate name.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
ianh wrote:
Quote:
Adrian F. wrote:Ok so from IanH's reply to my blind adherence to the above standard, you can't use allocatables or pointer variable types.
You can't do things relating to the allocation status of selectors with the allocatable attribute or the pointer association status of selectors with the pointer attribute, but you can still reference them and define them through the associate name (if the selector is defined/definable). If the selector has the target attribute (which is the case for anything that a associated pointer is pointing at) then the associate name also has the target attribute, so you can associate pointers with the associate name.
ok you can use them just not allocate them.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
And remember to be careful not to deallocate or reallocate an allocatable/pointer that has an active associated selector. (somewhat like using a C pointer where other code modified the memory state such that the pointer is no longer valid (though the memory may be a valid address).
This is another reason for making your associate blocks small enough to assure you do not make this faux pas.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I hope the associate is not transferred into called subroutines. ie is more like an include statement and limited to the file it is in. If so, it is easy to manage.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The associate name is only usable in the lexical scope of the associate construct (in the source that physically appears between the ASSOCIATE and END ASSOCIATE statements.. You can pass the object nominated by the associate name to other procedures though, but the characteristics of the actual argument are the characteristics of the associate name.
type :: t integer, allocatable :: z end type t t%z = 3 associate (chicken => t%z) ! t%z is allocatable, but chickens never are. call proc(chicken) end associate subroutine proc(arg) integer, intent(in) :: arg print *, arg ! will print 3. end subroutine proc
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page