- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I am trying to figure out the correct methodology for setting a user derived type variable at runtime based on some user input. The following would be a very simply example of two user derived types: One and Two.
type One integer :: ivalue=0 end type One type Two integer :: ivalue=0 end type Two
How would I go about setting a variable,x, to a specific user derived type based on user input. Pseudocode would be something along the lines of
if userinput = 1, then set x to type One
elseif userinput =2, then set x to type Two
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Use an abstract type from which your types one and two inherit.
module types
implicit none
public :: t1, one, two
type, abstract :: t1
integer :: ivalue = 0
contains
procedure(t1_print), deferred :: print
end type t1
type, extends(t1) :: one
contains
procedure :: print => one_print
end type one
type, extends(t1) :: two
contains
procedure :: print => two_print
end type two
abstract interface
subroutine t1_print (this)
import
class(t1), intent(in) :: this
end subroutine t1_print
end interface
contains
subroutine one_print (this)
class(one), intent(in) :: this
print *, "Type one!"
end subroutine one_print
subroutine two_print (this)
class(two), intent(in) :: this
print *, "Type two!"
end subroutine two_print
end module types
program main
use types
implicit none
class(t1), allocatable :: foo
integer :: x
x = 2
select case (x)
case (1)
allocate (one :: foo)
case (2)
allocate (two :: foo)
case default
print *, "Error!"
end select
call foo%print ()
end program main
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Great example!
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you very much! This will work perfectly for my purposes.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
A follow up question using the above example types module and main program. That example shows how to set class foo to either type one or two depending on some input. I have run into some errors accessing components of the either one or two -- note they have unique component names. When trying to access a type's component, I get the following compile error:
error #6460: This is not a field name that is defined in the encompassing structure.
I determined that the accessing must occur within a SELECT TYPE block.
select type(foo)
type is(one)
...access type one components here....
type is(two)
...access type one components here....
end select
Is this the only way to access the components? Could I call a subroutine within the SELECT TYPE in which the subroutine operates only on a specific type's components?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yes, you have to use a `select type` here. Or you have to use a deferred getter routine that is overridden in the different inheriting types one and two if at least the type of the different components of one and two is the same.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It appears that the scope of the SELECT TYPE construct does apply to the called subroutine within the TYPE IS block. Is this correct?
Expanding upon the earlier examples, I want to perform work data object. So I would need to have 2 subroutines to perform work on each type one or two. I basically have to encapsulate the entire subroutine with a SELECT TYPE construct. Some like the following...
subroutine work_on_type_one(input) use types implicit none class(t1), intent(inout), allocatable :: input ....define and initialize some local vars... select type(input) type is(one) ...main body of subroutine... end select return end subroutine work_on_type_one
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
As I said, if you do it with a deferred procedure, then you don't need a select type construct, but you could you an overridden function in the abstract type. Of course, this will not work if the two components of one and two types are TKR-different, but then it doesn't make such sense to have a unified getter for them. Here is the expanded example:
module types
implicit none
public :: t1, one, two
type, abstract :: t1
integer :: ivalue = 0
contains
procedure(t1_print), deferred :: print
procedure(t1_get_val), deferred :: get_val
end type t1
type, extends(t1) :: one
integer :: i_t1 = 42
contains
procedure :: print => one_print
procedure :: get_val => one_get_val
end type one
type, extends(t1) :: two
integer :: i_t2 = 43
contains
procedure :: print => two_print
procedure :: get_val => two_get_val
end type two
abstract interface
subroutine t1_print (this)
import
class(t1), intent(in) :: this
end subroutine t1_print
end interface
abstract interface
function t1_get_val (this) result (val)
import
class(t1), intent(in) :: this
integer :: val
end function t1_get_val
end interface
contains
subroutine one_print (this)
class(one), intent(in) :: this
print *, "Type one!"
end subroutine one_print
subroutine two_print (this)
class(two), intent(in) :: this
print *, "Type two!"
end subroutine two_print
function one_get_val (this) result (val)
class(one), intent(in) :: this
integer :: val
val = this%i_t1
end function one_get_val
function two_get_val (this) result (val)
class(two), intent(in) :: this
integer :: val
val = this%i_t2
end function two_get_val
end module types
program main
use types
implicit none
class(t1), allocatable :: foo
integer :: x, val
x = 2
select case (x)
case (1)
allocate (one :: foo)
case (2)
allocate (two :: foo)
case default
print *, "Error!"
end select
call foo%print ()
val = foo%get_val ()
print *, "val = ", val
end program main
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you again for more insight on this topic. Going off your example, I have a deferred procedure in my code to initialize the object. However, I will need the object to be an array of rank 1. When I modified the code to include dimension(:) where necessary, I get the following error:
error #8263: The passed-object dummy argument must be a scalar, nonpointer, nonallocatable dummy data object.
Using your example, I need foo to be
class(t1), allocatable, dimension(:) :: foo
Does the capability exist to have a deferred, initializing subroutine that will size the class object?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The code also works for
class(t1), allocatable, dimension(:) :: foo
and then e.g.
allocate (one :: foo(3))
and
do i = 1, 3 foo(i)%print () foo(i)%get_value () end do
Maybe you just consult one of the standard textbooks on Modern Fortran like Metcalfe, Cohen, Reid: "Modern Fortran Explained" or Jeanne Adams et al., "The Fortran 2003 Handbook".
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page