- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi, I'm working on the code that constructs CSR format array using linked list.
I followed the book Ed Akin - Object-oriented programming via Fortran 90-95 (2003)
module mCSR
implicit none
integer, parameter, private :: DBL = kind(0.d0)
Type :: z3CSR
integer :: nrow, ncol, nval
integer, dimension(:), allocatable :: ia, ja
complex(DBL), dimension(:), allocatable :: a
end type z3CSR
Type, public :: zcompCSR
integer :: col
complex(DBL) :: val
end type zcompCSR
Type :: znodeCSR
private
type(zcompCSR) :: comp
type(znodeCSR), pointer :: next => null()
end type znodeCSR
Type :: zlistCSR
private
Type(znodeCSR), pointer :: first => null()
end type zlistCSR
contains
subroutine z3AllocateCSR(nrow, ncol, nval, CSR)
integer, intent(in) :: nrow, ncol, nval
Type(z3CSR), intent(inout) :: CSR
CSR%nrow=nrow; CSR%ncol=ncol; CSR%nval=nval
if (allocated(CSR%ia)) deallocate(CSR%ia)
if (allocated(CSR%ja)) deallocate(CSR%ja)
if (allocated(CSR%a)) deallocate(CSR%a)
allocate(CSR%ia(nrow+1), CSR%ja(nval), CSR%a(nval))
CSR%ia(:)=0; CSR%ja(:)=0; CSR%a(:)=(0.d0,0.d0)
end subroutine z3AllocateCSR
subroutine z3DeallocateCSR(CSR)
Type(z3CSR), intent(inout) :: CSR
if (allocated(CSR%ia)) deallocate(CSR%ia)
if (allocated(CSR%ja)) deallocate(CSR%ja)
if (allocated(CSR%a)) deallocate(CSR%a)
end subroutine z3DeallocateCSR
subroutine zAllocateLinkedList(head)
type(zlistCSR), intent(inout) :: head
allocate(head%first)
nullify(head%first%next)
end subroutine zAllocateLinkedList
subroutine zInsertInOrder(comp, head, lnew)
type(zcompCSR), intent(in) :: comp
type(zlistCSR), intent(inout) :: head
logical, intent(out) :: lnew
! local
type(znodeCSR), pointer :: previous, current
lnew = .False.
previous => head%first
current => previous%next
do while (associated(current))
if (comp%col.LT.current%comp%col) exit
if (comp%col.EQ.current%comp%col) then
current%comp%val = current%comp%val + comp%val
nullify(previous, current)
return
end if
previous => current
current => current%next
end do
lnew = .True.
allocate(previous%next)
previous%next%comp = comp
previous%next%next => current
nullify(previous, current)
end subroutine zInsertInOrder
subroutine z3FillInCSR(heads, CSR)
type(zlistCSR), dimension(:), intent(in) :: heads
type(z3CSR), intent(inout) :: CSR
! local
type(znodeCSR), pointer :: current
integer :: i, icount
CSR%ia(1) = 1; icount = 0
do i = 1, CSR%nrow
current => heads(i)%first%next
do while (associated(current))
icount = icount + 1
CSR%ja(icount) = current%comp%col
CSR%a(icount) = current%comp%val
current => current%next
end do
CSR%ia(i+1) = icount + 1
end do
nullify(current)
end subroutine z3FillInCSR
subroutine zDeallocateLinkedList(head)
type(zlistCSR), intent(inout) :: head
! local
type(znodeCSR), pointer :: previous, current
previous => head%first
current => previous%next
do while (associated(current))
previous%next => current%next
deallocate(current)
end do
nullify(previous, current)
end subroutine zDeallocateLinkedList
end module mCSR
The code simply works like below:
program test
use mCSR
implicit none
integer, parameter :: ncomp = ! known value for test
integer, parameter :: nrow = ! known value for test
type(zcompCSR) :: comp
type(zlistCSR), dimension(:), allocatable :: heads
type(z3CSR) :: CSR
integer :: i, irow, icount
logical :: lnew
allocate(heads(nrow))
do i = 1, nrow
call zAllocateLinkedList(heads(i))
end do
open(1, file='comp.dat')
icount = 0
do i = 1, ncomp
read(1,*) irow, comp%col, comp%val
call zInsertInOrder(comp,heads(irow),lnew)
if (lnew) icount = icount + 1
end do
close(1)
call z3AllocateCSR(nrow, nrow, icount, CSR)
call z3FillInCSR(heads, CSR)
do i = 1, nrow
call zDeallocateLinkedList(heads(i))
end do
deallocate(heads)
... (use CSR for PARDISO or etc)
end program test
When I complied the codes with the option:
ifort -fpp -m64 -warn all -check all,noarg_temp_created -traceback -stand f03 -fstack-security-check
the program works fine.
But when I compiled the codes with the option:
ifort -O2 -qopenmp
all the CSR%ja = 0, and CSR%a only has the imaginary part of the input.
I found that the solution is not to initialize the pointer 'next' in the type 'znodeCSR'.
i.e.) modify
type(znodeCSR), pointer :: next => null()
to
type(znodeCSR), pointer :: next
But I can't figure out why.
Could you me know why I should not initialize the pointer 'next' and
why the initializtion of the pointer 'first' in 'zlistCSR' is okay?
* my computer system is centOS 7, and oneAPI version is 2022.1.1.119
- Tags:
- Linked List
- pointer
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Are there OpenMP directives in your code? If not, why did you use -qopenMP. There are several issues that are fixed when compiling with -qopenmp. Please try the latest compiler release that is part of oneAPI HPC Toolkit 2023.0. The ifort version is 2021.8.0.
If the latest compiler doesn't fix your issue, can you upload the complete reproducer?
When you don't specify -O[0123] the default is -O2.
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page