f_dst_f_ppf Function

public impure function f_dst_f_ppf(p, d1, d2, loc, scale) result(x)

Impure wrapper function for f_dst_f_ppf_core. Handles optional arguments and invalid values for arguments.

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in) :: p

probability (0.0 < p < 1.0)

real(kind=wp), intent(in) :: d1

numerator degrees of freedom

real(kind=wp), intent(in) :: d2

denominator degrees of freedom

real(kind=wp), intent(in), optional :: loc

location parameter

real(kind=wp), intent(in), optional :: scale

scale parameter

Return Value real(kind=wp)


Calls

proc~~f_dst_f_ppf~~CallsGraph proc~f_dst_f_ppf f_dst_f_ppf proc~f_dst_f_ppf_core f_dst_f_ppf_core proc~f_dst_f_ppf->proc~f_dst_f_ppf_core proc~s_err_print s_err_print proc~f_dst_f_ppf->proc~s_err_print proc~s_err_warn s_err_warn proc~f_dst_f_ppf->proc~s_err_warn proc~f_dst_f_cdf_core f_dst_f_cdf_core proc~f_dst_f_ppf_core->proc~f_dst_f_cdf_core proc~f_utl_r2c f_utl_r2c proc~s_err_print->proc~f_utl_r2c proc~f_dst_betai_core f_dst_betai_core proc~f_dst_f_cdf_core->proc~f_dst_betai_core

Called by

proc~~f_dst_f_ppf~~CalledByGraph proc~f_dst_f_ppf f_dst_f_ppf interface~fsml_f_ppf fsml_f_ppf interface~fsml_f_ppf->proc~f_dst_f_ppf

Source Code

impure function f_dst_f_ppf(p, d1, d2, loc, scale) result(x)

! ==== Description
!! Impure wrapper function for `f_dst_f_ppf_core`.
!! Handles optional arguments and invalid values for arguments.

! ==== Declarations
  real(wp), intent(in)           :: p                !! probability (0.0 < p < 1.0)
  real(wp), intent(in)           :: d1               !! numerator degrees of freedom
  real(wp), intent(in)           :: d2               !! denominator degrees of freedom
  real(wp), intent(in), optional :: loc              !! location parameter
  real(wp), intent(in), optional :: scale            !! scale parameter
  real(wp)                       :: loc_w            !! effective location
  real(wp)                       :: scale_w          !! effective scale
  real(wp)                       :: x                !! result: quantile at p

! ==== Instructions

! ---- handle input

  ! assume loc = 0, overwrite if specified
  loc_w = 0.0_wp
  if (present(loc)) loc_w = loc

  ! assume scale = 1, overwrite if specified
  scale_w = 1.0_wp
  if (present(scale)) scale_w = scale

  ! check if scale value is valid
  if (scale_w .le. 0.0_wp) then
     ! write error message and assign sentinel value if invalid
     call s_err_print(fsml_error(1))
     x = c_sentinel_r
     return
  endif

  ! check if numerator degrees of freedom value is valid
  if (d1 .le. 0.0_wp) then
     ! write error message and assign sentinel value if invalid
     call s_err_print(fsml_error(1))
     x = c_sentinel_r
     return
  endif

  ! check if denominator degrees of freedom value is valid
  if (d2 .le. 0.0_wp) then
     ! write error message and assign sentinel value if invalid
     call s_err_print(fsml_error(1))
     x = c_sentinel_r
     return
  endif

  ! check if p value is valid
  if (p .gt. 1.0_wp .or. p .lt. 0.0_wp) then
     ! write error message and assign sentinel value if invalid
     call s_err_print(fsml_error(1))
     x = c_sentinel_r
     return
  endif

! ---- compute PPF

  ! call pure function to calculate x
  x = f_dst_f_ppf_core(p, d1, d2, loc_w, scale_w)

  ! issue warning in case of suspicious result
  if (x .eq. c_sentinel_r) call s_err_warn(fsml_warning(1))

end function f_dst_f_ppf