codata_constant_type Derived Type

type, public :: codata_constant_type

Derived type for representing a Codata constant. (Specification)


Components

Type Visibility Attributes Name Initial
character(len=64), public :: name
real(kind=dp), public :: uncertainty
character(len=32), public :: unit
real(kind=dp), public :: value

Type-Bound Procedures

procedure, public :: print

  • private subroutine print(self)

    Print out the constant's name, value, uncertainty and unit.

    Arguments

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

generic, public :: to_real => to_real_sp, to_real_dp

  • private pure elemental function to_real_sp(self, mold, uncertainty) result(r)

    Get the constant value or uncertainty for the kind sp (Specification)

    Arguments

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

    Codata constant

    real(kind=sp), intent(in) :: mold

    dummy argument to disambiguate at compile time the generic interface

    logical, intent(in), optional :: uncertainty

    Set to true if the uncertainty is required. Default to .false..

    Return Value real(kind=sp)

  • private pure elemental function to_real_dp(self, mold, uncertainty) result(r)

    Get the constant value or uncertainty for the kind dp (Specification)

    Arguments

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

    Codata constant

    real(kind=dp), intent(in) :: mold

    dummy argument to disambiguate at compile time the generic interface

    logical, intent(in), optional :: uncertainty

    Set to true if the uncertainty is required. Default to .false..

    Return Value real(kind=dp)

procedure, public :: to_real_dp

  • private pure elemental function to_real_dp(self, mold, uncertainty) result(r)

    Get the constant value or uncertainty for the kind dp (Specification)

    Arguments

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

    Codata constant

    real(kind=dp), intent(in) :: mold

    dummy argument to disambiguate at compile time the generic interface

    logical, intent(in), optional :: uncertainty

    Set to true if the uncertainty is required. Default to .false..

    Return Value real(kind=dp)

procedure, public :: to_real_sp

  • private pure elemental function to_real_sp(self, mold, uncertainty) result(r)

    Get the constant value or uncertainty for the kind sp (Specification)

    Arguments

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

    Codata constant

    real(kind=sp), intent(in) :: mold

    dummy argument to disambiguate at compile time the generic interface

    logical, intent(in), optional :: uncertainty

    Set to true if the uncertainty is required. Default to .false..

    Return Value real(kind=sp)