unippf(3f) - [M_datapac:PERCENT_POINT] compute the Uniform percent
point function
SUBROUTINE UNIPPF(P,Ppf)
REAL(kind=wp),intent(in) :: P
REAL(kind=wp),intent(out) :: Ppf
UNIPPF(3f) computes the percent point function value for the uniform
(rectangular) distribution on the unit interval (0,1).
This distribution has mean = 0.5 and standard deviation = sqrt(1/12)
= 0.28867513. This distribution has the probability density function
f(X) = 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 and 1.0) at which the percent point
function is to be evaluated.
PPF The percent point function value.
Sample program:
program demo_unippf
use M_datapac, only : unippf, label
implicit none
call label('unippf')
! call unippf(x,y)
end program demo_unippf
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 UNIPPF(P,Ppf) REAL(kind=wp),intent(in) :: P REAL(kind=wp),intent(out) :: Ppf ! ! 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 UNIPPF(3f) is outside the allowable (0,1) interval *****') WRITE (G_IO,99002) P 99002 FORMAT (' ','***** The value of the argument is ',E15.8,' *****') RETURN ELSE Ppf = P ENDIF END SUBROUTINE UNIPPF