Skip to content

Commit a9a6432

Browse files
committed
Update implementaion of diff procedure.
1 parent b6f0ab1 commit a9a6432

File tree

5 files changed

+126
-29
lines changed

5 files changed

+126
-29
lines changed

CHANGELOG.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ Features available from the latest git source
2222
- new procedures `arg`, `argd` and `argpi`
2323
[#498](https://github.com/fortran-lang/stdlib/pull/498)
2424
- new procedure `diff`
25+
[#605](https://github.com/fortran-lang/stdlib/pull/605)
2526

2627
Changes to existing modules
2728

doc/specs/stdlib_math.md

Lines changed: 21 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -654,15 +654,17 @@ end program demo_math_all_close
654654

655655
#### Description
656656

657-
Computes differences between adjacent elements of the input array.
657+
Computes differences between adjacent elements of an array.
658658

659659
#### Syntax
660660

661+
For rank-1 array
661662
```fortran
662-
!> For rank-1 array
663-
Y = [[stdlib_math(module):diff(interface)]](X [, n])
664-
!> and for rank-2 array
665-
Y = [[stdlib_math(module):diff(interface)]](X [, n, dim])
663+
y = [[stdlib_math(module):diff(interface)]](x [, n, prepend, append])
664+
```
665+
and for rank-2 array
666+
```fortran
667+
y = [[stdlib_math(module):diff(interface)]](x [, n, dim, prepend, append])
666668
```
667669

668670
#### Status
@@ -675,10 +677,9 @@ Pure function.
675677

676678
#### Arguments
677679

678-
Note: If the value of `dim` is not equal to `1` or `2`,
679-
`1` will be used by the internal process of `diff`. (Not recommended)
680+
Note: The `x`, `prepend` and `append` arguments must have same `type`, `kind` and `rank`.
680681

681-
`X`: Shall be a `real/integer` and `rank-1/rank-2` array.
682+
`x`: Shall be a `real/integer` and `rank-1/rank-2` array.
682683
This argument is `intent(in)`.
683684

684685
`n`: Shall be an `integer` scalar.
@@ -689,9 +690,20 @@ It represents to calculate the n-th order difference.
689690
This argument is `intent(in)` and `optional`, which is `1` by default.
690691
It represents to calculate the difference along which dimension.
691692

693+
`prepend`: Shall be a `real/integer` and `rank-1/rank-2` array, which is no value by default.
694+
This argument is `intent(in)` and `optional`.
695+
696+
`append`: Shall be a `real/integer` and `rank-1/rank-2` array, which is no value by default.
697+
This argument is `intent(in)` and `optional`.
698+
699+
Note:
700+
- If the value of `n` is less than or equal to `0`, the return value of `y` is `x`. (Not recommended)
701+
- If the value of `dim` is not equal to `1` or `2`,
702+
`1` will be used by the internal process of `diff`. (Not recommended)
703+
692704
#### Result value
693705

694-
Note: That `Y` has one fewer element than `X`.
706+
Note: That `y` generally has one fewer element than `x`.
695707

696708
Returns a `real/integer` and `rank-1/rank-2` array.
697709

src/stdlib_math.fypp

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -362,20 +362,22 @@ module stdlib_math
362362

363363
!> Version: experimental
364364
!>
365-
!> Computes differences between adjacent elements of the input array.
365+
!> Computes differences between adjacent elements of an array.
366366
!> ([Specification](../page/specs/stdlib_math.html#diff))
367367
interface diff
368368
#:set RI_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES
369369
#:for k1, t1 in RI_KINDS_TYPES
370-
pure module function diff_1_${k1}$(x, n) result(Y)
370+
pure module function diff_1_${k1}$(x, n, prepend, append) result(y)
371371
${t1}$, intent(in) :: x(:)
372372
integer, intent(in), optional :: n
373-
${t1}$, allocatable :: Y(:)
373+
${t1}$, intent(in), optional :: prepend(:), append(:)
374+
${t1}$, allocatable :: y(:)
374375
end function diff_1_${k1}$
375-
pure module function diff_2_${k1}$(X, n, dim) result(Y)
376-
${t1}$, intent(in) :: X(:, :)
376+
pure module function diff_2_${k1}$(X, n, dim, prepend, append) result(y)
377+
${t1}$, intent(in) :: x(:, :)
377378
integer, intent(in), optional :: n, dim
378-
${t1}$, allocatable :: Y(:,:)
379+
${t1}$, intent(in), optional :: prepend(:, :), append(:, :)
380+
${t1}$, allocatable :: y(:, :)
379381
end function diff_2_${k1}$
380382
#:endfor
381383
end interface diff

src/stdlib_math_diff.fypp

Lines changed: 70 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
#! Originally written in 2016 by Keurfon Luu (keurfonluu@outlook.com)
1+
#! Inspired by original code (MIT license) written in 2016 by Keurfon Luu (keurfonluu@outlook.com)
22
#! https://github.com/keurfonluu/Forlab/blob/master/src/lib/forlab.f90#L2673
33

44
#:include "common.fypp"
@@ -9,31 +9,65 @@ submodule (stdlib_math) stdlib_math_diff
99

1010
contains
1111

12-
#! `diff` computes differences of arrays of the ${t1}$ type.
12+
#! `diff` computes differences of adjacent elements of an array of the ${t1}$ type.
1313

1414
#:for k1, t1 in RI_KINDS_TYPES
15-
pure module function diff_1_${k1}$(X, n) result(Y)
16-
${t1}$, intent(in) :: X(:)
15+
pure module function diff_1_${k1}$(x, n, prepend, append) result(y)
16+
${t1}$, intent(in) :: x(:)
1717
integer, intent(in), optional :: n
18-
${t1}$, allocatable :: Y(:)
18+
${t1}$, intent(in), optional :: prepend(:), append(:)
19+
${t1}$, allocatable :: y(:)
20+
integer :: size_prepend, size_append, size_x
21+
${t1}$, allocatable :: work(:)
1922
integer :: n_, i
2023

2124
n_ = optval(n, 1)
25+
if (n_ <= 0) then
26+
y = x
27+
return
28+
end if
29+
30+
size_prepend = 0
31+
size_append = 0
32+
if (present(prepend)) size_prepend = size(prepend)
33+
if (present(append)) size_append = size(append)
34+
size_x = size(x)
35+
36+
if (size_x + size_prepend + size_append <= n_) then
37+
allocate(y(0))
38+
return
39+
end if
2240

23-
Y = X
41+
allocate(work(size_x + size_prepend + size_append))
42+
if (size_prepend > 0) work(:size_prepend) = prepend
43+
work(size_prepend+1:size_prepend+size_x) = x
44+
if (size_append > 0) work(size_prepend+size_x+1:) = append
45+
2446
do i = 1, n_
25-
Y = Y(2:) - Y(:size(Y) - 1)
47+
work(2:) = work(2:) - work(1:size(work)-1)
2648
end do
49+
50+
y = work((n_+1):)
2751

2852
end function diff_1_${k1}$
2953

30-
pure module function diff_2_${k1}$(X, n, dim) result(Y)
31-
${t1}$, intent(in) :: X(:, :)
54+
pure module function diff_2_${k1}$(x, n, dim, prepend, append) result(y)
55+
${t1}$, intent(in) :: x(:, :)
3256
integer, intent(in), optional :: n, dim
33-
${t1}$, allocatable :: Y(:, :)
57+
${t1}$, intent(in), optional :: prepend(:, :), append(:, :)
58+
${t1}$, allocatable :: y(:, :)
59+
integer :: size_prepend, size_append, size_x
3460
integer :: n_, dim_, i
61+
${t1}$, allocatable :: work(:, :)
3562

3663
n_ = optval(n, 1)
64+
if (n_ <= 0) then
65+
y = x
66+
return
67+
end if
68+
69+
size_prepend = 0
70+
size_append = 0
3771
if (present(dim)) then
3872
if (dim == 1 .or. dim == 2) then
3973
dim_ = dim
@@ -44,15 +78,37 @@ contains
4478
dim_ = 1
4579
end if
4680

47-
Y = X
81+
if (present(prepend)) size_prepend = size(prepend, dim_)
82+
if (present(append)) size_append = size(append, dim_)
83+
size_x = size(x, dim_)
84+
85+
if (size_x + size_prepend + size_append <= n_) then
86+
allocate(y(0, 0))
87+
return
88+
end if
89+
4890
if (dim_ == 1) then
91+
allocate(work(size_x+size_prepend+size_append, size(x, 2)))
92+
if (size_prepend > 0) work(1:size_prepend, :) = prepend
93+
work(size_prepend+1:size_x+size_prepend, :) = x
94+
if (size_append > 0) work(size_x+size_prepend+1:, :) = append
4995
do i = 1, n_
50-
Y = Y(2:, :) - Y(:size(Y, 1) - 1, :)
96+
work(2:, :) = work(2:, :) - work(1:size(x, 1)-1, :)
5197
end do
52-
elseif (dim == 2) then
98+
99+
y = work((n_+1):, :)
100+
101+
elseif (dim_ == 2) then
102+
allocate(work(size(x, 1), size_x+size_prepend+size_append))
103+
if (size_prepend > 0) work(:, 1:size_prepend) = prepend
104+
work(:, size_prepend+1:size_x+size_prepend) = x
105+
if (size_append > 0) work(:, size_x+size_prepend+1:) = append
53106
do i = 1, n_
54-
Y = Y(:, 2:) - Y(:, :size(Y, 2) - 1)
107+
work(:, 2:) = work(:, 2:) - work(:, 1:size(work, 2)-1)
55108
end do
109+
110+
y = work(:, (n_+1):)
111+
56112
end if
57113

58114
end function diff_2_${k1}$

src/tests/math/test_stdlib_math.fypp

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -378,6 +378,7 @@ contains
378378
type(error_type), allocatable, intent(out) :: error
379379
${t1}$ :: x(6) = [${t1}$ :: 0, 5, 15, 30, 50, 75]
380380
${t1}$ :: A(1, 3) = reshape([${t1}$ :: 1, 3, 5], [1, 3])
381+
${t1}$ :: B(2) = [${t1}$ :: 1, 2]
381382

382383
call check(error, all_close(diff(x), [${t1}$ :: 5, 10, 15, 20, 25]), &
383384
"diff(x) in test_diff_real_${k1}$ failed")
@@ -387,10 +388,27 @@ contains
387388
"diff(x, n=2) in test_diff_real_${k1}$ failed")
388389
if (allocated(error)) return
389390

391+
call check(error, all_close(diff(x, prepend=[${t1}$ :: 1]), [${t1}$ :: -1, 5, 10, 15, 20, 25]), &
392+
"diff(x, prepend=[${t1}$ :: 1]) in test_diff_real_${k1}$ failed")
393+
if (allocated(error)) return
394+
call check(error, all_close(diff(x, append=[${t1}$ :: 1]), [${t1}$ :: 5, 10, 15, 20, 25, -74]), &
395+
"diff(x, append=[${t1}$ :: 1]) in test_diff_real_${k1}$ failed")
396+
if (allocated(error)) return
397+
390398
call check(error, all_close(diff(A, n=1, dim=2), reshape([${t1}$ :: 2, 2], [1, 2])), &
391399
"diff(x, n=1, dim=2) in test_diff_real_${k1}$ failed")
392400
if (allocated(error)) return
393401

402+
call check(error, all_close(diff(A, n=1, dim=2, prepend=reshape([${t1}$ :: 1], [1, 1]), &
403+
append=reshape([${t1}$ :: 2], [1, 1])), reshape([${t1}$ :: 0, 2, 2, -3], [1, 4])), &
404+
"diff(x, n=1, dim=2, prepend=reshape([${t1}$ :: 1], [1, 1]), &
405+
&append=reshape([${t1}$ :: 2], [1, 1])) in test_diff_real_${k1}$ failed")
406+
if (allocated(error)) return
407+
408+
call check(error, size(diff(B, 2)), 0, "size(diff(B, 2)) in test_diff_real_${k1}$ failed")
409+
if (allocated(error)) return
410+
call check(error, size(diff(B, 3)), 0, "size(diff(B, 3)) in test_diff_real_${k1}$ failed")
411+
394412
end subroutine test_diff_real_${k1}$
395413
#:endfor
396414

@@ -399,11 +417,15 @@ contains
399417
type(error_type), allocatable, intent(out) :: error
400418
${t1}$ :: x(6) = [${t1}$ :: 0, 5, 15, 30, 50, 75]
401419
${t1}$ :: A(1, 3) = reshape([${t1}$ :: 1, 3, 5], [1, 3])
420+
${t1}$ :: B(2) = [${t1}$ :: 1, 2]
402421

403422
call check(error, all(diff(x) == [${t1}$ :: 5, 10, 15, 20, 25]), &
404423
"diff(x) in test_diff_int_${k1}$ failed")
405424
if (allocated(error)) return
406425

426+
call check(error, all(diff(x, n=0) == x), &
427+
"diff(x, n=0) in test_diff_int_${k1}$ failed")
428+
if (allocated(error)) return
407429
call check(error, all(diff(x, n=2) == [${t1}$ :: 5, 5, 5, 5]), &
408430
"diff(x, n=2) in test_diff_int_${k1}$ failed")
409431
if (allocated(error)) return
@@ -412,6 +434,10 @@ contains
412434
"diff(A, n=1, dim=2) in test_diff_int_${k1}$ failed")
413435
if (allocated(error)) return
414436

437+
call check(error, size(diff(B, 2)), 0, "size(diff(B, 2)) in test_diff_real_${k1}$ failed")
438+
if (allocated(error)) return
439+
call check(error, size(diff(B, 3)), 0, "size(diff(B, 3)) in test_diff_real_${k1}$ failed")
440+
415441
end subroutine test_diff_int_${k1}$
416442
#:endfor
417443

0 commit comments

Comments
 (0)