- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						I was trying to put an example together for a different problem and frankly got rather lost. So the attached makes very little sense, but it does cause a "fortcom: Fatal: .... (C00000005)" with 11.1.051.
Thanks,
IanH
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
Thanks,
IanH
Link Copied
		18 Replies
	
		
		
			
			
			
					
	
			- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						
Thanks - we'll take a look.
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						Very amusing... Escalated as issue DPD200141584. Both the calls to SET and USE are required to trigger the error, at least in this example. As you discovered, renaming USE to something else avoids the error.
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						
Another example attached (TryingToBeGeneric.f90) that gives an ICE with 11.1.051, which is probably unrelated to the previous one (message is "internal error: Please visit..."). 
While I've still got your attention... some F2003 polymorphism questions. This example (TryingToBeSpecificInAnAbstractWay.f90), when compiled with /check:all /warn:all /traceback, compiles, but then dies with an access violation, apparently at the ALLOCATE statement (the very first executable statement of the program proper!). This is a bit disappointing even for me - normally I make it at least ten lines in before everything's gone to pot - so any hints appreciated. Without /check:all /warn:all the crash pops up later.
Second question is around type compatibility of polymorphic dummy and actual arguments. The previous example has an abstract "base" type (AbstractType) and then a "concrete" extension of that type (AbstractTypeExt). There is then a procedure (not a type bound one) that has a "CLASS(AbstractType), INTENT(IN) :: obj" dummy. Quoting from the good PDF... "A polymorphic entity that is not an unlimited polymorphic entity is type compatible with entities of the same type or any of its extensions". As a result, I would have thought that I could poke in a TYPE(AbstractTypeExt) actual argument to that procedure (see commented out statements with !xxx). Under 11.1.51 that doesn't "match" and I have to use the obj%parent syntax to get things to work. Is that just a IVF F2003 implementation-not-there-yet-issue, or an IanH F2003 standard-still-beyond-your-comprehension issue?
Thanks,
IanH
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
While I've still got your attention... some F2003 polymorphism questions. This example (TryingToBeSpecificInAnAbstractWay.f90), when compiled with /check:all /warn:all /traceback, compiles, but then dies with an access violation, apparently at the ALLOCATE statement (the very first executable statement of the program proper!). This is a bit disappointing even for me - normally I make it at least ten lines in before everything's gone to pot - so any hints appreciated. Without /check:all /warn:all the crash pops up later.
Second question is around type compatibility of polymorphic dummy and actual arguments. The previous example has an abstract "base" type (AbstractType) and then a "concrete" extension of that type (AbstractTypeExt). There is then a procedure (not a type bound one) that has a "CLASS(AbstractType), INTENT(IN) :: obj" dummy. Quoting from the good PDF... "A polymorphic entity that is not an unlimited polymorphic entity is type compatible with entities of the same type or any of its extensions". As a result, I would have thought that I could poke in a TYPE(AbstractTypeExt) actual argument to that procedure (see commented out statements with !xxx). Under 11.1.51 that doesn't "match" and I have to use the obj%parent syntax to get things to work. Is that just a IVF F2003 implementation-not-there-yet-issue, or an IanH F2003 standard-still-beyond-your-comprehension issue?
Thanks,
IanH
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						
Ian,
Thanks for these additional items. It will take me a few days to sort out the issues and get back to you. The issue you describe about type matching sounds familiar and may be a bug already reported but not yet fixed. I'll check into it.
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
Thanks for these additional items. It will take me a few days to sort out the issues and get back to you. The issue you describe about type matching sounds familiar and may be a bug already reported but not yet fixed. I'll check into it.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						
TryingToBeGeneric is issue DPD200141626. TryingToBeSpecificInAnAbstractWay is issue DPD200141627.
The other problem will have to wait till next week.
I really appreciate your reporting these problems to us and wish that you weren't encountering so many issues!
		
		
	
	
	
The other problem will have to wait till next week.
I really appreciate your reporting these problems to us and wish that you weren't encountering so many issues!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						
Thanks for the assistance. 
Another F2003/11.1.051 question - does a user defined type with an allocatable component have the component de-allocated on entry to a procedure when its associated with a dummy arg that's declared CLASS(xxx), INTENT(OUT)? I know it does for TYPE(xxx), INTENT(OUT), but the behaviour when the dummy is declared with class seems to be different. With the attached I get told off at runtime for trying to allocate something that's already allocated.
I've finished my conversion-from-C++ learning exercise, back to lurking.
Ta,
IanH
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
Another F2003/11.1.051 question - does a user defined type with an allocatable component have the component de-allocated on entry to a procedure when its associated with a dummy arg that's declared CLASS(xxx), INTENT(OUT)? I know it does for TYPE(xxx), INTENT(OUT), but the behaviour when the dummy is declared with class seems to be different. With the attached I get told off at runtime for trying to allocate something that's already allocated.
I've finished my conversion-from-C++ learning exercise, back to lurking.
Ta,
IanH
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Ian,
Yes, the deallocation of components of a polymorphic type should be done for INTENT(OUT) arguments. A similar issue arises for local polymorphic variables with allocatable components on routine exit. Our compiler completely misses these cases. The developers knew about the second but had not yet considered the first - that is our issue DPD200141685.
Unfortunately, we have to invent some new mechanisms in the compiler to deal with this and I don't expect it to be fixed soon. A workaround is to do a SELECT TYPE, test for allocation and deallocate manually, but you shouldn't have to do that.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
We have decided that TryingToBeSpecificInAnAbstractWay is not legal Fortran. In the future, the compiler will give:
error #8307: If the rightmost part-name is of abstract type, data-ref shall be polymorphic [ABSTRACTTYPE]
We had quite a lively argument about this and even went so far as to consult other standards committee members to see what they thought of it. We note that the NAG compiler also gives an access violation for this same program.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Quoting - Steve Lionel (Intel)
We have decided that TryingToBeSpecificInAnAbstractWay is not legal Fortran. In the future, the compiler will give:
error #8307: If the rightmost part-name is of abstract type, data-ref shall be polymorphic [ABSTRACTTYPE]
We had quite a lively argument about this and even went so far as to consult other standards committee members to see what they thought of it. We note that the NAG compiler also gives an access violation for this same program.
Thanks for the response.
I see in the standard where that restriction comes from, but I can't see where that restriction is being violated in the code. Could you (or someone else with F2003 experience) please elaborate?
Possibly unrelated to your point, but you don't need abstract types to cause an access violation in ALLOCATE - see snippet below (with 11.1.54, seems to need /warn:all at the command line to see the problem, which is odd in itself in that a compile time diagnostic option triggers a run time error):
[plain]MODULE ClassAllocateMod
  IMPLICIT NONE
  PRIVATE  
  ! Concrete class with single bound proc
  TYPE, PUBLIC :: Base
    INTEGER base_comp
  CONTAINS
    PROCEDURE :: proc => base_proc
  END TYPE Base  
CONTAINS
  SUBROUTINE base_proc(this)  
    CLASS(Base), INTENT(IN) :: this
    !****
    WRITE (*, "(A)") 'Hello!'
  END SUBROUTINE base_proc
END MODULE ClassAllocateMod
PROGRAM ClassAllocate
  USE ClassAllocateMod
  IMPLICIT NONE
  CLASS(Base), ALLOCATABLE :: obj
  !****
  ALLOCATE(obj)   ! boom
  CALL obj%proc
END PROGRAM ClassAllocate
[/plain]
I wondered whether it was having the ALLOCATE as an executable statement in at PROGRAM level that was the problem, bit when I added the following lines of code to the same source file I get a "catastrophic error" (again, needs /warn:all to see the problem).
[plain]MODULE ICE_machine
  USE ClassAllocateMod
  IMPLICIT NONE
CONTAINS
  SUBROUTINE Util
    CLASS(Base), ALLOCATABLE :: obj
    !****
    ALLOCATE(obj)
   CALL obj%proc
  END SUBROUTINE Util
END MODULE ICE_machine
[/plain]
Thanks for any pointers. Note that I'm not at all familar with F2003 OOP, so apologies if these learning exercises throws out a few red herrings which are programmer errors rather than compiler issues. IanH
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It's /warn:interface that is causing the problem for these last two. It's not supposed to change the generated code, but sometimes, due to a bug, it does. Both of them are ok in our latest internal sources, but I can reproduce the error in the released compiler.
The issue with TryingToBeSpecificInAnAbstractWay comes down to the interpretation of b%AbstractType as an actual argument. AbstractType is the parent type of AbstractTypeExt where b is CLASS(AbstractTypeExt). The question is: "what is the 'data-ref' here"? Is it b or is it b%AbstractType? Initially, I claimed it was b, which is polymorphic, but others said it was the whole thing, b%AbstractType, which if you look at it in the larger context of the actual argument is true.
To be honest, I still find myself confused about this, but enough "experts" agreed that it was an error that I'll go along with it. This polymorphic stuff still gives me a headache (and still gives the compiler indigestion at times.)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						Ok thanks - I see where the violation is now.  I was also just considering b on its own to be "data-ref", and not the whole thing.  I guess that means that you can never reference the parent component (only) of an object if the parent type is abstract.
If that's what the std says, then so be it, but one downside to that is how to access parent type bound procedures from within an overriden procedure in an extension, if that parent type is abstract (say it has a mix of deferred and not-deferred procedures - and we want to call a not-deferred procedure from an override of it). The call statement (in the case of a subroutine) looking something like "CALL data-ref % binding-name".
Practical application of this is in GUI type call-backs, where a subclassed window may want to add to the message processing behaviour of its superclass window - in some frameworks you do this all the time on Win32 when handling WM_INITDLG like messages. For what its worth, 11.1.54 does allow you to do this: CallingBackToBase.f90
I guess the "work around" (which is probably what you are supposed to do in the first place, but I'm being influenced by a C++ background) is to always provide a do-nothing procedure instead of a deferred binding in the parent class so that it's not abstract, or push all the deferred bindings up a further inheritance level, so that interface and implementation are strictly separate.
I've seen a few more oddities with respect to the wrong type bound procedure being called - these may have been reported by others: OverrideBinding.f90
Even with all these "quirks", the OOP stuff that is now in ivf is already helping to improve the structure of some of my code.
Thanks,
IanH
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
If that's what the std says, then so be it, but one downside to that is how to access parent type bound procedures from within an overriden procedure in an extension, if that parent type is abstract (say it has a mix of deferred and not-deferred procedures - and we want to call a not-deferred procedure from an override of it). The call statement (in the case of a subroutine) looking something like "CALL data-ref % binding-name".
Practical application of this is in GUI type call-backs, where a subclassed window may want to add to the message processing behaviour of its superclass window - in some frameworks you do this all the time on Win32 when handling WM_INITDLG like messages. For what its worth, 11.1.54 does allow you to do this: CallingBackToBase.f90
I guess the "work around" (which is probably what you are supposed to do in the first place, but I'm being influenced by a C++ background) is to always provide a do-nothing procedure instead of a deferred binding in the parent class so that it's not abstract, or push all the deferred bindings up a further inheritance level, so that interface and implementation are strictly separate.
I've seen a few more oddities with respect to the wrong type bound procedure being called - these may have been reported by others: OverrideBinding.f90
Even with all these "quirks", the OOP stuff that is now in ivf is already helping to improve the structure of some of my code.
Thanks,
IanH
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						The compiler error regarding the routine named USE is fixed in our sources. I expect the fix to appear in 11.1 Update 5, scheduled for mid-February. I'll post here when it is available.
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						The fix for "routine name USE" won't be in Update 5 - it should be in Update 6 (April).
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						And indeed it is.
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						Sorry to bump this old thread, but I am running into the same problem and I can't quite understand what is it that I am doing wrong.
		
		
	
	
	
I am trying to implement a factory pattern in OO Fortran, and took the example given in the Fortran Wiki.
[fortran]module factory_pattern
!Since there are different types of database connections, let us create an abstract
!class to encapsulate all sorts of connections. For simplicity, each connection has
!only one procedure, description, which prints out what type of connection it itself is.
!Every derived type must implement this subroutine (hence, deferred).
type, abstract :: Connection
    contains
    procedure(generic_desc), deferred, pass(self) :: description
end type Connection
interface
    subroutine generic_desc(self)
        import :: Connection
        class(Connection),intent(IN) :: self
    end subroutine generic_desc
end interface
!We are now ready to create concrete connections derived from the
!above type. Lets create two of them, Oracle and MySQL .
!! An Oracle connection
type, extends(Connection) :: OracleConnection
    contains
        procedure, pass(self) :: description => oracle_desc
end type OracleConnection
!! A MySQL connection
type, extends(Connection) :: MySQLConnection
    contains
        procedure, pass(self) :: description => mysql_desc
end type MySQLConnection
type CFactory
    private
        character(len=20) :: factory_type               !! Descriptive name for database
        class(Connection), pointer :: connection_type   !! Which type of database ?
    contains                                            !! Note 'class' not 'type' !
        procedure :: init                               !! Constructor
        procedure :: create_connection                  !! Connect to database
        procedure :: final                              !! Destructor
end type CFactory
contains
!The type-bound procedures are simple. They just print out who they are:
    subroutine oracle_desc(self)
        class(OracleConnection), intent(in) :: self
        write(*,'(A)') "You are now connected with Oracle"
    end subroutine oracle_desc
    subroutine mysql_desc(self)
        class(MySQLConnection), intent(in) :: self
        write(*,'(A)')  "You are now connected with MySQL"
    end subroutine mysql_desc
!Now comes the crucial part. How do we implement our factory ?
!The constructor simply initializes the private variables, including pointers.
!Well be allocating memory to our polymorphic class pointer, so the destructor has to free the memory.
    subroutine init(self, string)
        class(CFactory), intent(inout) :: self
        character(len=*), intent(in) :: string
        self%factory_type = trim(string)
        self%connection_type => null()            !! pointer is nullified
    end subroutine init
    subroutine final(self)
        class(CFactory), intent(inout) :: self
        deallocate(self%connection_type)          !! Free the memory
        nullify(self%connection_type)
    end subroutine final
!To create a connection, we simply search through (if-else) all the possible list
!of connections which our factory must be able to produce. This is the core part.
!A factory hides away how different objects are created.
    function create_connection(self)  result(ptr)
        class(CFactory) :: self
        class(Connection), pointer :: ptr
        if(self%factory_type == "Oracle") then
            if(associated(self%connection_type))   deallocate(self%connection_type)
            allocate(OracleConnection :: self%connection_type)
            ptr => self%connection_type
        elseif(self%factory_type == "MySQL") then
            if(associated(self%connection_type))   deallocate(self%connection_type)
            allocate(MySQLConnection :: self%connection_type)
            ptr => self%connection_type
        end if
    end function create_connection
end module factory_pattern
!So there you are. A pointer to the created object is returned.
!If the connection already exists and a new connection is being requested, we do so.
!We remove (_deallocate_) the old connection and freshly allocate a new connection.
!The client program could be like this:
program main
use factory_pattern
implicit none
    class(CFactory),allocatable :: factory
    class(Connection), pointer :: db_connect => null()
    allocate(factory)
    call factory%init("Oracle")
    db_connect => factory%create_connection()   !! Create Oracle DB
    call db_connect%description()
    !! The same factory can be used to create different connections
    call factory%init("MySQL")                  !! Create MySQL DB
    !! 'connect' is a 'class' pointer. So can be used for either Oracle or MySQL
    db_connect => factory%create_connection()
    call db_connect%description()
    call factory%final()        ! Destroy the object
end program main
[/fortran] I fixed a little the interface, and everything compiles up to the creation lines where I get the "data-ref" problem:
[bash]testFactory.f90(113): error #8307: If the rightmost part-name is of abstract type, data-ref shall be polymorphic   [CREATE_CONNECTION]
    db_connect => factory%create_connection()   !! Create Oracle DB
--------------------------^
testFactory.f90(120): error #8307: If the rightmost part-name is of abstract type, data-ref shall be polymorphic   [CREATE_CONNECTION]
    db_connect => factory%create_connection()
[/bash] I kind of see that create_connection() returns an abstract class and not a polymorphic object, thus the problem (even though I do not understand all the details). My question is: how can I have then a factory that returns a child from a parent class (which has the consistent interface), with the clients not knowing they received a child class?
I checked that, indeed, if Connection is a concrete class instead of an abstract one, the program runs ok. However for this I had to writethe do-nothing procedures that the children classes override. How can I NOT have to do this? It is kind of the point of having an abstract class and procedures, right?
					
				
			
			
				
			
			
			
			
			
			
			
		- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						I reckon this is a compiler bug. The data-ref (which has a single part-name) "factory" isn't abstract and it is polymorphic, so the error message is doubly wrong. "create_connection" is a binding-name for a procedure that returns a pointer to an abstract type, but I don't think that's relevant.
That aside, the example from the wiki's is a bit atypical of a "factory pattern" though (the following is all a bit subjective and depends on the intent of the code). There's not much point to a factory that can only have one entity extant at a time - the factory entity might as well be the connection entity. Classically CFactory would also be abstract, and you'd have separate concrete factory types for each type of connection - avoiding the big if-else construct in init.
More typical in a fortran sense would also be that the create_connection would return the object via an intent(out) argument which, if you weren't worried about the single-entity-at-once aspect, would be allocatable rather than a pointer.
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
That aside, the example from the wiki's is a bit atypical of a "factory pattern" though (the following is all a bit subjective and depends on the intent of the code). There's not much point to a factory that can only have one entity extant at a time - the factory entity might as well be the connection entity. Classically CFactory would also be abstract, and you'd have separate concrete factory types for each type of connection - avoiding the big if-else construct in init.
More typical in a fortran sense would also be that the create_connection would return the object via an intent(out) argument which, if you weren't worried about the single-entity-at-once aspect, would be allocatable rather than a pointer.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						Thank you and thank you.
		
		
	
	
	
I thought the same about the data-ref problem, but I was not sure because the whole issue is still confusing for me. I hope somebody from Intel can weigh in on this, and if it is a problem I can file it as a bug in premier.
On the factory pattern, I agree. Abstract factories are more versatile, but I was not even sure on how to implement it given that already the concrete factory does not compile. I understood this example, and it compiles in gfortran, so I made the post with it.
I kind of do not like intent(out) arguments [prefer functions that return things] but I see your point and it is a good idea, I didn't think of that. Performance-wise, it might be even better to have an allocatable than a pointer, right?
					
				
			
			
				
			
			
			
			
			
			
			
		- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
			
				
					
					
						Issue DPD200141685, involving the deallocation of components of a polymorphic type that is INTENT(OUT), will be fixed in a future version (not an update to 12.0.) As I noted earlier, it requires extensive work, but it will get fixed.
					
				
			
			
				
			
			
			
			
			
			
			
		
		
		
	
	
	
 
					
				
				
			
		
					
					Reply
					
						
	
		
				
				
				
					
						
					
				
					
				
				
				
				
			
			Topic Options
			
				
					
	
			
		
	- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page
