Skip to content

Commit 2827e9a

Browse files
committed
Add procedure diff.
1 parent bae6be5 commit 2827e9a

File tree

7 files changed

+207
-1
lines changed

7 files changed

+207
-1
lines changed

CHANGELOG.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,8 @@ Features available from the latest git source
1616
- new module `stdlib_io_npy`
1717
[#581](https://github.com/fortran-lang/stdlib/pull/581)
1818
- new procedures `save_npy`, `load_npy`
19+
- update module `stdlib_math`
20+
- new procedure `diff`
1921

2022
Changes to existing modules
2123

doc/specs/stdlib_math.md

Lines changed: 69 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -528,3 +528,72 @@ program demo_math_all_close
528528
529529
end program demo_math_all_close
530530
```
531+
532+
### `diff`
533+
534+
#### Description
535+
536+
Computes differences between adjacent elements of the input array.
537+
538+
#### Syntax
539+
540+
```fortran
541+
!> For rank-1 array
542+
Y = [[stdlib_math(module):diff(interface)]](X [, n])
543+
!> and for rank-2 array
544+
Y = [[stdlib_math(module):diff(interface)]](X [, n, dim])
545+
```
546+
547+
#### Status
548+
549+
Experimental.
550+
551+
#### Class
552+
553+
Pure function.
554+
555+
#### Arguments
556+
557+
Note: If the value of `dim` is not equal to `1` or `2`,
558+
`1` will be used by the internal process of `diff`. (Not recommended)
559+
560+
`X`: Shall be a `real/integer` and `rank-1/rank-2` array.
561+
This argument is `intent(in)`.
562+
563+
`n`: Shall be an `integer` scalar.
564+
This argument is `intent(in)` and `optional`, which is `1` by default.
565+
It represents to calculate the n-th order difference.
566+
567+
`dim`: Shall be an `integer` scalar.
568+
This argument is `intent(in)` and `optional`, which is `1` by default.
569+
It represents to calculate the difference along which dimension.
570+
571+
#### Result value
572+
573+
Note: That `Y` has one fewer element than `X`.
574+
575+
Returns a `real/integer` and `rank-1/rank-2` array.
576+
577+
#### Example
578+
579+
```fortran
580+
program demo_diff
581+
582+
use stdlib_math, only: diff
583+
implicit none
584+
585+
integer :: i(7) = [1, 1, 2, 3, 5, 8, 13]
586+
real :: x(6) = [0, 5, 15, 30, 50, 75]
587+
integer :: A(3, 3) = reshape([1, 7, 17, 3, 11, 19, 5, 13, 23], [3, 3])
588+
integer :: Y(3, 2)
589+
590+
print *, diff(i) !! [0, 1, 1, 2, 3, 5]
591+
print *, diff(x, 2) !! [5.0, 5.0, 5.0, 5.0]
592+
593+
Y = diff(A, n=1, dim=2)
594+
print *, Y(1, :) !! [2, 2]
595+
print *, Y(2, :) !! [4, 2]
596+
print *, Y(3, :) !! [2, 4]
597+
598+
end program demo_diff
599+
```

src/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ set(fppFiles
4242
stdlib_math_arange.fypp
4343
stdlib_math_is_close.fypp
4444
stdlib_math_all_close.fypp
45+
stdlib_math_diff.fypp
4546
stdlib_string_type.fypp
4647
stdlib_string_type_constructor.fypp
4748
stdlib_strings_to_string.fypp

src/Makefile.manual

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ SRCFYPP = \
3939
stdlib_math_logspace.fypp \
4040
stdlib_math_is_close.fypp \
4141
stdlib_math_all_close.fypp \
42+
stdlib_math_diff.fypp \
4243
stdlib_string_type.fypp \
4344
stdlib_string_type_constructor.fypp \
4445
stdlib_strings.fypp \
@@ -205,6 +206,7 @@ stdlib_math_is_close.o: \
205206
stdlib_math_all_close.o: \
206207
stdlib_math.o \
207208
stdlib_math_is_close.o
209+
stdlib_math_diff.o: stdlib_math.o
208210
stdlib_stringlist_type.o: stdlib_string_type.o \
209211
stdlib_math.o \
210212
stdlib_optval.o

src/stdlib_math.fypp

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ module stdlib_math
1515
#:endif
1616
public :: DEFAULT_LINSPACE_LENGTH, DEFAULT_LOGSPACE_BASE, DEFAULT_LOGSPACE_LENGTH
1717
public :: arange, is_close, all_close
18+
public :: diff
1819

1920
integer, parameter :: DEFAULT_LINSPACE_LENGTH = 100
2021
integer, parameter :: DEFAULT_LOGSPACE_LENGTH = 50
@@ -326,6 +327,26 @@ module stdlib_math
326327
#:endfor
327328
#:endfor
328329
end interface all_close
330+
331+
!> Version: experimental
332+
!>
333+
!> Computes differences between adjacent elements of the input array.
334+
!> ([Specification](../page/specs/stdlib_math.html#diff))
335+
interface diff
336+
#:set RI_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES
337+
#:for k1, t1 in RI_KINDS_TYPES
338+
pure module function diff_1_${k1}$(x, n) result(Y)
339+
${t1}$, intent(in) :: x(:)
340+
integer, intent(in), optional :: n
341+
${t1}$, allocatable :: Y(:)
342+
end function diff_1_${k1}$
343+
pure module function diff_2_${k1}$(X, n, dim) result(Y)
344+
${t1}$, intent(in) :: X(:, :)
345+
integer, intent(in), optional :: n, dim
346+
${t1}$, allocatable :: Y(:,:)
347+
end function diff_2_${k1}$
348+
#:endfor
349+
end interface diff
329350

330351
contains
331352

src/stdlib_math_diff.fypp

Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,61 @@
1+
#! Originally written in 2016 by Keurfon Luu (keurfonluu@outlook.com)
2+
#! https://github.com/keurfonluu/Forlab/blob/master/src/lib/forlab.f90#L2673
3+
4+
#:include "common.fypp"
5+
#:set RI_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES
6+
submodule (stdlib_math) stdlib_math_diff
7+
8+
implicit none
9+
10+
contains
11+
12+
#! `diff` computes differences of arrays of the ${t1}$ type.
13+
14+
#:for k1, t1 in RI_KINDS_TYPES
15+
pure module function diff_1_${k1}$(X, n) result(Y)
16+
${t1}$, intent(in) :: X(:)
17+
integer, intent(in), optional :: n
18+
${t1}$, allocatable :: Y(:)
19+
integer :: n_, i
20+
21+
n_ = optval(n, 1)
22+
23+
Y = X
24+
do i = 1, n_
25+
Y = Y(2:) - Y(:size(Y) - 1)
26+
end do
27+
28+
end function diff_1_${k1}$
29+
30+
pure module function diff_2_${k1}$(X, n, dim) result(Y)
31+
${t1}$, intent(in) :: X(:, :)
32+
integer, intent(in), optional :: n, dim
33+
${t1}$, allocatable :: Y(:, :)
34+
integer :: n_, dim_, i
35+
36+
n_ = optval(n, 1)
37+
if (present(dim)) then
38+
if (dim == 1 .or. dim == 2) then
39+
dim_ = dim
40+
else
41+
dim_ = 1
42+
end if
43+
else
44+
dim_ = 1
45+
end if
46+
47+
Y = X
48+
if (dim_ == 1) then
49+
do i = 1, n_
50+
Y = Y(2:, :) - Y(:size(Y, 1) - 1, :)
51+
end do
52+
elseif (dim == 2) then
53+
do i = 1, n_
54+
Y = Y(:, 2:) - Y(:, :size(Y, 2) - 1)
55+
end do
56+
end if
57+
58+
end function diff_2_${k1}$
59+
#:endfor
60+
61+
end submodule stdlib_math_diff

src/tests/math/test_stdlib_math.fypp

Lines changed: 51 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44

55
module test_stdlib_math
66
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
7-
use stdlib_math, only: clip, is_close, all_close
7+
use stdlib_math, only: clip, is_close, all_close, diff
88
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
99
implicit none
1010

@@ -40,6 +40,14 @@ contains
4040
, new_unittest("all_close-real-${k1}$", test_all_close_real_${k1}$) &
4141
, new_unittest("all_close-cmplx-${k1}$", test_all_close_cmplx_${k1}$) &
4242
#:endfor
43+
44+
!> Tests for `diff`
45+
#:for k1 in REAL_KINDS
46+
, new_unittest("diff-real-${k1}$", test_diff_real_${k1}$) &
47+
#:endfor
48+
#:for k1 in INT_KINDS
49+
, new_unittest("diff-int-${k1}$", test_diff_int_${k1}$) &
50+
#:endfor
4351
]
4452

4553
end subroutine collect_stdlib_math
@@ -294,6 +302,48 @@ contains
294302

295303
end subroutine test_all_close_cmplx_${k1}$
296304
#:endfor
305+
306+
#:for k1, t1 in REAL_KINDS_TYPES
307+
subroutine test_diff_real_${k1}$(error)
308+
type(error_type), allocatable, intent(out) :: error
309+
${t1}$ :: x(6) = [${t1}$ :: 0, 5, 15, 30, 50, 75]
310+
${t1}$ :: A(1, 3) = reshape([${t1}$ :: 1, 3, 5], [1, 3])
311+
312+
call check(error, all_close(diff(x), [${t1}$ :: 5, 10, 15, 20, 25]), &
313+
"diff(x) in test_diff_real_${k1}$ failed")
314+
if (allocated(error)) return
315+
316+
call check(error, all_close(diff(x, n=2), [${t1}$ :: 5, 5, 5, 5]), &
317+
"diff(x, n=2) in test_diff_real_${k1}$ failed")
318+
if (allocated(error)) return
319+
320+
call check(error, all_close(diff(A, n=1, dim=2), reshape([${t1}$ :: 2, 2], [1, 2])), &
321+
"diff(x, n=1, dim=2) in test_diff_real_${k1}$ failed")
322+
if (allocated(error)) return
323+
324+
end subroutine test_diff_real_${k1}$
325+
#:endfor
326+
327+
#:for k1, t1 in INT_KINDS_TYPES
328+
subroutine test_diff_int_${k1}$(error)
329+
type(error_type), allocatable, intent(out) :: error
330+
${t1}$ :: x(6) = [${t1}$ :: 0, 5, 15, 30, 50, 75]
331+
${t1}$ :: A(1, 3) = reshape([${t1}$ :: 1, 3, 5], [1, 3])
332+
333+
call check(error, all(diff(x) == [${t1}$ :: 5, 10, 15, 20, 25]), &
334+
"diff(x) in test_diff_int_${k1}$ failed")
335+
if (allocated(error)) return
336+
337+
call check(error, all(diff(x, n=2) == [${t1}$ :: 5, 5, 5, 5]), &
338+
"diff(x, n=2) in test_diff_int_${k1}$ failed")
339+
if (allocated(error)) return
340+
341+
call check(error, all(diff(A, n=1, dim=2) == reshape([${t1}$ :: 2, 2], [1, 2])), &
342+
"diff(A, n=1, dim=2) in test_diff_int_${k1}$ failed")
343+
if (allocated(error)) return
344+
345+
end subroutine test_diff_int_${k1}$
346+
#:endfor
297347

298348
end module test_stdlib_math
299349

0 commit comments

Comments
 (0)