Skip to content

Commit 817633f

Browse files
committed
Improved error messages
Changed error messages to use error stop, module name and procedure name. [ticket: X]
1 parent 21c9fc4 commit 817633f

File tree

2 files changed

+15
-8
lines changed

2 files changed

+15
-8
lines changed

src/stdlib_hashmap_open.f90

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -559,11 +559,10 @@ module subroutine map_open_entry(map, key, other, conflict)
559559

560560
subroutine allocate_open_map_entry(map, bucket)
561561
! allocates a hash bucket
562-
type(open_hashmap_type), intent(inout) :: map
563-
564-
type(open_map_entry_type), pointer, intent(out) :: bucket
562+
type(open_hashmap_type), intent(inout) :: map type(open_map_entry_type), pointer, intent(out) :: bucket
565563
type(open_map_entry_list), pointer :: free_list
566564
type(open_map_entry_pool), pointer :: pool
565+
character(*), parameter :: procedure_name = "ALLOCATE_MAP_ENTRY"
567566

568567
pool => map % cache
569568
map % num_entries = map % num_entries + 1
@@ -574,7 +573,9 @@ subroutine allocate_open_map_entry(map, bucket)
574573
map % free_list => free_list % next
575574
free_list % target => null()
576575
free_list % next => null()
577-
if (bucket % inmap == 0) stop "bucket % inmap == 0"
576+
if (bucket % inmap <= 0) &
577+
error stop submodule_name // " % " // procedure_name // &
578+
": Failed consistency check: BUCKET % INMAP <= 0"
578579
map % num_free = map % num_free - 1
579580
else
580581
! Get hash bucket from pool
@@ -589,7 +590,9 @@ subroutine allocate_open_map_entry(map, bucket)
589590
size( map % inverse, kind=int_index ) ) then
590591
call expand_inverse( map )
591592
end if
592-
if ( map % num_entries == 0 ) stop "MAP % NUM_ENTRIES == 0."
593+
if ( map % num_entries <= 0 ) &
594+
error stop submodule_name // " % " // procedure_name // &
595+
": Failed consistency check: MAP % NUM_ENTRIES <= 0."
593596
bucket % inmap = map % num_entries
594597
end if
595598

src/stdlib_hashmap_wrappers.f90

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,8 @@ module stdlib_hashmap_wrappers
5555
bits_char = character_storage_size, &
5656
bytes_char = bits_char/bits_int8
5757

58+
character(*), parameter :: module_name = "STDLIB_HASHMAP_WRAPPERS"
59+
5860
type :: key_type
5961
!! Version: Experimental
6062
!!
@@ -196,6 +198,7 @@ subroutine get_char_key( key, value )
196198
!! value - the contents of key mapped to a CHARACTER string
197199
type(key_type), intent(in) :: key
198200
character(:), allocatable, intent(out) :: value
201+
character(*), parameter :: procedure_name = "GET"
199202

200203
integer(int64) :: key_as_char
201204
integer(int64) :: key_size
@@ -206,9 +209,10 @@ subroutine get_char_key( key, value )
206209
key_as_char = key_size
207210
case(2)
208211
if ( iand( key_size, 1_int64 ) > 0 ) then
209-
error stop "Internal Error at stdlib_hashmaps:&
210-
& System uses 2 bytes per character, so&
211-
& key_size can't be an odd number"
212+
error stop module_name // " % " procedure_name // &
213+
": Internal Error at stdlib_hashmaps: " // &
214+
"System uses 2 bytes per character, so " // &
215+
"key_size can't be an odd number"
212216
end if
213217
key_as_char = ishft( key_size, -1 )
214218
case(4)

0 commit comments

Comments
 (0)