Skip to content

Commit

Permalink
Merge branch 'release/0.1.2'
Browse files Browse the repository at this point in the history
  • Loading branch information
szaghi committed Jan 24, 2017
2 parents 87c6403 + f729750 commit a8bbf6d
Show file tree
Hide file tree
Showing 31 changed files with 1,557 additions and 1,601 deletions.
7 changes: 5 additions & 2 deletions fobos
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,7 @@ $CSHARED_INT = -cpp -c -fpic -assume realloc_lhs
$LSHARED = -shared
$CSTATIC_GNU = -cpp -c -frealloc-lhs
$CSTATIC_INT = -cpp -c -assume realloc_lhs
$DEBUG_GNU = -Og -g3 -Warray-bounds -Wcharacter-truncation -Wline-truncation -Wimplicit-interface -Wimplicit-procedure -Wunderflow -fcheck=all -fmodule-private -ffree-line-length-132 -fimplicit-none -fbacktrace -fdump-core -finit-real=nan
; $DEBUG_GNU = -Og -g3 -Warray-bounds -Wcharacter-truncation -Wline-truncation -Wimplicit-interface -Wimplicit-procedure -Wunderflow -fcheck=all -fmodule-private -ffree-line-length-132 -fimplicit-none -fbacktrace -fdump-core -finit-real=nan -std=f2008 -fall-intrinsics
$DEBUG_GNU = -Og -g3 -Warray-bounds -Wcharacter-truncation -Wline-truncation -Wimplicit-interface -Wimplicit-procedure -Wunderflow -fcheck=all -fmodule-private -ffree-line-length-132 -fimplicit-none -fbacktrace -fdump-core -finit-real=nan -std=f2008 -fall-intrinsics
$DEBUG_INT = -O0 -debug all -check all -warn all -extend-source 132 -traceback -gen-interfaces#-fpe-all=0 -fp-stack-check -fstack-protector-all -ftrapuv -no-ftz -std08
$OPTIMIZE = -O2
$EXDIRS = FLAP/src/tests/ PENF/src/tests/ pyplot-fortran/src/tests/
Expand Down Expand Up @@ -121,6 +120,7 @@ jobs = 2
compiler = gnu
cflags = $CSHARED_GNU $DEBUG_GNU
lflags = $LSHARED $DEBUG_GNU
preproc = -DDEBUG
exclude_dirs = $EXDIRS
mod_dir = ./mod/
obj_dir = ./obj/
Expand All @@ -134,6 +134,7 @@ jobs = 2
compiler = gnu
cflags = $CSTATIC_GNU $DEBUG_GNU
lflags = $DEBUG_GNU
preproc = -DDEBUG
exclude_dirs = $EXDIRS
mod_dir = ./mod/
obj_dir = ./obj/
Expand Down Expand Up @@ -173,6 +174,7 @@ jobs = 2
compiler = intel
cflags = $CSHARED_INT $DEBUG_INT
lflags = $LSHARED $DEBUG_INT
preproc = -DDEBUG
exclude_dirs = $EXDIRS
mod_dir = ./mod/
obj_dir = ./obj/
Expand All @@ -186,6 +188,7 @@ jobs = 2
compiler = intel
cflags = $CSTATIC_INT $DEBUG_INT
lflags = $DEBUG_INT
preproc = -DDEBUG
exclude_dirs = $EXDIRS
mod_dir = ./mod/
obj_dir = ./obj/
Expand Down
40 changes: 40 additions & 0 deletions src/lib/abstract_objects/wenoof_alpha_object.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,40 @@
!< Abstract alpha (non linear weights) object.
module wenoof_alpha_object
!< Abstract alpha (non linear weights) object.

use penf, only : I_P, R_P
use wenoof_base_object
use wenoof_beta_object
use wenoof_kappa_object

implicit none
private
public :: alpha_object
public :: alpha_object_constructor

type, extends(base_object_constructor) :: alpha_object_constructor
!< Abstract alpha (non linear weights) object constructor.
contains
endtype alpha_object_constructor

type, extends(base_object), abstract :: alpha_object
!< Abstract alpha (non linear weights) object.
real(R_P), allocatable :: values(:,:) !< Alpha coefficients [1:2,0:S-1].
real(R_P), allocatable :: values_sum(:) !< Sum of alpha coefficients [1:2].
contains
! public deferred methods
procedure(compute_interface), pass(self), deferred :: compute !< Compute alpha.
endtype alpha_object

abstract interface
!< Abstract interfaces of [[alpha_object]].
pure subroutine compute_interface(self, beta, kappa)
!< Compute alpha.
import :: alpha_object, beta_object, kappa_object
class(alpha_object), intent(inout) :: self !< Alpha.
class(beta_object), intent(in) :: beta !< Beta.
class(kappa_object), intent(in) :: kappa !< Kappa.
endsubroutine compute_interface
endinterface

endmodule wenoof_alpha_object
100 changes: 100 additions & 0 deletions src/lib/abstract_objects/wenoof_base_object.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,100 @@
!< Abstract base object, the ancestor of all.
module wenoof_base_object
!< Abstract base object, the ancestor of all.
!<
!< Define a minimal, base, object that is used as ancestor of all objects, e.g. smoothness indicator, optimal weights, etc...

use penf

implicit none
private
public :: base_object
public :: base_object_constructor

real(R_P), parameter :: EPS_DEF=10._R_P**(-6) !< Small epsilon to avoid division by zero, default value.

type :: base_object_constructor
!< Abstract base object constructor.
integer(I_P) :: S=0_I_P !< Stencils dimension.
logical :: face_left=.true. !< Activate left-face interpolation computation.
logical :: face_right=.true. !< Activate right-face interpolation computation.
real(R_P) :: eps=EPS_DEF !< Small epsilon to avoid division by zero.
endtype base_object_constructor

type, abstract :: base_object
!< Abstract base object, the ancestor of all.
!<
!< Define a minimal, base, object that is used as ancestor of all objects, e.g. smoothness indicator, optimal weights, etc...
integer(I_P) :: S=0_I_P !< Stencils dimension.
integer(I_P) :: f1=1_I_P !< Lower bound of faces index.
integer(I_P) :: f2=2_I_P !< Upper bound of faces index.
integer(I_P) :: ff=0_I_P !< Offset (step) of faces index.
real(R_P) :: eps=EPS_DEF !< Small epsilon to avoid division by zero.
contains
! 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.
! public non overridable methods
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]].
subroutine create_interface(self, constructor)
!< Create object.
!<
!< @note Before call this method a concrete constructor must be instantiated.
import :: base_object, base_object_constructor
class(base_object), intent(inout) :: self !< Object.
class(base_object_constructor), intent(in) :: constructor !< Object constructor.
endsubroutine create_interface

pure function description_interface(self) result(string)
!< Return object string-description.
import :: base_object
class(base_object), intent(in) :: self !< Object.
character(len=:), allocatable :: string !< String-description.
endfunction description_interface

elemental subroutine destroy_interface(self)
!< Destroy object.
import :: base_object
class(base_object), intent(inout) :: self !< Object.
endsubroutine destroy_interface
endinterface

contains
! public non overridable methods
subroutine create_(self, constructor)
!< Create object.
class(base_object), intent(inout) :: self !< Object.
class(base_object_constructor), intent(in) :: constructor !< Object constructor.

call self%destroy_
select type(constructor)
class is(base_object_constructor)
self%S = constructor%S
if (constructor%face_left.and.constructor%face_right) then
self%f1 = 1_I_P; self%f2 = 2_I_P; self%ff = 0_I_P
elseif (constructor%face_left) then
self%f1 = 1_I_P; self%f2 = 1_I_P; self%ff = 0_I_P
elseif (constructor%face_right) then
self%f1 = 2_I_P; self%f2 = 2_I_P; self%ff = -1_I_P
endif
self%eps = constructor%eps
endselect
endsubroutine create_

elemental subroutine destroy_(self)
!< Destroy object.
class(base_object), intent(inout) :: self !< Object.

self%S = 0_I_P
self%f1 = 1_I_P
self%f2 = 2_I_P
self%ff = 0_I_P
self%eps = EPS_DEF
endsubroutine destroy_
endmodule wenoof_base_object
35 changes: 35 additions & 0 deletions src/lib/abstract_objects/wenoof_beta_object.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
!< Abstract Beta coefficients (smoothness indicators of stencil interpolations) object.
module wenoof_beta_object
!< Abstract Beta coefficients (smoothness indicators of stencil interpolations) object.

use penf, only : I_P, R_P
use wenoof_base_object

implicit none
private
public :: beta_object
public :: beta_object_constructor

type, extends(base_object_constructor) :: beta_object_constructor
!< Abstract Beta coefficients object constructor.
endtype beta_object_constructor

type, extends(base_object), abstract :: beta_object
!< Abstract Beta coefficients (smoothness indicators of stencil interpolations) object.
real(R_P), allocatable :: values(:,:) !< Beta values [1:2,0:S-1].
contains
! public deferred methods
procedure(compute_interface), pass(self), deferred :: compute !< Compute beta.
endtype beta_object

abstract interface
!< Abstract interfaces of [[beta_object]].
pure subroutine compute_interface(self, stencil)
!< Compute beta.
import :: beta_object, R_P
class(beta_object), intent(inout) :: self !< Beta.
real(R_P), intent(in) :: stencil(1:,1-self%S:) !< Stencil used for the interpolation, [1:2, 1-S:-1+S].
endsubroutine compute_interface
endinterface

endmodule wenoof_beta_object
35 changes: 35 additions & 0 deletions src/lib/abstract_objects/wenoof_interpolations_object.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
!< Abstract interpolations object.
module wenoof_interpolations_object
!< Abstract interpolations object.

use penf, only : I_P, R_P
use wenoof_base_object

implicit none
private
public :: interpolations_object
public :: interpolations_object_constructor

type, extends(base_object_constructor) :: interpolations_object_constructor
!< Abstract interpolations object constructor.
endtype interpolations_object_constructor

type, extends(base_object), abstract :: interpolations_object
!< Abstract interpolations object.
real(R_P), allocatable :: values(:,:) !< Stencil interpolations values [1:2,0:S-1].
contains
! public deferred methods
procedure(compute_interface), pass(self), deferred :: compute !< Compute beta.
endtype interpolations_object

abstract interface
!< Abstract interfaces of [[interpolations_object]].
pure subroutine compute_interface(self, stencil)
!< Compute interpolations.
import :: interpolations_object, R_P
class(interpolations_object), intent(inout) :: self !< Interpolations.
real(R_P), intent(in) :: stencil(1:,1-self%S:) !< Stencil used for the interpolation, [1:2, 1-S:-1+S].
endsubroutine compute_interface
endinterface

endmodule wenoof_interpolations_object
58 changes: 58 additions & 0 deletions src/lib/abstract_objects/wenoof_interpolator_object.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
!< Abstract interpolator object.
module wenoof_interpolator_object
!< Abstract interpolator object.

use penf, only : I_P, R_P
use wenoof_base_object
use wenoof_interpolations_object
use wenoof_weights_object

implicit none
private
public :: interpolator_object
public :: interpolator_object_constructor

type, extends(base_object_constructor) :: interpolator_object_constructor
!< Abstract interpolator object constructor.
!<
!< @note Every concrete WENO interpolator implementations must define their own constructor type.
class(interpolations_object_constructor), allocatable :: interpolations_constructor !< Stencil interpolations constructor.
class(weights_object_constructor), allocatable :: weights_constructor !< Weights of interpolations constructor.
endtype interpolator_object_constructor

type, extends(base_object), abstract :: interpolator_object
!< Abstract interpolator object.
!<
!< @note Do not implement any actual interpolator: provide the interface for the different interpolators implemented.
class(interpolations_object), allocatable :: interpolations !< Stencil interpolations.
class(weights_object), allocatable :: weights !< Weights of interpolations.
contains
! public deferred methods
procedure(interpolate_debug_interface), pass(self), deferred :: interpolate_debug !< Interpolate values, debug mode.
procedure(interpolate_standard_interface), pass(self), deferred :: interpolate_standard !< Interpolate values, standard mode.
! public methods
generic :: interpolate => interpolate_standard, interpolate_debug !< Interpolate values.
endtype interpolator_object

abstract interface
!< Abstract interfaces of [[interpolator_object]].
pure subroutine interpolate_debug_interface(self, stencil, interpolation, si, weights)
!< Interpolate values (providing also debug values).
import :: interpolator_object, R_P
class(interpolator_object), intent(inout) :: self !< Interpolator.
real(R_P), intent(in) :: stencil(1:, 1 - self%S:) !< Stencil of the interpolation [1:2, 1-S:-1+S].
real(R_P), intent(out) :: interpolation(1:) !< Result of the interpolation, [1:2].
real(R_P), intent(out) :: si(1:, 0:) !< Computed values of smoothness indicators [1:2, 0:S-1].
real(R_P), intent(out) :: weights(1:, 0:) !< Weights of the stencils, [1:2, 0:S-1].
endsubroutine interpolate_debug_interface

pure subroutine interpolate_standard_interface(self, stencil, interpolation)
!< Interpolate values (without providing debug values).
import :: interpolator_object, R_P
class(interpolator_object), intent(inout) :: self !< Interpolator.
real(R_P), intent(in) :: stencil(1:, 1 - self%S:) !< Stencil of the interpolation [1:2, 1-S:-1+S].
real(R_P), intent(out) :: interpolation(1:) !< Result of the interpolation, [1:2].
endsubroutine interpolate_standard_interface
endinterface

endmodule wenoof_interpolator_object
34 changes: 34 additions & 0 deletions src/lib/abstract_objects/wenoof_kappa_object.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
!< Abstract Kappa (optimal, linear weights of stencil interpolations) object.
module wenoof_kappa_object
!< Abstract Kappa (optimal, linear weights of stencil interpolations) object.

use penf, only : I_P, R_P
use wenoof_base_object

implicit none
private
public :: kappa_object
public :: kappa_object_constructor

type, extends(base_object_constructor) :: kappa_object_constructor
!< Abstract kappa object constructor.
endtype kappa_object_constructor

type, extends(base_object), abstract :: kappa_object
!< Kappa (optimal, linear weights of stencil interpolations) object.
real(R_P), allocatable :: values(:,:) !< Kappa coefficients values [1:2,0:S-1].
contains
! public deferred methods
procedure(compute_interface), pass(self), deferred :: compute !< Compute kappa.
endtype kappa_object

abstract interface
!< Abstract interfaces of [[kappa_object]].
pure subroutine compute_interface(self)
!< Compute kappa.
import :: kappa_object
class(kappa_object), intent(inout) :: self !< Kappa.
endsubroutine compute_interface
endinterface

endmodule wenoof_kappa_object
35 changes: 35 additions & 0 deletions src/lib/abstract_objects/wenoof_weights_object.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
!< Abstract weights object.
module wenoof_weights_object
!< Abstract weights object.

use penf, only : I_P, R_P
use wenoof_base_object

implicit none
private
public :: weights_object
public :: weights_object_constructor

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

type, extends(base_object), abstract :: weights_object
!< Weights of stencil interpolations object.
real(R_P), allocatable :: values(:,:) !< Weights values of stencil interpolations [1:2,0:S-1].
contains
! deferred public methods
procedure(compute_interface), pass(self), deferred :: compute !< Compute weights.
endtype weights_object

abstract interface
!< Abstract interfaces of [[weights_object]].
pure subroutine compute_interface(self, stencil)
!< Compute beta.
import :: weights_object, R_P
class(weights_object), intent(inout) :: self !< Weights.
real(R_P), intent(in) :: stencil(1:,1-self%S:) !< Stencil used for the interpolation, [1:2, 1-S:-1+S].
endsubroutine compute_interface
endinterface

endmodule wenoof_weights_object
Loading

0 comments on commit a8bbf6d

Please sign in to comment.