Skip to content

Commit e60bdea

Browse files
committed
From corr_dev
Squashed commit of the following: commit 9cd7538 Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 22:48:56 2020 +0200 corr_dev: addition of specs commit 4af1d2d Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 22:29:42 2020 +0200 corr_dev: addition of tests for csp and int32 commit aef4416 Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 22:29:08 2020 +0200 corr_dev: addition of tests for csp and int32 commit 0e6ec5d Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 22:19:56 2020 +0200 corr_dev: clarification commit 1fdabd9 Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 22:14:44 2020 +0200 corr_dev: correction of an issue with complex commit 1632355 Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 21:41:12 2020 +0200 corr_dev:completed impl commit 1fe73b1 Merge: 9da1d97 ce987d2 Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 13:13:46 2020 +0200 Merge remote-tracking branch 'upstream/master' into corr_dev commit 9da1d97 Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 12:46:05 2020 +0200 corr_dev: addition of tests for int64 commit d03d828 Author: Vandenplas, Jeremie <[email protected]> Date: Sat May 16 12:22:13 2020 +0200 corr_dev: addition of test for dp complex numbers commit 7901ee2 Author: Vandenplas, Jeremie <[email protected]> Date: Fri May 15 20:18:03 2020 +0200 corr_dev: correction for vector with all elements false commit 2a119c2 Author: Vandenplas, Jeremie <[email protected]> Date: Fri May 15 19:02:12 2020 +0200 corr_dev: done until mask commit 19c1f8e Author: Vandenplas, Jeremie <[email protected]> Date: Fri May 15 16:42:47 2020 +0200 corr_dev: implemented some correlation functions commit ec16e9c Author: Vandenplas, Jeremie <[email protected]> Date: Fri May 15 16:12:13 2020 +0200 corr_dev: init
1 parent ce987d2 commit e60bdea

File tree

6 files changed

+794
-1
lines changed

6 files changed

+794
-1
lines changed

doc/specs/stdlib_experimental_stats.md

Lines changed: 48 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,54 @@ title: experimental_stats
66

77
[TOC]
88

9+
## `corr` - Pearson correlation of array elements
10+
11+
### Description
12+
13+
Returns the Pearson correlation of the elements of `array` along dimension `dim` if the corresponding element in `mask` is `true`.
14+
15+
The Pearson correlation between two rows (or columns), say `x` and `y`, of `array` is defined as:
16+
17+
```
18+
corr(x, y) = cov(x, y) / sqrt( var(x) * var(y))
19+
```
20+
21+
### Syntax
22+
23+
`result = corr(array, dim [, mask])`
24+
25+
### Arguments
26+
27+
`array`: Shall be a rank-1 or a rank-2 array of type `integer`, `real`, or `complex`.
28+
29+
`dim`: Shall be a scalar of type `integer` with a value in the range from 1 to `n`, where `n` is the rank of `array`.
30+
31+
`mask` (optional): Shall be of type `logical` and either a scalar or an array of the same shape as `array`.
32+
33+
### Return value
34+
35+
If `array` is of rank 1 and of type `real` or `complex`, the result is of type `real` corresponding to the type of `array`.
36+
If `array` is of rank 2 and of type `real` or `complex`, the result is of the same type as `array`.
37+
If `array` is of type `integer`, the result is of type `real(dp)`.
38+
39+
If `array` is of rank 1 and of size larger than 1, a scalar equal to 1 is returned. Otherwise, IEEE `NaN` is returned.
40+
If `array` is of rank 2, a rank-2 array with the corresponding correlations is returned.
41+
42+
If `mask` is specified, the result is the Pearson correlation of all elements of `array` corresponding to `true` elements of `mask`. If every element of `mask` is `false`, the result is IEEE `NaN`.
43+
44+
### Example
45+
46+
```fortran
47+
program demo_corr
48+
use stdlib_experimental_stats, only: corr
49+
implicit none
50+
real :: x(1:6) = [ 1., 2., 3., 4., 5., 6. ]
51+
real :: y(1:2, 1:3) = reshape([ -1., 40., -3., 4., 10., 6. ], [ 2, 3])
52+
print *, corr(x, 1) !returns 1.
53+
print *, corr(y, 2) !returns reshape([ 1., -.32480, -.32480, 1. ], [ 2, 3])
54+
end program demo_corr
55+
```
56+
957
## `cov` - covariance of array elements
1058

1159
### Description

src/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ set(fppFiles
77
stdlib_experimental_linalg_diag.fypp
88
stdlib_experimental_optval.fypp
99
stdlib_experimental_stats.fypp
10+
stdlib_experimental_stats_corr.fypp
1011
stdlib_experimental_stats_cov.fypp
1112
stdlib_experimental_stats_mean.fypp
1213
stdlib_experimental_stats_moment.fypp

src/stdlib_experimental_stats.fypp

Lines changed: 95 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,101 @@ module stdlib_experimental_stats
88
implicit none
99
private
1010
! Public API
11-
public :: cov, mean, moment, var
11+
public :: corr, cov, mean, moment, var
12+
13+
interface corr
14+
#:for k1, t1 in RC_KINDS_TYPES
15+
#:set RName = rname("corr",1, t1, k1)
16+
module function ${RName}$(x, dim, mask) result(res)
17+
${t1}$, intent(in) :: x(:)
18+
integer, intent(in) :: dim
19+
logical, intent(in), optional :: mask
20+
real(${k1}$) :: res
21+
end function ${RName}$
22+
#:endfor
23+
24+
25+
#:for k1, t1 in INT_KINDS_TYPES
26+
#:set RName = rname("corr",1, t1, k1, 'dp')
27+
module function ${RName}$(x, dim, mask) result(res)
28+
${t1}$, intent(in) :: x(:)
29+
integer, intent(in) :: dim
30+
logical, intent(in), optional :: mask
31+
real(dp) :: res
32+
end function ${RName}$
33+
#:endfor
34+
35+
36+
#:for k1, t1 in RC_KINDS_TYPES
37+
#:set RName = rname("corr_mask",1, t1, k1)
38+
module function ${RName}$(x, dim, mask) result(res)
39+
${t1}$, intent(in) :: x(:)
40+
integer, intent(in) :: dim
41+
logical, intent(in) :: mask(:)
42+
real(${k1}$) :: res
43+
end function ${RName}$
44+
#:endfor
45+
46+
47+
#:for k1, t1 in INT_KINDS_TYPES
48+
#:set RName = rname("corr_mask",1, t1, k1, 'dp')
49+
module function ${RName}$(x, dim, mask) result(res)
50+
${t1}$, intent(in) :: x(:)
51+
integer, intent(in) :: dim
52+
logical, intent(in) :: mask(:)
53+
real(dp) :: res
54+
end function ${RName}$
55+
#:endfor
56+
57+
58+
#:for k1, t1 in RC_KINDS_TYPES
59+
#:set RName = rname("corr",2, t1, k1)
60+
module function ${RName}$(x, dim, mask) result(res)
61+
${t1}$, intent(in) :: x(:, :)
62+
integer, intent(in) :: dim
63+
logical, intent(in), optional :: mask
64+
${t1}$ :: res(merge(size(x, 1), size(x, 2), mask = 1<dim)&
65+
, merge(size(x, 1), size(x, 2), mask = 1<dim))
66+
end function ${RName}$
67+
#:endfor
68+
69+
70+
#:for k1, t1 in INT_KINDS_TYPES
71+
#:set RName = rname("corr",2, t1, k1, 'dp')
72+
module function ${RName}$(x, dim, mask) result(res)
73+
${t1}$, intent(in) :: x(:, :)
74+
integer, intent(in) :: dim
75+
logical, intent(in), optional :: mask
76+
real(dp) :: res(merge(size(x, 1), size(x, 2), mask = 1<dim)&
77+
, merge(size(x, 1), size(x, 2), mask = 1<dim))
78+
end function ${RName}$
79+
#:endfor
80+
81+
82+
#:for k1, t1 in RC_KINDS_TYPES
83+
#:set RName = rname("corr_mask",2, t1, k1)
84+
module function ${RName}$(x, dim, mask) result(res)
85+
${t1}$, intent(in) :: x(:, :)
86+
integer, intent(in) :: dim
87+
logical, intent(in) :: mask(:,:)
88+
${t1}$ :: res(merge(size(x, 1), size(x, 2), mask = 1<dim)&
89+
, merge(size(x, 1), size(x, 2), mask = 1<dim))
90+
end function ${RName}$
91+
#:endfor
92+
93+
#:for k1, t1 in INT_KINDS_TYPES
94+
#:set RName = rname("corr_mask",2, t1, k1, 'dp')
95+
module function ${RName}$(x, dim, mask) result(res)
96+
${t1}$, intent(in) :: x(:, :)
97+
integer, intent(in) :: dim
98+
logical, intent(in) :: mask(:,:)
99+
real(dp) :: res(merge(size(x, 1), size(x, 2), mask = 1<dim)&
100+
, merge(size(x, 1), size(x, 2), mask = 1<dim))
101+
end function ${RName}$
102+
#:endfor
103+
104+
end interface corr
105+
12106

13107
interface cov
14108
#:for k1, t1 in RC_KINDS_TYPES

0 commit comments

Comments
 (0)