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