Skip to content

Commit 3196fea

Browse files
committed
Add docs and examples
1 parent fd8fcf1 commit 3196fea

File tree

1 file changed

+282
-0
lines changed

1 file changed

+282
-0
lines changed

doc/specs/stdlib_linalg.md

Lines changed: 282 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -206,3 +206,285 @@ program demo_outer_product
206206
!A = reshape([3., 6., 9., 4., 8., 12.], [3,2])
207207
end program demo_outer_product
208208
```
209+
210+
## `is_square` - Checks if a matrix is square
211+
212+
### Status
213+
214+
Experimental
215+
216+
### Description
217+
218+
Checks if a matrix is square
219+
220+
### Syntax
221+
222+
`d = [[stdlib_linalg(module):is_square(interface)]](A)`
223+
224+
### Arguments
225+
226+
`A`: Shall be a rank-2 array
227+
228+
### Return value
229+
230+
Returns a logical value that is true if the input matrix is square, and false otherwise.
231+
232+
### Example
233+
234+
```fortran
235+
program demo_is_square
236+
use stdlib_linalg, only: is_square
237+
implicit none
238+
real :: A_true(2,2), A_false(3,2)
239+
logical :: res
240+
A_true = reshape([1., 2., 3., 4.], shape(A_true))
241+
A_false = reshape([1., 2., 3., 4., 5., 6.], shape(A_false))
242+
res = is_square(A_true)
243+
!res = .true.
244+
res = is_square(A_false)
245+
!res = .false.
246+
end program demo_is_square
247+
```
248+
249+
## `is_diagonal` - Checks if a matrix is diagonal
250+
251+
### Status
252+
253+
Experimental
254+
255+
### Description
256+
257+
Checks if a matrix is diagonal
258+
259+
### Syntax
260+
261+
`d = [[stdlib_linalg(module):is_diagonal(interface)]](A)`
262+
263+
### Arguments
264+
265+
`A`: Shall be a rank-2 array
266+
267+
### Return value
268+
269+
Returns a logical value that is true if the input matrix is diagonal, and false otherwise.
270+
Note that nonsquare matrices may be diagonal, so long as `a_ij = 0` when `i /= j`.
271+
272+
### Example
273+
274+
```fortran
275+
program demo_is_diagonal
276+
use stdlib_linalg, only: is_diagonal
277+
implicit none
278+
real :: A_true(2,2), A_false(2,2)
279+
logical :: res
280+
A_true = reshape([1., 0., 0., 4.], shape(A_true))
281+
A_false = reshape([1., 0., 3., 4.], shape(A_false))
282+
res = is_diagonal(A_true)
283+
!res = .true.
284+
res = is_diagonal(A_false)
285+
!res = .false.
286+
end program demo_is_diagonal
287+
```
288+
289+
## `is_symmetric` - Checks if a matrix is symmetric
290+
291+
### Status
292+
293+
Experimental
294+
295+
### Description
296+
297+
Checks if a matrix is symmetric
298+
299+
### Syntax
300+
301+
`d = [[stdlib_linalg(module):is_symmetric(interface)]](A)`
302+
303+
### Arguments
304+
305+
`A`: Shall be a rank-2 array
306+
307+
### Return value
308+
309+
Returns a logical value that is true if the input matrix is symmetric, and false otherwise.
310+
311+
### Example
312+
313+
```fortran
314+
program demo_is_symmetric
315+
use stdlib_linalg, only: is_symmetric
316+
implicit none
317+
real :: A_true(2,2), A_false(2,2)
318+
logical :: res
319+
A_true = reshape([1., 3., 3., 4.], shape(A_true))
320+
A_false = reshape([1., 0., 3., 4.], shape(A_false))
321+
res = is_symmetric(A_true)
322+
!res = .true.
323+
res = is_symmetric(A_false)
324+
!res = .false.
325+
end program demo_is_symmetric
326+
```
327+
328+
## `is_skew_symmetric` - Checks if a matrix is skew-symmetric
329+
330+
### Status
331+
332+
Experimental
333+
334+
### Description
335+
336+
Checks if a matrix is skew-symmetric
337+
338+
### Syntax
339+
340+
`d = [[stdlib_linalg(module):is_skew_symmetric(interface)]](A)`
341+
342+
### Arguments
343+
344+
`A`: Shall be a rank-2 array
345+
346+
### Return value
347+
348+
Returns a logical value that is true if the input matrix is skew-symmetric, and false otherwise.
349+
350+
### Example
351+
352+
```fortran
353+
program demo_is_skew_symmetric
354+
use stdlib_linalg, only: is_skew_symmetric
355+
implicit none
356+
real :: A_true(2,2), A_false(2,2)
357+
logical :: res
358+
A_true = reshape([0., -3., 3., 0.], shape(A_true))
359+
A_false = reshape([0., 3., 3., 0.], shape(A_false))
360+
res = is_skew_symmetric(A_true)
361+
!res = .true.
362+
res = is_skew_symmetric(A_false)
363+
!res = .false.
364+
end program demo_is_skew_symmetric
365+
```
366+
367+
## `is_hermitian` - Checks if a matrix is Hermitian
368+
369+
### Status
370+
371+
Experimental
372+
373+
### Description
374+
375+
Checks if a matrix is Hermitian
376+
377+
### Syntax
378+
379+
`d = [[stdlib_linalg(module):is_hermitian(interface)]](A)`
380+
381+
### Arguments
382+
383+
`A`: Shall be a rank-2 array
384+
385+
### Return value
386+
387+
Returns a logical value that is true if the input matrix is Hermitian, and false otherwise.
388+
389+
### Example
390+
391+
```fortran
392+
program demo_is_hermitian
393+
use stdlib_linalg, only: is_hermitian
394+
implicit none
395+
complex :: A_true(2,2), A_false(2,2)
396+
logical :: res
397+
A_true = reshape([cmplx(1.,0.), cmplx(3.,-1.), cmplx(3.,1.), cmplx(4.,0.)], shape(A_true))
398+
A_false = reshape([cmplx(1.,0.), cmplx(3.,1.), cmplx(3.,1.), cmplx(4.,0.)], shape(A_false))
399+
res = is_hermitian(A_true)
400+
!res = .true.
401+
res = is_hermitian(A_false)
402+
!res = .false.
403+
end program demo_is_hermitian
404+
```
405+
406+
## `is_triangular` - Checks if a matrix is triangular
407+
408+
### Status
409+
410+
Experimental
411+
412+
### Description
413+
414+
Checks if a matrix is triangular
415+
416+
### Syntax
417+
418+
`d = [[stdlib_linalg(module):is_triangular(interface)]](A,uplo)`
419+
420+
### Arguments
421+
422+
`A`: Shall be a rank-2 array
423+
424+
`uplo`: Shall be a single character from `{'u','U','l','L'}`
425+
426+
### Return value
427+
428+
Returns a logical value that is true if the input matrix is the type of triangular specified by `uplo` (upper or lower), and false otherwise.
429+
Note that the definition of triangular used here allows nonsquare matrices to be triangular.
430+
Specifically, upper triangular matrices satisfy `a_ij = 0` when `j < i`, and lower triangular matrices satisfy `a_ij = 0` when `j > i`.
431+
432+
### Example
433+
434+
```fortran
435+
program demo_is_triangular
436+
use stdlib_linalg, only: is_triangular
437+
implicit none
438+
real :: A_true(3,3), A_false(3,3)
439+
logical :: res
440+
A_true = reshape([1., 0., 0., 4., 5., 0., 7., 8., 9.], shape(A_true))
441+
A_false = reshape([1., 0., 3., 4., 5., 0., 7., 8., 9.], shape(A_false))
442+
res = is_triangular(A_true,'u')
443+
!res = .true.
444+
res = is_triangular(A_false,'u')
445+
!res = .false.
446+
end program demo_is_triangular
447+
```
448+
449+
## `is_hessenberg` - Checks if a matrix is hessenberg
450+
451+
### Status
452+
453+
Experimental
454+
455+
### Description
456+
457+
Checks if a matrix is Hessenberg
458+
459+
### Syntax
460+
461+
`d = [[stdlib_linalg(module):is_hessenberg(interface)]](A,uplo)`
462+
463+
### Arguments
464+
465+
`A`: Shall be a rank-2 array
466+
467+
`uplo`: Shall be a single character from `{'u','U','l','L'}`
468+
469+
### Return value
470+
471+
Returns a logical value that is true if the input matrix is the type of Hessenberg specified by `uplo` (upper or lower), and false otherwise.
472+
Note that the definition of Hessenberg used here allows nonsquare matrices to be Hessenberg.
473+
Specifically, upper Hessenberg matrices satisfy `a_ij = 0` when `j < i-1`, and lower Hessenberg matrices satisfy `a_ij = 0` when `j > i+1`.
474+
475+
### Example
476+
477+
```fortran
478+
program demo_is_hessenberg
479+
use stdlib_linalg, only: is_hessenberg
480+
implicit none
481+
real :: A_true(3,3), A_false(3,3)
482+
logical :: res
483+
A_true = reshape([1., 2., 0., 4., 5., 6., 7., 8., 9.], shape(A_true))
484+
A_false = reshape([1., 2., 3., 4., 5., 6., 7., 8., 9.], shape(A_false))
485+
res = is_hessenberg(A_true,'u')
486+
!res = .true.
487+
res = is_hessenberg(A_false,'u')
488+
!res = .false.
489+
end program demo_is_hessenberg
490+
```

0 commit comments

Comments
 (0)