Crash/No initializer for component given in the structure constructor

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:

It seems I’ve figured it out; I removed TARGET and POINTER attributes from s_pointer in NEW_B and used the TARGET attribute for s_pointer in NEW_A.

Sorry for being late on this, but in my experience TARGET means that a standard variable needs to have an address that would be available for a POINTER variable to point to… Generally meaningless as almost all variables will work when the right type of pointer is set to them… But an example of it’s use according to my memory is;

integer, target :: i
integer, pointer :: pointstoi

i=7
pointstoi => i
print *, pointstoi

Which should print 7 to the display.

I’m also confused about your setting pointers for allocatable arrays as pointers to arrays. Have I been doing that wrong? I don’t think so…

I don’t use OOP unless I completely need it, so I wouldn’t have bothered with the NEW_A. NEW_B simply because your so good at setting the structures and their defaults in the first place. I would rather create a;

function A_Factory(a,b,c,d,e,f) return(new_a)
  implicit none
  integer, intent(in) :: a,b,c,d,e,f
  type(T_AH), pointer :: new_a

  allocate(new_a)
  ...
  return(new_a)
end function

and use it;

my_a => A_Factory(a,b,c,d,e,f)

because that sets things that aren’t just the defaults and I can write it how I like it. OOP gets in my way if I let it so I don’t.

Just my 10cents…

Hope you enjoy…

To be honest, I must say that I’m not 100% sure about the need for the TARGET attribute in NEW_A anymore but at least my code works now, both, at compile and at runtime. As for the pointers: it’s complicated. I need pointers to one allocated portion of memory in several structures (from which I instantiate objects) so I don’t have to pass the respective variable to every PROCEDURE that requires access to it all the time. The need for that might be a consequence of the way the code has been structured along the years.

The main reasons I’m using OOP is that I have PROCEDUREs that access the members of a structure and do stuff with those. And while I could use separate SUBROUTINEs or FUNCTIONs for that, for me, it is just a far more logical grouping, as opposed to passing the object to some unbound routine dangling around.

And the second thing being transparent memory management using constructors and FINAL routines where I can allocate, set up and clean up stuff belonging to objects and sub-objects (because of the cascading invocation constructors of FINAL routines). Actually, the large code base I’m working on mainly uses procedural programming and believe me – it’s a mess that has grown over the years we were not allowed to use any features beyond F95. So where I see significant advantage, I’m introducing OOP to clean things up with old code (that makes stuff so much easier in my case) and use OOP consistently for new code.

The code also uses lots of global variables which are accessed from routines all over the place, so I’m moving those to the classes where they naturally belong to. Makes side effects much less likely.

Inheritance is not (yet) a thing I found the need for, but maybe just because the code has grown so convoluted over time that I have a hard time thinking out of the box for introducing a logical structure using that feature.

So far my apologetics for me using OOP (o;