Skip to content

Commit 4052bd2

Browse files
authored
Merge pull request #480 from fortran-fans/add_arange
[stdlib_math] Add arange function.
2 parents ce3a106 + 55da7c0 commit 4052bd2

8 files changed

+203
-3
lines changed

doc/specs/stdlib_math.md

+68
Original file line numberDiff line numberDiff line change
@@ -275,3 +275,71 @@ program demo_logspace_rstart_cbase
275275
276276
end program demo_logspace_rstart_cbase
277277
```
278+
## `arange`
279+
280+
### Status
281+
282+
Experimental
283+
284+
### Class
285+
286+
Pure function.
287+
288+
### Description
289+
290+
Creates a one-dimensional `array` of the `integer/real` type with fixed-spaced values of given spacing, within a given interval.
291+
292+
### Syntax
293+
294+
`result = [[stdlib_math(module):arange(interface)]](start [, end, step])`
295+
296+
### Arguments
297+
298+
All arguments should be the same type and kind.
299+
300+
`start`: Shall be an `integer/real` scalar.
301+
This is an `intent(in)` argument.
302+
The default `start` value is `1`.
303+
304+
`end`: Shall be an `integer/real` scalar.
305+
This is an `intent(in)` and `optional` argument.
306+
The default `end` value is the inputted `start` value.
307+
308+
`step`: Shall be an `integer/real` scalar and large than `0`.
309+
This is an `intent(in)` and `optional` argument.
310+
The default `step` value is `1`.
311+
312+
#### Warning
313+
If `step = 0`, the `step` argument will be corrected to `1/1.0` by the internal process of the `arange` function.
314+
If `step < 0`, the `step` argument will be corrected to `abs(step)` by the internal process of the `arange` function.
315+
316+
### Return value
317+
318+
Returns a one-dimensional `array` of fixed-spaced values.
319+
320+
For `integer` type arguments, the length of the result vector is `(end - start)/step + 1`.
321+
For `real` type arguments, the length of the result vector is `floor((end - start)/step) + 1`.
322+
323+
### Example
324+
325+
```fortran
326+
program demo_math_arange
327+
use stdlib_math, only: arange
328+
329+
print *, arange(3) !! [1,2,3]
330+
print *, arange(-1) !! [1,0,-1]
331+
print *, arange(0,2) !! [0,1,2]
332+
print *, arange(1,-1) !! [1,0,-1]
333+
print *, arange(0, 2, 2) !! [0,2]
334+
335+
print *, arange(3.0) !! [1.0,2.0,3.0]
336+
print *, arange(0.0,5.0) !! [0.0,1.0,2.0,3.0,4.0,5.0]
337+
print *, arange(0.0,6.0,2.5) !! [0.0,2.5,5.0]
338+
339+
print *, (1.0,1.0)*arange(3) !! [(1.0,1.0),(2.0,2.0),[3.0,3.0]]
340+
341+
print *, arange(0.0,2.0,-2.0) !! [0.0,2.0]. Not recommended: `step` argument is negative!
342+
print *, arange(0.0,2.0,0.0) !! [0.0,1.0,2.0]. Not recommended: `step` argument is zero!
343+
344+
end program demo_math_arange
345+
```

src/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ set(fppFiles
3232
stdlib_math.fypp
3333
stdlib_math_linspace.fypp
3434
stdlib_math_logspace.fypp
35+
stdlib_math_arange.fypp
3536
stdlib_string_type.fypp
3637
)
3738

src/Makefile.manual

+5-1
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ SRCFYPP =\
77
stdlib_linalg.fypp \
88
stdlib_linalg_diag.fypp \
99
stdlib_linalg_outer_product.fypp \
10+
stdlib_math_arange.fypp \
1011
stdlib_optval.fypp \
1112
stdlib_quadrature.fypp \
1213
stdlib_quadrature_trapz.fypp \
@@ -149,9 +150,12 @@ stdlib_string_type.o: stdlib_ascii.o \
149150
stdlib_strings.o: stdlib_ascii.o \
150151
stdlib_string_type.o \
151152
stdlib_optval.o
152-
stdlib_math.o: stdlib_kinds.o
153+
stdlib_math.o: stdlib_kinds.o \
154+
stdlib_optval.o
153155
stdlib_math_linspace.o: \
154156
stdlib_math.o
155157
stdlib_math_logspace.o: \
156158
stdlib_math_linspace.o
159+
stdlib_math_arange.o: \
160+
stdlib_math.o
157161
stdlib_linalg_outer_product.o: stdlib_linalg.o

src/stdlib_math.fypp

+18
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,14 @@
44

55
module stdlib_math
66
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, qp
7+
use stdlib_optval, only: optval
78

89
implicit none
910
private
1011
public :: clip, linspace, logspace
1112
public :: EULERS_NUMBER_SP, EULERS_NUMBER_DP, EULERS_NUMBER_QP
1213
public :: DEFAULT_LINSPACE_LENGTH, DEFAULT_LOGSPACE_BASE, DEFAULT_LOGSPACE_LENGTH
14+
public :: arange
1315

1416
integer, parameter :: DEFAULT_LINSPACE_LENGTH = 100
1517
integer, parameter :: DEFAULT_LOGSPACE_LENGTH = 50
@@ -261,6 +263,22 @@ module stdlib_math
261263

262264
end interface
263265

266+
!> Version: experimental
267+
!>
268+
!> `arange` creates a one-dimensional `array` of the `integer/real` type
269+
!> with fixed-spaced values of given spacing, within a given interval.
270+
!> ([Specification](../page/specs/stdlib_math.html#arange))
271+
interface arange
272+
#:set RI_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES
273+
#:for k1, t1 in RI_KINDS_TYPES
274+
pure module function arange_${t1[0]}$_${k1}$(start, end, step) result(result)
275+
${t1}$, intent(in) :: start
276+
${t1}$, intent(in), optional :: end, step
277+
${t1}$, allocatable :: result(:)
278+
end function arange_${t1[0]}$_${k1}$
279+
#:endfor
280+
end interface arange
281+
264282
contains
265283

266284
#:for k1, t1 in IR_KINDS_TYPES

src/stdlib_math_arange.fypp

+54
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,54 @@
1+
#:include "common.fypp"
2+
submodule(stdlib_math) stdlib_math_arange
3+
4+
contains
5+
6+
#:for k1, t1 in REAL_KINDS_TYPES
7+
!> `arange` creates a vector of the `${t1}$` type
8+
!> with evenly spaced values within a given interval.
9+
pure module function arange_${t1[0]}$_${k1}$(start, end, step) result(result)
10+
11+
${t1}$, intent(in) :: start
12+
${t1}$, intent(in), optional :: end, step
13+
${t1}$, allocatable :: result(:)
14+
15+
${t1}$ :: start_, end_, step_
16+
integer :: i
17+
18+
start_ = merge(start, 1.0_${k1}$, present(end))
19+
end_ = optval(end, start)
20+
step_ = optval(step, 1.0_${k1}$)
21+
step_ = sign(merge(step_, 1.0_${k1}$, step_ /= 0.0_${k1}$), end_ - start_)
22+
23+
allocate(result(floor((end_ - start_)/step_) + 1))
24+
25+
result = [(start_ + (i - 1)*step_, i=1, size(result), 1)]
26+
27+
end function arange_${t1[0]}$_${k1}$
28+
#:endfor
29+
30+
#:for k1, t1 in INT_KINDS_TYPES
31+
!> `arange` creates a vector of the `${t1}$` type
32+
!> with evenly spaced values within a given interval.
33+
pure module function arange_${t1[0]}$_${k1}$(start, end, step) result(result)
34+
35+
${t1}$, intent(in) :: start
36+
${t1}$, intent(in), optional :: end, step
37+
${t1}$, allocatable :: result(:)
38+
39+
${t1}$ :: start_, end_, step_
40+
${t1}$ :: i
41+
42+
start_ = merge(start, 1_${k1}$, present(end))
43+
end_ = optval(end, start)
44+
step_ = optval(step, 1_${k1}$)
45+
step_ = sign(merge(step_, 1_${k1}$, step_ /= 0_${k1}$), end_ - start_)
46+
47+
allocate(result((end_ - start_)/step_ + 1))
48+
49+
result = [(i, i=start_, end_, step_)]
50+
51+
end function arange_${t1[0]}$_${k1}$
52+
#:endfor
53+
54+
end submodule stdlib_math_arange

src/tests/math/CMakeLists.txt

+2-1
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
11
ADDTEST(stdlib_math)
22
ADDTEST(linspace)
3-
ADDTEST(logspace)
3+
ADDTEST(logspace)
4+
ADDTEST(math_arange)

src/tests/math/Makefile.manual

+2-1
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
PROGS_SRC = test_stdlib_math.f90 test_linspace.f90 test_logspace.f90
1+
PROGS_SRC = test_stdlib_math.f90 test_linspace.f90 test_logspace.f90 \
2+
test_math_arange.f90
23

34

45
include ../Makefile.manual.test.mk

src/tests/math/test_math_arange.f90

+53
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
!> SPDX-Identifier: MIT
2+
module test_math_arange
3+
4+
use stdlib_error, only: check
5+
use stdlib_math, only: arange
6+
implicit none
7+
8+
logical, private :: warn = .false.
9+
10+
contains
11+
12+
subroutine test_math_arange_real
13+
!> Normal
14+
call check(all(arange(3.0) == [1.0, 2.0, 3.0]), msg="all(arange(3.0) == [1.0,2.0,3.0]) failed.", warn=warn)
15+
call check(all(arange(-1.0) == [1.0, 0.0, -1.0]), msg="all(arange(-1.0) == [1.0,0.0,-1.0]) failed.", warn=warn)
16+
call check(all(arange(0.0, 2.0) == [0.0, 1.0, 2.0]), msg="all(arange(0.0,2.0) == [0.0,1.0,2.0]) failed.", warn=warn)
17+
call check(all(arange(1.0, -1.0) == [1.0, 0.0, -1.0]), msg="all(arange(1.0,-1.0) == [1.0,0.0,-1.0]) failed.", warn=warn)
18+
call check(all(arange(1.0, 1.0) == [1.0]), msg="all(arange(1.0,1.0) == [1.0]) failed.", warn=warn)
19+
call check(all(arange(0.0, 2.0, 2.0) == [0.0, 2.0]), msg="all(arange(0.0,2.0,2.0) == [0.0,2.0]) failed.", warn=warn)
20+
call check(all(arange(1.0, -1.0, 2.0) == [1.0, -1.0]), msg="all(arange(1.0,-1.0,2.0) == [1.0,-1.0]) failed.", warn=warn)
21+
!> Not recommended
22+
call check(all(arange(0.0, 2.0, -2.0) == [0.0, 2.0]), msg="all(arange(0.0,2.0,-2.0) == [0.0,2.0]) failed.", warn=warn)
23+
call check(all(arange(1.0, -1.0, -2.0) == [1.0, -1.0]),msg="all(arange(1.0,-1.0,-2.0) == [1.0,-1.0]) failed.", warn=warn)
24+
call check(all(arange(0.0, 2.0, 0.0) == [0.0,1.0,2.0]),msg="all(arange(0.0, 2.0, 0.0) == [0.0,1.0,2.0]) failed.", warn=warn)
25+
end subroutine test_math_arange_real
26+
27+
subroutine test_math_arange_integer
28+
!> Normal
29+
call check(all(arange(3) == [1, 2, 3]), msg="all(arange(3) == [1,2,3]) failed.", warn=warn)
30+
call check(all(arange(-1) == [1, 0, -1]), msg="all(arange(-1) == [1,0,-1]) failed.", warn=warn)
31+
call check(all(arange(0, 2) == [0, 1, 2]), msg="all(arange(0,2) == [0,1,2]) failed.", warn=warn)
32+
call check(all(arange(1, -1) == [1, 0, -1]), msg="all(arange(1,-1) == [1,0,-1]) failed.", warn=warn)
33+
call check(all(arange(1, 1) == [1]), msg="all(arange(1,1) == [1]) failed.", warn=warn)
34+
call check(all(arange(0, 2, 2) == [0, 2]), msg="all(arange(0,2,2) == [0,2]) failed.", warn=warn)
35+
call check(all(arange(1, -1, 2) == [1, -1]), msg="all(arange(1,-1,2) == [1,-1]) failed.", warn=warn)
36+
!> Not recommended
37+
call check(all(arange(0, 2, -2) == [0, 2]), msg="all(arange(0,2,-2) == [0,2]) failed.", warn=warn)
38+
call check(all(arange(1, -1, -2) == [1, -1]), msg="all(arange(1,-1,-2) == [1,-1]) failed.", warn=warn)
39+
call check(all(arange(0, 2, 0) == [0,1,2]), msg="all(arange(0, 2, 0) == [0,1,2]) failed.", warn=warn)
40+
end subroutine test_math_arange_integer
41+
42+
end module test_math_arange
43+
44+
program tester
45+
46+
use test_math_arange
47+
48+
call test_math_arange_real
49+
call test_math_arange_integer
50+
51+
print *, "All tests in `test_math_arange` passed."
52+
53+
end program tester

0 commit comments

Comments
 (0)