Edit (I now describe the whole story from where it started, i.e. a weird crash instead of only the compile error):
First off: the problem at hand is very, very complicated to describe.
I get a weird crash in my program but I cannot reproduce it in a standalone program.
It looks something like this (I hope I got the analogy to my original program right):
libc.so.6!__memmove_avx_unaligned_erms (Unknown Source:0)
x.so!mod_test::new_b(Type t_pointer s_pointer) (mod_test.f90:...)
The code is something like this:
MODULE MOD_TEST
TYPE T_COMMON
INTEGER :: a = 7
END TYPE T_COMMON
TYPE T_INFO
INTEGER :: a = 0
TYPE(T_COMMON) :: s_common
END TYPE T_INFO
TYPE T_POINTER
INTEGER :: x = 5
INTEGER, DIMENSION(:), POINTER :: somearray => NULL()
END TYPE T_POINTER
TYPE T_A
TYPE(T_COMMON), PRIVATE :: s_common
TYPE(T_INFO) :: s_info
TYPE(T_POINTER), POINTER :: s_pointer => NULL()
END TYPE T_A
TYPE T_CONTAINER
TYPE(T_A), DIMENSION(:), POINTER :: s_a => NULL()
END TYPE T_CONTAINER
TYPE T_B
TYPE(T_INFO) :: s_info
TYPE(T_A), POINTER :: s_a => NULL()
END TYPE T_B
INTERFACE T_A
MODULE PROCEDURE :: NEW_A
END INTERFACE T_A
INTERFACE T_B
MODULE PROCEDURE :: NEW_B
END INTERFACE T_B
CONTAINS
FUNCTION NEW_A(s_pointer) RESULT(self)
IMPLICIT NONE
TYPE(T_A) :: self
TYPE(T_POINTER), TARGET :: s_pointer
self%s_pointer => s_pointer
END FUNCTION NEW_A
FUNCTION NEW_B(s_pointer) RESULT(self)
IMPLICIT NONE
TYPE(T_B) :: self
TYPE(T_POINTER), TARGET :: s_pointer
ALLOCATE(self%s_a)
self%s_a = T_A(s_pointer)
END FUNCTION NEW_B
END MODULE MOD_TEST
PROGRAM testprog
USE MOD_TEST
TYPE(T_POINTER), POINTER :: s_pointer
TYPE(T_CONTAINER), POINTER :: s_container
TYPE(T_A), DIMENSION(:), POINTER :: s_a
TYPE(T_B), POINTER :: s_b
! that struct shall only be pointed to in s_a
ALLOCATE(s_pointer)
ALLOCATE(s_container)
ALLOCATE(s_container%s_a(3))
s_container%s_a(1) = T_A(s_pointer)
ALLOCATE(s_b)
s_b = T_B(s_pointer)
WRITE(*,*) s_container%s_a(1)%s_pointer%x
END PROGRAM testprog
Now I tried using the POINTER
attribute for s_pointer in the constructors NEW_A
and NEW_B
but then I got an error compiling my program that I can’t figure out but also cannot reproduce in a standalone example:
s_a(1) = T_A(s_pointer)
1
Error: No initializer for component ‘s_info’ given in the structure constructor at (1)
N.B.: s_a
is actually an allocated pointer in some containing structure but it does not change the outcome of the test program.
I read something about types containing PRIVATE
members but I also removed that attribute for that member in T_A
for testing and the error was still thrown. T_INFO
contains no PRIVATE
components either.
Edit 2: One more confusing thing: it seems to matter in which order in the types A and B I put the pointer members (s_a
being allocated in T_B
and s_pointer
pointing to the externally allocated structure) as I get different compiler messages as to which types are missing an initializer and it seems that somehow the type (memory) alignment is messed up.
I know it’s hard to diagnose what triggers that error with no minimal example that shows the problem but could you probably search your minds and give me some guesses as to what I could be doing wrong? I’m quite desperate )o: