Skip to content

Commit d3b45ed

Browse files
authored
Merge pull request #481 from fortran-fans/update_eye
[stdlib_linalg] Update eye function.
2 parents 5089a40 + 2e4d681 commit d3b45ed

File tree

5 files changed

+71
-21
lines changed

5 files changed

+71
-21
lines changed

doc/specs/stdlib_linalg.md

+33-5
Original file line numberDiff line numberDiff line change
@@ -101,30 +101,58 @@ end program demo_diag5
101101

102102
Experimental
103103

104+
### Class
105+
106+
Pure function.
107+
104108
### Description
105109

106-
Construct the identity matrix
110+
Construct the identity matrix.
107111

108112
### Syntax
109113

110-
`I = [[stdlib_linalg(module):eye(function)]](n)`
114+
`I = [[stdlib_linalg(module):eye(function)]](dim1 [, dim2])`
111115

112116
### Arguments
113117

114-
`n`: Shall be a scalar of default type `integer`.
118+
`dim1`: Shall be a scalar of default type `integer`.
119+
This is an `intent(in)` argument.
120+
121+
`dim2`: Shall be a scalar of default type `integer`.
122+
This is an `intent(in)` and `optional` argument.
115123

116124
### Return value
117125

118-
Returns the identity matrix, i.e. a square matrix with ones on the main diagonal and zeros elsewhere. The return value is of type `integer(int8)`.
126+
Return the identity matrix, i.e. a matrix with ones on the main diagonal and zeros elsewhere. The return value is of type `integer(int8)`.
127+
The use of `int8` was suggested to save storage.
128+
129+
#### Warning
130+
131+
Since the result of `eye` is of `integer(int8)` type, one should be careful about using it in arithmetic expressions. For example:
132+
```fortran
133+
real :: A(:,:)
134+
!> Be careful
135+
A = eye(2,2)/2 !! A == 0.0
136+
!> Recommend
137+
A = eye(2,2)/2.0 !! A == diag([0.5, 0.5])
138+
```
119139

120140
### Example
121141

122142
```fortran
123143
program demo_eye1
124144
use stdlib_linalg, only: eye
125145
implicit none
146+
integer :: i(2,2)
126147
real :: a(3,3)
127-
A = eye(3)
148+
real :: b(2,3) !! Matrix is non-square.
149+
complex :: c(2,2)
150+
I = eye(2) !! [1,0; 0,1]
151+
A = eye(3) !! [1.0,0.0,0.0; 0.0,1.0,0.0; 0.0,0.0,1.0]
152+
A = eye(3,3) !! [1.0,0.0,0.0; 0.0,1.0,0.0; 0.0,0.0,1.0]
153+
B = eye(2,3) !! [1.0,0.0,0.0; 0.0,1.0,0.0]
154+
C = eye(2,2) !! [(1.0,0.0),(0.0,0.0); (0.0,0.0),(1.0,0.0)]
155+
C = (1.0,1.0)*eye(2,2) !! [(1.0,1.0),(0.0,0.0); (0.0,0.0),(1.0,1.0)]
128156
end program demo_eye1
129157
```
130158

src/stdlib_linalg.fypp

+24-14
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module stdlib_linalg
55
!! ([Specification](../page/specs/stdlib_linalg.html))
66
use stdlib_kinds, only: sp, dp, qp, &
77
int8, int16, int32, int64
8+
use stdlib_optval, only: optval
89
implicit none
910
private
1011

@@ -82,20 +83,28 @@ module stdlib_linalg
8283

8384
contains
8485

85-
function eye(n) result(res)
86-
!! version: experimental
87-
!!
88-
!! Constructs the identity matrix
89-
!! ([Specification](../page/specs/stdlib_linalg.html#description_1))
90-
integer, intent(in) :: n
91-
integer(int8) :: res(n, n)
92-
integer :: i
93-
res = 0
94-
do i = 1, n
95-
res(i, i) = 1
96-
end do
97-
end function eye
86+
!> Version: experimental
87+
!>
88+
!> Constructs the identity matrix.
89+
!> ([Specification](../page/specs/stdlib_linalg.html#eye-construct-the-identity-matrix))
90+
pure function eye(dim1, dim2) result(result)
91+
92+
integer, intent(in) :: dim1
93+
integer, intent(in), optional :: dim2
94+
integer(int8), allocatable :: result(:, :)
95+
96+
integer :: dim2_
97+
integer :: i
9898

99+
dim2_ = optval(dim2, dim1)
100+
allocate(result(dim1, dim2_))
101+
102+
result = 0_int8
103+
do i = 1, min(dim1, dim2_)
104+
result(i, i) = 1_int8
105+
end do
106+
107+
end function eye
99108

100109
#:for k1, t1 in RCI_KINDS_TYPES
101110
function trace_${t1[0]}$${k1}$(A) result(res)
@@ -108,4 +117,5 @@ contains
108117
end do
109118
end function trace_${t1[0]}$${k1}$
110119
#:endfor
111-
end module
120+
121+
end module stdlib_linalg

src/tests/Makefile.manual

+1
Original file line numberDiff line numberDiff line change
@@ -11,3 +11,4 @@ all test clean:
1111
$(MAKE) -f Makefile.manual --directory=stats $@
1212
$(MAKE) -f Makefile.manual --directory=string $@
1313
$(MAKE) -f Makefile.manual --directory=math $@
14+
$(MAKE) -f Makefile.manual --directory=linalg $@

src/tests/linalg/Makefile.manual

+4
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
PROGS_SRC = test_linalg.f90
2+
3+
4+
include ../Makefile.manual.test.mk

src/tests/linalg/test_linalg.f90

+9-2
Original file line numberDiff line numberDiff line change
@@ -81,12 +81,19 @@ subroutine test_eye
8181
integer :: i
8282
write(*,*) "test_eye"
8383

84+
call check(all(eye(3,3) == diag([(1,i=1,3)])), &
85+
msg="all(eye(3,3) == diag([(1,i=1,3)])) failed.",warn=warn)
86+
87+
rye = eye(3,4)
88+
call check(sum(abs(rye(:,1:3) - diag([(1.0_sp,i=1,3)]))) < sptol, &
89+
msg="sum(abs(rye(:,1:3) - diag([(1.0_sp,i=1,3)]))) < sptol failed", warn=warn)
90+
8491
call check(all(eye(5) == diag([(1,i=1,5)])), &
8592
msg="all(eye(5) == diag([(1,i=1,5)] failed.",warn=warn)
8693

8794
rye = eye(6)
88-
call check(sum(rye - diag([(1.0_sp,i=1,6)])) < sptol, &
89-
msg="sum(rye - diag([(1.0_sp,i=1,6)])) < sptol failed.",warn=warn)
95+
call check(sum(abs(rye - diag([(1.0_sp,i=1,6)]))) < sptol, &
96+
msg="sum(abs(rye - diag([(1.0_sp,i=1,6)]))) < sptol failed.",warn=warn)
9097

9198
cye = eye(7)
9299
call check(abs(trace(cye) - cmplx(7.0_sp,0.0_sp,kind=sp)) < sptol, &

0 commit comments

Comments
 (0)