Skip to content

Commit

Permalink
Merge pull request #41 from BerkeleyLab/fix-assertions
Browse files Browse the repository at this point in the history
Fix and improve assertions
  • Loading branch information
rouson authored Feb 21, 2025
2 parents d6e8f76 + bf28f49 commit 6c8f40c
Show file tree
Hide file tree
Showing 6 changed files with 32 additions and 22 deletions.
Original file line number Diff line number Diff line change
@@ -1,14 +1,17 @@
! Copyright (c) 2024, The Regents of the University of California and Sourcery Institute
! Terms of use are as specified in LICENSE.txt

#include "assert_macros.h"

submodule(julienne_bin_m) julienne_bin_s
use assert_m, only : assert, intrinsic_array_t
use assert_m
implicit none

contains

module procedure construct

call assert( num_items>=num_bins, "bin_s(construct): num_items>=num_bins", intrinsic_array_t([num_items,num_bins]))
call_assert_diagnose( num_items>=num_bins, "bin_s(construct): num_items>=num_bins", intrinsic_array_t([num_items,num_bins]))

associate( remainder => mod(num_items, num_bins), items_per_bin => num_items/num_bins)

Expand Down
Original file line number Diff line number Diff line change
@@ -1,8 +1,11 @@
! Copyright (c) 2024, The Regents of the University of California and Sourcery Institute
! Terms of use are as specified in LICENSE.txt

#include "assert_macros.h"

submodule(julienne_file_m) julienne_file_s
use iso_fortran_env, only : iostat_end, iostat_eor, output_unit
use assert_m, only : assert
use assert_m
implicit none

contains
Expand All @@ -19,11 +22,11 @@

integer file_unit, io_status, l

call assert(allocated(self%lines_), "file_t%write_lines: allocated(self%lines_)")
call_assert(allocated(self%lines_))

if (present(file_name)) then
open(newunit=file_unit, file=file_name%string(), form='formatted', status='unknown', iostat=io_status, action='write')
call assert(io_status==0,"write_lines: io_status==0 after 'open' statement", file_name%string())
call_assert_diagnose(io_status==0,"write_lines: io_status==0 after 'open' statement", file_name%string())
else
file_unit = output_unit
end if
Expand All @@ -48,7 +51,7 @@
integer, allocatable :: lengths(:)

open(newunit=file_unit, file=file_name%string(), form='formatted', status='old', iostat=io_status, action='read')
call assert(io_status==0,"from_file_with_string_name: io_status==0 after 'open' statement", file_name%string())
call_assert_diagnose(io_status==0,"from_file_with_string_name: io_status==0 after 'open' statement", file_name%string())

lengths = line_lengths(file_unit)

Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,9 @@
! Copyright (c) 2024, The Regents of the University of California and Sourcery Institute
! Terms of use are as specified in LICENSE.txt
#include "assert_macros.h"

submodule(julienne_string_m) julienne_string_s
use assert_m, only : assert, intrinsic_array_t
use assert_m
implicit none

integer, parameter :: integer_width_supremum = 11, default_real_width_supremum = 20, double_precision_width_supremum = 25
Expand Down Expand Up @@ -183,7 +185,7 @@
module procedure get_real
character(len=:), allocatable :: raw_line, string_value

call assert(key==self%get_json_key(), "string_s(get_real): key==self%get_json_key()", key)
call_assert_diagnose(key==self%get_json_key(), "string_s(get_real): key==self%get_json_key()", key)

raw_line = self%string()
associate(text_after_colon => raw_line(index(raw_line, ':')+1:))
Expand All @@ -202,7 +204,7 @@
module procedure get_double_precision
character(len=:), allocatable :: raw_line, string_value

call assert(key==self%get_json_key(), "string_s(get_double_precision): key==self%get_json_key()", key)
call_assert_diagnose(key==self%get_json_key(), "string_s(get_double_precision): key==self%get_json_key()", key)

raw_line = self%string()
associate(text_after_colon => raw_line(index(raw_line, ':')+1:))
Expand Down Expand Up @@ -239,7 +241,7 @@
character(len=:), allocatable :: raw_line
integer i, comma, opening_quotes, closing_quotes

call assert(key==self%get_json_key(), "key==self%get_string_json()", key)
call_assert_diagnose(key==self%get_json_key(), "key==self%get_string_json()", key)

raw_line = self%string()

Expand Down Expand Up @@ -267,7 +269,7 @@

character(len=:), allocatable :: raw_line

call assert(key==self%get_json_key(), "key==self%get_string_json()", key)
call_assert_diagnose(key==self%get_json_key(), "key==self%get_string_json()", key)

raw_line = self%string()
associate(text_after_colon => raw_line(index(raw_line, ':')+1:))
Expand All @@ -291,7 +293,7 @@
module procedure get_logical
character(len=:), allocatable :: raw_line, string_value

call assert(key==self%get_json_key(), "string_s(get_logical): key==self%get_json_key()", key)
call_assert_diagnose(key==self%get_json_key(), "string_s(get_logical): key==self%get_json_key()", key)

raw_line = self%string()
associate(text_after_colon => raw_line(index(raw_line, ':')+1:))
Expand All @@ -301,8 +303,7 @@
else
string_value = trim(adjustl((text_after_colon(:trailing_comma-1))))
end if
call assert(string_value=="true" .or. string_value=="false", &
'string_s(get_logical): string_value=="true" .or. string_value="false"', string_value)
call_assert_diagnose(string_value=="true" .or. string_value=="false", 'string_s(get_logical): string_value=="true" .or. string_value="false"', string_value)
value_ = string_value == "true"
end associate
end associate
Expand All @@ -312,7 +313,7 @@
module procedure get_integer
character(len=:), allocatable :: raw_line, string_value

call assert(key==self%get_json_key(), "string_s(get_logical): key==self%get_json_key()", key)
call_assert_diagnose(key==self%get_json_key(), "string_s(get_logical): key==self%get_json_key()", key)

raw_line = self%string()
associate(text_after_colon => raw_line(index(raw_line, ':')+1:))
Expand Down Expand Up @@ -353,7 +354,7 @@
real, allocatable :: real_array(:)
integer i

call assert(key==self%get_json_key(), "string_s(get_{real,integer}_array): key==self%get_json_key()", key)
call_assert_diagnose(key==self%get_json_key(), "string_s(get_{real,integer}_array): key==self%get_json_key()", key)

raw_line = self%string()
associate(colon => index(raw_line, ":"))
Expand All @@ -377,7 +378,7 @@
double precision, allocatable :: double_precision_array(:)
integer i

call assert(key==self%get_json_key(), "string_s(get_{double precision,integer}_array): key==self%get_json_key()", key)
call_assert_diagnose(key==self%get_json_key(), "string_s(get_{double precision,integer}_array): key==self%get_json_key()", key)

raw_line = self%string()
associate(colon => index(raw_line, ":"))
Expand Down
4 changes: 2 additions & 2 deletions src/julienne/julienne_test_diagnosis_m.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,11 +47,11 @@ elemental module function test_passed(self) result(passed)
logical passed
end function

elemental module function diagnostics_string(self) result(string)
elemental module function diagnostics_string(self) result(string_)
!! The result is a string describing the condition(s) that caused a test failure
implicit none
class(test_diagnosis_t), intent(in) :: self
type(string_t) string
type(string_t) string_
end function

end interface
Expand Down
2 changes: 1 addition & 1 deletion src/julienne/julienne_test_diagnosis_s.F90
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,6 @@

module procedure diagnostics_string
call_assert(allocated(self%diagnostics_string_))
string = string_t(self%diagnostics_string_)
string_ = string_t(self%diagnostics_string_)
end procedure
end submodule julienne_test_diagnosis_s
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
! Copyright (c) 2024, The Regents of the University of California and Sourcery Institute
! Terms of use are as specified in LICENSE.txt

#include "assert_macros.h"

submodule(julienne_vector_test_description_m) julienne_vector_test_description_s
use assert_m, only : assert
use assert_m
implicit none

contains
Expand All @@ -23,7 +26,7 @@

module procedure run
associate(vector_result => self%vector_function_strategy_%vector_function())
call assert(size(self%description_vector_)==size(vector_result), "julienne_vector_test_description_s: size match")
call_assert(size(self%description_vector_)==size(vector_result))
test_results = test_result_t(self%description_vector_, vector_result)
end associate
end procedure
Expand Down

0 comments on commit 6c8f40c

Please sign in to comment.