I have an array sort_cent
which is a two dimensional array and unallocated initially. When I call the subroutine rbind by call subroutine rbind(sort_cent,tmparray([arg],:))
, which modifies the array in its values and size, signal SIGSEGV is called and the program interupts.
However, the subroutine does reaches at the end as it prints the value "End of the function" after compilation. I guess there is problem in returning the array. Here is the code:
module triangulate
implicit none
contains
subroutine rbind(a,b)
! combine matrices a and b by row
real, intent(in) :: b(:,:)
real,intent(inout),allocatable::a(:,:)
real, allocatable :: ab(:,:)
integer :: n1a,n1,n2,i,err
if(.not. allocated(a)) then
n2 = size(b,2)
n1a = 0
n1 = n1a + size(b,1)
allocate (ab(n1,n2))
print*,shape(ab),n1a
! if(n1a .ne. 0) then
! ! ab(:n1a,:) = a
! ab(1:n1a,:) = a
! ab(n1a+1:,:) = b
! else
ab(n1a+1:,:) = b
allocate(a,source=ab)
! print*,a
if (allocated(ab)) deallocate(ab, stat=err)
if (err /= 0) print *, "ab: Deallocation request denied"
! endif
else
print*,"In the else part"
n2 = size(b,2)
! if (size(b,2) /= n2) stop "need size(a,2) == size(b,2)"
n1a = size(a,1)
n1 = n1a + size(b,1)
allocate (ab(n1,n2))
print*,shape(ab),n1a
! if(n1a .ne. 0) then
! ab(:n1a,:) = a
ab(1:n1a,:) = a
ab(n1a+1:,:) = b
deallocate(a)
allocate(a,source=ab)
deallocate(ab)
endif
! call MOVE_ALLOC(ab,a)
do i=1,size(a,1)
print*,a(i,:)
end do
print*,shape(a)
print*,"End of the function"
! deallocate(a)
! return
end subroutine rbind
end module
And the subroutine which calls the above subroutine is:
subroutine sortanticlockwise(triangle,c,coord,sort_cent)
real,intent(in)::coord(:,:)
integer,intent(in)::triangle(:)
real,allocatable,intent(inout)::sort_cent(:,:)
integer,intent(in)::c(:)
real,allocatable::tmparray(:,:),tmp(:,:)
integer::i,j,k,ISTAT
real::pi
real,allocatable::dist(:)
real ,allocatable::angles(:)
real::center(1,2)
integer,allocatable::arg(:)
center=reshape([1,0], shape=[1,2])
pi=4*atan(1.0)
! allocate(sort_cent(0,2), STAT = ISTAT )
! IF ( ISTAT .NE. 0 ) THEN
! WRITE( *, '( A, I10)' ) 'Buffer allocation failed: STAT=', ISTAT
! STOP
! END IF
j=0
do i=1,1
allocate(tmparray(size(triangle(j+1:c(i)+j)),2))
! allocate(tmp(size(triangle(j+1:c(i)+j)),2)) !!Fixed
! print*,size(triangle(j+1:c(i)+j))
tmparray=coord([triangle(j+1:c(i)+j)],:) ! * Fixed
j=j+c(i)
! print*,size(tmparray)
allocate(dist(size(tmparray,1)))
allocate(angles(size(tmparray,1)))
allocate(arg(size(tmparray,1)))
dist=norm2(tmparray-spread(center(1,:),1,size(tmparray,1)),2) ! *Correct till here
where (tmparray(:,2) >0 )
angles= acos((tmparray(:,1)-1)/dist)
elsewhere
angles= 2*pi- acos((tmparray(:,1)-1)/dist)
end where
! arg=argsort(angles)
arg=argsort(angles)
!!!!!
open(103,file='angles1.out', status='replace', action='write')
do k=1, size(arg)
write(103,*) arg(k)
end do
close(103)
!!!!
print*,allocated(sort_cent)
call rbind(sort_cent,tmparray([arg],:))
print*,"Correct"
deallocate(tmparray)
deallocate(dist)
deallocate(angles)
deallocate(arg)
enddo
end subroutine sortanticlockwise
The output is:
F
249 2 0
1.14597142 3.33256181E-03
1.14644611 6.66513247E-03
1.14643490 1.33300433E-02
1.14594853 1.66623611E-02
1.14608729 2.33216006E-02
1.14546788 2.66483724E-02
1.14534485 3.32915969E-02
.
.
.
.
1.14571607 -3.33803333E-03
249 2
End of the function
Program received signal SIGSEGV: Segmentation fault - invalid memory reference.
Backtrace for this error:
#0 0x7f8d8ea23ad0 in ???
#1 0x7f8d8ea22c35 in ???
#2 0x7f8d8e63bcef in ???
at ./signal/../sysdeps/unix/sysv/linux/x86_64/libc_sigaction.c:0
#3 0x7f8d8e6a09d9 in arena_for_chunk
at ./malloc/arena.c:162
#4 0x7f8d8e6a09d9 in arena_for_chunk
at ./malloc/arena.c:160
#5 0x7f8d8e6a09d9 in __GI___libc_free
at ./malloc/malloc.c:3384
#6 0x55ccfb1a696c in sortanticlockwise
at /home/abhishek/abhishektiwari/test.f90:156
#7 0x55ccfb1a49f6 in test
at /home/abhishek/abhishektiwari/test.f90:69
#8 0x55ccfb1a6c08 in main
at /home/abhishek/abhishektiwari/test.f90:3
Segmentation fault (core dumped)
Further, the above subroutine is again called by the line in main as:
real,dimension(:,:),allocatable :: sorted_centroid
.
.
.
.
call sortanticlockwise(trianglesinsurface,c3,coord,sorted_centroid)
I am using gcompiler latest version to compile the above program. The fortran version is also latest.
I tried suggestions on this, this and numerous others. However, I still kept gettting the error after implementing the solutions in the above websites. Can anyone help?