Description
Description
I wrote an example of hashmaps usage like below:
program hashmap
use, intrinsic :: iso_fortran_env
use stdlib_hashmaps, only: hashmap_type, open_hashmap_type, chaining_hashmap_type
use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, other_type, set, get
implicit none
class(hashmap_type), allocatable :: map
allocate (open_hashmap_type :: map)
call map%init(fnv_1_hasher)
block
type(key_type) :: key
type(other_type) :: other
logical :: conflict
class(*), allocatable :: data
call set(key, "apple")
call set(other, 100)
call map%map_entry(key, other, conflict)
if (.not. conflict) then
call set(key, "apple")
call map%get_other_data(key, other)
call get(other, data)
select type (data); type is (integer(int32))
print *, data, "is mapped to apple"
end select
end if
end block
end program hashmap
When using the open_hashmap_type
, the program is abnormally terminated.
>fpm run --example hashmap
Project is up to date
Program received signal SIGSEGV: Segmentation fault - invalid memory reference.
Expected Behaviour
I expected that the program finished without error and showed the message blow:
100 is mapped to apple
The program normally finished if I changed from the open_hashmap_type
to the chaining_hashmap_type
.
- allocate (open_hashmap_type :: map)
+ allocate (chaining_hashmap_type:: map)
>fpm run --example hashmap
hashmap.f90 done.
hashmap.exe done.
[100%] Project compiled successfully.
100 is mapped to apple
Version of stdlib
Platform and Architecture
Windows 10 22H2 64bit, gfortran 11.2 bundled with quickstart Fortran on Windows, Intel Fortran 2021.5.0
Additional Information
To determine the cause of this abnormal termination, re-build and re-run with the following command:
>fpm run --compiler ifort --profile debug --example hashmap
hashmap.f90 done.
hashmap.exe done.
[100%] Project compiled successfully.
forrtl: severe (157): Program Exception - access violation
Image PC Routine Line Source
hashmap.exe 00007FF69BA69631 STDLIB_HASHMAPS_m 286 stdlib_hashmap_open.f90
hashmap.exe 00007FF69BA61B92 MAIN__ 24 hashmap.f90
hashmap.exe 00007FF69BB49DBE Unknown Unknown Unknown
hashmap.exe 00007FF69BB4A8B8 Unknown Unknown Unknown
KERNEL32.DLL 00007FFC871E7604 Unknown Unknown Unknown
ntdll.dll 00007FFC885A26A1 Unknown Unknown Unknown
Intel Fortran clarified that the error occurred on line 286 of stdlib_hashmap_open.f90
On line 286, a logical value .true.
is assigned to the optional argument exists
without the presence check, as is done on line 278.
stdlib/src/stdlib_hashmap_open.f90
Lines 277 to 288 in 2fdfab4
Line 286 can be modified to make the open_hashmap_type
safer and more robust.
- exists = .true.
+ if ( present(exists) ) exists = .true.