penf_b_size.F90 Source File

This File Depends On

sourcefile~~penf_b_size.f90~~EfferentGraph sourcefile~penf_b_size.f90 penf_b_size.F90 sourcefile~penf_global_parameters_variables.f90 penf_global_parameters_variables.F90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_b_size.f90
Help

Files Dependent On This One

sourcefile~~penf_b_size.f90~~AfferentGraph sourcefile~penf_b_size.f90 penf_b_size.F90 sourcefile~penf_stringify.f90 penf_stringify.F90 sourcefile~penf_b_size.f90->sourcefile~penf_stringify.f90 sourcefile~penf.f90 penf.F90 sourcefile~penf_b_size.f90->sourcefile~penf.f90 sourcefile~penf_stringify.f90->sourcefile~penf.f90 sourcefile~hasty_key_base.f90 hasty_key_base.f90 sourcefile~penf.f90->sourcefile~hasty_key_base.f90 sourcefile~compact_real.f90 compact_real.f90 sourcefile~penf.f90->sourcefile~compact_real.f90 sourcefile~hasty_hash_table.f90 hasty_hash_table.F90 sourcefile~penf.f90->sourcefile~hasty_hash_table.f90 sourcefile~hasty_dictionary.f90 hasty_dictionary.f90 sourcefile~penf.f90->sourcefile~hasty_dictionary.f90 sourcefile~test_all.f90 test_all.F90 sourcefile~penf.f90->sourcefile~test_all.f90 sourcefile~hasty_dictionary_node.f90 hasty_dictionary_node.f90 sourcefile~penf.f90->sourcefile~hasty_dictionary_node.f90 sourcefile~hasty_key_morton.f90 hasty_key_morton.f90 sourcefile~penf.f90->sourcefile~hasty_key_morton.f90 sourcefile~hasty_key_base.f90->sourcefile~hasty_hash_table.f90 sourcefile~hasty_key_base.f90->sourcefile~hasty_dictionary.f90 sourcefile~hasty_key_base.f90->sourcefile~hasty_dictionary_node.f90 sourcefile~hasty_key_base.f90->sourcefile~hasty_key_morton.f90 sourcefile~hasty.f90 hasty.f90 sourcefile~hasty_key_base.f90->sourcefile~hasty.f90 sourcefile~hasty_hash_table.f90->sourcefile~hasty.f90 sourcefile~hasty_dictionary.f90->sourcefile~hasty_hash_table.f90 sourcefile~hasty_dictionary.f90->sourcefile~hasty.f90 sourcefile~hasty_dictionary_node.f90->sourcefile~hasty_dictionary.f90 sourcefile~hasty_dictionary_node.f90->sourcefile~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

module penf_b_size
!-----------------------------------------------------------------------------------------------------------------------------------
!< PENF bit/byte size functions.
!-----------------------------------------------------------------------------------------------------------------------------------
use penf_global_parameters_variables
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
implicit none
private
save
public :: bit_size, byte_size
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
interface bit_size
  !< Overloading of the intrinsic *bit_size* function for computing the number of bits of (also) real and character variables.
  module procedure                &
#ifdef r16p
                   bit_size_R16P, &
#endif
                   bit_size_R8P,  &
                   bit_size_R4P,  &
                   bit_size_chr
endinterface
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
interface byte_size
  !< Compute the number of bytes of a variable.
  module procedure                 &
                   byte_size_I8P,  &
                   byte_size_I4P,  &
                   byte_size_I2P,  &
                   byte_size_I1P,  &
#ifdef r16p
                   byte_size_R16p, &
#endif
                   byte_size_R8P,  &
                   byte_size_R4P,  &
                   byte_size_chr
endinterface
!-----------------------------------------------------------------------------------------------------------------------------------
contains
  elemental function bit_size_R16P(i) result(bits)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bits of a real variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R16P), intent(in) :: i       !< Real variable whose number of bits must be computed.
  integer(I2P)           :: bits    !< Number of bits of r.
  integer(I1P)           :: mold(1) !< "Molding" dummy variable for bits counting.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bits = size(transfer(i, mold), dim=1, kind=I2P) * 8_I2P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction bit_size_R16P

  elemental function bit_size_R8P(i) result(bits)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bits of a real variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R8P), intent(in) :: i       !< Real variable whose number of bits must be computed.
  integer(I1P)          :: bits    !< Number of bits of r.
  integer(I1P)          :: mold(1) !< "Molding" dummy variable for bits counting.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bits = size(transfer(i, mold), dim=1, kind=I1P) * 8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction bit_size_R8P

  elemental function bit_size_R4P(i) result(bits)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bits of a real variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R4P), intent(in) :: i       !< Real variable whose number of bits must be computed.
  integer(I1P)          :: bits    !< Number of bits of r.
  integer(I1P)          :: mold(1) !< "Molding" dummy variable for bits counting.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bits = size(transfer(i, mold), dim=1, kind=I1P) * 8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction bit_size_R4P

  elemental function bit_size_chr(i) result(bits)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bits of a character variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  character(*), intent(IN) :: i       !< Character variable whose number of bits must be computed.
  integer(I4P)             :: bits    !< Number of bits of c.
  integer(I1P)             :: mold(1) !< "Molding" dummy variable for bits counting.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bits = size(transfer(i, mold), dim=1, kind=I4P) * 8_I4P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction bit_size_chr

  elemental function byte_size_I8P(i) result(bytes)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bytes of an integer variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I8P), intent(in) :: i     !< Integer variable whose number of bytes must be computed.
  integer(I1P)             :: bytes !< Number of bytes of i.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bytes = bit_size(i)/8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction byte_size_I8P

  elemental function byte_size_I4P(i) result(bytes)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bytes of an integer variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I4P), intent(in) :: i     !< Integer variable whose number of bytes must be computed.
  integer(I1P)             :: bytes !< Number of bytes of i.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bytes = bit_size(i)/8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction byte_size_I4P

  elemental function byte_size_I2P(i) result(bytes)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bytes of an integer variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I2P), intent(in) :: i     !< Integer variable whose number of bytes must be computed.
  integer(I1P)             :: bytes !< Number of bytes of i.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bytes = bit_size(i)/8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction byte_size_I2P

  elemental function byte_size_I1P(i) result(bytes)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bytes of an integer variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I1P), intent(in) :: i     !< Integer variable whose number of bytes must be computed.
  integer(I1P)             :: bytes !< Number of bytes of i.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bytes = bit_size(i)/8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction byte_size_I1P

  elemental function byte_size_R16P(i) result(bytes)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bytes of a real variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R16P), intent(in) :: i     !< Real variable whose number of bytes must be computed.
  integer(I1P)           :: bytes !< Number of bytes of r.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bytes = bit_size(i)/8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction byte_size_R16P

  elemental function byte_size_R8P(i) result(bytes)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bytes of a real variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R8P), intent(in) :: i     !< Real variable whose number of bytes must be computed.
  integer(I1P)          :: bytes !< Number of bytes of r.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bytes = bit_size(i)/8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction byte_size_R8P

  elemental function byte_size_R4P(i) result(bytes)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bytes of a real variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R4P), intent(in) :: i     !< Real variable whose number of bytes must be computed.
  integer(I1P)          :: bytes !< Number of bytes of r.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bytes = bit_size(i)/8_I1P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction byte_size_R4P

  elemental function byte_size_chr(i) result(bytes)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Compute the number of bytes of a character variable.
  !---------------------------------------------------------------------------------------------------------------------------------
  character(*), intent(in) :: i     !< Character variable whose number of bytes must be computed.
  integer(I4P)             :: bytes !< Number of bytes of c.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  bytes = bit_size(i)/8_I4P
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endfunction byte_size_chr
endmodule penf_b_size