Skip to content

Commit 0c9036c

Browse files
committed
Rename function seq to arange.
Update related docs.
1 parent 780944f commit 0c9036c

File tree

9 files changed

+106
-98
lines changed

9 files changed

+106
-98
lines changed

doc/specs/stdlib_math.md

Lines changed: 31 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -275,7 +275,7 @@ program demo_logspace_rstart_cbase
275275
276276
end program demo_logspace_rstart_cbase
277277
```
278-
## `seq` - Creates an vector of `integer/real` type with evenly spaced values within a given interval.
278+
## `arange` - Create a vector of the `integer/real` type with evenly spaced values within a given interval.
279279

280280
### Status
281281

@@ -287,49 +287,56 @@ Pure function.
287287

288288
### Description
289289

290-
Creates an vector of `integer/real` type with evenly spaced values within a given interval.
290+
Create a vector of the `integer/real` type with evenly spaced values within a given interval.
291291

292292
### Syntax
293293

294-
`result = [[stdlib_math(module):seq(interface)]](start [, end, by])`
294+
`result = [[stdlib_math(module):arange(interface)]](start [, end, by])`
295295

296296
### Arguments
297297

298298
`start`: Shall be an `integer/real` scalar.
299-
This is an `intent(in)` argument.
299+
This is an `intent(in)` argument.
300+
The default `start` value is `1`.
300301

301302
`end`: Shall be an `integer/real` scalar.
302-
This is an `intent(in)` and `optional` argument.
303-
304-
`by`: Shall be an `integer/real` scalar and large than `0`.
305303
This is an `intent(in)` and `optional` argument.
304+
The default `end` value is the inputted `start` value.
305+
306+
`by`: Shall be an `integer/real` scalar and large than `0`.
307+
This is an `intent(in)` and `optional` argument.
308+
The default `by` value is `1`.
306309

307-
Warning:
308-
If `by = 0`, the `by` argument will be corrected to `1/1.0` by the internal process of the `seq` function.
309-
If `by < 0`, the `by` argument will be corrected to `abs(by)` by the internal process of the `seq` function.
310+
#### Warning
311+
If `by = 0`, the `by` argument will be corrected to `1/1.0` by the internal process of the `arange` function.
312+
If `by < 0`, the `by` argument will be corrected to `abs(by)` by the internal process of the `arange` function.
310313

311314
### Return value
312315

313-
Vector of evenly spaced values.
316+
Return a vector of evenly spaced values.
314317

315-
For floating point arguments, the length of the result is `floor((end - start)/by) + 1`.
318+
For `real` type arguments, the length of the result vector is `floor((end - start)/by) + 1`.
316319

317320
### Example
318321

319322
```fortran
320-
program demo_math_seq
321-
use stdlib_math, only: seq
323+
program demo_math_arange
324+
use stdlib_math, only: arange
325+
326+
print *, arange(3) !! [1,2,3]
327+
print *, arange(-1) !! [1,0,-1]
328+
print *, arange(0,2) !! [0,1,2]
329+
print *, arange(1,-1) !! [1,0,-1]
330+
print *, arange(0, 2, 2) !! [0,2]
331+
332+
print *, arange(3.0) !! [1.0,2.0,3.0]
333+
print *, arange(0.0,5.0) !! [0.0,1.0,2.0,3.0,4.0,5.0]
334+
print *, arange(0.0,5.0,2.0) !! [0.0,2.0,4.0]
322335
323-
print *, seq(3) !! [1,2,3]
324-
print *, seq(3.0) !! [1.0,2.0,3.0]
325-
print *, seq(-1) !! [1,0,-1]
326-
print *, seq(0,2) !! [0,1,2]
327-
print *, seq(1,-1) !! [1,0,-1]
328-
print *, seq(0, 2, 2) !! [0,2]
329-
print *, (1.0,1.0)*seq(3) !! [(1.0,1.0),(2.0,2.0),[3.0,3.0]]
336+
print *, (1.0,1.0)*arange(3) !! [(1.0,1.0),(2.0,2.0),[3.0,3.0]]
330337
331-
print *, seq(0.0,2.0,-2.0) !! [0.0,2.0]. Not recommended: `by` argument is negative!
332-
print *, seq(0.0,2.0,0.0) !! [0.0,1.0]. Not recommended: `by` argument is zero!
338+
print *, arange(0.0,2.0,-2.0) !! [0.0,2.0]. Not recommended: `by` argument is negative!
339+
print *, arange(0.0,2.0,0.0) !! [0.0,1.0,2.0]. Not recommended: `by` argument is zero!
333340
334-
end program demo_math_seq
341+
end program demo_math_arange
335342
```

src/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ set(fppFiles
3232
stdlib_math.fypp
3333
stdlib_math_linspace.fypp
3434
stdlib_math_logspace.fypp
35-
stdlib_math_seq.fypp
35+
stdlib_math_arange.fypp
3636
stdlib_string_type.fypp
3737
)
3838

src/Makefile.manual

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ SRCFYPP =\
77
stdlib_linalg.fypp \
88
stdlib_linalg_diag.fypp \
99
stdlib_linalg_outer_product.fypp \
10-
stdlib_math_seq.fypp \
10+
stdlib_math_arange.fypp \
1111
stdlib_optval.fypp \
1212
stdlib_quadrature.fypp \
1313
stdlib_quadrature_trapz.fypp \
@@ -155,7 +155,7 @@ stdlib_math_linspace.o: \
155155
stdlib_math.o
156156
stdlib_math_logspace.o: \
157157
stdlib_math_linspace.o
158-
stdlib_math_seq.o: \
158+
stdlib_math_arange.o: \
159159
stdlib_math.o \
160160
stdlib_kinds.o
161161
stdlib_linalg_outer_product.o: stdlib_linalg.o

src/stdlib_math.fypp

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ module stdlib_math
1010
public :: clip, linspace, logspace
1111
public :: EULERS_NUMBER_SP, EULERS_NUMBER_DP, EULERS_NUMBER_QP
1212
public :: DEFAULT_LINSPACE_LENGTH, DEFAULT_LOGSPACE_BASE, DEFAULT_LOGSPACE_LENGTH
13-
public :: seq
13+
public :: arange
1414

1515
integer, parameter :: DEFAULT_LINSPACE_LENGTH = 100
1616
integer, parameter :: DEFAULT_LOGSPACE_LENGTH = 50
@@ -264,18 +264,21 @@ module stdlib_math
264264

265265
!> Version: experimental
266266
!>
267-
!> `seq` creates an vector of `integer/real` type
267+
!> `arange` creates a vector of the `integer/real` type
268268
!> with evenly spaced values within a given interval.
269-
interface seq
269+
!> ([Specification](../page/specs/stdlib_math.html#
270+
!>arange-create-a-vector-of-the-integerreal-type-
271+
!>with-evenly-spaced-values-within-a-given-interval))
272+
interface arange
270273
#:set RI_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES
271274
#:for k1, t1 in RI_KINDS_TYPES
272-
pure module function seq_${t1[0]}$_${k1}$(start, end, by) result(result)
275+
pure module function arange_${t1[0]}$_${k1}$(start, end, by) result(result)
273276
${t1}$, intent(in) :: start
274277
${t1}$, intent(in), optional :: end, by
275278
${t1}$, allocatable :: result(:)
276-
end function seq_${t1[0]}$_${k1}$
279+
end function arange_${t1[0]}$_${k1}$
277280
#:endfor
278-
end interface seq
281+
end interface arange
279282

280283
contains
281284

src/stdlib_math_seq.fypp renamed to src/stdlib_math_arange.fypp

Lines changed: 8 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,14 @@
11
#:include "common.fypp"
2-
submodule(stdlib_math) stdlib_math_seq
2+
submodule(stdlib_math) stdlib_math_arange
33

44
implicit none
55

66
contains
77

88
#:for k1, t1 in REAL_KINDS_TYPES
9-
!> `seq` creates an vector of `${t1}$` type
9+
!> `arange` creates a vector of the `${t1}$` type
1010
!> with evenly spaced values within a given interval.
11-
pure module function seq_${t1[0]}$_${k1}$(start, end, by) result(result)
11+
pure module function arange_${t1[0]}$_${k1}$(start, end, by) result(result)
1212

1313
${t1}$, intent(in) :: start
1414
${t1}$, intent(in), optional :: end, by
@@ -23,18 +23,16 @@ contains
2323
1.0_${k1}$, present(by)), end_ - start_)
2424

2525
allocate(result(floor((end_ - start_)/by_) + 1))
26-
#!TODO: ??
27-
#! floor or ceiling, floor is better.
2826

2927
result = [(start_ + (i - 1)*by_, i=1, size(result), 1)]
3028

31-
end function seq_${t1[0]}$_${k1}$
29+
end function arange_${t1[0]}$_${k1}$
3230
#:endfor
3331

3432
#:for k1, t1 in INT_KINDS_TYPES
35-
!> `seq` creates an vector of `${t1}$` type
33+
!> `arange` creates a vector of the `${t1}$` type
3634
!> with evenly spaced values within a given interval.
37-
pure module function seq_${t1[0]}$_${k1}$(start, end, by) result(result)
35+
pure module function arange_${t1[0]}$_${k1}$(start, end, by) result(result)
3836

3937
${t1}$, intent(in) :: start
4038
${t1}$, intent(in), optional :: end, by
@@ -52,7 +50,7 @@ contains
5250

5351
result = [(i, i=start_, end_, by_)]
5452

55-
end function seq_${t1[0]}$_${k1}$
53+
end function arange_${t1[0]}$_${k1}$
5654
#:endfor
5755

58-
end submodule stdlib_math_seq
56+
end submodule stdlib_math_arange

src/tests/math/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
11
ADDTEST(stdlib_math)
22
ADDTEST(linspace)
33
ADDTEST(logspace)
4-
ADDTEST(math_seq)
4+
ADDTEST(math_arange)

src/tests/math/Makefile.manual

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
PROGS_SRC = test_stdlib_math.f90 test_linspace.f90 test_logspace.f90 \
2-
test_math_seq.f90
2+
test_math_arange.f90
33

44

55
include ../Makefile.manual.test.mk

src/tests/math/test_math_arange.f90

Lines changed: 53 additions & 0 deletions
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

src/tests/math/test_math_seq.f90

Lines changed: 0 additions & 53 deletions
This file was deleted.

0 commit comments

Comments
 (0)