Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions src/assertions_implementation.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@
module procedure assert
use iso_fortran_env, only : error_unit
use string_functions_interface, only : string
use object_interface, only : object
use object_interface, only : object_t

character(len=:), allocatable :: header, trailer
integer, parameter :: max_this_image_digits=9
Expand Down Expand Up @@ -41,7 +41,7 @@
trailer = prefix // diagnostic_data
type is(integer)
trailer = prefix // string(diagnostic_data)
class is(object)
class is(object_t)
trailer = repeat(" ", ncopies = max_data_length)
write(trailer,*) diagnostic_data
class default
Expand Down
12 changes: 6 additions & 6 deletions src/object_interface.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,9 +10,9 @@ module object_interface
implicit none

private
public :: object
public :: object_t

type, abstract :: object
type, abstract :: object_t
!! author: Damian Rouson, GSE LLC
!! category: Morfeus-FD
!! summary: Abstract type to ensure all objects extending it implement the required methods
Expand All @@ -35,23 +35,23 @@ module object_interface
pure module subroutine mark_as_defined(this)
!! Mark the object as user-defined
implicit none
class(object), intent(inout) :: this
class(object_t), intent(inout) :: this
end subroutine

pure module function user_defined(this) result(is_defined)
!! Return a boolean result indicating whether this object has been initialized since its declaration
implicit none
class(object), intent(in) :: this
class(object_t), intent(in) :: this
logical :: is_defined
end function

end interface

abstract interface
subroutine write_interface(self, unit, iotype, v_list, iostat, iomsg)
import object
import object_t
implicit none
class(object), intent(in) :: self
class(object_t), intent(in) :: self
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
Expand Down
2 changes: 1 addition & 1 deletion src/oracle_implementation.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
contains

module procedure within_tolerance
class(oracle), allocatable :: error
class(oracle_t), allocatable :: error

error = this - reference
in_tolerance = (error%norm() <= tolerance)
Expand Down
18 changes: 9 additions & 9 deletions src/oracle_interface.f90
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
module oracle_interface
!! verify actual output against expected
use object_interface, only : object
use object_interface, only : object_t
implicit none

private
public :: oracle
public :: oracle_t

type, abstract, extends(object) :: oracle
type, abstract, extends(object_t) :: oracle_t
!! define procedures for testing output values against expected values
contains
procedure(subtract_interface), deferred :: subtract
Expand All @@ -19,17 +19,17 @@ module oracle_interface

function subtract_interface(this, rhs) result(difference)
!! result has components corresponding to subtracting rhs's components fron this object's components
import oracle
import oracle_t
implicit none
class(oracle), intent(in) :: this, rhs
class(oracle), allocatable :: difference
class(oracle_t), intent(in) :: this, rhs
class(oracle_t), allocatable :: difference
end function

pure function norm_interface(this) result(norm_of_this)
!! result is a norm of the array formed by concatenating the real components of this object
import oracle
import oracle_t
implicit none
class(oracle), intent(in) :: this
class(oracle_t), intent(in) :: this
real norm_of_this
end function

Expand All @@ -42,7 +42,7 @@ module function within_tolerance(this, reference, tolerance) result(in_tolerance
!! (impure because of internal call to 'subtract' binding)
!! The existence of this procedure eliminates the need to rewrite similar code for every oracle child type.
implicit none
class(oracle), intent(in) :: this, reference
class(oracle_t), intent(in) :: this, reference
real, intent(in) :: tolerance
logical in_tolerance
end function
Expand Down
18 changes: 9 additions & 9 deletions tests/object_interface_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,13 @@ module object_interface_test
use vegetables, only: &
result_t, input_t, integer_input_t, test_item_t, & ! types
describe, it, assert_equals, assert_that, assert_not ! functions
use object_interface, only : object
use object_interface, only : object_t
implicit none

private
public :: test_object

type, extends(object) :: subject
type, extends(object_t) :: subject
contains
procedure write_formatted
end type
Expand All @@ -33,23 +33,23 @@ function test_object() result(tests)

function check_default_initialization() result(result_)
!! Verify that user_defined() is .false. for a default-initialied object
class(object), allocatable :: object_
class(object_t), allocatable :: object
type(result_t) result_

allocate(subject :: object_)
allocate(subject :: object)

result_ = assert_not(object_%user_defined())
result_ = assert_not(object%user_defined())
end function

function check_mark_as_defined() result(result_)
!! Verify that mark_as_defined results in user_defined() being .true.
class(object), allocatable :: object_
class(object_t), allocatable :: object
type(result_t) result_

allocate(subject :: object_)
allocate(subject :: object)

call object_%mark_as_defined
result_ = assert_that(object_%user_defined())
call object%mark_as_defined
result_ = assert_that(object%user_defined())
end function

subroutine write_formatted(self, unit, iotype, v_list, iostat, iomsg)
Expand Down