hfnppf(3f) - [M_datapac:PERCENT_POINT] compute the half-normal percent
point function
SUBROUTINE HFNPPF(P,Ppf)
REAL(kind=wp),intent(in) :: P
REAL(kind=wp),intent(out) :: Ppf
HFNPPF(3f) computes the percent point function value for the halfnormal
distribution.
The halfnormal distribution used herein has mean = sqrt(2/pi) =
0.79788456 and standard deviation = 1. this distribution is defined
for all non-negative X and has the probability density function
f(X) = (2/sqrt(2*pi)) * exp(-X*X/2).
The halfnormal distribution used herein is the distribution of the
variate X = abs(Z) where the variate Z is normally distributed with
mean = 0 and standard deviation = 1.
Note that the percent point function of a distribution is identically
the same as the inverse cumulative distribution function of the
distribution.
P The value (between 0.0 (inclusively) and 1.0 (exclusively))
at which the percent point function is to be evaluated.
PPF The percent point function value for the halfnormal
distribution
Sample program:
program demo_hfnppf
use M_datapac, only : hfnppf
implicit none
! call hfnppf(x,y)
end program demo_hfnppf
Results:
The original DATAPAC library was written by James Filliben of the
Statistical Engineering Division, National Institute of Standards
and Technology.
John Urban, 2022.05.31
CC0-1.0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=wp), | intent(in) | :: | P | |||
real(kind=wp), | intent(out) | :: | Ppf |
SUBROUTINE HFNPPF(P,Ppf) REAL(kind=wp),intent(in) :: P REAL(kind=wp),intent(out) :: Ppf REAL(kind=wp) :: arg ! ! CHECK THE INPUT ARGUMENTS FOR ERRORS ! IF ( P<0.0_wp .OR. P>=1.0_wp ) THEN WRITE (G_IO,99001) 99001 FORMAT(' ***** FATAL ERROR--THE FIRST INPUT ARGUMENT TO HFNPPF(3f) IS OUTSIDE THE ALLOWABLE (0,1) INTERVAL *****') WRITE (G_IO,99002) P 99002 FORMAT (' ***** THE VALUE OF THE ARGUMENT IS ',E15.8, ' *****') Ppf = 0.0_wp ELSE arg = (1.0_wp+P)/2.0_wp CALL NORPPF(arg,Ppf) IF ( Ppf<=0.0_wp ) Ppf = 0.0_wp ENDIF ! END SUBROUTINE HFNPPF