@@ -146,6 +146,38 @@ module stdlib_intrinsics
146146 #:endfor
147147 end interface
148148 public :: kahan_kernel
149+
150+ interface stdlib_matmul
151+ !! version: experimental
152+ !!
153+ !!### Summary
154+ !! compute the matrix multiplication of more than two matrices with a single function call.
155+ !! ([Specification](../page/specs/stdlib_intrinsics.html#stdlib_matmul))
156+ !!
157+ !!### Description
158+ !!
159+ !! matrix multiply more than two matrices with a single function call
160+ !! the multiplication with the optimal bracketization is done automatically
161+ !! Supported data types are `real`, `integer` and `complex`.
162+ !!
163+ #:for k, t, s in I_KINDS_TYPES + R_KINDS_TYPES + C_KINDS_TYPES
164+ pure module function stdlib_matmul_${s}$_3 (a, b, c) result(d)
165+ ${t}$, intent(in) :: a(:,:), b(:,:), c(:,:)
166+ ${t}$, allocatable :: d(:,:)
167+ end function stdlib_matmul_${s}$_3
168+
169+ pure module function stdlib_matmul_${s}$_4 (a, b, c, d) result(e)
170+ ${t}$, intent(in) :: a(:,:), b(:,:), c(:,:), d(:,:)
171+ ${t}$, allocatable :: e(:,:)
172+ end function stdlib_matmul_${s}$_4
173+
174+ pure module function stdlib_matmul_${s}$_5 (a, b, c, d, e) result(f)
175+ ${t}$, intent(in) :: a(:,:), b(:,:), c(:,:), d(:,:), e(:,:)
176+ ${t}$, allocatable :: f(:,:)
177+ end function stdlib_matmul_${s}$_5
178+ #:endfor
179+ end interface stdlib_matmul
180+ public :: stdlib_matmul
149181
150182contains
151183
0 commit comments