10
0
mirror of https://github.com/LCPQ/quantum_package synced 2024-06-26 07:02:14 +02:00

mmap seems OK

This commit is contained in:
Anthony Scemama 2016-06-16 12:47:08 +02:00
parent 7c523340a2
commit ff391db161
9 changed files with 125 additions and 126 deletions

View File

@ -223,6 +223,7 @@ END_PROVIDER
ao_bi_elec_integral_beta_tmp = 0.d0
!$OMP DO SCHEDULE(dynamic)
!DIR$ NOVECTOR
do i8=0_8,ao_integrals_map%map_size
n_elements = n_elements_max
call get_cache_map(ao_integrals_map,i8,keys,values,n_elements)

View File

@ -1,2 +1 @@
Pseudo Bitmask ZMQ

View File

@ -351,7 +351,6 @@ BEGIN_PROVIDER [ logical, ao_bielec_integrals_in_map ]
real :: map_mb
if (read_ao_integrals) then
integer :: load_ao_integrals
print*,'Reading the AO integrals'
call map_load_from_disk(trim(ezfio_filename)//'/work/ao_ints',ao_integrals_map)
print*, 'AO integrals provided'

View File

@ -227,9 +227,11 @@ subroutine ao_bielec_integrals_in_map_collector
control = get_ao_map_size(ao_integrals_map)
if (control /= accu) then
print *, irp_here, 'Control : ', control
print *, 'Accu : ', accu
print *, 'Some integrals were lost during the parallel computation. (2)'
print *, ''
print *, irp_here
print *, 'Control : ', control
print *, 'Accu : ', accu
print *, 'Some integrals were lost during the parallel computation.'
print *, 'Try to reduce the number of threads.'
stop
endif

View File

@ -13,7 +13,7 @@ BEGIN_PROVIDER [ type(map_type), ao_integrals_map ]
call bielec_integrals_index(ao_num,ao_num,ao_num,ao_num,key_max)
sze = key_max
call map_init(ao_integrals_map,sze)
print*, 'AO map initialized'
print*, 'AO map initialized : ', sze
END_PROVIDER
subroutine bielec_integrals_index(i,j,k,l,i1)

View File

@ -28,7 +28,6 @@ BEGIN_PROVIDER [ logical, mo_bielec_integrals_in_map ]
mo_bielec_integrals_in_map = .True.
if (read_mo_integrals) then
integer :: load_mo_integrals
print*,'Reading the MO integrals'
call map_load_from_disk(trim(ezfio_filename)//'/work/mo_ints',mo_integrals_map)
print*, 'MO integrals provided'

View File

@ -0,0 +1 @@

View File

@ -0,0 +1,115 @@
subroutine map_save_to_disk(filename,map)
use map_module
use mmap_module
implicit none
character*(*), intent(in) :: filename
type(map_type), intent(inout) :: map
type(c_ptr) :: c_pointer(3)
integer :: fd(3)
integer*8 :: i,k
integer :: j
if (map % consolidated) then
stop 'map already consolidated'
endif
call mmap(trim(filename)//'_consolidated_idx', (/ map % map_size + 2_8 /), 8, fd(1), .False., c_pointer(1))
call c_f_pointer(c_pointer(1),map % consolidated_idx, (/ map % map_size +2_8/))
call mmap(trim(filename)//'_consolidated_key', (/ map % n_elements /), cache_key_kind, fd(2), .False., c_pointer(2))
call c_f_pointer(c_pointer(2),map % consolidated_key, (/ map % n_elements /))
call mmap(trim(filename)//'_consolidated_value', (/ map % n_elements /), integral_kind, fd(3), .False., c_pointer(3))
call c_f_pointer(c_pointer(3),map % consolidated_value, (/ map % n_elements /))
if (.not.associated(map%consolidated_key)) then
stop 'cannot consolidate map : consolidated_key not associated'
endif
if (.not.associated(map%consolidated_value)) then
stop 'cannot consolidate map : consolidated_value not associated'
endif
if (.not.associated(map%consolidated_idx)) then
stop 'cannot consolidate map : consolidated_idx not associated'
endif
call map_sort(map)
k = 1_8
do i=0_8, map % map_size
map % consolidated_idx (i+1) = k
do j=1, map % map(i) % n_elements
map % consolidated_value(k) = map % map(i) % value(j)
map % consolidated_key (k) = map % map(i) % key(j)
k = k+1_8
enddo
deallocate(map % map(i) % value)
deallocate(map % map(i) % key)
map % map(i) % value => map % consolidated_value ( map % consolidated_idx (i+1) :)
map % map(i) % key => map % consolidated_key ( map % consolidated_idx (i+1) :)
enddo
map % consolidated_idx (map % map_size + 2_8) = k
map % consolidated = .True.
! call munmap( (/ map % map_size + 2_8 /), 8, fd(1), c_pointer(1))
! call mmap(trim(filename)//'_consolidated_idx', (/ map % map_size + 2_8 /), 8, fd(1), .True., c_pointer(1))
! call c_f_pointer(c_pointer(1),map % consolidated_idx, (/ map % map_size +2_8/))
!
! call munmap( (/ map % n_elements /), cache_key_kind, fd(2), c_pointer(2))
! call mmap(trim(filename)//'_consolidated_key', (/ map % n_elements /), cache_key_kind, fd(2), .True., c_pointer(2))
! call c_f_pointer(c_pointer(2),map % consolidated_key, (/ map % n_elements /))
!
! call munmap( (/ map % n_elements /), integral_kind, fd(3), c_pointer(3))
! call mmap(trim(filename)//'_consolidated_value', (/ map % n_elements /), integral_kind, fd(3), .True., c_pointer(3))
! call c_f_pointer(c_pointer(3),map % consolidated_value, (/ map % n_elements /))
end
subroutine map_load_from_disk(filename,map)
use map_module
use mmap_module
implicit none
character*(*), intent(in) :: filename
type(map_type), intent(inout) :: map
type(c_ptr) :: c_pointer(3)
integer :: fd(3)
integer*8 :: i,k
integer :: n_elements
if (map % consolidated) then
stop 'map already consolidated'
endif
call mmap(trim(filename)//'_consolidated_idx', (/ map % map_size + 2_8 /), 8, fd(1), .True., c_pointer(1))
call c_f_pointer(c_pointer(1),map % consolidated_idx, (/ map % map_size + 2_8/))
map% n_elements = map % consolidated_idx (map % map_size+2_8)-1
call mmap(trim(filename)//'_consolidated_key', (/ map % n_elements /), cache_key_kind, fd(2), .True., c_pointer(2))
call c_f_pointer(c_pointer(2),map % consolidated_key, (/ map % n_elements /))
call mmap(trim(filename)//'_consolidated_value', (/ map % n_elements /), integral_kind, fd(3), .True., c_pointer(3))
call c_f_pointer(c_pointer(3),map % consolidated_value, (/ map % n_elements /))
k = 1_8
do i=0_8, map % map_size
deallocate(map % map(i) % value)
deallocate(map % map(i) % key)
map % map(i) % value => map % consolidated_value ( map % consolidated_idx (i+1) :)
map % map(i) % key => map % consolidated_key ( map % consolidated_idx (i+1) :)
map % map(i) % sorted = .True.
n_elements = map % consolidated_idx (i+2) - k
k = map % consolidated_idx (i+2)
map % map(i) % map_size = n_elements
map % map(i) % n_elements = n_elements
enddo
map % n_elements = k-1
map % sorted = .True.
map % consolidated = .True.
end

View File

@ -39,7 +39,7 @@ module map_module
end type cache_map_type
type map_type
type(cache_map_type), pointer :: map(:)
type(cache_map_type), allocatable :: map(:)
real(integral_kind), pointer :: consolidated_value(:)
integer(cache_key_kind), pointer :: consolidated_key(:)
integer*8, pointer :: consolidated_idx(:)
@ -850,126 +850,9 @@ subroutine get_cache_map(map,map_idx,keys,values,n_elements)
n_elements = map%map(map_idx)%n_elements
do i=1,n_elements
keys(i) = map%map(map_idx)%key(i) + shift
keys(i) = map%map(map_idx)%key(i) + shift
values(i) = map%map(map_idx)%value(i)
enddo
end
subroutine map_save_to_disk(filename,map)
use map_module
use mmap_module
implicit none
character*(*), intent(in) :: filename
type(map_type), intent(inout) :: map
type(c_ptr) :: c_pointer(3)
integer :: fd(3)
integer*8 :: i,k
integer :: j
if (map % consolidated) then
stop 'map already consolidated'
endif
call mmap(trim(filename)//'_consolidated_idx', (/ map % map_size + 2_8 /), 8, fd(1), .False., c_pointer(1))
call c_f_pointer(c_pointer(1),map % consolidated_idx, (/ map % map_size +2_8/))
call mmap(trim(filename)//'_consolidated_key', (/ map % n_elements /), cache_key_kind, fd(2), .False., c_pointer(2))
call c_f_pointer(c_pointer(2),map % consolidated_key, (/ map % n_elements /))
call mmap(trim(filename)//'_consolidated_value', (/ map % n_elements /), integral_kind, fd(3), .False., c_pointer(3))
call c_f_pointer(c_pointer(3),map % consolidated_value, (/ map % n_elements /))
if (.not.associated(map%consolidated_key)) then
stop 'cannot consolidate map : consolidated_key not associated'
endif
if (.not.associated(map%consolidated_value)) then
stop 'cannot consolidate map : consolidated_value not associated'
endif
if (.not.associated(map%consolidated_idx)) then
stop 'cannot consolidate map : consolidated_idx not associated'
endif
call map_sort(map)
k = 1_8
do i=0_8, map % map_size
map % consolidated_idx (i+1) = k
do j=1, map % map(i) % n_elements
map % consolidated_value(k) = map % map(i) % value(j)
map % consolidated_key (k) = map % map(i) % key(j)
k = k+1_8
enddo
deallocate(map % map(i) % value)
deallocate(map % map(i) % key)
map % map(i) % value => map % consolidated_value ( map % consolidated_idx (i+1) :)
map % map(i) % key => map % consolidated_key ( map % consolidated_idx (i+1) :)
enddo
map % consolidated_idx (map % map_size + 2_8) = k
map % consolidated = .True.
! call munmap( (/ map % map_size + 2_8 /), 8, fd(1), c_pointer(1))
! call mmap(trim(filename)//'_consolidated_idx', (/ map % map_size + 2_8 /), 8, fd(1), .True., c_pointer(1))
! call c_f_pointer(c_pointer(1),map % consolidated_idx, (/ map % map_size +2_8/))
!
! call munmap( (/ map % n_elements /), cache_key_kind, fd(2), c_pointer(2))
! call mmap(trim(filename)//'_consolidated_key', (/ map % n_elements /), cache_key_kind, fd(2), .True., c_pointer(2))
! call c_f_pointer(c_pointer(2),map % consolidated_key, (/ map % n_elements /))
!
! call munmap( (/ map % n_elements /), integral_kind, fd(3), c_pointer(3))
! call mmap(trim(filename)//'_consolidated_value', (/ map % n_elements /), integral_kind, fd(3), .True., c_pointer(3))
! call c_f_pointer(c_pointer(3),map % consolidated_value, (/ map % n_elements /))
end
subroutine map_load_from_disk(filename,map)
use map_module
use mmap_module
implicit none
character*(*), intent(in) :: filename
type(map_type), intent(inout) :: map
type(c_ptr) :: c_pointer(3)
integer :: fd(3)
integer*8 :: i,k
integer :: n_elements
if (map % consolidated) then
stop 'map already consolidated'
endif
call mmap(trim(filename)//'_consolidated_idx', (/ map % map_size + 2_8 /), 8, fd(1), .True., c_pointer(1))
call c_f_pointer(c_pointer(1),map % consolidated_idx, (/ map % map_size + 2_8/))
map% n_elements = map % consolidated_idx (map % map_size+2_8)-1
call mmap(trim(filename)//'_consolidated_key', (/ map % n_elements /), cache_key_kind, fd(2), .True., c_pointer(2))
call c_f_pointer(c_pointer(2),map % consolidated_key, (/ map % n_elements /))
call mmap(trim(filename)//'_consolidated_value', (/ map % n_elements /), integral_kind, fd(3), .True., c_pointer(3))
call c_f_pointer(c_pointer(3),map % consolidated_value, (/ map % n_elements /))
k = 1_8
do i=0_8, map % map_size
deallocate(map % map(i) % value)
deallocate(map % map(i) % key)
map % map(i) % value => map % consolidated_value ( map % consolidated_idx (i+1) :)
map % map(i) % key => map % consolidated_key ( map % consolidated_idx (i+1) :)
map % map(i) % sorted = .True.
n_elements = map % consolidated_idx (i+2) - k
k = map % consolidated_idx (i+2)
map % map(i) % map_size = n_elements
map % map(i) % n_elements = n_elements
enddo
map % n_elements = k-1
map % sorted = .True.
map % consolidated = .True.
end