Skip to content

Commit

Permalink
Merge branch 'release/0.3.0'
Browse files Browse the repository at this point in the history
  • Loading branch information
szaghi committed May 2, 2017
2 parents ef18b26 + 88f6a02 commit ef89f34
Show file tree
Hide file tree
Showing 18 changed files with 377 additions and 328 deletions.
4 changes: 2 additions & 2 deletions src/lib/foodie.f90
Original file line number Diff line number Diff line change
Expand Up @@ -62,8 +62,8 @@ module foodie
!<```

use, intrinsic :: iso_fortran_env, only : stderr=>error_unit
use foodie_adt_integrand, only : integrand
use foodie_error_codes, only : ERROR_UNSUPPORTED_SCHEME
use foodie_integrand_object, only : integrand_object
use foodie_integrator_object, only : integrator_object
use foodie_integrator_adams_bashforth, only : integrator_adams_bashforth
use foodie_integrator_adams_bashforth_moulton, only : integrator_adams_bashforth_moulton
Expand All @@ -85,7 +85,7 @@ module foodie
public :: foodie_integrator
public :: foodie_integrator_class_names
public :: foodie_integrator_schemes
public :: integrand
public :: integrand_object
public :: integrator_object
public :: integrator_adams_bashforth
public :: integrator_adams_bashforth_moulton
Expand Down
92 changes: 0 additions & 92 deletions src/lib/foodie_adt_integrand.f90

This file was deleted.

128 changes: 128 additions & 0 deletions src/lib/foodie_integrand_object.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,128 @@
!< Define the abstract type *integrand* for building FOODIE ODE integrators.

module foodie_integrand_object
!< Define the abstract type *integrand* for building FOODIE ODE integrators.

use penf, only : I_P, R_P

implicit none
private
public :: integrand_object

type, abstract :: integrand_object
!< Abstract type for building FOODIE ODE integrators.
#ifdef CAF
class(*), allocatable :: dummy_to_allow_extensions[:] !< Dummy member to allow concrete extensions with coarray members.
#endif
contains
! public deferred procedures that concrete integrand-field must implement
procedure(time_derivative), pass(self), deferred, public :: t !< Time derivative, residuals.
! operators
procedure(local_error_operator), pass(lhs), deferred, public :: local_error !< `||integrand - integrand||` operator.
generic, public :: operator(.lterror.) => local_error !< Estimate local truncation error.
! +
procedure(symmetric_operator), pass(lhs), deferred, public :: integrand_add_integrand !< `+` operator.
procedure(integrand_op_real), pass(lhs), deferred, public :: integrand_add_real !< `+ real` operator.
procedure(real_op_integrand), pass(rhs), deferred, public :: real_add_integrand !< `real +` operator.
generic, public :: operator(+) => integrand_add_integrand, &
integrand_add_real, &
real_add_integrand !< Overloading `+` operator.
! *
procedure(symmetric_operator), pass(lhs), deferred, public :: integrand_multiply_integrand !< `*` operator.
procedure(integrand_op_real), pass(lhs), deferred, public :: integrand_multiply_real !< `* real` operator.
procedure(real_op_integrand), pass(rhs), deferred, public :: real_multiply_integrand !< `real *` operator.
procedure(integrand_op_real_scalar), pass(lhs), deferred, public :: integrand_multiply_real_scalar !< `* real_scalar` operator.
procedure(real_scalar_op_integrand), pass(rhs), deferred, public :: real_scalar_multiply_integrand !< `real_scalar *` operator.
generic, public :: operator(*) => integrand_multiply_integrand, &
integrand_multiply_real, &
real_multiply_integrand, &
integrand_multiply_real_scalar, &
real_scalar_multiply_integrand !< Overloading `*` operator.
! -
procedure(symmetric_operator), pass(lhs), deferred, public :: integrand_sub_integrand !< `-` operator.
procedure(integrand_op_real), pass(lhs), deferred, public :: integrand_sub_real !< `- real` operator.
procedure(real_op_integrand), pass(rhs), deferred, public :: real_sub_integrand !< `real -` operator.
generic, public :: operator(-) => integrand_sub_integrand, &
integrand_sub_real, &
real_sub_integrand !< Overloading `-` operator.
! =
procedure(assignment_integrand), pass(lhs), deferred, public :: assign_integrand !< `=` operator.
procedure(assignment_real), pass(lhs), deferred, public :: assign_real !< `= real` operator.
generic, public :: assignment(=) => assign_integrand, assign_real !< Overloading `=` assignament.
endtype integrand_object

abstract interface
!< Abstract type bound procedures necessary for implementing a concrete extension of [[integrand_object]].

function time_derivative(self, t) result(dState_dt)
!< Time derivative function of integrand class, i.e. the residuals function.
import :: integrand_object, R_P
class(integrand_object), intent(in) :: self !< Integrand field.
real(R_P), optional, intent(in) :: t !< Time.
real(R_P), allocatable :: dState_dt(:) !< Result of the time derivative function of integrand field.
endfunction time_derivative

! operators
function local_error_operator(lhs, rhs) result(error)
!< Estimate local truncation error between 2 solution approximations.
import :: integrand_object, R_P
class(integrand_object), intent(in) :: lhs !< Left hand side.
class(integrand_object), intent(in) :: rhs !< Right hand side.
real(R_P) :: error !< Error estimation.
endfunction local_error_operator

pure function integrand_op_real(lhs, rhs) result(operator_result)
!< Asymmetric type operator `integrand.op.real`.
import :: integrand_object, R_P
class(integrand_object), intent(in) :: lhs !< Left hand side.
real(R_P), intent(in) :: rhs(1:) !< Right hand side.
real(R_P), allocatable :: operator_result(:) !< Operator result.
endfunction integrand_op_real

pure function real_op_integrand(lhs, rhs) result(operator_result)
!< Asymmetric type operator `real.op.integrand`.
import :: integrand_object, R_P
class(integrand_object), intent(in) :: rhs !< Right hand side.
real(R_P), intent(in) :: lhs(1:) !< Left hand side.
real(R_P), allocatable :: operator_result(:) !< Operator result.
endfunction real_op_integrand

pure function integrand_op_real_scalar(lhs, rhs) result(operator_result)
!< Asymmetric type operator `integrand.op.real`.
import :: integrand_object, R_P
class(integrand_object), intent(in) :: lhs !< Left hand side.
real(R_P), intent(in) :: rhs !< Right hand side.
real(R_P), allocatable :: operator_result(:) !< Operator result.
endfunction integrand_op_real_scalar

pure function real_scalar_op_integrand(lhs, rhs) result(operator_result)
!< Asymmetric type operator `real.op.integrand`.
import :: integrand_object, R_P
real(R_P), intent(in) :: lhs !< Left hand side.
class(integrand_object), intent(in) :: rhs !< Right hand side.
real(R_P), allocatable :: operator_result(:) !< Operator result.
endfunction real_scalar_op_integrand

pure function symmetric_operator(lhs, rhs) result(operator_result)
!< Symmetric type operator integrand.op.integrand.
import :: integrand_object, R_P
class(integrand_object), intent(in) :: lhs !< Left hand side.
class(integrand_object), intent(in) :: rhs !< Right hand side.
real(R_P), allocatable :: operator_result(:) !< Operator result.
endfunction symmetric_operator

pure subroutine assignment_integrand(lhs, rhs)
!< Symmetric assignment integrand = integrand.
import :: integrand_object
class(integrand_object), intent(inout) :: lhs !< Left hand side.
class(integrand_object), intent(in) :: rhs !< Right hand side.
endsubroutine assignment_integrand

pure subroutine assignment_real(lhs, rhs)
!< Symmetric assignment integrand = integrand.
import :: integrand_object, R_P
class(integrand_object), intent(inout) :: lhs !< Left hand side.
real(R_P), intent(in) :: rhs(1:) !< Right hand side.
endsubroutine assignment_real
endinterface
endmodule foodie_integrand_object
10 changes: 5 additions & 5 deletions src/lib/foodie_integrator_adams_bashforth.f90
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,8 @@ module foodie_integrator_adams_bashforth
!<
!< [2] *Linear multistep method*, [wikipedia article](https://en.wikipedia.org/wiki/Linear_multistep_method).

use foodie_adt_integrand, only : integrand
use foodie_error_codes, only : ERROR_UNSUPPORTED_SCHEME
use foodie_integrand_object, only : integrand_object
use foodie_integrator_object, only : integrator_object
use penf, only : I_P, R_P

Expand Down Expand Up @@ -341,8 +341,8 @@ subroutine initialize(self, scheme)
subroutine integrate(self, U, previous, Dt, t, autoupdate)
!< Integrate field with Adams-Bashforth class scheme.
class(integrator_adams_bashforth), intent(in) :: self !< Integrator.
class(integrand), intent(inout) :: U !< Field to be integrated.
class(integrand), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand field.
class(integrand_object), intent(inout) :: U !< Field to be integrated.
class(integrand_object), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand field.
real(R_P), intent(in) :: Dt !< Time steps.
real(R_P), intent(in) :: t(:) !< Times.
logical, optional, intent(in) :: autoupdate !< Perform cyclic autoupdate of previous time steps.
Expand All @@ -359,8 +359,8 @@ subroutine integrate(self, U, previous, Dt, t, autoupdate)
subroutine update_previous(self, U, previous)
!< Cyclic update previous time steps.
class(integrator_adams_bashforth), intent(in) :: self !< Integrator.
class(integrand), intent(in) :: U !< Field to be integrated.
class(integrand), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand field.
class(integrand_object), intent(in) :: U !< Field to be integrated.
class(integrand_object), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand field.
integer(I_P) :: s !< Steps counter.

do s=1, self%steps - 1
Expand Down
6 changes: 3 additions & 3 deletions src/lib/foodie_integrator_adams_bashforth_moulton.f90
Original file line number Diff line number Diff line change
Expand Up @@ -76,8 +76,8 @@ module foodie_integrator_adams_bashforth_moulton
!<#### Bibliography
!<

use foodie_adt_integrand, only : integrand
use foodie_error_codes, only : ERROR_UNSUPPORTED_SCHEME
use foodie_integrand_object, only : integrand_object
use foodie_integrator_adams_bashforth, only : integrator_adams_bashforth
use foodie_integrator_adams_moulton, only : integrator_adams_moulton
use foodie_integrator_object, only : integrator_object
Expand Down Expand Up @@ -232,8 +232,8 @@ subroutine initialize(self, scheme)
subroutine integrate(self, U, previous, Dt, t, iterations)
!< Integrate field with Adams-Bashforth-Moulton class scheme.
class(integrator_adams_bashforth_moulton), intent(in) :: self !< Integrator.
class(integrand), intent(inout) :: U !< Field to be integrated.
class(integrand), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand.
class(integrand_object), intent(inout) :: U !< Field to be integrated.
class(integrand_object), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand.
real(R_P), intent(in) :: Dt !< Time steps.
real(R_P), intent(in) :: t(:) !< Times.
integer(I_P), intent(in), optional :: iterations !< Fixed point iterations of AM scheme.
Expand Down
12 changes: 6 additions & 6 deletions src/lib/foodie_integrator_adams_moulton.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,8 +27,8 @@ module foodie_integrator_adams_moulton
!<
!< [2] *Linear multistep method*, [wikipedia article](https://en.wikipedia.org/wiki/Linear_multistep_method).

use foodie_adt_integrand, only : integrand
use foodie_error_codes, only : ERROR_UNSUPPORTED_SCHEME
use foodie_integrand_object, only : integrand_object
use foodie_integrator_object, only : integrator_object
use penf, only : I_P, R_P

Expand Down Expand Up @@ -339,14 +339,14 @@ subroutine initialize(self, scheme)
subroutine integrate(self, U, previous, Dt, t, iterations, autoupdate)
!< Integrate field with Adams-Moulton class scheme.
class(integrator_adams_moulton), intent(in) :: self !< Integrator.
class(integrand), intent(inout) :: U !< Field to be integrated.
class(integrand), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand field.
class(integrand_object), intent(inout) :: U !< Field to be integrated.
class(integrand_object), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand field.
real(R_P), intent(in) :: Dt !< Time steps.
real(R_P), intent(in) :: t(:) !< Times.
integer(I_P), intent(in), optional :: iterations !< Fixed point iterations.
logical, intent(in), optional :: autoupdate !< Cyclic autoupdate of previous time steps flag.
logical :: autoupdate_ !< Cyclic autoupdate of previous time steps flag, dummy var.
class(integrand), allocatable :: delta !< Delta RHS for fixed point iterations.
class(integrand_object), allocatable :: delta !< Delta RHS for fixed point iterations.
integer(I_P) :: s !< Steps counter.

autoupdate_ = .true. ; if (present(autoupdate)) autoupdate_ = autoupdate
Expand Down Expand Up @@ -375,8 +375,8 @@ subroutine integrate(self, U, previous, Dt, t, iterations, autoupdate)
subroutine update_previous(self, U, previous)
!< Cyclic update previous time steps.
class(integrator_adams_moulton), intent(in) :: self !< Integrator.
class(integrand), intent(in) :: U !< Field to be integrated.
class(integrand), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand field.
class(integrand_object), intent(in) :: U !< Field to be integrated.
class(integrand_object), intent(inout) :: previous(1:) !< Previous time steps solutions of integrand field.
integer(I_P) :: s !< Steps counter.

if (self%steps>0) then
Expand Down
Loading

0 comments on commit ef89f34

Please sign in to comment.