Skip to content

Commit

Permalink
Cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
cnegre committed Sep 17, 2022
1 parent 0111ee5 commit 12187d5
Show file tree
Hide file tree
Showing 6 changed files with 45 additions and 37 deletions.
3 changes: 1 addition & 2 deletions CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -84,9 +84,8 @@ if(BML_ROCSPARSE)
message(STATUS "HIP rocSPARSE libraries: ${rocsparse_LIBRARIES}")
endif()

set(BML_OPENMP TRUE CACHE BOOL "Whether the bml was built with OpenMP")
set(PROGRESS_OPENMP TRUE CACHE BOOL "Whether to compile with OpenMP support")
if(PROGRESS_OPENMP OR BML_OPENMP)
if(PROGRESS_OPENMP)
message(STATUS "Looking for OpenMP")
include(FindOpenMP)
if(OPENMP_FOUND)
Expand Down
3 changes: 0 additions & 3 deletions build.sh
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,6 @@ EOF
echo "CC Path to C compiler (default is ${CC})"
echo "CXX Path to C++ compiler (default is ${CXX})"
echo "FC Path to Fortran compiler (default is ${FC})"
echo "BML_OPENMP {yes,no} (default is ${BML_OPENMP})"
echo "BML_ROCSPARSE Build with rocSPARSE (default is ${BML_ROCSPARSE})"
echo "PROGRESS_OPENMP {yes,no} (default is ${PROGRESS_OPENMP})"
echo "BLAS_VENDOR {Default} (default is ${BLAS_VENDOR})"
Expand All @@ -60,7 +59,6 @@ set_defaults() {
: ${CC:=gcc}
: ${CXX:=g++}
: ${FC:=gfortran}
: ${BML_OPENMP:=yes}
: ${BML_ROCSPARSE:=no}
: ${PROGRESS_OPENMP:=yes}
: ${PROGRESS_MPI:=no}
Expand Down Expand Up @@ -123,7 +121,6 @@ configure() {
${CMAKE_CXX_FLAGS:+-DCMAKE_CXX_FLAGS="${CMAKE_CXX_FLAGS}"} \
${CMAKE_Fortran_FLAGS:+-DCMAKE_Fortran_FLAGS="${CMAKE_Fortran_FLAGS}"} \
-DCMAKE_INSTALL_PREFIX="${INSTALL_DIR}" \
-DBML_OPENMP="${BML_OPENMP}" \
-DBML_ROCSPARSE="${BML_ROCSPARSE}" \
-DPROGRESS_OPENMP="${PROGRESS_OPENMP}" \
-DPROGRESS_MPI="${PROGRESS_MPI}" \
Expand Down
1 change: 0 additions & 1 deletion build_scaling.sh
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,6 @@ else
export CXX=${CXX:=g++}
fi

export BML_OPENMP=${BML_OPENMP:=yes}
export PROGRESS_OPENMP=${PROGRESS_OPENMP:=yes}
export PROGRESS_GRAPHLIB=${PROGRESS_GRAPHLIB:=yes}
export PROGRESS_TESTING=${PROGRESS_TESTING:=yes}
Expand Down
57 changes: 35 additions & 22 deletions src/latte_mods/neighborlist_latte_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -36,11 +36,11 @@ module neighborlist_latte_mod
real(dp), allocatable :: nnRz(:,:)

!> x-integer translation of neighbor J to I within RCut (including atoms in the skin)
integer(kind=low), allocatable :: nnIx(:,:)
integer, allocatable :: nnIx(:,:)
!> y-integer translation of neighbor J to I within RCut (including atoms in the skin)
integer(kind=low), allocatable :: nnIy(:,:)
integer, allocatable :: nnIy(:,:)
!> z-integer translation of neighbor J to I within RCut (including atoms in the skin)
integer(kind=low), allocatable :: nnIz(:,:)
integer, allocatable :: nnIz(:,:)

!> The neighbor J of I corresponds to some translated atom number in the box that we need to keep track of.
integer, allocatable :: nnType(:,:)
Expand Down Expand Up @@ -108,7 +108,8 @@ subroutine build_nlist_int(coords,lattice_vectors,rcut,nl,verbose)
real(dp) :: dLx, dLy, dLz
real(dp) :: Ty, Tz, calpha, coulcut
real(dp) :: coulvol, dist, pi, sqrtx
real(dp), allocatable :: head(:), list(:), buffer(:,:), distvec(:), trtmp(:,:)
real(dp), allocatable :: buffer(:,:), distvec(:), trtmp(:,:)
integer, allocatable :: head(:), list(:)
real(dp), intent(in) :: coords(:,:), lattice_vectors(:,:), rcut
type(neighlist_type), intent(inout) :: nl
logical(1) :: found
Expand All @@ -134,18 +135,20 @@ subroutine build_nlist_int(coords,lattice_vectors,rcut,nl,verbose)
if(verbose >= 1) write(*,*) "min(nx,ny,nz) =", min(nx,ny,nz)

if(.not.(allocated(nl%nrnnlist)))then
if(min(Lx,Ly,Lz)/2.0_dp < rcut)then
!if(min(Lx,Ly,Lz)/2.0_dp < rcut)then
if(.not. allocated(nl%nnIx))then
allocate(nl%nnIx(natspblock,nats));
allocate(nl%nnIy(natspblock,nats));
allocate(nl%nnIz(natspblock,nats));
endif
!endif
allocate(nl%nnType(natspblock,nats))
allocate(nl%nnStruct(natspblock,nats))
allocate(nl%nrnnStruct(nats))
allocate(nl%nrnnlist(nats))
endif

if(min(nx,ny,nz) < 1000)then ! Brute force for small systems!
if((min(nx,ny,nz) .lt. 3000) .or. (nats < 80))then ! Brute force for small systems!

if(verbose >= 1) write(*,*) "Performing brute force for small system ..."

Expand Down Expand Up @@ -177,6 +180,7 @@ subroutine build_nlist_int(coords,lattice_vectors,rcut,nl,verbose)
nl%nnIz(cnt,i) = l
else
found = .true.
STOP "ERROR in neighb list ..."
endif
endif
if(found .eqv. .true.)exit
Expand Down Expand Up @@ -204,25 +208,29 @@ subroutine build_nlist_int(coords,lattice_vectors,rcut,nl,verbose)
deallocate(tmp)

else ! Do the same but now with linked lists in O(N)

allocate(head(nx*ny*nz));
allocate(list(nats));
!write(*,*)"nxn","nxnynz",nats*nats,nx*ny*nz
!allocate(head(nx*ny*nz));
allocate(head(nats*nats));
allocate(list(10*nats));
allocate(ntype(10*nats));
allocate(buffer(3,nats*26)) !Allocate max buffer atoms
allocate(trtmp(3,nats*26)) !Allocate max buffer atoms
allocate(buffer(3,10*nats)) !Allocate max buffer atoms
allocate(trtmp(3,10*nats)) !Allocate max buffer atoms

buffer(:,1:nats) = coords

head = 0
list = 0
ntype = 0
do i = 1,nats
cell = 1 + floor(nx*coords(1,i)/Lx) + floor(ny*coords(2,i)/Ly)*nx &
+ floor(nz*coords(3,i)/Lz)*nx*ny;
cell = int(1.0_dp + floor(nx*coords(1,i)/Lx) + floor(ny*coords(2,i)/Ly)*nx &
+ floor(nz*coords(3,i)/Lz)*nx*ny)
list(i) = head(cell);
head(cell) = i;
ntype(i) = i;
!write(*,*)"i,cell,list,head,ntype",i,cell,list(i),head(cell),ntype(i),size(list),size(head),size(ntype),size(coords,dim=2)
enddo


!And now add a skin or surface buffer to account for periodic BC, all 26 of them!
cnt = 0;
do i = 1,nx*ny !All boxes in the first (z=0) layer
Expand Down Expand Up @@ -565,31 +573,31 @@ subroutine build_nlist_int(coords,lattice_vectors,rcut,nl,verbose)
ny = ny+2;
nz = nz+2;

deallocate(head)
deallocate(list)
allocate(head(nx*ny*nz))
allocate(list(nats+Nskin))
head = 0
list = 0

do i = 1,nats+Nskin
cell = 1 + floor(nx*buffer(1,i)/Lx) + floor(ny*buffer(2,i)/Ly)*nx + floor(nz*buffer(3,i)/Lz)*nx*ny;
list(i) = head(cell);
head(cell) = i;
!write(*,*)"i,cell,head,list",i,cell,head(cell),list(i),size(list),size(head)
enddo

!$omp parallel do default(none) private(i) &
!$omp private(cnt,j,k,l,Tx,Ty,Tz) &
!$omp private(cnt,cnt2,j,k,l,Tx,Ty,Tz) &
!$omp private(cell,dist,t) &
!$omp shared(nats,dLx,dLy,dLz,buffer,nx,ny,nz,Lx,Ly,Lz)&
!$omp shared(head,Rcut,trtmp,ntype,list,nl)
do i = 1,nats
cnt = 0;
cnt = 0
cnt2 = 0
do j = -1,1
do k = -1,1
do l = -1,1
Tx = buffer(1,i)+j*dLx;
Ty = buffer(2,i)+k*dLy;
Tz = buffer(3,i)+l*dLz;
cell = 1 + floor(nx*Tx/Lx) + floor(ny*Ty/Ly)*nx + floor(nz*Tz/Lz)*nx*ny;
cell = int(1.0_dp + floor(nx*Tx/Lx) + floor(ny*Ty/Ly)*nx + floor(nz*Tz/Lz)*nx*ny)
t = head(cell);
do while(t > 0)

Expand All @@ -605,9 +613,13 @@ subroutine build_nlist_int(coords,lattice_vectors,rcut,nl,verbose)
nl%nnIz(cnt,i) = trtmp(3,t)
nl%nnType(cnt,i) = ntype(t);
nl%nnStruct(cnt,i) = ntype(t);
nl%nnStructMindist(cnt,i) = dist
!nl%nnStructMindist(cnt,i) = dist

! distvec(ntype(t)) = min(distvec(ntype(t)),dist)
!if (t <= nats) then
! cnt2 = cnt2 + 1
! nl%nnStruct(i,cnt2) = ntype(t)
!endif

endif

Expand All @@ -618,6 +630,7 @@ subroutine build_nlist_int(coords,lattice_vectors,rcut,nl,verbose)
enddo

nl%nrnnlist(i) = cnt;
!nl%nrnnStruct(i) = cnt2;
nl%nrnnStruct(i) = cnt;

! do ss = 1,nats
Expand All @@ -632,8 +645,8 @@ subroutine build_nlist_int(coords,lattice_vectors,rcut,nl,verbose)
enddo
!$omp end parallel do

deallocate(ntype)
deallocate(head)
deallocate(ntype)
deallocate(list)
deallocate(buffer) !Allocate max buffer atoms
deallocate(trtmp)
Expand Down
4 changes: 2 additions & 2 deletions src/prg_densitymatrix_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -433,7 +433,7 @@ subroutine prg_get_evalsDvalsEvects(ham_bml, threshold, hindex,&
enddo
deallocate(row)
deallocate(aux)

end subroutine prg_get_evalsDvalsEvects


Expand Down Expand Up @@ -885,7 +885,7 @@ real(dp) function fermi(e,ef,kbt)
if ((e-ef)/kbt > 100.0_dp) then
fermi = 0.0_dp
else
fermi = 1.0_dp/(1.0_dp+exp((e-ef)/(kbt)))
fermi = 1.0_dp/(1.0_dp+exp((e-ef)/(kbt)))
endif

end function fermi
Expand Down
14 changes: 7 additions & 7 deletions src/prg_system_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -726,7 +726,7 @@ subroutine prg_destroy_estr(estr)
if(allocated(estr%dvals)) deallocate(estr%dvals)
if(allocated(estr%ker)) deallocate(estr%ker)

end subroutine prg_destroy_estr
end subroutine prg_destroy_estr


!> Write system in .xyz, .dat or pdb file.
Expand All @@ -738,7 +738,7 @@ subroutine prg_write_system(system,filename,extin)
implicit none
character(len=*) :: filename
character(10) :: dummyc(10)
character(11) :: xyzformat
character(34) :: xyzformat
character(3), optional, intent(in) :: extin
character(3) :: extension
character(50) :: io_name, nametmp
Expand Down Expand Up @@ -766,17 +766,17 @@ subroutine prg_write_system(system,filename,extin)
write(io_unit,*)nats
io_message = trim(adjustl(io_name))//" Generated by the PROGRESS library"
write(io_unit,*)trim(adjustl(io_message))
xyzformat = '(A2,3F10.5)'
xyzformat = '(A2,A2,1F10.5,A2,1F10.5,A2,1F10.5)'
do i=1,nats
write(io_unit,xyzformat)system%symbol(i),system%coordinate(1,i),system%coordinate(2,i),system%coordinate(3,i)
write(io_unit,xyzformat)system%symbol(i)," ",system%coordinate(1,i)," ",system%coordinate(2,i)," ",system%coordinate(3,i)
enddo

!The following is not part of an xyz format but
!VMD, babel, xmakemol and pymol can still read this file.
write(io_unit,*)"#lattice vectors"
write(io_unit,"(3F10.5)")system%lattice_vector(1,1),system%lattice_vector(1,2),system%lattice_vector(1,3)
write(io_unit,"(3F10.5)")system%lattice_vector(2,1),system%lattice_vector(2,2),system%lattice_vector(2,3)
write(io_unit,"(3F10.5)")system%lattice_vector(3,1),system%lattice_vector(3,2),system%lattice_vector(3,3)
write(io_unit,"(3F20.5)")system%lattice_vector(1,1),system%lattice_vector(1,2),system%lattice_vector(1,3)
write(io_unit,"(3F20.5)")system%lattice_vector(2,1),system%lattice_vector(2,2),system%lattice_vector(2,3)
write(io_unit,"(3F20.5)")system%lattice_vector(3,1),system%lattice_vector(3,2),system%lattice_vector(3,3)

close(io_unit)

Expand Down

0 comments on commit 12187d5

Please sign in to comment.