Skip to content

Commit 089f325

Browse files
authored
Merge pull request #272 from Jim-215-Fisher/Distribution-Uniform
Probability Distribution and Statistical Functions -- Uniform Distribution Module
2 parents 1e81f0b + bcd876c commit 089f325

9 files changed

+1234
-3
lines changed

doc/specs/index.md

+1
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ This is and index/directory of the specifications (specs) for each new module/fe
2424
- [random](./stdlib_random.html) - Probability Distributions random number generator
2525
- [sorting](./stdlib_sorting.html) - Sorting of rank one arrays
2626
- [stats](./stdlib_stats.html) - Descriptive Statistics
27+
- [stats_distributions_uniform](./stdlib_stats_distribution_uniform.html) - Uniform Probability Distribution
2728
- [string\_type](./stdlib_string_type.html) - Basic string support
2829
- [strings](./stdlib_strings.html) - String handling and manipulation routines
2930
- [stringlist_type](./stdlib_stringlist_type.html) - 1-Dimensional list of strings
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,379 @@
1+
---
2+
title: stats_distribution_uniform
3+
---
4+
5+
# Statistical Distributions -- Uniform Distribution Module
6+
7+
[TOC]
8+
9+
## `shuffle` - Using Fisher-Yates algorithm to generate a random permutation of a list
10+
11+
### Status
12+
13+
Experimental
14+
15+
### Description
16+
17+
Applying Fisher-Yates algorithm to generate an unbiased permutation for any list of intrinsic numerical data types.
18+
19+
### Syntax
20+
21+
`result = [[stdlib_stats_distribution_uniform(module):shuffle(interface)]]( list )`
22+
23+
### Class
24+
25+
Function.
26+
27+
### Arguments
28+
29+
`list`: argument has `intent(in)` and is a rank one array of `integer`, `real`, or `complex` type.
30+
31+
### Return value
32+
33+
Return a randomized rank one array of the input type.
34+
35+
### Example
36+
37+
```fortran
38+
program demo_shuffle
39+
use stdlib_stats_distribution_PRNG, only : random_seed
40+
use stdlib_stats_distribution_uniform, only : shuffle
41+
implicit none
42+
integer :: seed_put, seed_get, i
43+
real :: x(10)
44+
integer :: n(10)
45+
complex :: z(10)
46+
47+
do i=1, 10
48+
n(i) = i
49+
x(i) = real(i)
50+
z(i) = cmplx(real(i), real(i))
51+
end do
52+
seed_put = 32165498
53+
call random_seed(seed_put, seed_get) ! set and get current value of seed
54+
print *, shuffle(n) ! get randomized n
55+
56+
!10 6 9 2 8 1 3 5 7 4
57+
58+
print *, shuffle(x) ! get randomized x
59+
60+
!5.0 10.0 9.0 4.0 3.0 8.0 2.0 1.0 7.0 6.0
61+
62+
print *, shuffle(z) ! get randomized z
63+
64+
!(8.0, 8.0) (7.0, 7.0) (4.0, 4.0) (1.0, 1.0) (5.0, 5.0)
65+
!(9.0, 9.0) (6.0, 6.0) (3.0, 3.0) (2.0, 2.0) (10.0, 10.0)
66+
67+
end program demo_shuffle
68+
```
69+
70+
## `rvs_uniform` - uniform distribution random variates
71+
72+
### Status
73+
74+
Experimental
75+
76+
### Description
77+
78+
Without argument the function returns a scalar standard uniformly distributed variate U(0,1) of `real` type with single precision on [0,1].
79+
80+
With single argument `scale` of `integer` type the function returns a scalar uniformly distributed variate of `integer` type on [0,scale]. This is the standard Rectangular distribution.
81+
82+
With single argument `scale` of `real` or `complex` type the function returns a scalar uniformly distributed variate of `real` or `complex` type on [0, scale].
83+
84+
With double arguments `loc` and `scale` the function returns a scalar uniformly distributed random variates of `integer`, `real` or `complex` type on [loc, loc + scale] dependent of input type.
85+
86+
With triple arguments `loc`, `scale` and `array_size` the function returns a rank one array of uniformly distributed variates of `integer`, `real` or `complex` type with an array size of `array_size`.
87+
88+
For `complex` type, the real part and imaginary part are independent of each other.
89+
90+
### Syntax
91+
92+
`result = [[stdlib_stats_distribution_uniform(module):rvs_uniform(interface)]]([[loc,] scale] [[[,array_size]]])`
93+
94+
### Class
95+
96+
Elemental function (without the third argument).
97+
98+
### Arguments
99+
100+
`loc`: optional argument has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
101+
102+
`scale`: optional argument has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
103+
104+
`array_size`: optional argument has `intent(in)` and is a scalar of type `integer`.
105+
106+
`loc` and `scale` must have the same type and kind when both are present.
107+
108+
### Return value
109+
110+
The result is a scalar or a rank one array, with size of `array_size`, of type `integer`, `real` or `complex` depending on the input type.
111+
112+
### Example
113+
114+
```fortran
115+
program demo_uniform_rvs
116+
use stdlib_stats_distribution_PRNG, only:random_seed
117+
use stdlib_stats_distribution_uniform, only:uni=> rvs_uniform
118+
119+
implicit none
120+
complex :: loc, scale
121+
real :: a(3,4,5), b(3,4,5)
122+
integer :: seed_put, seed_get
123+
124+
seed_put = 1234567
125+
call random_seed(seed_put, seed_get)
126+
127+
print *, uni( ) !real standard uniform random variate in [0., 1.]
128+
! 0.161520019
129+
130+
print *, uni(3.0) !an uniform random variate in [0., 3.]
131+
! 1.65974522
132+
133+
print *, uni(-0.5, 1.0) !an uniform random variate in [-0.5, 0.5]
134+
! 0.486900032
135+
136+
print *, uni(-1.0,2.0,10)
137+
!an array of 10 uniform random variates in [-1., 1.]
138+
139+
!0.884182811 -0.771520197 0.560377002 0.709313750 -7.12267756E-02
140+
!-0.431066573 0.497536063 -0.396331906 -0.325983286 0.137686729
141+
142+
print *, uni(20) !a random integer variate in [0, 20]
143+
! 17
144+
145+
print *, uni(5,13) !a random integer variate in [5, 18]
146+
! 15
147+
148+
print *, uni(3,19,10) !an array of 10 integer variates in [3,22]
149+
150+
!7 16 16 12 9 21 19 4 3 19
151+
152+
loc = (-0.5, -0.5)
153+
scale = (1.0, 1.0)
154+
155+
print *, uni(scale) !a complex uniform random variate in unit square
156+
157+
!(0.139202669, 0.361759573)
158+
159+
print *, uni(loc,scale)
160+
!a complex uniform random variate in [(-0.5, -0.5), (0.5, 0.5)]
161+
162+
!(0.296536088,-0.143987954)
163+
164+
print *, uni(loc, scale, 10)
165+
!an array of 10 complex uniform random variate in [(-0.5, -0.5), (0.5, 0.5)]
166+
167+
!(-0.302334785,-0.401923567) (0.281620383,9.534919262E-02)
168+
! (-0.374348879,0.457528770) (0.442990601,-0.240510434)
169+
! (-0.421572685,0.279313922) (-0.182090610,5.901372433E-02)
170+
! (-7.864198089E-02,0.378484428) (-0.423258364,-0.201292425)
171+
! (0.193327367,-0.353985727) (-0.397661150,0.355926156)
172+
173+
a(:,:,:) = -0.5
174+
b(:,:,:) = 1.0
175+
176+
print *, uni(a,b)
177+
!a rank 3 array of random variates in [-0.5,0.5]
178+
179+
! -0.249188632 -0.199248433 -0.389813602 2.88307667E-03 0.238479793,
180+
! 0.264856219 -0.205177426 -0.480921626 0.131218433 0.252170086,
181+
! -0.303151041 -8.89462233E-02 -0.377370685 0.341802299 0.323204756,
182+
! 0.358679056 -0.138909757 0.384329498 -0.109372199 0.132353067,
183+
! 0.494320452 0.419343710 -0.103044361 0.461389005 0.403132677
184+
! 0.121850729 0.403839290 -0.349389791 0.490482628 0.156600773
185+
! 8.46788883E-02 -0.483680278 0.388107836 0.119698405 0.154214382
186+
! 0.153113484 0.236523747 0.155937552 -0.135760903 0.219589531
187+
! 0.394639254 6.30156994E-02 -0.342692465 -0.444846451 -0.215700030
188+
! 0.204189956 -0.208748132 0.355063021 8.98272395E-02 -0.237928331
189+
! 2.98077464E-02 -0.485149682 -8.06870461E-02 -0.372713923
190+
! -0.178335011 0.283877611 -2.13934183E-02 -9.21690464E-03
191+
! 4.56320047E-02 0.220112979
192+
193+
end program demo_uniform_rvs
194+
```
195+
196+
## `pdf_uniform` - Uniform probability density function
197+
198+
### Status
199+
200+
Experimental
201+
202+
### Description
203+
204+
The probability density function of the uniform distribution.
205+
206+
f(x) = 1 / (scale + 1); for discrete uniform distribution.
207+
208+
f(x) = 1 / scale; for continuous uniform distribution.
209+
210+
f(x) = 1 / (scale%re * scale%im); for complex uniform distribution.
211+
212+
### Syntax
213+
214+
`result = [[stdlib_stats_distribution_uniform(module):pdf_uniform(interface)]](x, loc, scale)`
215+
216+
### Class
217+
218+
Elemental function.
219+
220+
### Arguments
221+
222+
`x`: has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
223+
224+
`loc`: has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
225+
226+
`scale`: has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
227+
228+
All three arguments must have the same type and kind.
229+
230+
### Return value
231+
232+
The result is a scalar or an array, with a shape conformable to arguments, of type `real`.
233+
234+
### Example
235+
236+
```fortran
237+
program demo_uniform_pdf
238+
use stdlib_stats_distribution_PRNG, only : random_seed
239+
use stdlib_stats_distribution_uniform, only : uni_pdf => pdf_uniform, &
240+
uni => rvs_uniform
241+
242+
implicit none
243+
complex :: loc, scale
244+
real :: a(3,4,5), b(3,4,5), x(3,4,5)
245+
integer :: seed_put, seed_get
246+
247+
seed_put = 1234567
248+
call random_seed(seed_put, seed_get)
249+
250+
print *, uni_pdf(3, 2, 10) !probability density at 3 in range [2, 10]
251+
252+
! 9.09090936E-02
253+
254+
print *, uni_pdf(0.5,0.0,1.0) !a probability density at 0.5 in [0., 1.]
255+
256+
! 1.00000000
257+
258+
259+
print *, uni_pdf(0.7,-1.0,2.0) !a probability density at 0.7 in [-1., 1.]
260+
261+
! 0.500000000
262+
263+
a(:,:,:) = 0.0
264+
b(:,:,:) = 2.0
265+
x = reshape(uni(0.,2.,60),[3,4,5])! uniform random variates array in [0., 2.]
266+
print *, uni_pdf(x, a, b) ! probability density array in [0., 2.]
267+
268+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
269+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
270+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
271+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
272+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
273+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
274+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
275+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
276+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
277+
! 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000 0.500000000
278+
279+
loc = (-0.5,-0.5)
280+
scale = (1.0,1.0)
281+
print *, uni_pdf((-0.1,0.2), loc, scale)
282+
! joint probability density at (-0.1,0.2) in [(-0.5, -0.5), (0.5, 0.5)]
283+
284+
! 1.00000000
285+
end program demo_uniform_pdf
286+
287+
```
288+
289+
## `cdf_uniform` - Uniform cumulative distribution function
290+
291+
### Status
292+
293+
Experimental
294+
295+
### Description
296+
297+
Cumulative distribution function of the uniform distribution
298+
299+
F(x) = (x - loc + 1) / (scale + 1); for discrete uniform distribution.
300+
301+
F(x) = (x - loc) / scale; for continuous uniform distribution.
302+
303+
F(x) = (x%re - loc%re)(x%im - loc%im) / (scale%re * scale%im); for complex uniform distribution.
304+
305+
### Syntax
306+
307+
`result = [[stdlib_stats_distribution_uniform(module):cdf_uniform(interface)]](x, loc, scale)`
308+
309+
### Class
310+
311+
Elemental function.
312+
313+
### Arguments
314+
315+
`x`: has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
316+
317+
`loc`: has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
318+
319+
`scale`: has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
320+
321+
All three arguments must have the same type and kind.
322+
323+
### Return value
324+
325+
The result is a scalar or an array, with a shape conformable to arguments, of type `real`.
326+
327+
### Example
328+
329+
```fortran
330+
program demo_uniform_cdf
331+
use stdlib_stats_distribution_PRNG, only : random_seed
332+
use stdlib_stats_distribution_uniform, only : uni_cdf => cdf_uniform, &
333+
uni => rvs_uniform
334+
335+
implicit none
336+
real :: x(3,4,5), a(3,4,5), b(3,4,5)
337+
complex :: loc, scale
338+
integer :: seed_put, seed_get
339+
340+
seed_put = 1234567
341+
call random_seed(seed_put, seed_get)
342+
343+
print *, uni_cdf(0.5,0.,1.) ! a cumulative at 0.5 in [0., 1.]
344+
345+
!0.500000000
346+
347+
print *, uni_cdf(0.7,-1.0,2.0) ! a cumulative at 0.7 in [-1.0, 1.0]
348+
349+
! 0.850000024
350+
351+
print *, uni_cdf(6, 2, 10) ! a cumulative at 6 in [2, 10]
352+
353+
! 0.454545468
354+
355+
a(:,:,:) = -1.0
356+
b(:,:,:) = 2.0
357+
x = reshape(uni(-1.0,2.0,60),[3,4,5]) ! uniform random variates array
358+
print *, uni_cdf(x,a,b) ! cumulative array in [-1.0, 1.0]
359+
360+
!0.161520004 0.553248405 0.986900032 0.942091405 0.114239901 0.780188501
361+
! 0.854656875 0.464386612 0.284466714 0.748768032 0.301834047 0.337008357
362+
!0.568843365 0.596165061 0.180993259 0.614166319 0.214835495 7.98164606E-02
363+
!0.641274095 0.607101977 0.701139212 0.230517209 1.97925568E-02 0.857982159
364+
!0.712761045 0.139202654 0.361759573 0.796536088 0.356012046 0.197665215
365+
!9.80764329E-02 0.781620383 0.595349193 0.125651121 0.957528770 0.942990601
366+
!0.259489566 7.84273148E-02 0.779313922 0.317909390 0.559013724 0.421358019
367+
!0.878484428 7.67416358E-02 0.298707575 0.693327367 0.146014273 0.102338850
368+
!0.855926156 0.250811368 0.300751567 0.110186398 0.502883077 0.738479793
369+
!0.764856219 0.294822574 1.90783739E-02 0.631218433 0.752170086 0.196848959
370+
371+
loc = (0., 0.)
372+
scale=(2., 1.)
373+
print *, uni_cdf((1.2,0.5), loc, scale)
374+
! joint cumulative distribution at (1.2,0.5) in [(0.,0.), (2.,1.)]
375+
376+
! 0.300000012
377+
end program demo_uniform_cdf
378+
379+
```

0 commit comments

Comments
 (0)