cgf Derived Type

type, public, extends(gf) :: cgf

A complex data instance of the abstract grid function class.


Inherits

type~~cgf~~InheritsGraph type~cgf cgf type~gf gf type~cgf->type~gf type~element_cdata element_cdata type~cgf->type~element_cdata elems type~element_data element_data type~element_cdata->type~element_data

Inherited by

type~~cgf~~InheritedByGraph type~cgf cgf type~cgf_pointer cgf_pointer type~cgf_pointer->type~cgf p type~cpde_equation cpde_equation type~cpde_equation->type~cgf eq_data, eq_rhs_data, eq_tmp_data type~cpde_equation->type~cgf_pointer data_pointer type~scal_schw scal_schw type~scal_schw->type~cgf eq_flux_data type~scal_schw->type~cpde_equation type~scal_schw_eff scal_schw_eff type~scal_schw->type~scal_schw_eff effs type~eff_source eff_source type~eff_source->type~cgf source type~cobserver cobserver type~cobserver->type~cgf p type~sing_observer sing_observer type~sing_observer->type~eff_source p type~scal_schw_eff->type~eff_source type~sf_observer sf_observer type~sf_observer->type~scal_schw p

Contents

Source Code

cgf

Components

TypeVisibility AttributesNameInitial
integer(kind=ip), public :: n

The number of elements.

character(len=:), public, allocatable:: vname

The name of the grid function.

integer(kind=ip), public :: io_id

The file unit used for output of this grid function.

type(element_cdata), public, dimension(:), allocatable:: elems

A 1d array of the complex element data class.


Constructor

public interface cgf

The constructor for a complex data type grid function.

  • public interface init_cgf()

    Arguments

    None

Finalization Procedures

final :: deallocate_cgf

The finalizer.


Type-Bound Procedures

procedure, public, non_overridable :: output => output_cgf

Generic type bound procedure for output.

  • interface

    public module subroutine output_cgf(this, coord)

    The interface for an output routine for a complex data type grid function.

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    Has to be called with an cgf class.

    type(rgf), intent(in) :: coord

    A real grid function that contains the coordinates.

procedure, public, non_overridable :: copy => copy_cgf

Generic type bound procedure for copying the data from one complex grid function to another.

  • interface

    public module subroutine copy_cgf(this, gf)

    The interface for a procedure for copying the data from one complex grid function to another.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

    class(cgf), intent(in) :: gf

    The grid function to copy.

procedure, public, non_overridable :: zero => zero_cgf

Generic type bound procedure for setting a complex grid function to zero.

  • interface

    public module subroutine zero_cgf(this)

    The interface for a procedure for setting a complex grid function to zero.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

procedure, public, non_overridable :: mult_sc => mult_sc_cgf

Generic type bound procedure for multplying a complex grid function with a real scalar.

  • interface

    public module subroutine mult_sc_cgf(this, scalar)

    The interface for a procedure for multplying a complex grid function with a real scalar.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

    real(kind=wp), intent(in) :: scalar

    The scalar to multiply with.

procedure, public, non_overridable :: sc_mult_gf => sc_mult_gf_cgf

Generic type bound procedure for multplying a complex grid function with a real scalar and storing the result in another complex grid function.

  • interface

    public module subroutine sc_mult_gf_cgf(this, scalar, gf)

    The interface for a procedure for multplying a complex grid function with a real scalar and storing the result in another complex grid function.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

    real(kind=wp), intent(in) :: scalar

    The scalar to multiply with.

    class(cgf), intent(in) :: gf

    The grid function to multiply with.

procedure, public, non_overridable :: add_gf => add_gf_cgf

Generic type bound procedure for adding 2 complex grid functions together and storing the result in the first one.

  • interface

    public module subroutine add_gf_cgf(this, gf)

    The interface for a procedure for adding 2 complex grid functions together and storing the result in the first one.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

    class(cgf), intent(in) :: gf

    The grid function to add.

procedure, public, non_overridable :: add_sc_mult_gf => add_sc_mult_gf_cgf

Generic type bound procedure adding together a grid function and a scalar multiplying another grid function and storing the result in the first one.

  • interface

    public module subroutine add_sc_mult_gf_cgf(this, scalar, gf)

    The interface for a procedure adding together a grid function and a scalar multiplying another grid function and storing the result in the first one.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

    real(kind=wp), intent(in) :: scalar

    The scalar to multiply with.

    class(cgf), intent(in) :: gf

    The second grid function.

procedure, public, non_overridable :: mult_sc_add_sc_mult_gf => mult_sc_add_sc_mult_gf_cgf

Generic type bound procedure for adding together a scalar multiplying a grid function with another scalar multiplying another grid function and storing the result in the first one.

  • interface

    public module subroutine mult_sc_add_sc_mult_gf_cgf(this, scalar1, scalar2, gf)

    The interface for a procedure for adding together a scalar multiplying a grid function with another scalar multiplying another grid function and storing the result in the first one.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

    real(kind=wp), intent(in) :: scalar1

    The first scalar.

    real(kind=wp), intent(in) :: scalar2

    The second scalar.

    class(cgf), intent(in) :: gf

    The second grid function.

procedure, public, non_overridable :: gf1_plus_sc_mult_gf2 => gf1_plus_sc_mult_gf2_cgf

Generic type bound procedure for storing the result of adding a second grid function with a scalar multiplying a third grid function in a grid function.

  • interface

    public module subroutine gf1_plus_sc_mult_gf2_cgf(this, gf1, scalar, gf2)

    The interface for a procedure for storing the result of adding a second grid function with a scalar multiplying a third grid function in a grid function.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

    class(cgf), intent(in) :: gf1

    The second grid function.

    real(kind=wp), intent(in) :: scalar

    The scalar.

    class(cgf), intent(in) :: gf2

    The third grid function.

procedure, public, non_overridable :: sc_mult_gf1_plus_sc_mult_gf2 => sc_mult_gf1_plus_sc_mult_gf2_cgf

Generic type bound procedure for storing the result of adding a scalar multiplying a second grid function with another scalar multiplying a third grid function in a grid function.

  • interface

    public module subroutine sc_mult_gf1_plus_sc_mult_gf2_cgf(this, gf1, scalar1, gf2, scalar2)

    The interface for a procedure for storing the result of adding a scalar multiplying a second grid function with another scalar multiplying a third grid function in a grid function.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(cgf), intent(inout) :: this

    The routine is called on this object.

    class(cgf), intent(in) :: gf1

    The second grid function.

    real(kind=wp), intent(in) :: scalar1

    The first scalar.

    class(cgf), intent(in) :: gf2

    The third grid function.

    real(kind=wp), intent(in) :: scalar2

    The second scalar.

Source Code

  type, extends(gf) :: cgf
  !! A complex data instance of the abstract grid function class.
    type(element_cdata), dimension(:), allocatable :: elems
    !! A 1d array of the complex element data class.
    contains
      procedure, non_overridable :: output => output_cgf
      !! Generic type bound procedure for output.
      procedure, non_overridable :: copy => copy_cgf
      !! Generic type bound procedure for copying the data from one complex
      !! grid function to another.
      procedure, non_overridable :: zero => zero_cgf
      !! Generic type bound procedure for setting a complex grid function
      !! to zero.
      procedure, non_overridable :: mult_sc => mult_sc_cgf
      !! Generic type bound procedure for multplying a complex grid function
      !! with a real scalar.
      procedure, non_overridable :: sc_mult_gf => sc_mult_gf_cgf
      !! Generic type bound procedure for multplying a complex grid function
      !! with a real scalar and storing the result in another complex
      !! grid function.
      procedure, non_overridable :: add_gf => add_gf_cgf
      !! Generic type bound procedure for adding 2 complex grid functions
      !! together and storing the result in the first one.
      procedure, non_overridable :: add_sc_mult_gf => add_sc_mult_gf_cgf
      !! Generic type bound procedure adding together a grid function and
      !! a scalar multiplying another grid function and storing the result
      !! in the first one.
      procedure, non_overridable :: mult_sc_add_sc_mult_gf => mult_sc_add_sc_mult_gf_cgf
      !! Generic type bound procedure for adding together a scalar multiplying
      !! a grid function with another scalar multiplying another grid function
      !! and storing the result in the first one.
      procedure, non_overridable :: gf1_plus_sc_mult_gf2 => gf1_plus_sc_mult_gf2_cgf
      !! Generic type bound procedure for storing the result of adding a
      !! second grid function with a scalar multiplying a third grid function
      !! in a grid function.
      procedure, non_overridable :: sc_mult_gf1_plus_sc_mult_gf2 => sc_mult_gf1_plus_sc_mult_gf2_cgf
      !! Generic type bound procedure for storing the result of adding a
      !! scalar multiplying a second grid function with another scalar
      !! multiplying a third grid function in a grid function.
      final :: deallocate_cgf
      !! The finalizer.
  end type cgf