Skip to content

Commit

Permalink
Merge branch 'release/0.2.1'
Browse files Browse the repository at this point in the history
  • Loading branch information
szaghi committed Apr 20, 2017
2 parents d6f322d + d2499f9 commit ec620bb
Show file tree
Hide file tree
Showing 24 changed files with 782 additions and 100 deletions.
57 changes: 52 additions & 5 deletions src/lib/abstract_objects/wenoof_base_object.f90
Original file line number Diff line number Diff line change
Expand Up @@ -15,10 +15,17 @@ module wenoof_base_object

type, abstract :: base_object_constructor
!< Abstract base object constructor.
integer(I_P) :: S=0_I_P !< Stencils dimension.
real(R_P) :: eps=EPS_DEF !< Small epsilon to avoid division by zero.
integer(I_P) :: S=0_I_P !< Stencils dimension.
real(R_P) :: eps=EPS_DEF !< Small epsilon to avoid division by zero.
contains
! public methods
procedure, pass(self) :: create => create_base_object_constructor
! public operators
generic :: assignment(=) => constr_assign_constr !< `=` overloading.
! public deferred methods
procedure(constr_assign_constr_interface), pass(lhs), deferred :: constr_assign_constr !< `=` operator.
! public non overridable methods
procedure, pass(lhs), non_overridable :: assign_ => assign_constr_ !< Assign object.
endtype base_object_constructor

type, abstract :: base_object
Expand All @@ -28,17 +35,38 @@ module wenoof_base_object
integer(I_P) :: S=0_I_P !< Stencils dimension.
real(R_P) :: eps=EPS_DEF !< Small epsilon to avoid division by zero.
contains
! public operators
generic :: assignment(=) => object_assign_object !< `=` overloading.
! public deferred methods
procedure(create_interface), pass(self), deferred :: create !< Create object.
procedure(description_interface), pass(self), deferred :: description !< Return object string-description.
procedure(destroy_interface), pass(self), deferred :: destroy !< Destroy object.
procedure(create_interface), pass(self), deferred :: create !< Create object.
procedure(description_interface), pass(self), deferred :: description !< Return object string-description.
procedure(destroy_interface), pass(self), deferred :: destroy !< Destroy object.
procedure(object_assign_object_interface), pass(lhs), deferred :: object_assign_object !< `=` operator.
! public non overridable methods
procedure, pass(lhs), non_overridable :: assign_ !< Assign object.
procedure, pass(self), non_overridable :: create_ !< Create object.
procedure, pass(self), non_overridable :: destroy_ !< Destroy object.
endtype base_object

abstract interface
!< Abstract interfaces of [[base_object_constructor]].
subroutine constr_assign_constr_interface(lhs, rhs)
!< `=` operator.
import :: base_object_constructor
class(base_object_constructor), intent(inout) :: lhs !< Left hand side.
class(base_object_constructor), intent(in) :: rhs !< Right hand side.
endsubroutine constr_assign_constr_interface
endinterface

abstract interface
!< Abstract interfaces of [[base_object]].
subroutine object_assign_object_interface(lhs, rhs)
!< `=` operator.
import :: base_object
class(base_object), intent(inout) :: lhs !< Left hand side.
class(base_object), intent(in) :: rhs !< Right hand side.
endsubroutine object_assign_object_interface

subroutine create_interface(self, constructor)
!< Create object.
!<
Expand Down Expand Up @@ -77,9 +105,28 @@ subroutine create_base_object_constructor(self, S, eps)
if (present(eps)) self%eps = eps
endsubroutine create_base_object_constructor

! public non overridable methods
subroutine assign_constr_(lhs, rhs)
!< Assign object constructor.
class(base_object_constructor), intent(inout) :: lhs !< Left hand side.
class(base_object_constructor), intent(in) :: rhs !< Right hand side.

lhs%S = rhs%S
lhs%eps = rhs%eps
endsubroutine assign_constr_

! base object

! public non overridable methods
subroutine assign_(lhs, rhs)
!< Assign object.
class(base_object), intent(inout) :: lhs !< Left hand side.
class(base_object), intent(in) :: rhs !< Right hand side.

lhs%S = rhs%S
lhs%eps = rhs%eps
endsubroutine assign_

subroutine create_(self, constructor)
!< Create object.
class(base_object), intent(inout) :: self !< Object.
Expand Down
2 changes: 0 additions & 2 deletions src/lib/abstract_objects/wenoof_interpolations_object.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,6 @@ module wenoof_interpolations_object

type, extends(base_object_constructor), abstract :: interpolations_object_constructor
!< Abstract interpolations object constructor.
real(R_P), allocatable :: stencil(:) !< Stencil used for interpolation, [1-S:S-1].
real(R_P) :: x_target !< Coordinate of the interpolation point.
endtype interpolations_object_constructor

type, extends(base_object), abstract :: interpolations_object
Expand Down
2 changes: 1 addition & 1 deletion src/lib/abstract_objects/wenoof_weights_object.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module wenoof_weights_object
public :: weights_object
public :: weights_object_constructor

type, extends(base_object_constructor) :: weights_object_constructor
type, extends(base_object_constructor), abstract :: weights_object_constructor
!< Abstract weights object constructor.
endtype weights_object_constructor

Expand Down
35 changes: 29 additions & 6 deletions src/lib/concrete_objects/wenoof_alpha_int_js.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module wenoof_alpha_int_js

use penf, only : I_P, R_P, str
use wenoof_alpha_object, only : alpha_object, alpha_object_constructor
use wenoof_base_object, only : base_object_constructor
use wenoof_base_object, only : base_object, base_object_constructor

implicit none
private
Expand All @@ -16,6 +16,9 @@ module wenoof_alpha_int_js

type, extends(alpha_object_constructor) :: alpha_int_js_constructor
!< Jiang-Shu alpha object constructor.
contains
! public deferred methods
procedure, pass(lhs) :: constr_assign_constr !< `=` operator.
endtype alpha_int_js_constructor

type, extends(alpha_object) :: alpha_int_js
Expand All @@ -25,14 +28,26 @@ module wenoof_alpha_int_js
!< ENO Schemes*, Guang-Shan Jiang, Chi-Wang Shu, JCP, 1996, vol. 126, pp. 202--228, doi:10.1006/jcph.1996.0130.
contains
! public deferred methods
procedure, pass(self) :: create !< Create alpha.
procedure, pass(self) :: compute_int !< Compute alpha (interpolate).
procedure, pass(self) :: compute_rec !< Compute alpha (reconstruct).
procedure, pass(self) :: description !< Return object string-description.
procedure, pass(self) :: destroy !< Destroy alpha.
procedure, pass(self) :: create !< Create alpha.
procedure, pass(self) :: compute_int !< Compute alpha (interpolate).
procedure, pass(self) :: compute_rec !< Compute alpha (reconstruct).
procedure, pass(self) :: description !< Return object string-description.
procedure, pass(self) :: destroy !< Destroy alpha.
procedure, pass(lhs) :: object_assign_object !< `=` operator.
endtype alpha_int_js

contains
! constructor

! deferred public methods
subroutine constr_assign_constr(lhs, rhs)
!< `=` operator.
class(alpha_int_js_constructor), intent(inout) :: lhs !< Left hand side.
class(base_object_constructor), intent(in) :: rhs !< Right hand side.

call lhs%assign_(rhs=rhs)
endsubroutine constr_assign_constr

! deferred public methods
subroutine create(self, constructor)
!< Create alpha.
Expand Down Expand Up @@ -85,4 +100,12 @@ elemental subroutine destroy(self)

call self%destroy_
endsubroutine destroy

subroutine object_assign_object(lhs, rhs)
!< `=` operator.
class(alpha_int_js), intent(inout) :: lhs !< Left hand side.
class(base_object), intent(in) :: rhs !< Right hand side.

call lhs%assign_(rhs=rhs)
endsubroutine object_assign_object
endmodule wenoof_alpha_int_js
50 changes: 43 additions & 7 deletions src/lib/concrete_objects/wenoof_alpha_int_m.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module wenoof_alpha_int_m
use wenoof_alpha_object, only : alpha_object, alpha_object_constructor
use wenoof_alpha_rec_js, only : alpha_rec_js, alpha_rec_js_constructor
use wenoof_alpha_rec_z, only : alpha_rec_z, alpha_rec_z_constructor
use wenoof_base_object, only : base_object_constructor
use wenoof_base_object, only : base_object, base_object_constructor

implicit none
private
Expand All @@ -20,6 +20,9 @@ module wenoof_alpha_int_m
type, extends(alpha_object_constructor) :: alpha_int_m_constructor
!< Henrick alpha (non linear weights) object constructor.
character(len=:), allocatable :: base_type !< Base alpha coefficient type.
contains
! public deferred methods
procedure, pass(lhs) :: constr_assign_constr !< `=` operator.
endtype alpha_int_m_constructor

type, extends(alpha_object) :: alpha_int_m
Expand All @@ -28,17 +31,33 @@ module wenoof_alpha_int_m
!< @note The provided alpha implements the alpha coefficients defined in *Mapped weighted essentially non-oscillatory schemes:
!< Achieving optimal order near critical points*, Andrew K. Henrick, Tariq D. Aslam, Joseph M. Powers,
!< JCP, 2005, vol. 207, pp. 542-567, doi:10.1016/j.jcp.2005.01.023.
class(alpha_object), allocatable :: alpha_base !< Base alpha to be re-mapped.
class(alpha_object), allocatable :: alpha_base !< Base alpha to be re-mapped.
contains
! public deferred methods
procedure, pass(self) :: create !< Create alpha.
procedure, pass(self) :: compute_int !< Compute alpha (interpolate).
procedure, pass(self) :: compute_rec !< Compute alpha (reconstruct).
procedure, pass(self) :: description !< Return object string-description.
procedure, pass(self) :: destroy !< Destroy alpha.
procedure, pass(self) :: create !< Create alpha.
procedure, pass(self) :: compute_int !< Compute alpha (interpolate).
procedure, pass(self) :: compute_rec !< Compute alpha (reconstruct).
procedure, pass(self) :: description !< Return object string-description.
procedure, pass(self) :: destroy !< Destroy alpha.
procedure, pass(lhs) :: object_assign_object !< `=` operator.
endtype alpha_int_m

contains
! constructor

! deferred public methods
subroutine constr_assign_constr(lhs, rhs)
!< `=` operator.
class(alpha_int_m_constructor), intent(inout) :: lhs !< Left hand side.
class(base_object_constructor), intent(in) :: rhs !< Right hand side.

call lhs%assign_(rhs=rhs)
select type(rhs)
type is(alpha_int_m_constructor)
if (allocated(rhs%base_type)) lhs%base_type = rhs%base_type
endselect
endsubroutine constr_assign_constr

! deferred public methods
subroutine create(self, constructor)
!< Create alpha.
Expand Down Expand Up @@ -125,4 +144,21 @@ elemental subroutine destroy(self)
call self%destroy_
if (allocated(self%alpha_base)) deallocate(self%alpha_base)
endsubroutine destroy

subroutine object_assign_object(lhs, rhs)
!< `=` operator.
class(alpha_int_m), intent(inout) :: lhs !< Left hand side.
class(base_object), intent(in) :: rhs !< Right hand side.

call lhs%assign_(rhs=rhs)
select type(rhs)
type is(alpha_int_m)
if (allocated(rhs%alpha_base)) then
if (.not.allocated(lhs%alpha_base)) allocate(lhs%alpha_base, mold=rhs%alpha_base)
lhs%alpha_base = rhs%alpha_base
else
if (allocated(lhs%alpha_base)) deallocate(lhs%alpha_base)
endif
endselect
endsubroutine object_assign_object
endmodule wenoof_alpha_int_m
35 changes: 29 additions & 6 deletions src/lib/concrete_objects/wenoof_alpha_int_z.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module wenoof_alpha_int_z

use penf, only : I_P, R_P, str
use wenoof_alpha_object, only : alpha_object, alpha_object_constructor
use wenoof_base_object, only : base_object_constructor
use wenoof_base_object, only : base_object, base_object_constructor

implicit none
private
Expand All @@ -17,6 +17,9 @@ module wenoof_alpha_int_z

type, extends(alpha_object_constructor) :: alpha_int_z_constructor
!< Borges alpha (non linear weights) object constructor.
contains
! public deferred methods
procedure, pass(lhs) :: constr_assign_constr !< `=` operator.
endtype alpha_int_z_constructor

type, extends(alpha_object) :: alpha_int_z
Expand All @@ -27,13 +30,25 @@ module wenoof_alpha_int_z
!< 2008, vol. 227, pp. 3191-3211, doi: 10.1016/j.jcp.2007.11.038.
contains
! public deferred methods
procedure, pass(self) :: create !< Create alpha.
procedure, pass(self) :: compute_int !< Compute alpha (interpolate).
procedure, pass(self) :: compute_rec !< Compute alpha (reconstruct).
procedure, pass(self) :: description !< Return object string-description.
procedure, pass(self) :: destroy !< Destroy alpha.
procedure, pass(self) :: create !< Create alpha.
procedure, pass(self) :: compute_int !< Compute alpha (interpolate).
procedure, pass(self) :: compute_rec !< Compute alpha (reconstruct).
procedure, pass(self) :: description !< Return object string-description.
procedure, pass(self) :: destroy !< Destroy alpha.
procedure, pass(lhs) :: object_assign_object !< `=` operator.
endtype alpha_int_z
contains
! constructor

! deferred public methods
subroutine constr_assign_constr(lhs, rhs)
!< `=` operator.
class(alpha_int_z_constructor), intent(inout) :: lhs !< Left hand side.
class(base_object_constructor), intent(in) :: rhs !< Right hand side.

call lhs%assign_(rhs=rhs)
endsubroutine constr_assign_constr

! public deferred methods
subroutine create(self, constructor)
!< Create alpha.
Expand Down Expand Up @@ -87,6 +102,14 @@ elemental subroutine destroy(self)
call self%destroy_
endsubroutine destroy

subroutine object_assign_object(lhs, rhs)
!< `=` operator.
class(alpha_int_z), intent(inout) :: lhs !< Left hand side.
class(base_object), intent(in) :: rhs !< Right hand side.

call lhs%assign_(rhs=rhs)
endsubroutine object_assign_object

! private non TBP
pure function tau(S, beta) result(w_tau)
!< Compute the tau coefficient used in the WENO-Z alpha coefficients.
Expand Down
35 changes: 29 additions & 6 deletions src/lib/concrete_objects/wenoof_alpha_rec_js.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module wenoof_alpha_rec_js

use penf, only : I_P, R_P, str
use wenoof_alpha_object, only : alpha_object, alpha_object_constructor
use wenoof_base_object, only : base_object_constructor
use wenoof_base_object, only : base_object, base_object_constructor

implicit none
private
Expand All @@ -16,6 +16,9 @@ module wenoof_alpha_rec_js

type, extends(alpha_object_constructor) :: alpha_rec_js_constructor
!< Jiang-Shu alpha object constructor.
contains
! public deferred methods
procedure, pass(lhs) :: constr_assign_constr !< `=` operator.
endtype alpha_rec_js_constructor

type, extends(alpha_object) :: alpha_rec_js
Expand All @@ -25,14 +28,26 @@ module wenoof_alpha_rec_js
!< ENO Schemes*, Guang-Shan Jiang, Chi-Wang Shu, JCP, 1996, vol. 126, pp. 202--228, doi:10.1006/jcph.1996.0130.
contains
! public deferred methods
procedure, pass(self) :: create !< Create alpha.
procedure, pass(self) :: compute_int !< Compute alpha (interpolate).
procedure, pass(self) :: compute_rec !< Compute alpha (reconstruct).
procedure, pass(self) :: description !< Return object string-description.
procedure, pass(self) :: destroy !< Destroy alpha.
procedure, pass(self) :: create !< Create alpha.
procedure, pass(self) :: compute_int !< Compute alpha (interpolate).
procedure, pass(self) :: compute_rec !< Compute alpha (reconstruct).
procedure, pass(self) :: description !< Return object string-description.
procedure, pass(self) :: destroy !< Destroy alpha.
procedure, pass(lhs) :: object_assign_object !< `=` operator.
endtype alpha_rec_js

contains
! constructor

! deferred public methods
subroutine constr_assign_constr(lhs, rhs)
!< `=` operator.
class(alpha_rec_js_constructor), intent(inout) :: lhs !< Left hand side.
class(base_object_constructor), intent(in) :: rhs !< Right hand side.

call lhs%assign_(rhs=rhs)
endsubroutine constr_assign_constr

! deferred public methods
subroutine create(self, constructor)
!< Create alpha.
Expand Down Expand Up @@ -87,4 +102,12 @@ elemental subroutine destroy(self)

call self%destroy_
endsubroutine destroy

subroutine object_assign_object(lhs, rhs)
!< `=` operator.
class(alpha_rec_js), intent(inout) :: lhs !< Left hand side.
class(base_object), intent(in) :: rhs !< Right hand side.

call lhs%assign_(rhs=rhs)
endsubroutine object_assign_object
endmodule wenoof_alpha_rec_js
Loading

0 comments on commit ec620bb

Please sign in to comment.