11module stdlib_stats_distribution_uniform
2- use stdlib_kinds
2+ use stdlib_kinds, only : sp, dp, xdp, qp, int8, int16, int32, int64
33 use stdlib_error, only : error_stop
44 use stdlib_random, only : dist_rand
55
@@ -798,28 +798,30 @@ end function pdf_unif_iint64
798798 elemental function pdf_unif_rsp (x , loc , scale ) result(res)
799799
800800 real (sp), intent (in ) :: x, loc, scale
801- real :: res
801+ real (sp) :: res
802+ real (sp), parameter :: zero = 0.0_sp , one = 1.0_sp
802803
803- if (scale == 0.0_sp ) then
804- res = 0.0
804+ if (scale == zero ) then
805+ res = zero
805806 else if (x < loc .or. x > (loc + scale)) then
806- res = 0.0
807+ res = zero
807808 else
808- res = 1.0 / scale
809+ res = one / scale
809810 end if
810811 end function pdf_unif_rsp
811812
812813 elemental function pdf_unif_rdp (x , loc , scale ) result(res)
813814
814815 real (dp), intent (in ) :: x, loc, scale
815- real :: res
816+ real (dp) :: res
817+ real (dp), parameter :: zero = 0.0_dp , one = 1.0_dp
816818
817- if (scale == 0.0_dp ) then
818- res = 0.0
819+ if (scale == zero ) then
820+ res = zero
819821 else if (x < loc .or. x > (loc + scale)) then
820- res = 0.0
822+ res = zero
821823 else
822- res = 1.0 / scale
824+ res = one / scale
823825 end if
824826 end function pdf_unif_rdp
825827
@@ -829,34 +831,34 @@ end function pdf_unif_rdp
829831 elemental function pdf_unif_csp (x , loc , scale ) result(res)
830832
831833 complex (sp), intent (in ) :: x, loc, scale
832- real :: res
833- real (sp) :: tr, ti
834+ real (sp) :: res, tr, ti
835+ real (sp), parameter :: zero = 0.0_sp , one = 1.0_sp
834836
835837 tr = loc % re + scale % re; ti = loc % im + scale % im
836- if (scale == (0.0_sp , 0.0_sp )) then
837- res = 0.0
838+ if (scale == (zero, zero )) then
839+ res = zero
838840 else if ((x % re >= loc % re .and. x % re <= tr) .and. &
839841 (x % im >= loc % im .and. x % im <= ti)) then
840- res = 1.0 / (scale % re * scale % im)
842+ res = one / (scale % re * scale % im)
841843 else
842- res = 0.0
844+ res = zero
843845 end if
844846 end function pdf_unif_csp
845847
846848 elemental function pdf_unif_cdp (x , loc , scale ) result(res)
847849
848850 complex (dp), intent (in ) :: x, loc, scale
849- real :: res
850- real (dp) :: tr, ti
851+ real (dp) :: res, tr, ti
852+ real (dp), parameter :: zero = 0.0_dp , one = 1.0_dp
851853
852854 tr = loc % re + scale % re; ti = loc % im + scale % im
853- if (scale == (0.0_dp , 0.0_dp )) then
854- res = 0.0
855+ if (scale == (zero, zero )) then
856+ res = zero
855857 else if ((x % re >= loc % re .and. x % re <= tr) .and. &
856858 (x % im >= loc % im .and. x % im <= ti)) then
857- res = 1.0 / (scale % re * scale % im)
859+ res = one / (scale % re * scale % im)
858860 else
859- res = 0.0
861+ res = zero
860862 end if
861863 end function pdf_unif_cdp
862864
@@ -933,32 +935,34 @@ end function cdf_unif_iint64
933935 elemental function cdf_unif_rsp (x , loc , scale ) result(res)
934936
935937 real (sp), intent (in ) :: x, loc, scale
936- real :: res
938+ real (sp) :: res
939+ real (sp), parameter :: zero = 0.0_sp , one = 1.0_sp
937940
938- if (scale == 0.0_sp ) then
939- res = 0.0
941+ if (scale == zero ) then
942+ res = zero
940943 else if (x < loc) then
941- res = 0.0
944+ res = zero
942945 else if (x >= loc .and. x <= (loc + scale)) then
943946 res = (x - loc) / scale
944947 else
945- res = 1.0
948+ res = one
946949 end if
947950 end function cdf_unif_rsp
948951
949952 elemental function cdf_unif_rdp (x , loc , scale ) result(res)
950953
951954 real (dp), intent (in ) :: x, loc, scale
952- real :: res
955+ real (dp) :: res
956+ real (dp), parameter :: zero = 0.0_dp , one = 1.0_dp
953957
954- if (scale == 0.0_dp ) then
955- res = 0.0
958+ if (scale == zero ) then
959+ res = zero
956960 else if (x < loc) then
957- res = 0.0
961+ res = zero
958962 else if (x >= loc .and. x <= (loc + scale)) then
959963 res = (x - loc) / scale
960964 else
961- res = 1.0
965+ res = one
962966 end if
963967 end function cdf_unif_rdp
964968
@@ -968,58 +972,60 @@ end function cdf_unif_rdp
968972 elemental function cdf_unif_csp (x , loc , scale ) result(res)
969973
970974 complex (sp), intent (in ) :: x, loc, scale
971- real :: res
975+ real (sp) :: res
976+ real (sp), parameter :: zero = 0.0_sp , one = 1.0_sp
972977 logical :: r1, r2, i1, i2
973978
974- if (scale == (0.0_sp , 0.0_sp )) then
975- res = 0.0
979+ if (scale == (zero, zero )) then
980+ res = zero
976981 return
977982 end if
978983 r1 = x % re < loc % re
979984 r2 = x % re > (loc % re + scale % re)
980985 i1 = x % im < loc % im
981986 i2 = x % im > (loc % im + scale % im)
982987 if (r1 .or. i1) then
983- res = 0.0
988+ res = zero
984989 else if ((.not. r1) .and. (.not. r2) .and. i2) then
985990 res = (x % re - loc % re) / scale % re
986991 else if ((.not. i1) .and. (.not. i2) .and. r2) then
987992 res = (x % im - loc % im) / scale % im
988993 else if ((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
989994 then
990- res = (x % re - loc % re) * (x % im - loc % im) / &
991- (scale % re * scale % im)
995+ res = (( x % re - loc % re) / scale % re) * (( x % im - loc % im) / &
996+ scale % im)
992997 else if (r2 .and. i2)then
993- res = 1.0
998+ res = one
994999 end if
9951000 end function cdf_unif_csp
9961001
9971002 elemental function cdf_unif_cdp (x , loc , scale ) result(res)
9981003
9991004 complex (dp), intent (in ) :: x, loc, scale
1000- real :: res
1005+ real (dp) :: res
1006+ real (dp), parameter :: zero = 0.0_dp , one = 1.0_dp
10011007 logical :: r1, r2, i1, i2
10021008
1003- if (scale == (0.0_dp , 0.0_dp )) then
1004- res = 0.0
1009+ if (scale == (zero, zero )) then
1010+ res = zero
10051011 return
10061012 end if
10071013 r1 = x % re < loc % re
10081014 r2 = x % re > (loc % re + scale % re)
10091015 i1 = x % im < loc % im
10101016 i2 = x % im > (loc % im + scale % im)
10111017 if (r1 .or. i1) then
1012- res = 0.0
1018+ res = zero
10131019 else if ((.not. r1) .and. (.not. r2) .and. i2) then
10141020 res = (x % re - loc % re) / scale % re
10151021 else if ((.not. i1) .and. (.not. i2) .and. r2) then
10161022 res = (x % im - loc % im) / scale % im
10171023 else if ((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
10181024 then
1019- res = (x % re - loc % re) * (x % im - loc % im) / &
1020- (scale % re * scale % im)
1025+ res = (( x % re - loc % re) / scale % re) * (( x % im - loc % im) / &
1026+ scale % im)
10211027 else if (r2 .and. i2)then
1022- res = 1.0
1028+ res = one
10231029 end if
10241030 end function cdf_unif_cdp
10251031
0 commit comments