op_obj Derived Type

type, public :: op_obj

Utitlity that manages interpolations and differential operators


Inherits

type~~op_obj~~InheritsGraph type~op_obj op_obj type~block_obj block_obj type~op_obj->type~block_obj block type~parallel_obj parallel_obj type~op_obj->type~parallel_obj parallel type~block_obj->type~parallel_obj parallel MPI_Datatype MPI_Datatype type~block_obj->MPI_Datatype gc_slab_r, gc_slab_i type~axis_obj axis_obj type~block_obj->type~axis_obj axis, axis_partition type~hdf5_obj hdf5_obj type~block_obj->type~hdf5_obj hdf5 type~parallel_obj->MPI_Datatype REAL_SP, REAL_DP, REAL_WP, COMPLEX_SP, COMPLEX_DP, COMPLEX_WP, INTEGER, INT8, LOGICAL type~communicators communicators type~parallel_obj->type~communicators comm type~patch patch type~parallel_obj->type~patch rank MPI_Comm MPI_Comm type~communicators->MPI_Comm w, g type~hdf5_obj->type~parallel_obj parallel type~hashtbl_obj hashtbl_obj type~hdf5_obj->type~hashtbl_obj tbl type~sllist_obj sllist_obj type~hashtbl_obj->type~sllist_obj vec type~sllist_obj->type~sllist_obj child

Inherited by

type~~op_obj~~InheritedByGraph type~op_obj op_obj type~cdifs_obj cdifs_obj type~cdifs_obj->type~op_obj op type~marker_set marker_set type~cdifs_obj->type~marker_set IB type~respart_set ResPart_set type~cdifs_obj->type~respart_set RP type~collision_obj collision_obj type~cdifs_obj->type~collision_obj collisions type~grans_obj grans_obj type~grans_obj->type~op_obj op type~grans_obj->type~marker_set IB type~particle_set particle_set type~grans_obj->type~particle_set PP type~grans_obj->type~respart_set RP type~grans_obj->type~collision_obj collisions type~marker_set->type~op_obj op type~particle_set->type~op_obj op type~respart_set->type~op_obj op type~respart_set->type~marker_set ib type~collision_obj->type~marker_set IB type~collision_obj->type~particle_set PP type~collision_obj->type~respart_set RP type~solid_obj solid_obj type~solid_obj->type~marker_set type~solid_set solid_set type~solid_set->type~solid_obj p

Components

Type Visibility Attributes Name Initial
real(kind=wp), public, allocatable :: alpha(:)

Morinishi's coeff for high-order schemes

type(block_obj), public, pointer :: block => null()

Parent block structure

real(kind=wp), public, allocatable :: c_d1dx1(:,:)

Differentiate x1-centered data in x1-dir, result is at x1m

real(kind=wp), public, allocatable :: c_d1dx1m(:,:)

Differentiate x1m-centered data in x1-dir, result is at x1

real(kind=wp), public, allocatable :: c_d1dx2(:,:)

Differentiate x2-centered data in x2-dir, result is at x2m

real(kind=wp), public, allocatable :: c_d1dx2m(:,:)

Differentiate x2m-centered data in x2-dir, result is at x2

real(kind=wp), public, allocatable :: c_d1dx3(:,:)

Differentiate x3-centered data in x3-dir, result is at x3m

real(kind=wp), public, allocatable :: c_d1dx3m(:,:)

Differentiate x3m-centered data in x3-dir, result is at x3

real(kind=wp), public, allocatable :: c_intrp1(:,:)

Interpolate from x1 to x1m

real(kind=wp), public, allocatable :: c_intrp1m(:,:)

Interpolate from x1m to x1

real(kind=wp), public, allocatable :: c_intrp2(:,:)

Interpolate from x2 to x2m

real(kind=wp), public, allocatable :: c_intrp2m(:,:)

Interpolate from x2m to x2

real(kind=wp), public, allocatable :: c_intrp3(:,:)

Interpolate from x3 to x3m

real(kind=wp), public, allocatable :: c_intrp3m(:,:)

Interpolate from x3m to x3

real(kind=wp), public, allocatable :: morinishi_ddx(:,:)

Morinishi's differntiations

real(kind=wp), public, allocatable :: morinishi_int(:,:)

Morinishi's interpolations

type(parallel_obj), public, pointer :: parallel => null()

Parent parallel structure

integer, public :: st = 1

Stencil size

integer, private :: scheme_order = 2

Operator order (supports up to 6th order)


Type-Bound Procedures

procedure, public :: ApplyLaplacianDC => op_obj_ApplyLaplacianDC

  • private impure subroutine op_obj_ApplyLaplacianDC(this, rhs, bcs, varname)

    Applies Dirichlet boundary conditions to the RHS of a Laplacian equation.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(inout) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(inout) :: rhs

    Right hand side

    type(bc_set), intent(inout) :: bcs

    Boundary conditions utility

    character(len=*), intent(in) :: varname

    Variable name

procedure, public :: BuildLaplacian => op_obj_BuildLaplacian

  • private pure subroutine op_obj_BuildLaplacian(this, mat, stm)

    Builds Laplacian operator using Morinishi's schemes.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(inout) :: this

    Differential operators utility

    real(kind=wp), intent(out), allocatable :: mat(:,:,:,:,:)

    Matrix that stores the laplacian operator

    integer, intent(out) :: stm

    Stencil extent

procedure, public :: Finalize => op_obj_Final

  • private pure subroutine op_obj_Final(this)

    Finalizes object and frees memory.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(inout) :: this

    Differential operators utility

procedure, public :: Initialize => op_obj_Init

  • private impure subroutine op_obj_Init(this, block, parallel, Order)

    Initializes object. The operator order can be specified by the optional parameter. Otherwise, the object initializes 2nd order operators by default.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(inout) :: this

    Differential operators utility

    type(block_obj), intent(in), target :: block

    A block object

    type(parallel_obj), intent(in), target :: parallel

    Parallel structure to link with

    integer, intent(in), optional :: Order

    Order of interpolation/differentiation schemes

procedure, public :: StrainRate => op_obj_StrainRate

  • private impure function op_obj_StrainRate(this, U, V, W) result(S)

    Computes the strain rate tensor from the velocity field. Result is on mid points (staggering=0). Tensor is stored as follows: S = 0.5*( grad(u) + grad(u)^T ) ( S(1) S(4) S(6) ) = ( S(4) S(2) S(5) ) ( S(6) S(5) S(3) )

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: U

    Fluid velocity field in 1-dir

    type(eulerian_obj_r), intent(in) :: V

    Fluid velocity field in 2-dir

    type(eulerian_obj_r), intent(in) :: W

    Fluid velocity field in 3-dir

    Return Value type(eulerian_obj_r), (6)

    Result

procedure, public :: conv11 => op_obj_conv11

  • private impure function op_obj_conv11(this, in1, in2) result(out)

    Computes d(U1 U1)/dx1.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: conv12 => op_obj_conv12

  • private impure function op_obj_conv12(this, in1, in2) result(out)

    Computes d(U1 U2)/dx1.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: conv13 => op_obj_conv13

  • private impure function op_obj_conv13(this, in1, in2) result(out)

    Computes d(U1 U1)/dx1.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: conv21 => op_obj_conv21

  • private impure function op_obj_conv21(this, in1, in2) result(out)

    Computes d(U2 U1)/dx2.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: conv22 => op_obj_conv22

  • private impure function op_obj_conv22(this, in1, in2) result(out)

    Computes d(U2 U2)/dx2.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: conv23 => op_obj_conv23

  • private impure function op_obj_conv23(this, in1, in2) result(out)

    Computes d(U2 U1)/dx2.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: conv31 => op_obj_conv31

  • private impure function op_obj_conv31(this, in1, in2) result(out)

    Computes d(U3 U1)/dx1.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: conv32 => op_obj_conv32

  • private impure function op_obj_conv32(this, in1, in2) result(out)

    Computes d(U3 U1)/dx1.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: conv33 => op_obj_conv33

  • private impure function op_obj_conv33(this, in1, in2) result(out)

    Computes d(U3 U1)/dx1.

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in1

    Convecting velocity: Ui

    type(eulerian_obj_r), intent(in) :: in2

    Velocity Uj

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: d1dx1 => op_obj_d1dx1

  • private impure function op_obj_d1dx1(this, in) result(out)

    Computes the derivative in the x1-direction. Note: If input is face-centered (on x1), result is cell-centered (on x1m). If input is cell-centered (on x1m), result is face-centered (on x1).

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in

    Field to differentiate

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: d1dx2 => op_obj_d1dx2

  • private impure function op_obj_d1dx2(this, in) result(out)

    Computes the derivative in the x2-direction. Note: If input is face-centered (on x2), result is cell-centered (on x2m). If input is cell-centered (on x2m), result is face-centered (on x2).

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in

    Field to differentiate

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: d1dx3 => op_obj_d1dx3

  • private impure function op_obj_d1dx3(this, in) result(out)

    Computes the derivative in the x3-direction. Note: If input is face-centered (on x3), result is cell-centered (on x3m). If input is cell-centered (on x3m), result is face-centered (on x3).

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in

    Field to differentiate

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: div => op_obj_div

  • private impure function op_obj_div(this, name, in1, in2, in3) result(out)

    Computes the divergence of a vector (in1,in2,in3). This function takes in1,in2,in3 cell-centered (stag=0) and returns the divergence on cell centers (stag=0)

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    character(len=*), intent(in) :: name

    Name to give this variable

    type(eulerian_obj_r), intent(in) :: in1

    Component in 1-dir

    type(eulerian_obj_r), intent(in) :: in2

    Component in 2-dir

    type(eulerian_obj_r), intent(in) :: in3

    Component in 3-dir

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: intrp1 => op_obj_intrp1

  • private impure function op_obj_intrp1(this, in) result(out)

    Interpolates in the x1-direction. Note: If input is face-centered (on x1), result is cell-centered (on x1m). If input is cell-centered (on x1m), result is face-centered (on x1).

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in

    Field to interpolate

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: intrp2 => op_obj_intrp2

  • private impure function op_obj_intrp2(this, in) result(out)

    Interpolates in the x2-direction. Note: If input is face-centered (on x2), result is cell-centered (on x2m). If input is cell-centered (on x2m), result is face-centered (on x2).

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in

    Field to interpolate

    Return Value type(eulerian_obj_r)

    Result

procedure, public :: intrp3 => op_obj_intrp3

  • private impure function op_obj_intrp3(this, in) result(out)

    Interpolates in the x3-direction. Note: If input is face-centered (on x3), result is cell-centered (on x3m). If input is cell-centered (on x3m), result is face-centered (on x3).

    Arguments

    Type IntentOptional Attributes Name
    class(op_obj), intent(in) :: this

    Differential operators utility

    type(eulerian_obj_r), intent(in) :: in

    Field to interpolate

    Return Value type(eulerian_obj_r)

    Result

Source Code

  type :: op_obj
    !> Utitlity that manages interpolations and differential operators
    type(parallel_obj), pointer :: parallel     => null()                      !! Parent parallel structure
    type(block_obj),    pointer :: block        => null()                      !! Parent block structure
    integer,            private :: scheme_order  = 2                           !! Operator order (supports up to 6th order)
    integer                     :: st            = 1                           !! Stencil size
    real(wp),       allocatable :: morinishi_int(:,:)                          !! Morinishi's interpolations
    real(wp),       allocatable :: morinishi_ddx(:,:)                          !! Morinishi's differntiations
    real(wp),       allocatable :: alpha(:)                                    !! Morinishi's coeff for high-order schemes
    real(wp),       allocatable :: c_intrp1m(:,:)                              !! Interpolate from x1m to x1
    real(wp),       allocatable :: c_intrp2m(:,:)                              !! Interpolate from x2m to x2
    real(wp),       allocatable :: c_intrp3m(:,:)                              !! Interpolate from x3m to x3
    real(wp),       allocatable :: c_intrp1 (:,:)                              !! Interpolate from x1  to x1m
    real(wp),       allocatable :: c_intrp2 (:,:)                              !! Interpolate from x2  to x2m
    real(wp),       allocatable :: c_intrp3 (:,:)                              !! Interpolate from x3  to x3m
    real(wp),       allocatable :: c_d1dx1m(:,:)                               !! Differentiate x1m-centered data in x1-dir, result is at x1
    real(wp),       allocatable :: c_d1dx2m(:,:)                               !! Differentiate x2m-centered data in x2-dir, result is at x2
    real(wp),       allocatable :: c_d1dx3m(:,:)                               !! Differentiate x3m-centered data in x3-dir, result is at x3
    real(wp),       allocatable :: c_d1dx1 (:,:)                               !! Differentiate x1-centered  data in x1-dir, result is at x1m
    real(wp),       allocatable :: c_d1dx2 (:,:)                               !! Differentiate x2-centered  data in x2-dir, result is at x2m
    real(wp),       allocatable :: c_d1dx3 (:,:)                               !! Differentiate x3-centered  data in x3-dir, result is at x3m
    contains
    procedure :: Initialize       => op_obj_Init
    procedure :: Finalize         => op_obj_Final
    procedure :: BuildLaplacian   => op_obj_BuildLaplacian
    procedure :: ApplyLaplacianDC => op_obj_ApplyLaplacianDC
    procedure :: StrainRate       => op_obj_StrainRate
    procedure :: div              => op_obj_div
    ! Interpolations:
    procedure :: intrp1           => op_obj_intrp1
    procedure :: intrp2           => op_obj_intrp2
    procedure :: intrp3           => op_obj_intrp3
    ! Differentiation: d(phi)/dx_i
    procedure :: d1dx1            => op_obj_d1dx1
    procedure :: d1dx2            => op_obj_d1dx2
    procedure :: d1dx3            => op_obj_d1dx3
    ! Convective operator: div(Ui Uj)
    procedure :: conv11           => op_obj_conv11
    procedure :: conv21           => op_obj_conv21
    procedure :: conv31           => op_obj_conv31
    procedure :: conv12           => op_obj_conv12
    procedure :: conv22           => op_obj_conv22
    procedure :: conv32           => op_obj_conv32
    procedure :: conv13           => op_obj_conv13
    procedure :: conv23           => op_obj_conv23
    procedure :: conv33           => op_obj_conv33
  end type op_obj