@@ -275,3 +275,71 @@ program demo_logspace_rstart_cbase
275275
276276end 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+ ```
0 commit comments