hasty_key_morton.f90 Source File

HASTY Morton (Z-order) key class.

This File Depends On

sourcefile~~hasty_key_morton.f90~~EfferentGraph sourcefile~hasty_key_morton.f90 hasty_key_morton.f90 sourcefile~hasty_key_base.f90 hasty_key_base.f90 sourcefile~hasty_key_base.f90->sourcefile~hasty_key_morton.f90 sourcefile~penf.f90 penf.F90 sourcefile~penf.f90->sourcefile~hasty_key_morton.f90 sourcefile~penf.f90->sourcefile~hasty_key_base.f90 sourcefile~penf_b_size.f90 penf_b_size.F90 sourcefile~penf_b_size.f90->sourcefile~penf.f90 sourcefile~penf_stringify.f90 penf_stringify.F90 sourcefile~penf_b_size.f90->sourcefile~penf_stringify.f90 sourcefile~penf_global_parameters_variables.f90 penf_global_parameters_variables.F90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf.f90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_b_size.f90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_stringify.f90 sourcefile~penf_stringify.f90->sourcefile~penf.f90
Help

Files Dependent On This One

sourcefile~~hasty_key_morton.f90~~AfferentGraph sourcefile~hasty_key_morton.f90 hasty_key_morton.f90 sourcefile~hasty.f90 hasty.f90 sourcefile~hasty_key_morton.f90->sourcefile~hasty.f90 sourcefile~hasty_test_hash_table_homokey_failure.f90 hasty_test_hash_table_homokey_failure.f90 sourcefile~hasty.f90->sourcefile~hasty_test_hash_table_homokey_failure.f90 sourcefile~hasty_test_hash_table.f90 hasty_test_hash_table.f90 sourcefile~hasty.f90->sourcefile~hasty_test_hash_table.f90 sourcefile~hasty_test_hash_table_homo.f90 hasty_test_hash_table_homo.f90 sourcefile~hasty.f90->sourcefile~hasty_test_hash_table_homo.f90 sourcefile~hasty_test_dictionary.f90 hasty_test_dictionary.f90 sourcefile~hasty.f90->sourcefile~hasty_test_dictionary.f90 sourcefile~hasty_test_caf_get_clone.f90 hasty_test_caf_get_clone.F90 sourcefile~hasty.f90->sourcefile~hasty_test_caf_get_clone.f90 sourcefile~hasty_test_hash_table_homocontent_failure.f90 hasty_test_hash_table_homocontent_failure.f90 sourcefile~hasty.f90->sourcefile~hasty_test_hash_table_homocontent_failure.f90 sourcefile~hasty_test_caf_basic.f90 hasty_test_caf_basic.F90 sourcefile~hasty.f90->sourcefile~hasty_test_caf_basic.f90
Help

Source Code


Source Code

!< HASTY Morton (Z-order) **key** class.
module hasty_key_morton
!-----------------------------------------------------------------------------------------------------------------------------------
!< HASTY Morton (Z-order) **key** class.
!-----------------------------------------------------------------------------------------------------------------------------------
use hasty_key_base
use penf
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
implicit none
private
public :: key_morton
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
type, extends(key_base) :: key_morton
  !< Morton (Z-order) **key** class to identify a node.
  integer(I8P) :: key=0_I8P !< The key.
  contains
    ! public deferred methods
    procedure, pass(self) :: destroy   !< Destroy the key.
    procedure, pass(self) :: stringify !< Return a string representation of the key.
    ! private deferred methods
    procedure, pass(lhs), private :: is_equal !< Implement `==` operator.
endtype key_morton
!-----------------------------------------------------------------------------------------------------------------------------------
contains
  ! public deferred methods
  elemental subroutine destroy(self)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Destroy the key.
  !---------------------------------------------------------------------------------------------------------------------------------
  class(key_morton), intent(inout) :: self !< The key.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  ! there is no dynamic memory, nothing to destroy
  self%key = 0_I8P
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine destroy

  pure function stringify(self) result(str_key)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Return a string representation of the key.
  !---------------------------------------------------------------------------------------------------------------------------------
  class(key_morton), intent(in) :: self    !< The key.
  character(len=:), allocatable :: str_key !< The key stringified.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  str_key = trim(str(self%key))
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction stringify

  ! private deferred methods
  elemental logical function is_equal(lhs, rhs)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Implement `==` operator.
  !---------------------------------------------------------------------------------------------------------------------------------
  class(key_morton), intent(in) :: lhs !< Left hand side.
  class(*),          intent(in) :: rhs !< Rigth hand side.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  is_equal = .false.
  select type(rhs)
  type is(key_morton)
    is_equal = lhs%key==rhs%key
  endselect
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction is_equal
endmodule hasty_key_morton