Skip to content

Commit c598899

Browse files
authored
Merge pull request #432 from ghbrown/outer_product
Outer product
2 parents 1b93a60 + e852bb5 commit c598899

6 files changed

+241
-25
lines changed

doc/specs/stdlib_linalg.md

+38
Original file line numberDiff line numberDiff line change
@@ -168,3 +168,41 @@ program demo_trace
168168
print *, trace(A) ! 1 + 5 + 9
169169
end program demo_trace
170170
```
171+
172+
## `outer_product` - Computes the outer product of two vectors
173+
174+
### Status
175+
176+
Experimental
177+
178+
### Description
179+
180+
Computes the outer product of two vectors
181+
182+
### Syntax
183+
184+
`d = [[stdlib_linalg(module):outer_product(interface)]](u, v)`
185+
186+
### Arguments
187+
188+
`u`: Shall be a rank-1 array
189+
190+
`v`: Shall be a rank-1 array
191+
192+
### Return value
193+
194+
Returns a rank-2 array equal to `u v^T` (where `u, v` are considered column vectors). The shape of the returned array is `[size(u), size(v)]`.
195+
196+
### Example
197+
198+
```fortran
199+
program demo_outer_product
200+
use stdlib_linalg, only: outer_product
201+
implicit none
202+
real, allocatable :: A(:,:), u(:), v(:)
203+
u = [1., 2., 3. ]
204+
v = [3., 4.]
205+
A = outer_product(u,v)
206+
!A = reshape([3., 6., 9., 4., 8., 12.], [3,2])
207+
end program demo_outer_product
208+
```

src/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ set(fppFiles
99
stdlib_io.fypp
1010
stdlib_linalg.fypp
1111
stdlib_linalg_diag.fypp
12+
stdlib_linalg_outer_product.fypp
1213
stdlib_optval.fypp
1314
stdlib_sorting.fypp
1415
stdlib_sorting_ord_sort.fypp

src/Makefile.manual

+2
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ SRCFYPP =\
66
stdlib_io.fypp \
77
stdlib_linalg.fypp \
88
stdlib_linalg_diag.fypp \
9+
stdlib_linalg_outer_product.fypp \
910
stdlib_optval.fypp \
1011
stdlib_quadrature.fypp \
1112
stdlib_quadrature_trapz.fypp \
@@ -131,3 +132,4 @@ stdlib_strings.o: stdlib_ascii.o \
131132
stdlib_string_type.o \
132133
stdlib_optval.o
133134
stdlib_math.o: stdlib_kinds.o
135+
stdlib_linalg_outer_product.o: stdlib_linalg.o

src/stdlib_linalg.fypp

+17
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module stdlib_linalg
1111
public :: diag
1212
public :: eye
1313
public :: trace
14+
public :: outer_product
1415

1516
interface diag
1617
!! version: experimental
@@ -52,6 +53,7 @@ module stdlib_linalg
5253
#:endfor
5354
end interface
5455

56+
5557
! Matrix trace
5658
interface trace
5759
!! version: experimental
@@ -63,6 +65,21 @@ module stdlib_linalg
6365
#:endfor
6466
end interface
6567

68+
69+
! Outer product (of two vectors)
70+
interface outer_product
71+
!! version: experimental
72+
!!
73+
!! Computes the outer product of two vectors, returning a rank-2 array
74+
!! ([Specification](../page/specs/stdlib_linalg.html#description_3))
75+
#:for k1, t1 in RCI_KINDS_TYPES
76+
pure module function outer_product_${t1[0]}$${k1}$(u, v) result(res)
77+
${t1}$, intent(in) :: u(:), v(:)
78+
${t1}$ :: res(size(u),size(v))
79+
end function outer_product_${t1[0]}$${k1}$
80+
#:endfor
81+
end interface outer_product
82+
6683
contains
6784

6885
function eye(n) result(res)

src/stdlib_linalg_outer_product.fypp

+20
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
#:include "common.fypp"
2+
#:set RCI_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES + INT_KINDS_TYPES
3+
submodule (stdlib_linalg) stdlib_linalg_outer_product
4+
5+
implicit none
6+
7+
contains
8+
9+
#:for k1, t1 in RCI_KINDS_TYPES
10+
pure module function outer_product_${t1[0]}$${k1}$(u, v) result(res)
11+
${t1}$, intent(in) :: u(:), v(:)
12+
${t1}$ :: res(size(u),size(v))
13+
integer :: col
14+
do col = 1, size(v)
15+
res(:,col) = v(col) * u
16+
end do
17+
end function outer_product_${t1[0]}$${k1}$
18+
#:endfor
19+
20+
end submodule

0 commit comments

Comments
 (0)