ubounds_m.f90 Source File


Files dependent on this one

sourcefile~~ubounds_m.f90~~AfferentGraph sourcefile~ubounds_m.f90 ubounds_m.f90 sourcefile~inference_engine_m.f90 inference_engine_m.f90 sourcefile~inference_engine_m.f90->sourcefile~ubounds_m.f90 sourcefile~concurrent-inferences.f90 concurrent-inferences.f90 sourcefile~concurrent-inferences.f90->sourcefile~inference_engine_m.f90 sourcefile~learn-addition.f90 learn-addition.F90 sourcefile~learn-addition.f90->sourcefile~inference_engine_m.f90 sourcefile~learn-exponentiation.f90 learn-exponentiation.F90 sourcefile~learn-exponentiation.f90->sourcefile~inference_engine_m.f90 sourcefile~learn-microphysics-procedures.f90 learn-microphysics-procedures.F90 sourcefile~learn-microphysics-procedures.f90->sourcefile~inference_engine_m.f90 sourcefile~thompson_tensors_m.f90 thompson_tensors_m.f90 sourcefile~learn-microphysics-procedures.f90->sourcefile~thompson_tensors_m.f90 sourcefile~learn-multiplication.f90 learn-multiplication.F90 sourcefile~learn-multiplication.f90->sourcefile~inference_engine_m.f90 sourcefile~learn-power-series.f90 learn-power-series.F90 sourcefile~learn-power-series.f90->sourcefile~inference_engine_m.f90 sourcefile~learn-saturated-mixing-ratio.f90 learn-saturated-mixing-ratio.F90 sourcefile~learn-saturated-mixing-ratio.f90->sourcefile~inference_engine_m.f90 sourcefile~saturated_mixing_ratio_m.f90 saturated_mixing_ratio_m.f90 sourcefile~learn-saturated-mixing-ratio.f90->sourcefile~saturated_mixing_ratio_m.f90 sourcefile~print-training-configuration.f90 print-training-configuration.F90 sourcefile~print-training-configuration.f90->sourcefile~inference_engine_m.f90 sourcefile~saturated_mixing_ratio_m.f90->sourcefile~inference_engine_m.f90 sourcefile~thompson_tensors_m.f90->sourcefile~inference_engine_m.f90 sourcefile~train-and-write.f90 train-and-write.F90 sourcefile~train-and-write.f90->sourcefile~inference_engine_m.f90 sourcefile~training_configuration_s.f90 training_configuration_s.F90 sourcefile~training_configuration_s.f90->sourcefile~inference_engine_m.f90 sourcefile~write-read-infer.f90 write-read-infer.F90 sourcefile~write-read-infer.f90->sourcefile~inference_engine_m.f90

Source Code

! Copyright (c), The Regents of the University of California
! Terms of use are as specified in LICENSE.txt
module ubounds_m
  !! This module serves only to support array bounds checking in the main program below
  implicit none

  type ubounds_t
    integer, allocatable :: ubounds_(:)
  contains
    procedure equals
    generic :: operator(==) => equals
  end type
 
contains

  elemental function equals(lhs, rhs) result(lhs_equals_rhs)
    class(ubounds_t), intent(in) :: lhs, rhs
    logical lhs_equals_rhs
    lhs_equals_rhs = all(lhs%ubounds_ == rhs%ubounds_)
  end function

end module