supercell_type Derived Type

type, private :: supercell_type

This is the next level up of data and represents the supercell type. A supercell represents a collection of connected cells


Contents

Source Code


Components

Type Visibility Attributes Name Initial
type(cell_type), public, dimension(:), allocatable :: cells

These are the cells

integer, public :: ncell
integer, public :: nextend

Length of the extended domain

integer, public :: nrow

The number of rows and columns. Equal to nextend*nfield

integer, public :: ncol

The number of rows and columns. Equal to nextend*nfield

integer, public :: it_leftmost

It index of leftmost cell

integer, public :: head_iproc

The proc id (in sc_sub_all) of the head proc

integer, public :: head_iproc_pd

The proc id (in sc_sub_pd) of the head proc

logical, public :: is_local

Does this supercell have any data on this proc?

logical, public :: is_empty

Have we got any data for this supercell on this proc?

logical, public :: is_all_local

Is all of this supercells data on this proc?

complex, public, dimension(:), allocatable :: tmp_sum

Work space for field update

type(comm_type), public :: sc_sub_all

Sub communicator involving all processors with this supercell

type(comm_type), public :: sc_sub_pd

Sub communicator for all procs with some data but not all of it

type(comm_type), public :: parent_sub

Sub communicator involving all processors in parent

integer, public, dimension(:), allocatable :: nb_req_hand

For non-blocking broadcast request handle storage

logical, public :: initdone

Have we finished initialising this block?

logical, public, dimension(:), allocatable :: initialised

Have we initialised each point?

logical, public :: is_head = .false.

Are we the head of this supercell?

integer, public :: is_ind

The is_ind value is the index of the supercell in the parent ky_type's supercell array.

integer, public :: is_label

The is_label is the supercell_label of this supercell as determined by calculate_supercell_labels from elsewhere.

integer, public :: ik_ind

Parent properties

integer, public :: collective_request
real, public :: condition_number = -1

Condition number of the associated response matrix. Only valid on the head.


Type-Bound Procedures

procedure, private, :: deallocate => sc_deallocate

  • private subroutine sc_deallocate(self)

    Deallocate storage space

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: allocate => sc_allocate

  • private subroutine sc_allocate(self)

    Allocate storage space

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: init => sc_init

  • private subroutine sc_init(self, is, itmin, ik, nfield, nbound)

    Initialise the supercell instance by setting and calculating some basic properties. Does not deal with allocating all storage etc.

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self
    integer, intent(in) :: is
    integer, intent(in) :: itmin
    integer, intent(in) :: ik
    integer, intent(in) :: nfield
    integer, intent(inout) :: nbound

procedure, private, :: debug_print => sc_debug_print

  • private subroutine sc_debug_print(self)

    Debug printing

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self

procedure, private, :: get_field_update => sc_get_field_update

  • private subroutine sc_get_field_update(self, fq, fqa, fqp)

    Get the field update DD>TAGGED

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self
    complex, intent(in), dimension(:,:) :: fq
    complex, intent(in), dimension(:,:) :: fqa
    complex, intent(in), dimension(:,:) :: fqp

procedure, private, :: reduce_tmpsum => sc_reduce_tmpsum

  • private subroutine sc_reduce_tmpsum(self)

    Reduce the field update across cells to give the final answer DD>TAGGED: As we currently have to do fm_gather_fields on every time step we only need

    DD> At this point the head of the supercell has the field update stored in self%tmp_sum

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: iex_to_dims => sc_iex_to_dims

  • private subroutine sc_iex_to_dims(self, iex, ig, ic, it, ifl)

    Convert the extended domain index to ig, it and ifl

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self
    integer, intent(in) :: iex
    integer, intent(out) :: ig
    integer, intent(out) :: ic
    integer, intent(out) :: it
    integer, intent(out) :: ifl

procedure, private, :: iex_to_ifl => sc_iex_to_ifl

  • private subroutine sc_iex_to_ifl(self, iex, ifl)

    Convert the extended domain index to ifl

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self
    integer, intent(in) :: iex
    integer, intent(out) :: ifl

procedure, private, :: iex_to_ic => sc_iex_to_ic

  • private subroutine sc_iex_to_ic(self, iex, ic)

    Convert the extended domain index to ic

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self
    integer, intent(in) :: iex
    integer, intent(out) :: ic

procedure, private, :: iex_to_ig => sc_iex_to_ig

  • private subroutine sc_iex_to_ig(self, iex, ig)

    Convert the extended domain index to ig

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self
    integer, intent(in) :: iex
    integer, intent(out) :: ig

procedure, private, :: iex_to_it => sc_iex_to_it

  • private subroutine sc_iex_to_it(self, iex, it)

    Convert the extended domain index to it

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self
    integer, intent(in) :: iex
    integer, intent(out) :: it

procedure, private, :: has_it => sc_has_it

  • private function sc_has_it(self, it)

    Is the passed it a member of this supercell

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self
    integer, intent(in) :: it

    Return Value logical

procedure, private, :: reset => sc_reset

  • private subroutine sc_reset(self)

    A routine to reset the object

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: set_locality => sc_set_locality

  • private subroutine sc_set_locality(self)

    Set the locality of each object

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: get_left_it => sc_get_left_it

  • private function sc_get_left_it(self, it)

    Given an it value get the it of the left connected cell

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self
    integer, intent(in) :: it

    Return Value integer

procedure, private, :: store_fq => sc_store_fq

  • private subroutine sc_store_fq(self, fq, fqa, fqp, ifl_in, it_in, ig_in)

    Store the field equations at row level

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self
    complex, intent(in), dimension(:, :) :: fq
    complex, intent(in), dimension(:, :) :: fqa
    complex, intent(in), dimension(:, :) :: fqp
    integer, intent(in) :: ifl_in
    integer, intent(in) :: it_in
    integer, intent(in) :: ig_in

procedure, private, :: pull_rows_to_arr => sc_pull_rows_to_arr

  • private subroutine sc_pull_rows_to_arr(self, arr)

    A routine to collect all the row level data and store in passed array Gather the row blocks up for this cell to fill an array DD>FOR NOW USE ALL_REDUCE AS EASIER, BUT SHOULD BE ABLE

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(in) :: self
    complex, intent(out), dimension(:,:) :: arr

procedure, private, :: push_arr_to_rows => sc_push_arr_to_rows

  • private subroutine sc_push_arr_to_rows(self, arr)

    A routine to distribute an array to appropriate row blocks

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self
    complex, intent(in), dimension(self%nrow,self%ncol) :: arr

procedure, private, :: prepare => sc_prepare

  • private subroutine sc_prepare(self, prepare_type)

    Prepare the field matrix for calculating field updates

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self
    integer, intent(in) :: prepare_type

procedure, private, :: invert => sc_invert

  • private subroutine sc_invert(self)

    A routine to invert the field matrix

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: invert_local => sc_invert_local

  • private subroutine sc_invert_local(self)

    A routine to invert the field matrix locally

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: invert_mpi => sc_invert_mpi

  • private subroutine sc_invert_mpi(self)

    A routine to invert the field matrix using mpi

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: dump => sc_dump

  • private subroutine sc_dump(self, prefix)

    Debug routine to dump the current supercell

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self
    character(len=*), intent(in), optional :: prefix

procedure, private, :: make_subcom_1 => sc_make_subcom_1

  • private subroutine sc_make_subcom_1(self)

    Create primary (top level) sub communicators

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: make_subcom_2 => sc_make_subcom_2

  • private subroutine sc_make_subcom_2(self)

    Create the secondary (intraobject) subcommunicators

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

procedure, private, :: dump_to_file => sc_dump_to_file

  • private subroutine sc_dump_to_file(self, suffix)

    Routine to write the response matrix for this supercell to netcdf file.

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

    The instance of the supercell class

    character(len=*), intent(in), optional :: suffix

    If passed then use as part of file suffix

procedure, private, :: read_from_file => sc_read_from_file

  • private subroutine sc_read_from_file(self, could_read, suffix)

    Routine to read the response matrix for this supercell from netcdf file.

    Arguments

    Type IntentOptional Attributes Name
    class(supercell_type), intent(inout) :: self

    The instance of the supercell class

    logical, intent(out) :: could_read

    Flag to indicate if the file was successfully read

    character(len=*), intent(in), optional :: suffix

    If passed then use as part of file suffix

Source Code

  type, private :: supercell_type
     type(cell_type), dimension(:), allocatable :: cells !< These are the cells
     integer :: ncell
     integer :: nextend !< Length of the extended domain
     integer :: nrow, ncol !< The number of rows and columns. Equal to nextend*nfield
     integer :: it_leftmost !< It index of leftmost cell
     integer :: head_iproc !< The proc id (in sc_sub_all) of the head proc
     integer :: head_iproc_pd !< The proc id (in sc_sub_pd) of the head proc
     logical :: is_local !< Does this supercell have any data on this proc?
     logical :: is_empty !< Have we got any data for this supercell on this proc?
     logical :: is_all_local !< Is all of this supercells data on this proc?
     complex, dimension(:),allocatable :: tmp_sum !< Work space for field update
     type(comm_type) :: sc_sub_all !< Sub communicator involving all processors with this supercell
     type(comm_type) :: sc_sub_pd !< Sub communicator for all procs with some data but not all of it
     type(comm_type) :: parent_sub !< Sub communicator involving all processors in parent
     integer, dimension(:),allocatable :: nb_req_hand !< For non-blocking broadcast request handle storage
     logical :: initdone !< Have we finished initialising this block?
     logical, dimension(:), allocatable :: initialised !< Have we initialised each point?
     logical :: is_head = .false. !< Are we the head of this supercell?
     !Cell and parent properties. Mostly for debug printing.
     !> The is_ind value is the index of the supercell in the parent ky_type's
     !> supercell array.
     integer :: is_ind
     !> The is_label is the supercell_label of this supercell as determined
     !> by calculate_supercell_labels from elsewhere.
     integer :: is_label
     integer :: ik_ind !< Parent properties
     integer :: collective_request
     real :: condition_number = -1 !< Condition number of the associated response matrix. Only valid on the head.
   contains
     private
     procedure :: deallocate => sc_deallocate
     procedure :: allocate => sc_allocate
     procedure :: init => sc_init
     procedure :: debug_print => sc_debug_print
     procedure :: get_field_update => sc_get_field_update
     procedure :: reduce_tmpsum => sc_reduce_tmpsum
     procedure :: iex_to_dims => sc_iex_to_dims
     procedure :: iex_to_ifl => sc_iex_to_ifl
     procedure :: iex_to_ic => sc_iex_to_ic
     procedure :: iex_to_ig => sc_iex_to_ig
     procedure :: iex_to_it => sc_iex_to_it
     procedure :: has_it => sc_has_it
     procedure :: reset => sc_reset
     procedure :: set_locality => sc_set_locality
     procedure :: get_left_it => sc_get_left_it
     procedure :: store_fq => sc_store_fq
     procedure :: pull_rows_to_arr => sc_pull_rows_to_arr
     procedure :: push_arr_to_rows => sc_push_arr_to_rows
     procedure :: prepare => sc_prepare
     procedure :: invert => sc_invert
     procedure :: invert_local => sc_invert_local
     procedure :: invert_mpi => sc_invert_mpi
     procedure :: dump => sc_dump
     procedure :: make_subcom_1 => sc_make_subcom_1
     procedure :: make_subcom_2 => sc_make_subcom_2
     procedure :: dump_to_file => sc_dump_to_file
     procedure :: read_from_file => sc_read_from_file
  end type supercell_type