Skip to content

Commit 8476d65

Browse files
authored
Merge pull request #764 from Ivanou34/meshgrid
Addition of the `meshgrid` subroutine in `stdlib_math`
2 parents 90a3e9c + 76aaad5 commit 8476d65

File tree

8 files changed

+297
-1
lines changed

8 files changed

+297
-1
lines changed

doc/specs/stdlib_math.md

Lines changed: 56 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -554,3 +554,59 @@ When both `prepend` and `append` are not present, the result `y` has one fewer e
554554
```fortran
555555
{!example/math/example_diff.f90!}
556556
```
557+
558+
### `meshgrid` subroutine
559+
560+
#### Description
561+
562+
Computes a list of coordinate matrices from coordinate vectors.
563+
564+
For $n \geq 1$ coordinate vectors $(x_1, x_2, ..., x_n)$ of sizes $(s_1, s_2, ..., s_n)$, `meshgrid` computes $n$ coordinate matrices $(X_1, X_2, ..., X_n)$ with identical shape corresponding to the selected indexing:
565+
- Cartesian indexing (default behavior): the shape of the coordinate matrices is $(s_2, s_1, s_3, s_4, ... s_n)$.
566+
- matrix indexing: the shape of the coordinate matrices is $(s_1, s_2, s_3, s_4, ... s_n)$.
567+
568+
#### Syntax
569+
570+
For a 2D problem in Cartesian indexing:
571+
`call [[stdlib_math(module):meshgrid(interface)]](x, y, xm, ym)`
572+
573+
For a 3D problem in Cartesian indexing:
574+
`call [[stdlib_math(module):meshgrid(interface)]](x, y, z, xm, ym, zm)`
575+
576+
For a 3D problem in matrix indexing:
577+
`call [[stdlib_math(module):meshgrid(interface)]](x, y, z, xm, ym, zm, indexing="ij")`
578+
579+
The subroutine can be called in `n`-dimensional situations, as long as `n` is inferior to the maximum allowed array rank.
580+
581+
#### Status
582+
583+
Experimental.
584+
585+
#### Class
586+
587+
Subroutine.
588+
589+
#### Arguments
590+
591+
For a `n`-dimensional problem, with `n >= 1`:
592+
593+
`x1, x2, ..., xn`: The coordinate vectors.
594+
Shall be `real/integer` and `rank-1` arrays.
595+
These arguments are `intent(in)`.
596+
597+
`xm1, xm2, ..., xmn`: The coordinate matrices.
598+
Shall be arrays of type `real` or `integer` of adequate shape:
599+
- for Cartesian indexing, the shape of the coordinate matrices must be `[size(x2), size(x1), size(x3), ..., size(xn)]`.
600+
- for matrix indexing, the shape of the coordinate matrices must be `[size(x1), size(x2), size(x3), ..., size(xn)]`.
601+
602+
These argument are `intent(out)`.
603+
604+
`indexing`: the selected indexing.
605+
Shall be an `integer` equal to `stdlib_meshgrid_xy` for Cartesian indexing (default), or `stdlib_meshgrid_ij` for matrix indexing. `stdlib_meshgrid_xy` and `stdlib_meshgrid_ij` are public constants defined in the module.
606+
This argument is `intent(in)` and `optional`, and is equal to `stdlib_meshgrid_xy` by default.
607+
608+
#### Example
609+
610+
```fortran
611+
{!example/math/example_meshgrid.f90!}
612+
```

example/math/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,3 +13,4 @@ ADD_EXAMPLE(math_argd)
1313
ADD_EXAMPLE(math_arg)
1414
ADD_EXAMPLE(math_argpi)
1515
ADD_EXAMPLE(math_is_close)
16+
ADD_EXAMPLE(meshgrid)

example/math/example_meshgrid.f90

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,37 @@
1+
program example_meshgrid
2+
3+
use stdlib_math, only: meshgrid, linspace, stdlib_meshgrid_ij
4+
use stdlib_kinds, only: sp
5+
6+
implicit none
7+
8+
integer, parameter :: nx = 3, ny = 2
9+
real(sp) :: x(nx), y(ny), &
10+
xm_cart(ny, nx), ym_cart(ny, nx), &
11+
xm_mat(nx, ny), ym_mat(nx, ny)
12+
13+
x = linspace(0_sp, 1_sp, nx)
14+
y = linspace(0_sp, 1_sp, ny)
15+
16+
call meshgrid(x, y, xm_cart, ym_cart)
17+
print *, "xm_cart = "
18+
call print_2d_array(xm_cart)
19+
print *, "ym_cart = "
20+
call print_2d_array(ym_cart)
21+
22+
call meshgrid(x, y, xm_mat, ym_mat, indexing=stdlib_meshgrid_ij)
23+
print *, "xm_mat = "
24+
call print_2d_array(xm_mat)
25+
print *, "ym_mat = "
26+
call print_2d_array(ym_mat)
27+
28+
contains
29+
subroutine print_2d_array(array)
30+
real(sp), intent(in) :: array(:, :)
31+
integer :: i
32+
33+
do i = 1, size(array, dim=1)
34+
print *, array(i, :)
35+
end do
36+
end subroutine
37+
end program example_meshgrid

src/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ set(fppFiles
5555
stdlib_math_is_close.fypp
5656
stdlib_math_all_close.fypp
5757
stdlib_math_diff.fypp
58+
stdlib_math_meshgrid.fypp
5859
stdlib_str2num.fypp
5960
stdlib_string_type.fypp
6061
stdlib_string_type_constructor.fypp

src/stdlib_math.fypp

Lines changed: 29 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,8 @@ module stdlib_math
1414
public :: EULERS_NUMBER_QP
1515
#:endif
1616
public :: DEFAULT_LINSPACE_LENGTH, DEFAULT_LOGSPACE_BASE, DEFAULT_LOGSPACE_LENGTH
17-
public :: arange, arg, argd, argpi, is_close, all_close, diff
17+
public :: stdlib_meshgrid_ij, stdlib_meshgrid_xy
18+
public :: arange, arg, argd, argpi, is_close, all_close, diff, meshgrid
1819

1920
integer, parameter :: DEFAULT_LINSPACE_LENGTH = 100
2021
integer, parameter :: DEFAULT_LOGSPACE_LENGTH = 50
@@ -32,6 +33,9 @@ module stdlib_math
3233
real(kind=${k1}$), parameter :: PI_${k1}$ = acos(-1.0_${k1}$)
3334
#:endfor
3435

36+
!> Values for optional argument `indexing` of `meshgrid`
37+
integer, parameter :: stdlib_meshgrid_xy = 0, stdlib_meshgrid_ij = 1
38+
3539
interface clip
3640
#:for k1, t1 in IR_KINDS_TYPES
3741
module procedure clip_${k1}$
@@ -382,6 +386,30 @@ module stdlib_math
382386
#:endfor
383387
end interface diff
384388

389+
390+
!> Version: experimental
391+
!>
392+
!> Computes a list of coordinate matrices from coordinate vectors.
393+
!> ([Specification](../page/specs/stdlib_math.html#meshgrid))
394+
interface meshgrid
395+
#:set RANKS = range(1, MAXRANK + 1)
396+
#:for k1, t1 in IR_KINDS_TYPES
397+
#:for rank in RANKS
398+
#:set RName = rname("meshgrid", rank, t1, k1)
399+
module subroutine ${RName}$(&
400+
${"".join(f"x{i}, " for i in range(1, rank + 1))}$ &
401+
${"".join(f"xm{i}, " for i in range(1, rank + 1))}$ &
402+
indexing &
403+
)
404+
#:for i in range(1, rank + 1)
405+
${t1}$, intent(in) :: x${i}$(:)
406+
${t1}$, intent(out) :: xm${i}$ ${ranksuffix(rank)}$
407+
#:endfor
408+
integer, intent(in), optional :: indexing
409+
end subroutine ${RName}$
410+
#:endfor
411+
#:endfor
412+
end interface meshgrid
385413
contains
386414

387415
#:for k1, t1 in IR_KINDS_TYPES

src/stdlib_math_meshgrid.fypp

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
#:include "common.fypp"
2+
#:set IR_KINDS_TYPES = INT_KINDS_TYPES + REAL_KINDS_TYPES
3+
#:set RANKS = range(1, MAXRANK + 1)
4+
5+
#:def meshgrid_loop(indices)
6+
#:for j in reversed(indices)
7+
do i${j}$ = 1, size(x${j}$)
8+
#:endfor
9+
#:for j in indices
10+
xm${j}$(${"".join(f"i{j}," for j in indices).removesuffix(",")}$) = &
11+
x${j}$(i${j}$)
12+
#:endfor
13+
#:for j in indices
14+
end do
15+
#:endfor
16+
#:enddef
17+
18+
submodule(stdlib_math) stdlib_math_meshgrid
19+
20+
use stdlib_error, only: error_stop
21+
22+
contains
23+
24+
#:for k1, t1 in IR_KINDS_TYPES
25+
#:for rank in RANKS
26+
#:if rank == 1
27+
#:set XY_INDICES = [1]
28+
#:set IJ_INDICES = [1]
29+
#:else
30+
#:set XY_INDICES = [2, 1] + [j for j in range(3, rank + 1)]
31+
#:set IJ_INDICES = [1, 2] + [j for j in range(3, rank + 1)]
32+
#:endif
33+
#: set RName = rname("meshgrid", rank, t1, k1)
34+
module procedure ${RName}$
35+
36+
integer :: ${"".join(f"i{j}," for j in range(1, rank + 1)).removesuffix(",")}$
37+
38+
select case (optval(indexing, stdlib_meshgrid_xy))
39+
case (stdlib_meshgrid_xy)
40+
$:meshgrid_loop(XY_INDICES)
41+
case (stdlib_meshgrid_ij)
42+
$:meshgrid_loop(IJ_INDICES)
43+
case default
44+
call error_stop("ERROR (meshgrid): unexpected indexing.")
45+
end select
46+
end procedure
47+
#:endfor
48+
#:endfor
49+
50+
end submodule

test/math/CMakeLists.txt

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
11
set(
22
fppFiles
33
"test_stdlib_math.fypp"
4+
"test_meshgrid.fypp"
45
)
56
fypp_f90("${fyppFlags}" "${fppFiles}" outFiles)
67

78
ADDTEST(stdlib_math)
89
ADDTEST(linspace)
910
ADDTEST(logspace)
11+
ADDTEST(meshgrid)

test/math/test_meshgrid.fypp

Lines changed: 121 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,121 @@
1+
! SPDX-Identifier: MIT
2+
3+
#:include "common.fypp"
4+
#:set IR_KINDS_TYPES = INT_KINDS_TYPES + REAL_KINDS_TYPES
5+
#:set RANKS = range(1, MAXRANK + 1)
6+
#:set INDEXINGS = ["default", "xy", "ij"]
7+
8+
#:def OPTIONAL_PART_IN_SIGNATURE(indexing)
9+
#:if indexing in ("xy", "ij")
10+
${f', stdlib_meshgrid_{indexing}'}$
11+
#:endif
12+
#:enddef
13+
14+
module test_meshgrid
15+
use testdrive, only : new_unittest, unittest_type, error_type, check
16+
use stdlib_math, only: meshgrid, stdlib_meshgrid_ij, stdlib_meshgrid_xy
17+
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
18+
implicit none
19+
20+
public :: collect_meshgrid
21+
22+
contains
23+
24+
!> Collect all exported unit tests
25+
subroutine collect_meshgrid(testsuite)
26+
!> Collection of tests
27+
type(unittest_type), allocatable, intent(out) :: testsuite(:)
28+
29+
testsuite = [ &
30+
#:for k1, t1 in IR_KINDS_TYPES
31+
#:for rank in RANKS
32+
#:for INDEXING in INDEXINGS
33+
#: set RName = rname(f"meshgrid_{INDEXING}", rank, t1, k1)
34+
new_unittest("${RName}$", test_${RName}$), &
35+
#:endfor
36+
#:endfor
37+
#:endfor
38+
new_unittest("dummy", test_dummy) &
39+
]
40+
41+
end subroutine collect_meshgrid
42+
43+
#:for k1, t1 in IR_KINDS_TYPES
44+
#:for rank in RANKS
45+
#:for INDEXING in INDEXINGS
46+
#:if rank == 1
47+
#:set INDICES = [1]
48+
#:else
49+
#:if INDEXING in ("default", "xy")
50+
#:set INDICES = [2, 1] + [j for j in range(3, rank + 1)]
51+
#:elif INDEXING == "ij"
52+
#:set INDICES = [1, 2] + [j for j in range(3, rank + 1)]
53+
#:endif
54+
#:endif
55+
#:set RName = rname(f"meshgrid_{INDEXING}", rank, t1, k1)
56+
#:set GRIDSHAPE = "".join("length," for j in range(rank)).removesuffix(",")
57+
subroutine test_${RName}$(error)
58+
!> Error handling
59+
type(error_type), allocatable, intent(out) :: error
60+
integer, parameter :: length = 3
61+
${t1}$ :: ${"".join(f"x{j}(length)," for j in range(1, rank + 1)).removesuffix(",")}$
62+
${t1}$ :: ${"".join(f"xm{j}({GRIDSHAPE})," for j in range(1, rank + 1)).removesuffix(",")}$
63+
${t1}$ :: ${"".join(f"xm{j}_exact({GRIDSHAPE})," for j in range(1, rank + 1)).removesuffix(",")}$
64+
integer :: i
65+
integer :: ${"".join(f"i{j}," for j in range(1, rank + 1)).removesuffix(",")}$
66+
${t1}$, parameter :: ZERO = 0
67+
! valid test case
68+
#:for index in range(1, rank + 1)
69+
x${index}$ = [(i, i = length * ${index - 1}$ + 1, length * ${index}$)]
70+
#:endfor
71+
#:for j in range(1, rank + 1)
72+
xm${j}$_exact = reshape( &
73+
[${"".join("(" for dummy in range(rank)) + f"x{j}(i{j})" + "".join(f", i{index} = 1, size(x{index}))" for index in INDICES)}$], &
74+
shape=[${GRIDSHAPE}$] &
75+
)
76+
#:endfor
77+
call meshgrid( &
78+
${"".join(f"x{j}," for j in range(1, rank + 1))}$ &
79+
${"".join(f"xm{j}," for j in range(1, rank + 1)).removesuffix(",")}$ &
80+
${OPTIONAL_PART_IN_SIGNATURE(INDEXING)}$ )
81+
#:for j in range(1, rank + 1)
82+
call check(error, maxval(abs(xm${j}$ - xm${j}$_exact)), ZERO)
83+
if (allocated(error)) return
84+
#:endfor
85+
end subroutine test_${RName}$
86+
#:endfor
87+
#:endfor
88+
#:endfor
89+
90+
subroutine test_dummy(error)
91+
!> Error handling
92+
type(error_type), allocatable, intent(out) :: error
93+
end subroutine
94+
95+
end module test_meshgrid
96+
97+
program tester
98+
use, intrinsic :: iso_fortran_env, only : error_unit
99+
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
100+
use test_meshgrid, only : collect_meshgrid
101+
implicit none
102+
integer :: stat, is
103+
type(testsuite_type), allocatable :: testsuites(:)
104+
character(len=*), parameter :: fmt = '("#", *(1x, a))'
105+
106+
stat = 0
107+
108+
testsuites = [ &
109+
new_testsuite("meshgrid", collect_meshgrid) &
110+
]
111+
112+
do is = 1, size(testsuites)
113+
write(error_unit, fmt) "Testing:", testsuites(is)%name
114+
call run_testsuite(testsuites(is)%collect, error_unit, stat)
115+
end do
116+
117+
if (stat > 0) then
118+
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
119+
error stop
120+
end if
121+
end program tester

0 commit comments

Comments
 (0)