Relocation truncated to fit error when trying to compile

Compiler: ifort
Options: -O3

Hi all, I get this error:

/opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o): in function `for__process_start_time':
for_init.c:(.text+0xc): relocation truncated to fit: R_X86_64_PC32 against `for_process_start_time'
/opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o): in function `handle_flt_und':
for_init.c:(.text+0x3d): relocation truncated to fit: R_X86_64_PC32 against symbol `for__l_fpe_mask' defined in .bss section in /opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o)
for_init.c:(.text+0x344): relocation truncated to fit: R_X86_64_PC32 against symbol `for__l_undcnt' defined in .bss section in /opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o)
for_init.c:(.text+0x396): relocation truncated to fit: R_X86_64_PC32 against symbol `for__l_undcnt' defined in .bss section in /opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o)
for_init.c:(.text+0x39e): relocation truncated to fit: R_X86_64_PC32 against symbol `for__l_undcnt' defined in .bss section in /opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o)
for_init.c:(.text+0x3aa): relocation truncated to fit: R_X86_64_PC32 against symbol `for__l_excpt_info' defined in .bss section in /opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o)
for_init.c:(.text+0x3cb): relocation truncated to fit: R_X86_64_PC32 against symbol `for__l_excpt_info' defined in .bss section in /opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o)
for_init.c:(.text+0x41e): relocation truncated to fit: R_X86_64_PC32 against symbol `for__l_undcnt' defined in .bss section in /opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o)
/opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libifcoremt.a(for_init.o): in function `for__signal_handler':
for_init.c:(.text+0x91a): relocation truncated to fit: R_X86_64_PC32 against `.bss'
for_init.c:(.text+0x944): relocation truncated to fit: R_X86_64_PC32 against `.bss'
for_init.c:(.text+0x961): additional relocation overflows omitted from the output
/opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libirc.a(tbk_backtrace.o): in function `tbk_signal_handler':
tbk_backtrace.c:(.text+0x49d): failed to convert GOTPCREL relocation against 'tbk__jmp_env'; relink with --no-relax
/opt/intel/oneapi/compiler/2022.0.2/linux/compiler/lib/intel64_lin/libirc.a(tbk_backtrace.o): in function `tbk_trace_stack_impl':
tbk_backtrace.c:(.text+0x190c): failed to convert GOTPCREL relocation against 'tbk__jmp_env'; relink with --no-relax
tbk_backtrace.c:(.text+0x1a5b): failed to convert GOTPCREL relocation against 'tbk__jmp_env'; relink with --no-relax

This is my code:

program int_64_check
  use iso_fortran_env
  implicit none


  type data
     real :: phi,x,y,area,h
  end type data

  type(data) :: maximum
  real :: check
  integer(kind=int64) :: i,j,k,n
  integer(kind=int64),parameter :: total=1300*2500*18000
  type(data) :: arr(total)
  real,parameter :: pi=3.14159
  real,parameter,dimension(1:2500) :: mi=[(i*0.01,i=1,2500)]
  real,parameter,dimension(1:18000) :: mk=[(i*(pi/180.)*0.01,i=1,18000)]

  n=1

  do concurrent(i=1:1300,j=1:2500,k=1:18000)
     arr(n)%x=mi(i)
     arr(n)%y=mi(j)
     arr(n)%phi=mk(k)
     n=n+1
  end do

  call calculate(arr%x,arr%y,arr%phi,arr%h,arr%area)
  maximum%area=0.



contains
  
  elemental subroutine calculate(x,y,phi,h,area)
    real,intent(in) :: x,y,phi
    real,intent(out) :: h,area
    real :: b1,b2

    h=sin(phi)*x
    b1=(2*(cos(phi))+x)+y
    b2=y
    area=(1./2.)*h*(b1+b2)
  end subroutine calculate

end program int_64_check

1 Like

As I understand it, this kind of error occurs when the addresses of statically allocated data don’t fit into the address space (2 GB default).

What happens if you add -mcmodel=medium to the compiler flags?

From the ifort manual:

       -mcmodel=mem_model (L*X only)

              Tells the compiler to use a specific
                     memory model to generate code and store data.

              Architecture Restrictions: Only available on Intel(R) 64 architecture

              Arguments:

              mem_model         Is the memory model to use. Possible values are:

                                small          Tells  the compiler to restrict code and data to the first 2GB of address space. All accesses of code
                                               and data can be done with Instruction Pointer (IP)-relative addressing.

                                medium         Tells the compiler to restrict code to the first 2GB;  it  places  no  memory  restriction  on  data.
                                               Accesses  of  code  can  be  done with IP-relative addressing, but accesses of data must be done with
                                               absolute addressing.

                                large          Places no memory restriction on code or data.  All accesses of  code  and  data  must  be  done  with
                                               absolute addressing.

              Default:

              -mcmodel=small    On  systems  using Intel(R) 64 architecture, the compiler restricts code and data to the first 2GB of address space.
                                Instruction Pointer (IP)-relative addressing can be used to access code and data.
...

Also, type(data) :: arr(total) is very large. Make sure it can fit in your computer’s RAM.

1 Like

@milancurcic
It compiles with the tag, but I get a segmentation fault error when I try to run it :sweat_smile:

About the size, what’s the max size array that can be worked on at compilation time ?

Does the flag /heaps-arrays0 work?
On linux it is -heap-arrays

1 Like

Nope :frowning: , sadly I get the same error
I even tried with the previous tag suggested.

yeah I see, the error I got is,

1>x64\Release\avx.obj: catastrophic error: Variable INT_64_CHECK$ARR.0.1 too large for NTCOFF.  Bigger than 2GB.  Use heap instead

I have also did

But still got the same error. The 2147483647 is largest I can set, it is the upper bound of int32.

You parameter total is out of the bound of int32 and it is int64, so it seems does not fit.

I changed your code to below using allocatable array.

program int_64_check
  use iso_fortran_env
  implicit none


  type data
     real :: phi,x,y,area,h
  end type data

  type(data) :: maximum
  real :: check
  integer(kind=int64) :: i,j,k,n 
  integer(kind=int64) :: n1300,n2500,n18000,ntotal
  type(data), allocatable :: arr(:)
  real,parameter :: pi=3.14159
  real,allocatable :: mi(:)
  real,allocatable :: mk(:)

  n=1
  
  n1300 = 1300
  n2500 = 2500
  n18000 = 18000
  ntotal = n1300*n2500*n18000
  mi=[(i*0.01,i=1,n2500)]
  mk=[(i*(pi/180.)*0.01,i=1,n18000)]
  allocate(arr(ntotal))

  do concurrent(i=1:n1300,j=1:n2500,k=1:n18000)
     arr(n)%x=mi(i)
     arr(n)%y=mi(j)
     arr(n)%phi=mk(k)
     n=n+1
  end do

  call calculate(arr%x,arr%y,arr%phi,arr%h,arr%area)
  maximum%area=0.



contains
  
  elemental subroutine calculate(x,y,phi,h,area)
    real,intent(in) :: x,y,phi
    real,intent(out) :: h,area
    real :: b1,b2

    h=sin(phi)*x
    b1=(2*(cos(phi))+x)+y
    b2=y
    area=(1./2.)*h*(b1+b2)
  end subroutine calculate

end program int_64_check

But it shows not sufficient virtual memory, the I realize your array is indeed too big,

18000 * 2500 * 1300 * 8/1024/1024/1024=432GB or so. It is too big for my memory.

Perhaps the below link may help,

1 Like

alright thank you . I’ll just make them allocatable

1 Like

The 8 in 18000 * 2500 * 1300 * 8 is for real 8 which means 8 bytes.
See my edited post above (I use allocatable array), however, if I calculated correctly, your array may be really too big, lol.

1 Like

Perhaps you may use Monte Carlo to calculate your area.
Or instead of using big arrays, you can use do loop instead.
Using such big array (even if it fits you physics memory) is very likely make you memory bandwidth the bottleneck.

1 Like

I will try the suggestions out :slight_smile: Thank you

I am very sure you could figure out how to solve the problem :slight_smile:
For numerical integration, perhaps quadpack may help,

https://people.sc.fsu.edu/~jburkardt/f77_src/quadpack/quadpack.html
Good luck.

1 Like

Thank you

Is there a library for 2D functions ?

Perhaps there are other ones for numerical integration. But the one by @jacobwilliams may be a decent one,

Well, actually I should give the above link before, I mistakenly it with quadpack (I mistakenly though quadpack can deal with 2 or more dimensional numerical integrals). Perhaps @Beliavsky know some other libraries too.

I personally may use Monte Carlo.

Also, from

I found

1 Like

Thank you

1 Like