norsf(3f) - [M_datapac:SPARSITY] compute the normal sparsity function
SUBROUTINE NORSF(P,Sf)
REAL(kind=wp),intent(in) :: P
REAL(kind=wp),intent(out) :: Sf
NORSF(3f) computes the sparsity function value for the normal
(Gaussian) distribution with mean = 0 and standard deviation = 1.
This distribution is defined for all X and has the probability
density function
f(X) = (1/sqrt(2*pi))*exp(-x*x/2)
Note that the sparsity function of a distribution is the derivative
of the percent point function, and also is the reciprocal of the
probability density function (but in units of P rather than X).
P The value at which the sparsity function is to be evaluated.
P should be between 0.0 and 1.0, exclusively.
SF The sparsity function value.
Sample program:
program demo_norsf
use M_datapac, only : norsf
implicit none
! call norsf(x,y)
end program demo_norsf
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) | :: | Sf |
SUBROUTINE NORSF(P,Sf) REAL(kind=wp),intent(in) :: P REAL(kind=wp),intent(out) :: Sf REAL(kind=wp) :: c, pdf, ppf !--------------------------------------------------------------------- DATA c/0.3989422804_wp/ ! ! 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 NORSF(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 CALL NORPPF(P,ppf) pdf = c*EXP(-(ppf*ppf)/2.0_wp) Sf = 1.0_wp/pdf ENDIF ! END SUBROUTINE NORSF