Pointer to pointer - ALLOCATE - Undefined reference

Hi,

I am currently working on a question of migration from Fortran 90 to Fortran 2003, where a pointer p1 containing itself a pointer p2 generates when calling the statement ALLOCATE the error message undefined reference for the pointer p2.

The two pointers are declared as follows:

Within the struct_ames.f90 file:

type(p1), dimension(:), pointer::p1=>null()

Within the p1.f90 file:

CHARACTER(LEN=50),DIMENSION(:,:),pointer:: p2=>null()

Would you know how to solve this problem?

Thanks for your help !

Welcome to the discourse @dev, could you post a Minimal Working Example (MWE) of your problem

We need to see more code, in particular the definition of the p1 derived type, and the allocate statement that fails.

Thanks for your answer.

Here are the relevant details :
The undefined reference return is for the following statement:
ALLOCATE(output_ames%grids_ames(nbfiles))

In the data structure:
type STRUCT_AMES
CHARACTER(LEN=12) :: string
type(grid_ames), dimension(:), pointer::grids_ames
type(head_ames) :: head
end type STRUCT_AMES

Note the declaration of the variable grids_ames as a pointer of type grid_ames.

The grid_ames type itself having the pointer arrMeasurements:
type GRID_AMES
CHARACTER(LEN=14) :: datemeasurement
CHARACTER(LEN=12) :: hour
CHARACTER(LEN=4) :: year
CHARACTER(LEN=2) :: month
CHARACTER(LEN=10) :: cmois
CHARACTER(LEN=2) :: day
CHARACTER(LEN=2) :: hour
CHARACTER(LEN=2) :: minute
CHARACTER(LEN=2) :: second
REAL, DIMENSION(:,:),pointer:: arrMeasurements=>null()
end type GRID_AMES

The error message obtained during compilation is as follows:
pgf90 -o treat_files_list functions_mod.o head_ames_mod.o grid_ames_mod.o struct_ames_mod.o lidar_mod.o treat_files_list.o
/usr/bin/ld: treat_files_list.o: in function MAIN_': treat_files_list.f90:154: undefined reference to grid_ames_mod___grid_ames__td_’
/usr/bin/ld: treat_files_list.f90:154: undefined reference to `grid_ames_mod___grid_ames__td_’
make: *** [Makefile:19: treat_files_list] Error 2

I tried compiling (with gfortran and ifort) and running something from these pieces of code, and didn’t encounter any error (I just had to correct a few things like the double declaration of hour, use an arbitrary nbfiles, and remove the type(head_ames) declaration as I don’t have the definition).

I think you really need to provide a Minimal Working Example (actually not working in your case) that reproduces the problem.

PS: please use the code formatting features (using single or triple backticks)

Thanks for your answer.

Here is the detail for treat_file_list.f90 :

PROGRAM treat_files_list

USE fonctions_mod
USE grid_ames_mod
USE head_ames_mod
USE struct_ames_mod
USE lidar_mod

IMPLICIT NONE

CHARACTER(LEN=300) :: temp_string, temp_string2
CHARACTER(LEN=41) :: temp_string4
CHARACTER(LEN=28) :: temp_string5
CHARACTER(LEN=14) :: temp_string6
CHARACTER(LEN=120) :: temp_string80
CHARACTER(LEN=250) :: filein,list_files,tmp_list
CHARACTER(LEN=100) :: cmoismin,cmoismax,cheuremin,cheuremax ,temp_string3
CHARACTER(LEN=100) :: rep_data,rep_so,chaine,chaine2,rep_lo,file_lo
CHARACTER(LEN=50) :: link
CHARACTER(LEN=8) :: tdate
CHARACTER(LEN=5) :: coltemp,col1
CHARACTER(LEN=7) :: col2, col5, col6, col8
CHARACTER(LEN=7) :: col10,col9
CHARACTER(LEN=10) :: col11,col7
CHARACTER(LEN=4) :: mois,annee
CHARACTER(LEN=6) :: col4
CHARACTER(LEN=8) :: col3
CHARACTER(LEN=10) :: ttime
CHARACTER(LEN=5) :: tzone
INTEGER, DIMENSION(8) :: tvalues
CHARACTER(LEN=200) :: screen,line,line2
INTEGER :: i,j,indice,idatemesure,idatemesuremax,idatemesuremin,nblcomment,ifdatemesure
INTEGER :: unit,ios,ios2,iosres,debug,nbfile,ios3,lecture,ulog,nbfiles,ifile,temp_int,temp_int2
type(grid_ames) :: sortie_asc,temp_ames
type(struct_ames) :: sortie_ames
LOGICAL :: retour
REAL :: temp_real

COMMON screen,rep_so,debug
COMMON rep_lo,file_lo,ulog

!lecture du fichier temporaire devant contenir la liste des fichiers de donnees a traiter
call getarg(1,tmp_list)
nbfiles=0
debug=1
ifile=0

!ouverture liste des fichiers asc a traiter
OPEN( UNIT=2, &
FILE=tmp_list, &
FORM=“formatted”, &
ACCESS=“sequential”, &
STATUS=“old”, &
ACTION=“read”, &
POSITION=“rewind”, &
IOSTAT=ios3 )

READ(2,IOSTAT=ios3, FMT=‘(A)’) filein

if (ios3 /= 0 ) then
screen="Impossible d ouvrir le fichier temporaire des fichiers de donnees a traiter : "//adjustl(trim(filein))
retour=printl()
STOP
endif

rep_data=filein
screen="DATA DIRECTORY : "//rep_data
retour=printl()

mois=“”
annee=“”

READ(2,IOSTAT=ios3, FMT=‘(I)’) nbfiles
READ(2,IOSTAT=ios3,FMT=‘(I)’) debug
READ(2,IOSTAT=ios3,FMT=) mois
READ(2,IOSTAT=ios3,FMT=
) annee

!creation du fichier de sortie ames
OPEN( UNIT=14, &
FILE=“ohto”//trim(adjustl(annee(3:4)))//trim(adjustl(mois))//“.anl”, &
FORM=“formatted”, &
ACCESS=“sequential”, &
STATUS=“unknown”, &
ACTION=“readwrite”, &
POSITION=“rewind”, &
IOSTAT=iosres )

    if (iosres /= 0 ) then
            screen="Impossible de creer le fichier des grilles"
            retour=printl()
            STOP
    endif

READ(2,IOSTAT=ios3, FMT=‘(A)’) filein

ALLOCATE(sortie_ames%grids_ames(nbfiles))

Actually, the compilation is allowed with pgf90 13.10 but not with pgf90 21.9.

`PROGRAM treat_files_list

USE fonctions_mod
USE grid_ames_mod
USE head_ames_mod
USE struct_ames_mod
USE lidar_mod

IMPLICIT NONE

CHARACTER(LEN=300) :: temp_string, temp_string2
CHARACTER(LEN=41) :: temp_string4
CHARACTER(LEN=28) :: temp_string5
CHARACTER(LEN=14) :: temp_string6
CHARACTER(LEN=120) :: temp_string80
CHARACTER(LEN=250) :: filein,list_files,tmp_list
CHARACTER(LEN=100) :: cmoismin,cmoismax,cheuremin,cheuremax ,temp_string3
CHARACTER(LEN=100) :: rep_data,rep_so,chaine,chaine2,rep_lo,file_lo
CHARACTER(LEN=50) :: link
CHARACTER(LEN=8) :: tdate
CHARACTER(LEN=5) :: coltemp,col1
CHARACTER(LEN=7) :: col2, col5, col6, col8
CHARACTER(LEN=7) :: col10,col9
CHARACTER(LEN=10) :: col11,col7
CHARACTER(LEN=4) :: mois,annee
CHARACTER(LEN=6) :: col4
CHARACTER(LEN=8) :: col3
CHARACTER(LEN=10) :: ttime
CHARACTER(LEN=5) :: tzone
INTEGER, DIMENSION(8) :: tvalues
CHARACTER(LEN=200) :: screen,line,line2
INTEGER :: i,j,indice,idatemesure,idatemesuremax,idatemesuremin,nblcomment,ifdatemesure
INTEGER :: unit,ios,ios2,iosres,debug,nbfile,ios3,lecture,ulog,nbfiles,ifile,temp_int,temp_int2
type(grid_ames) :: sortie_asc,temp_ames
type(struct_ames) :: sortie_ames
LOGICAL :: retour
REAL :: temp_real

COMMON screen,rep_so,debug
COMMON rep_lo,file_lo,ulog

!lecture du fichier temporaire devant contenir la liste des fichiers de donnees a traiter
call getarg(1,tmp_list)
nbfiles=0
debug=1
ifile=0

!ouverture liste des fichiers asc a traiter
OPEN( UNIT=2, &
FILE=tmp_list, &
FORM=“formatted”, &
ACCESS=“sequential”, &
STATUS=“old”, &
ACTION=“read”, &
POSITION=“rewind”, &
IOSTAT=ios3 )

READ(2,IOSTAT=ios3, FMT=‘(A)’) filein

if (ios3 /= 0 ) then
screen="Impossible d ouvrir le fichier temporaire des fichiers de donnees a traiter : "//adjustl(trim(filein))
retour=printl()
STOP
endif

rep_data=filein
screen="DATA DIRECTORY : "//rep_data
retour=printl()

mois=“”
annee=“”

READ(2,IOSTAT=ios3, FMT=‘(I)’) nbfiles
READ(2,IOSTAT=ios3,FMT=‘(I)’) debug
READ(2,IOSTAT=ios3,FMT=) mois
READ(2,IOSTAT=ios3,FMT=
) annee

!creation du fichier de sortie ames
OPEN( UNIT=14, &
FILE=“ohto”//trim(adjustl(annee(3:4)))//trim(adjustl(mois))//“.anl”, &
FORM=“formatted”, &
ACCESS=“sequential”, &
STATUS=“unknown”, &
ACTION=“readwrite”, &
POSITION=“rewind”, &
IOSTAT=iosres )

    if (iosres /= 0 ) then
            screen="Impossible de creer le fichier des grilles"
            retour=printl()
            STOP
    endif

READ(2,IOSTAT=ios3, FMT=‘(A)’) filein

ALLOCATE(sortie_ames%grids_ames(nbfiles))`

Actually compiling is working with pgf90 13.10 but not pgf90 21.9 :


USE fonctions_mod 
USE grid_ames_mod
USE head_ames_mod
USE struct_ames_mod
USE lidar_mod

IMPLICIT NONE

CHARACTER(LEN=300)				:: temp_string, temp_string2
CHARACTER(LEN=41)				:: temp_string4
CHARACTER(LEN=28)				:: temp_string5
CHARACTER(LEN=14)				:: temp_string6
CHARACTER(LEN=120)				:: temp_string80
CHARACTER(LEN=250)				:: filein,list_files,tmp_list
CHARACTER(LEN=100)				:: cmoismin,cmoismax,cheuremin,cheuremax ,temp_string3
CHARACTER(LEN=100)				:: rep_data,rep_so,chaine,chaine2,rep_lo,file_lo
CHARACTER(LEN=50)				:: link
CHARACTER(LEN=8)				:: tdate
CHARACTER(LEN=5)				:: coltemp,col1
CHARACTER(LEN=7)				:: col2, col5, col6, col8
CHARACTER(LEN=7)				:: col10,col9
CHARACTER(LEN=10)				:: col11,col7
CHARACTER(LEN=4)				:: mois,annee
CHARACTER(LEN=6)				:: col4 
CHARACTER(LEN=8)				:: col3 
CHARACTER(LEN=10)				:: ttime
CHARACTER(LEN=5)				:: tzone
INTEGER, DIMENSION(8)				:: tvalues
CHARACTER(LEN=200)				:: screen,line,line2 
INTEGER						:: i,j,indice,idatemesure,idatemesuremax,idatemesuremin,nblcomment,ifdatemesure
INTEGER 					:: unit,ios,ios2,iosres,debug,nbfile,ios3,lecture,ulog,nbfiles,ifile,temp_int,temp_int2
type(grid_ames)			                :: sortie_asc,temp_ames
type(struct_ames)		                :: sortie_ames
LOGICAL						:: retour
REAL						:: temp_real

COMMON                                                                  screen,rep_so,debug
COMMON                                                                  rep_lo,file_lo,ulog

!lecture du fichier temporaire devant contenir la liste des fichiers de donnees a traiter
call getarg(1,tmp_list)
nbfiles=0
debug=1
ifile=0

!ouverture liste des fichiers asc a traiter
OPEN(   UNIT=2, &
        FILE=tmp_list, &
        FORM="formatted", &
        ACCESS="sequential", &
        STATUS="old", &
        ACTION="read", &
        POSITION="rewind", &
        IOSTAT=ios3 )


READ(2,IOSTAT=ios3, FMT='(A)') filein 

if (ios3 /= 0 ) then
	screen="Impossible d ouvrir le fichier temporaire des fichiers de donnees a traiter : "//adjustl(trim(filein))
        retour=printl()
        STOP
endif

rep_data=filein
screen="DATA DIRECTORY : "//rep_data
retour=printl()

mois=""
annee=""

READ(2,IOSTAT=ios3, FMT='(I)') nbfiles
READ(2,IOSTAT=ios3,FMT='(I)') debug
READ(2,IOSTAT=ios3,FMT=*) mois 
READ(2,IOSTAT=ios3,FMT=*) annee

!creation du fichier de sortie ames
OPEN( UNIT=14, &
        FILE="ohto"//trim(adjustl(annee(3:4)))//trim(adjustl(mois))//".anl", &
        FORM="formatted", &
        ACCESS="sequential", &
        STATUS="unknown", &
        ACTION="readwrite", &
        POSITION="rewind", &
        IOSTAT=iosres )

        if (iosres /= 0 ) then
                screen="Impossible de creer le fichier des grilles"
                retour=printl()
                STOP
        endif


READ(2,IOSTAT=ios3, FMT='(A)') filein

ALLOCATE(sortie_ames%grids_ames(nbfiles))```

Actually compiling is working with pgf90 13.10 but not pgf90 21.9.


USE fonctions_mod 
USE grid_ames_mod
USE head_ames_mod
USE struct_ames_mod
USE lidar_mod

IMPLICIT NONE

CHARACTER(LEN=300)				:: temp_string, temp_string2
CHARACTER(LEN=41)				:: temp_string4
CHARACTER(LEN=28)				:: temp_string5
CHARACTER(LEN=14)				:: temp_string6
CHARACTER(LEN=120)				:: temp_string80
CHARACTER(LEN=250)				:: filein,list_files,tmp_list
CHARACTER(LEN=100)				:: cmoismin,cmoismax,cheuremin,cheuremax ,temp_string3
CHARACTER(LEN=100)				:: rep_data,rep_so,chaine,chaine2,rep_lo,file_lo
CHARACTER(LEN=50)				:: link
CHARACTER(LEN=8)				:: tdate
CHARACTER(LEN=5)				:: coltemp,col1
CHARACTER(LEN=7)				:: col2, col5, col6, col8
CHARACTER(LEN=7)				:: col10,col9
CHARACTER(LEN=10)				:: col11,col7
CHARACTER(LEN=4)				:: mois,annee
CHARACTER(LEN=6)				:: col4 
CHARACTER(LEN=8)				:: col3 
CHARACTER(LEN=10)				:: ttime
CHARACTER(LEN=5)				:: tzone
INTEGER, DIMENSION(8)				:: tvalues
CHARACTER(LEN=200)				:: screen,line,line2 
INTEGER						:: i,j,indice,idatemesure,idatemesuremax,idatemesuremin,nblcomment,ifdatemesure
INTEGER 					:: unit,ios,ios2,iosres,debug,nbfile,ios3,lecture,ulog,nbfiles,ifile,temp_int,temp_int2
type(grid_ames)			                :: sortie_asc,temp_ames
type(struct_ames)		                :: sortie_ames
LOGICAL						:: retour
REAL						:: temp_real

COMMON                                                                  screen,rep_so,debug
COMMON                                                                  rep_lo,file_lo,ulog

!lecture du fichier temporaire devant contenir la liste des fichiers de donnees a traiter
call getarg(1,tmp_list)
nbfiles=0
debug=1
ifile=0

!ouverture liste des fichiers asc a traiter
OPEN(   UNIT=2, &
        FILE=tmp_list, &
        FORM="formatted", &
        ACCESS="sequential", &
        STATUS="old", &
        ACTION="read", &
        POSITION="rewind", &
        IOSTAT=ios3 )


READ(2,IOSTAT=ios3, FMT='(A)') filein 

if (ios3 /= 0 ) then
	screen="Impossible d ouvrir le fichier temporaire des fichiers de donnees a traiter : "//adjustl(trim(filein))
        retour=printl()
        STOP
endif

rep_data=filein
screen="DATA DIRECTORY : "//rep_data
retour=printl()

mois=""
annee=""

READ(2,IOSTAT=ios3, FMT='(I)') nbfiles
READ(2,IOSTAT=ios3,FMT='(I)') debug
READ(2,IOSTAT=ios3,FMT=*) mois 
READ(2,IOSTAT=ios3,FMT=*) annee

!creation du fichier de sortie ames
OPEN( UNIT=14, &
        FILE="ohto"//trim(adjustl(annee(3:4)))//trim(adjustl(mois))//".anl", &
        FORM="formatted", &
        ACCESS="sequential", &
        STATUS="unknown", &
        ACTION="readwrite", &
        POSITION="rewind", &
        IOSTAT=iosres )

        if (iosres /= 0 ) then
                screen="Impossible de creer le fichier des grilles"
                retour=printl()
                STOP
        endif


READ(2,IOSTAT=ios3, FMT='(A)') filein

ALLOCATE(sortie_ames%grids_ames(nbfiles))```

PROGRAM treat_files_list

USE fonctions_mod
USE grid_ames_mod
USE head_ames_mod
USE struct_ames_mod
USE lidar_mod

IMPLICIT NONE

CHARACTER(LEN=300) :: temp_string, temp_string2
CHARACTER(LEN=41) :: temp_string4
CHARACTER(LEN=28) :: temp_string5
CHARACTER(LEN=14) :: temp_string6
CHARACTER(LEN=120) :: temp_string80
CHARACTER(LEN=250) :: filein,list_files,tmp_list
CHARACTER(LEN=100) :: cmoismin,cmoismax,cheuremin,cheuremax ,temp_string3
CHARACTER(LEN=100) :: rep_data,rep_so,chaine,chaine2,rep_lo,file_lo
CHARACTER(LEN=50) :: link
CHARACTER(LEN=8) :: tdate
CHARACTER(LEN=5) :: coltemp,col1
CHARACTER(LEN=7) :: col2, col5, col6, col8
CHARACTER(LEN=7) :: col10,col9
CHARACTER(LEN=10) :: col11,col7
CHARACTER(LEN=4) :: mois,annee
CHARACTER(LEN=6) :: col4
CHARACTER(LEN=8) :: col3
CHARACTER(LEN=10) :: ttime
CHARACTER(LEN=5) :: tzone
INTEGER, DIMENSION(8) :: tvalues
CHARACTER(LEN=200) :: screen,line,line2
INTEGER :: i,j,indice,idatemesure,idatemesuremax,idatemesuremin,nblcomment,ifdatemesure
INTEGER :: unit,ios,ios2,iosres,debug,nbfile,ios3,lecture,ulog,nbfiles,ifile,temp_int,temp_int2
type(grid_ames) :: sortie_asc,temp_ames
type(struct_ames) :: sortie_ames
LOGICAL :: retour
REAL :: temp_real

COMMON screen,rep_so,debug
COMMON rep_lo,file_lo,ulog

!lecture du fichier temporaire devant contenir la liste des fichiers de donnees a traiter
call getarg(1,tmp_list)
nbfiles=0
debug=1
ifile=0

!ouverture liste des fichiers asc a traiter
OPEN( UNIT=2, &
FILE=tmp_list, &
FORM=“formatted”, &
ACCESS=“sequential”, &
STATUS=“old”, &
ACTION=“read”, &
POSITION=“rewind”, &
IOSTAT=ios3 )

READ(2,IOSTAT=ios3, FMT=‘(A)’) filein

if (ios3 /= 0 ) then
screen="Impossible d ouvrir le fichier temporaire des fichiers de donnees a traiter : "//adjustl(trim(filein))
retour=printl()
STOP
endif

rep_data=filein
screen="DATA DIRECTORY : "//rep_data
retour=printl()

mois=“”
annee=“”

READ(2,IOSTAT=ios3, FMT=‘(I)’) nbfiles
READ(2,IOSTAT=ios3,FMT=‘(I)’) debug
READ(2,IOSTAT=ios3,FMT=) mois
READ(2,IOSTAT=ios3,FMT=
) annee

!creation du fichier de sortie ames
OPEN( UNIT=14, &
FILE=“ohto”//trim(adjustl(annee(3:4)))//trim(adjustl(mois))//“.anl”, &
FORM=“formatted”, &
ACCESS=“sequential”, &
STATUS=“unknown”, &
ACTION=“readwrite”, &
POSITION=“rewind”, &
IOSTAT=iosres )

    if (iosres /= 0 ) then
            screen="Impossible de creer le fichier des grilles"
            retour=printl()
            STOP
    endif

READ(2,IOSTAT=ios3, FMT=‘(A)’) filein

ALLOCATE(sortie_ames%grids_ames(nbfiles))

PROGRAM treat_files_list

USE fonctions_mod 
USE grid_ames_mod
USE head_ames_mod
USE struct_ames_mod
USE lidar_mod

IMPLICIT NONE

CHARACTER(LEN=300)				:: temp_string, temp_string2
CHARACTER(LEN=41)				:: temp_string4
CHARACTER(LEN=28)				:: temp_string5
CHARACTER(LEN=14)				:: temp_string6
CHARACTER(LEN=120)				:: temp_string80
CHARACTER(LEN=250)				:: filein,list_files,tmp_list
CHARACTER(LEN=100)				:: cmoismin,cmoismax,cheuremin,cheuremax ,temp_string3
CHARACTER(LEN=100)				:: rep_data,rep_so,chaine,chaine2,rep_lo,file_lo
CHARACTER(LEN=50)				:: link
CHARACTER(LEN=8)				:: tdate
CHARACTER(LEN=5)				:: coltemp,col1
CHARACTER(LEN=7)				:: col2, col5, col6, col8
CHARACTER(LEN=7)				:: col10,col9
CHARACTER(LEN=10)				:: col11,col7
CHARACTER(LEN=4)				:: mois,annee
CHARACTER(LEN=6)				:: col4 
CHARACTER(LEN=8)				:: col3 
CHARACTER(LEN=10)				:: ttime
CHARACTER(LEN=5)				:: tzone
INTEGER, DIMENSION(8)				:: tvalues
CHARACTER(LEN=200)				:: screen,line,line2 
INTEGER						:: i,j,indice,idatemesure,idatemesuremax,idatemesuremin,nblcomment,ifdatemesure
INTEGER 					:: unit,ios,ios2,iosres,debug,nbfile,ios3,lecture,ulog,nbfiles,ifile,temp_int,temp_int2
type(grid_ames)			                :: sortie_asc,temp_ames
type(struct_ames)		                :: sortie_ames
LOGICAL						:: retour
REAL						:: temp_real

COMMON                                                                  screen,rep_so,debug
COMMON                                                                  rep_lo,file_lo,ulog

!lecture du fichier temporaire devant contenir la liste des fichiers de donnees a traiter
call getarg(1,tmp_list)
nbfiles=0
debug=1
ifile=0

!ouverture liste des fichiers asc a traiter
OPEN(   UNIT=2, &
        FILE=tmp_list, &
        FORM="formatted", &
        ACCESS="sequential", &
        STATUS="old", &
        ACTION="read", &
        POSITION="rewind", &
        IOSTAT=ios3 )


READ(2,IOSTAT=ios3, FMT='(A)') filein 

if (ios3 /= 0 ) then
	screen="Impossible d ouvrir le fichier temporaire des fichiers de donnees a traiter : "//adjustl(trim(filein))
        retour=printl()
        STOP
endif

rep_data=filein
screen="DATA DIRECTORY : "//rep_data
retour=printl()

mois=""
annee=""

READ(2,IOSTAT=ios3, FMT='(I)') nbfiles
READ(2,IOSTAT=ios3,FMT='(I)') debug
READ(2,IOSTAT=ios3,FMT=*) mois 
READ(2,IOSTAT=ios3,FMT=*) annee

!creation du fichier de sortie ames
OPEN( UNIT=14, &
        FILE="ohto"//trim(adjustl(annee(3:4)))//trim(adjustl(mois))//".anl", &
        FORM="formatted", &
        ACCESS="sequential", &
        STATUS="unknown", &
        ACTION="readwrite", &
        POSITION="rewind", &
        IOSTAT=iosres )

        if (iosres /= 0 ) then
                screen="Impossible de creer le fichier des grilles"
                retour=printl()
                STOP
        endif


READ(2,IOSTAT=ios3, FMT='(A)') filein

ALLOCATE(sortie_ames%grids_ames(nbfiles))

Where is grid_ames type defined? In a module? Is grid_ames_mod.o file a compiled version of that module? I am asking because, as @PierU have noticed, the code of type grid_ames contains an error (component hour defined twice), so I wander how were you able to create .o file

Here is the code for grid_ames_mod.f90.
The double definition of the time was related to a translation error from google translate.

MODULE grid_ames_mod 

IMPLICIT NONE

CONTAINS

type GRID_AMES
	CHARACTER(LEN=14)				:: datemesure
	CHARACTER(LEN=4)				:: annee
	CHARACTER(LEN=4)				:: yearmes 
	CHARACTER(LEN=10)				:: monthmes 
	CHARACTER(LEN=10)				:: cmois 
	CHARACTER(LEN=10)				:: cheure 
	CHARACTER(LEN=2)				:: daymes 
	CHARACTER(LEN=2)				:: deb_heuremes 
	CHARACTER(LEN=2)				:: deb_minutemes 
	CHARACTER(LEN=2)				:: deb_secondemes 
	CHARACTER(LEN=2)                                :: fin_heuremes
        CHARACTER(LEN=2)                                :: fin_minutemes
        CHARACTER(LEN=2)                                :: fin_secondemes
	CHARACTER(LEN=10)				:: dureemes		
	CHARACTER(LEN=10)				:: julianday 
	CHARACTER(LEN=10)				:: deb_alt 
	CHARACTER(LEN=10),DIMENSION(15)			:: top	
	CHARACTER(LEN=50),DIMENSION(:,:),pointer	:: tabMesures=>null()
	CHARACTER(LEN=10)	                       	:: v_resolution
        CHARACTER(LEN=10) 	                       	:: wave_length
        CHARACTER(LEN=10)	      	               	:: nb_shot
        CHARACTER(LEN=10)	                       	:: frequency
end type GRID_AMES

END MODULE grid_ames_mod 

Still, it is not compilable, you cannot put a definition of type after CONTAINS

$ gfortran -c grid_ames_mod.f90 
grid_ames_mod.f90:7:14:

    7 | type GRID_AMES
      |              1
Error: Unexpected derived type declaration statement in CONTAINS section at (1)

Even after commenting out CONTAINS line and compiling the module, the main program fails to compile in many places, partly due to absence of other modules USEd (struct_ames) but also due to non-standard use of format (I) without any width. The ALLOCATE statement that you complain about cannot be checked as it operates on sortie_ames object, defined as type(struct_ames) :: sortie_ames, and we still do not have the module.

So, to summarize, you have still not given a MWE, Minimal Working Example, here to be interpreted as the minimal bunch of code of which the only problem to compile is the ALLOCATE statement.

I’m going to take a wild guess here and suggest that the error is a run-time error, not a compile-time error, and that upon executing the line

The variable output_ames is itself a pointer or allocatable, and has not been allocated. Thus simply referencing the component grids_ames, let alone trying to allocate, is invalid.

FYI, copy pasting the exact error message would make things easier for everybody.

The OP cited upthread an error during compilation, but maybe it was while trying to prepare a MWE, not the original code.

@everythingfunctional output_ames is also named sortie_ames before translation, and the latter is not defined as a pointer. Anyway, without a MWE we can indeed just guess…

Thanks for these explanations.

Here is a MWE :

Module treat_files_list.f90 :

PROGRAM treat_files_list
 
USE grid_ames_mod 
USE struct_ames_mod 

IMPLICIT NONE

CHARACTER(LEN=300)				:: temp_string, temp_string2
CHARACTER(LEN=41)				:: temp_string4
CHARACTER(LEN=28)				:: temp_string5
CHARACTER(LEN=14)				:: temp_string6
CHARACTER(LEN=120)				:: temp_string80
CHARACTER(LEN=250)				:: filein,list_files,tmp_list
CHARACTER(LEN=100)				:: cmoismin,cmoismax,cheuremin,cheuremax ,temp_string3
CHARACTER(LEN=100)				:: rep_data,rep_so,chaine,chaine2,rep_lo,file_lo
CHARACTER(LEN=50)				:: link
CHARACTER(LEN=8)				:: tdate
CHARACTER(LEN=5)				:: coltemp,col1
CHARACTER(LEN=7)				:: col2, col5, col6, col8
CHARACTER(LEN=7)				:: col10,col9
CHARACTER(LEN=10)				:: col11,col7
CHARACTER(LEN=4)				:: mois,annee
CHARACTER(LEN=6)				:: col4 
CHARACTER(LEN=8)				:: col3 
CHARACTER(LEN=10)				:: ttime
CHARACTER(LEN=5)				:: tzone
INTEGER, DIMENSION(8)				:: tvalues
CHARACTER(LEN=200)				:: screen,line,line2 
INTEGER						:: i,j,indice,idatemesure,idatemesuremax,idatemesuremin,nblcomment,ifdatemesure
INTEGER 					:: unit,ios,ios2,iosres,debug,nbfile,ios3,lecture,ulog,nbfiles,ifile,temp_int,temp_int2
type(grid_ames)			                :: sortie_asc,temp_ames
type(struct_ames)		                :: sortie_ames
LOGICAL						:: retour
REAL						:: temp_real

COMMON                                                                  screen,rep_so,debug
COMMON                                                                  rep_lo,file_lo,ulog

!lecture du fichier temporaire devant contenir la liste des fichiers de donnees a traiter
call getarg(1,tmp_list)
nbfiles=0
debug=1
ifile=0

!ouverture liste des fichiers asc a traiter
OPEN(   UNIT=2, &
        FILE=tmp_list, &
        FORM="formatted", &
        ACCESS="sequential", &
        STATUS="old", &
        ACTION="read", &
        POSITION="rewind", &
        IOSTAT=ios3 )


READ(2,IOSTAT=ios3, FMT='(A)') filein 

if (ios3 /= 0 ) then
	screen="Impossible d ouvrir le fichier temporaire des fichiers de donnees a traiter : "//adjustl(trim(filein))
        retour=printl()
        STOP
endif

rep_data=filein
screen="DATA DIRECTORY : "//rep_data
retour=printl()

mois=""
annee=""

READ(2,IOSTAT=ios3, FMT='(I)') nbfiles
READ(2,IOSTAT=ios3,FMT='(I)') debug
READ(2,IOSTAT=ios3,FMT=*) mois 
READ(2,IOSTAT=ios3,FMT=*) annee

!creation du fichier de sortie ames
OPEN( UNIT=14, &
        FILE="ohto"//trim(adjustl(annee(3:4)))//trim(adjustl(mois))//".anl", &
        FORM="formatted", &
        ACCESS="sequential", &
        STATUS="unknown", &
        ACTION="readwrite", &
        POSITION="rewind", &
        IOSTAT=iosres )

        if (iosres /= 0 ) then
                screen="Impossible de creer le fichier des grilles"
                retour=printl()
                STOP
        endif


READ(2,IOSTAT=ios3, FMT='(A)') filein

ALLOCATE(sortie_ames%grids_ames(nbfiles))

Module grid_ames_mod.f90

MODULE grid_ames_mod

IMPLICIT NONE

CONTAINS

type GRID_AMES
	CHARACTER(LEN=14)				:: datemesure
	CHARACTER(LEN=4)				:: annee
	CHARACTER(LEN=4)				:: yearmes 
	CHARACTER(LEN=10)				:: monthmes 
	CHARACTER(LEN=10)				:: cmois 
	CHARACTER(LEN=10)				:: cheure 
	CHARACTER(LEN=2)				:: daymes 
	CHARACTER(LEN=2)				:: deb_heuremes 
	CHARACTER(LEN=2)				:: deb_minutemes 
	CHARACTER(LEN=2)				:: deb_secondemes 
	CHARACTER(LEN=2)                                :: fin_heuremes
        CHARACTER(LEN=2)                                :: fin_minutemes
        CHARACTER(LEN=2)                                :: fin_secondemes
	CHARACTER(LEN=10)				:: dureemes		
	CHARACTER(LEN=10)				:: julianday 
	CHARACTER(LEN=10)				:: deb_alt 
	CHARACTER(LEN=10),DIMENSION(15)			:: top	
	CHARACTER(LEN=50),DIMENSION(:,:),pointer	:: tabMesures=>null()
	CHARACTER(LEN=10)	                       	:: v_resolution
        CHARACTER(LEN=10) 	                       	:: wave_length
        CHARACTER(LEN=10)	      	               	:: nb_shot
        CHARACTER(LEN=10)	                       	:: frequency
end type GRID_AMES

END MODULE grid_ames_mod 

Module head_ames_mod.f90

MODULE head_ames_mod 

IMPLICIT NONE

CONTAINS

type HEAD_AMES

	CHARACTER(LEN=12)                       :: station
        CHARACTER(LEN=12)                       :: instrument
        CHARACTER(LEN=40)                       :: instrument2
        CHARACTER(LEN=20)                       :: pi
        CHARACTER(LEN=40)                       :: pi2
        CHARACTER(LEN=12)                       :: specie
        CHARACTER(LEN=100)                      :: date
	CHARACTER(LEN=50)			:: datemin, datemax
        CHARACTER(LEN=100)                      :: lab
        CHARACTER(LEN=100)                      :: head_line
        INTEGER					:: julianday 
	CHARACTER(LEN=5)			:: altitude
	CHARACTER(LEN=5)			:: latitude 
	CHARACTER(LEN=5)			:: longitude 

end type HEAD_AMES

END MODULE head_ames_mod 

Module struct_ames_mod.f90

MODULE struct_ames_mod 

IMPLICIT NONE

CONTAINS
USE head_ames_mod
USE grid_ames_mod


type STRUCT_AMES
	CHARACTER(LEN=12)			:: chaine 
	type(grid_ames),DIMENSION(:),pointer    :: grids_ames=>null()	
	type(head_ames)     		   	:: head	 	

end type STRUCT_AMES

END MODULE struct_ames_mod 

Makefile

#!/bin/bash

OBJ     =  head_ames_mod.o grid_ames_mod.o struct_ames_mod.o   treat_files_list.o
FC      = pgf90
FLAGS   =
.SUFFIXES : .f90
all:	treat_files_list    
clean:
	rm -f *.o *.mod
.f90.o:
	$(FC) $(FLAGS) -c head_ames_mod.f90
	$(FC) $(FLAGS) -c grid_ames_mod.f90
	$(FC) $(FLAGS) -c struct_ames_mod.f90  
	$(FC) $(FLAGS) -c treat_files_list.f90

treat_files_list: $(OBJ)
	$(FC) -o treat_files_list $(OBJ) 

Working compilation :
pgf90 --version
pgf90 13.10-0 64-bit target on x86-64 Linux -tp sandybridge
The Portland Group - PGI Compilers and Tools
Copyright (c) 2013, NVIDIA CORPORATION. All rights reserved.

Not working compilation
pgf90 --version
pgf90 (aka nvfortran) 21.9-0 64-bit target on x86-64 Linux -tp zen
PGI Compilers and Tools
Copyright (c) 2021, NVIDIA CORPORATION & AFFILIATES. All rights reserved.

Error message
vFortran$ make
pgf90 -c head_ames_mod.f90
pgf90 -c grid_ames_mod.f90
pgf90 -c struct_ames_mod.f90
pgf90 -c treat_files_list.f90
pgf90 -o treat_files_list head_ames_mod.o grid_ames_mod.o struct_ames_mod.o treat_files_list.o
/usr/bin/ld: treat_files_list.o: in function MAIN_': vFortran/treat_files_list.f90:154: undefined reference to grid_ames_mod___grid_ames__td_’
/usr/bin/ld: vFortran/treat_files_list.f90:154: undefined reference to `grid_ames_mod___grid_ames__td_’
make: *** [Makefile:19: treat_files_list] Error 2

This is still not a MWE, I had to correct many errors before be able to compile it: there are type definitions after contains statements (I removed the contains), FMT='(I)' misses a length (modified to FMT='(I10)'), there are USE statements after IMPLICIT NONE, END PROGRAM is missing, and the printl() function is not defined.

At the end I could compile (with gfortran-12)… without the error you are encountering: I could build an executable. But again this is not concluding, as this is clearly not a code that you have compiled…

Note that your error is at link time, not at compile time.

A guess: your main program has two USE statements, one for grid_ames_mod and one for struct_ames_mod. But grid_ames_mod is already used by grid_ames_mod and is hence seen twice by the main program: gfortran does complain about that, but maybe pfg 21 is confused. Try commenting USE grid_ames_mod in the main program.

That is something that occurs all the time in fortran, and it should not be a problem. Modules in fortran are designed to allow that without the compiler being confused. Is there something special in this code that does cause a compiler to be confused?