From f7c5ae9b4c394ce0aa4632bf5f51889aec470cb2 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 16:26:52 +0800
Subject: [PATCH 01/14] Create stdlib_linalg_repmat.fypp

---
 src/stdlib_linalg_repmat.fypp | 29 +++++++++++++++++++++++++++++
 1 file changed, 29 insertions(+)
 create mode 100644 src/stdlib_linalg_repmat.fypp

diff --git a/src/stdlib_linalg_repmat.fypp b/src/stdlib_linalg_repmat.fypp
new file mode 100644
index 000000000..e7ffd5c58
--- /dev/null
+++ b/src/stdlib_linalg_repmat.fypp
@@ -0,0 +1,29 @@
+#:include "common.fypp"
+#:set RCI_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES + INT_KINDS_TYPES
+submodule (stdlib_linalg) stdlib_linalg_repmat
+
+  implicit none
+
+contains
+
+  #:for k1, t1 in RCI_KINDS_TYPES
+    pure module function repmat_${t1[0]}$${k1}$(a, m, n) result(res)
+      ${t1}$, intent(in) :: a(:,:)
+      ${t1}$, intent(in) :: m,n
+      ${t1}$ :: res(m*size(a,1),n*size(a,2))
+      associate(ma=>size(a,1),na=>size(a,2))
+         do j=1,n
+            do l=1,na
+               do i=1,m
+                  do k=1,ma
+                     c((i-1)*ma+k,(j-1)*na+l)=a(k,l)
+                  end do
+               end do
+            end do
+         end do
+      end associate
+    end function repmat_${t1[0]}$${k1}$
+
+  #:endfor
+
+end submodule

From 5211579293beebf7d73f2cabfe43a35d98a74bd1 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 16:39:50 +0800
Subject: [PATCH 02/14] Update stdlib_linalg.fypp

---
 src/stdlib_linalg.fypp | 15 +++++++++++++++
 1 file changed, 15 insertions(+)

diff --git a/src/stdlib_linalg.fypp b/src/stdlib_linalg.fypp
index bc1017f0a..fb72d434c 100644
--- a/src/stdlib_linalg.fypp
+++ b/src/stdlib_linalg.fypp
@@ -92,6 +92,21 @@ module stdlib_linalg
     #:endfor
   end interface outer_product
 
+  ! repeat matrix (of 2d array)
+  interface repmat
+    !! version: experimental
+    !!
+    !! Creates large matrices from a small array, `repmat()` repeats the given values of the array to create the large matrix.
+    !! ([Specification](../page/specs/stdlib_linalg.html#
+    !! repmat-creates-large-matrices-from-a-small-array))
+    #:for k1, t1 in RCI_KINDS_TYPES
+      pure module function repmat_${t1[0]}$${k1}$(a,m,n) result(res)
+        ${t1}$, intent(in) :: a(:,:)
+        ${t1}$, intent(in) :: m,n
+        ${t1}$ :: res(m*size(a,1),n*size(a,2))
+      end function repmat_${t1[0]}$${k1}$
+    #:endfor
+  end interface repmat
 
   ! Check for squareness
   interface is_square

From c30d5cf67c3ea4b13dcb4e1884c0986bb44327f4 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 16:46:47 +0800
Subject: [PATCH 03/14] Create example_linalg_repmat.f90

---
 example/linalg/example_linalg_repmat.f90 | 12 ++++++++++++
 1 file changed, 12 insertions(+)
 create mode 100644 example/linalg/example_linalg_repmat.f90

diff --git a/example/linalg/example_linalg_repmat.f90 b/example/linalg/example_linalg_repmat.f90
new file mode 100644
index 000000000..c907ec879
--- /dev/null
+++ b/example/linalg/example_linalg_repmat.f90
@@ -0,0 +1,12 @@
+program example_repmat
+  use stdlib_linalg, only: repmat
+  implicit none
+  real, allocatable :: a(:, :),b(:,:)
+  a = reshape([1., 2., 3., 4.],[2, 2],order=[2, 1])
+  b = repmat(a, 2, 2)
+! A = reshape([1., 2., 1., 2.,&
+!              3., 4., 3., 4.,&
+!              1., 2., 1., 2.,&
+!              3., 4., 3., 4.,&
+!               ], [4, 4],order=[2, 1])
+end program example_repmat

From 4b0df3232137f7b044ec49b531e9482ac236c870 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 16:54:30 +0800
Subject: [PATCH 04/14] Update stdlib_linalg_repmat.fypp

---
 src/stdlib_linalg_repmat.fypp | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/src/stdlib_linalg_repmat.fypp b/src/stdlib_linalg_repmat.fypp
index e7ffd5c58..96db9ca12 100644
--- a/src/stdlib_linalg_repmat.fypp
+++ b/src/stdlib_linalg_repmat.fypp
@@ -9,7 +9,7 @@ contains
   #:for k1, t1 in RCI_KINDS_TYPES
     pure module function repmat_${t1[0]}$${k1}$(a, m, n) result(res)
       ${t1}$, intent(in) :: a(:,:)
-      ${t1}$, intent(in) :: m,n
+      integer, intent(in) :: m,n
       ${t1}$ :: res(m*size(a,1),n*size(a,2))
       associate(ma=>size(a,1),na=>size(a,2))
          do j=1,n

From 5196eddfbe1ab44799e72e762bf1a7fafb1dc401 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 17:02:49 +0800
Subject: [PATCH 05/14] Update stdlib_linalg.fypp

---
 src/stdlib_linalg.fypp | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/src/stdlib_linalg.fypp b/src/stdlib_linalg.fypp
index fb72d434c..25dae9514 100644
--- a/src/stdlib_linalg.fypp
+++ b/src/stdlib_linalg.fypp
@@ -102,7 +102,7 @@ module stdlib_linalg
     #:for k1, t1 in RCI_KINDS_TYPES
       pure module function repmat_${t1[0]}$${k1}$(a,m,n) result(res)
         ${t1}$, intent(in) :: a(:,:)
-        ${t1}$, intent(in) :: m,n
+        integer, intent(in) :: m,n
         ${t1}$ :: res(m*size(a,1),n*size(a,2))
       end function repmat_${t1[0]}$${k1}$
     #:endfor

From 8fe746788b158d761360149a96bd6dd8d550106d Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 17:13:34 +0800
Subject: [PATCH 06/14] Rename example_linalg_repmat.f90 to example_repmat.f90

---
 example/linalg/{example_linalg_repmat.f90 => example_repmat.f90} | 0
 1 file changed, 0 insertions(+), 0 deletions(-)
 rename example/linalg/{example_linalg_repmat.f90 => example_repmat.f90} (100%)

diff --git a/example/linalg/example_linalg_repmat.f90 b/example/linalg/example_repmat.f90
similarity index 100%
rename from example/linalg/example_linalg_repmat.f90
rename to example/linalg/example_repmat.f90

From 4f18fab4b5944a711e94ea6e90ab7aa4ac797c4b Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 17:14:09 +0800
Subject: [PATCH 07/14] Update stdlib_linalg.fypp

---
 src/stdlib_linalg.fypp | 1 +
 1 file changed, 1 insertion(+)

diff --git a/src/stdlib_linalg.fypp b/src/stdlib_linalg.fypp
index 25dae9514..d064c948e 100644
--- a/src/stdlib_linalg.fypp
+++ b/src/stdlib_linalg.fypp
@@ -14,6 +14,7 @@ module stdlib_linalg
   public :: eye
   public :: trace
   public :: outer_product
+  public :: repmat
   public :: is_square
   public :: is_diagonal
   public :: is_symmetric

From 1f54a832a76049b7c606271a39b81cd3401e576c Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 17:28:09 +0800
Subject: [PATCH 08/14] Update test_linalg.fypp

---
 test/linalg/test_linalg.fypp | 203 ++++++++++++++++++++++++++++++++++-
 1 file changed, 202 insertions(+), 1 deletion(-)

diff --git a/test/linalg/test_linalg.fypp b/test/linalg/test_linalg.fypp
index f74cbff6b..2d8b4ccaa 100644
--- a/test/linalg/test_linalg.fypp
+++ b/test/linalg/test_linalg.fypp
@@ -57,7 +57,17 @@ contains
             new_unittest("outer_product_int8", test_outer_product_int8), &
             new_unittest("outer_product_int16", test_outer_product_int16), &
             new_unittest("outer_product_int32", test_outer_product_int32), &
-            new_unittest("outer_product_int64", test_outer_product_int64) &
+            new_unittest("outer_product_int64", test_outer_product_int64), &
+            new_unittest("test_repmat_rsp",test_repmat_rsp), &
+            new_unittest("test_repmat_rdp",test_repmat_rdp), &
+            new_unittest("test_repmat_rqp",test_repmat_rqp), &
+            new_unittest("test_repmat_csp",test_repmat_csp), &
+            new_unittest("test_repmat_cdp",test_repmat_cdp), &
+            new_unittest("test_repmat_cqp",test_repmat_cqp), &
+            new_unittest("test_repmat_int8",test_repmat_int8), &
+            new_unittest("test_repmat_int16",test_repmat_int16), &
+            new_unittest("test_repmat_int32",test_repmat_int32), &
+            new_unittest("test_repmat_int64",test_repmat_int64) &
             ]
 
     end subroutine collect_linalg
@@ -703,6 +713,197 @@ contains
     end subroutine test_outer_product_int64
 
 
+    subroutine test_repmat_rqp(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+#:if WITH_QP
+       integer, parameter :: n = 2
+       real(qp) :: a(n,n)
+       real(qp),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+#:else
+        call skip_test(error, "Quadruple precision is not enabled")
+#:endif
+    end subroutine test_repmat_rqp
+    subroutine test_repmat_cqp(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+#:if WITH_QP
+       integer, parameter :: n = 2
+       complex(qp) :: a(n,n)
+       complex(qp),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+#:else
+        call skip_test(error, "Quadruple precision is not enabled")
+#:endif
+    end subroutine test_repmat_cqp
+
+
+    subroutine test_repmat_rsp(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+       integer, parameter :: n = 2
+       real(sp) :: a(n,n)
+       real(sp),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+    end subroutine test_repmat_rsp
+
+    subroutine test_repmat_rdp(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+       integer, parameter :: n = 2
+       real(dp) :: a(n,n)
+       real(dp),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+    end subroutine test_repmat_rdp
+
+
+    subroutine test_repmat_csp(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+       integer, parameter :: n = 2
+       complex(sp) :: a(n,n)
+       complex(sp),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+    end subroutine test_repmat_csp
+
+    subroutine test_repmat_cdp(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+       integer, parameter :: n = 2
+       complex(dp) :: a(n,n)
+       complex(dp),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+    end subroutine test_repmat_cdp
+   
+    subroutine test_repmat_int8(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+       integer, parameter :: n = 2
+       integer(int8) :: a(n,n)
+       integer(int8),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+    end subroutine test_repmat_int8
+
+    subroutine test_repmat_int16(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+       integer, parameter :: n = 2
+       integer(int16) :: a(n,n)
+       integer(int16),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+    end subroutine test_repmat_int16
+
+    subroutine test_repmat_int32(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+       integer, parameter :: n = 2
+       integer(int32) :: a(n,n)
+       integer(int32),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+    end subroutine test_repmat_int32
+
+    subroutine test_repmat_int64(error)
+       !> Error handling
+       type(error_type), allocatable, intent(out) :: error
+       integer, parameter :: n = 2
+       integer(int64) :: a(n,n)
+       integer(int64),allocatable:: expected(:,:)
+
+       a=reshape([1,2,3,4],shape(a),order=[2,1])
+       expected = reshape([&
+          1,2,1,2,&
+          3,4,3,4,&
+          1,2,1,2,&
+          3,4,3,4 ],[4,4],order=[2,1])
+       diff = expected - repmat(a, 2, 2)
+       call check(error, all(abs(diff) == 0), &
+          "all(abs(diff) == 0) failed.")
+    end subroutine test_repmat_int64
+
+
+
     pure recursive function catalan_number(n) result(value)
         integer, intent(in) :: n
         integer :: value

From aa410fe40d8b941dafc06f0df54b2fc24865531c Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 17:29:35 +0800
Subject: [PATCH 09/14] Update stdlib_linalg_repmat.fypp

---
 src/stdlib_linalg_repmat.fypp | 1 +
 1 file changed, 1 insertion(+)

diff --git a/src/stdlib_linalg_repmat.fypp b/src/stdlib_linalg_repmat.fypp
index 96db9ca12..d51f7b1cb 100644
--- a/src/stdlib_linalg_repmat.fypp
+++ b/src/stdlib_linalg_repmat.fypp
@@ -11,6 +11,7 @@ contains
       ${t1}$, intent(in) :: a(:,:)
       integer, intent(in) :: m,n
       ${t1}$ :: res(m*size(a,1),n*size(a,2))
+      integer ::i,j,k,l
       associate(ma=>size(a,1),na=>size(a,2))
          do j=1,n
             do l=1,na

From 0f82104a9f189e8fcfc754d0bb97317933cab397 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 17:33:17 +0800
Subject: [PATCH 10/14] Update stdlib_linalg_repmat.fypp

---
 src/stdlib_linalg_repmat.fypp | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/src/stdlib_linalg_repmat.fypp b/src/stdlib_linalg_repmat.fypp
index d51f7b1cb..3ea47a064 100644
--- a/src/stdlib_linalg_repmat.fypp
+++ b/src/stdlib_linalg_repmat.fypp
@@ -17,7 +17,7 @@ contains
             do l=1,na
                do i=1,m
                   do k=1,ma
-                     c((i-1)*ma+k,(j-1)*na+l)=a(k,l)
+                     res((i-1)*ma+k,(j-1)*na+l)=a(k,l)
                   end do
                end do
             end do

From 78bebd7ba72aecc140c727aab8a5b422610a31c2 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 17:39:01 +0800
Subject: [PATCH 11/14] Update test_linalg.fypp

---
 test/linalg/test_linalg.fypp | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/test/linalg/test_linalg.fypp b/test/linalg/test_linalg.fypp
index 2d8b4ccaa..131c5d797 100644
--- a/test/linalg/test_linalg.fypp
+++ b/test/linalg/test_linalg.fypp
@@ -3,7 +3,7 @@
 module test_linalg
     use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
     use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64
-    use stdlib_linalg, only: diag, eye, trace, outer_product
+    use stdlib_linalg, only: diag, eye, trace, outer_product,repmat
 
     implicit none
 

From 911b199a9b5bed6e4ffc10061a6a879a3f236c93 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 17:50:19 +0800
Subject: [PATCH 12/14] Update test_linalg.fypp

---
 test/linalg/test_linalg.fypp | 20 ++++++++++----------
 1 file changed, 10 insertions(+), 10 deletions(-)

diff --git a/test/linalg/test_linalg.fypp b/test/linalg/test_linalg.fypp
index 131c5d797..6e906d2ec 100644
--- a/test/linalg/test_linalg.fypp
+++ b/test/linalg/test_linalg.fypp
@@ -719,7 +719,7 @@ contains
 #:if WITH_QP
        integer, parameter :: n = 2
        real(qp) :: a(n,n)
-       real(qp),allocatable:: expected(:,:)
+       real(qp),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -740,7 +740,7 @@ contains
 #:if WITH_QP
        integer, parameter :: n = 2
        complex(qp) :: a(n,n)
-       complex(qp),allocatable:: expected(:,:)
+       complex(qp),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -762,7 +762,7 @@ contains
        type(error_type), allocatable, intent(out) :: error
        integer, parameter :: n = 2
        real(sp) :: a(n,n)
-       real(sp),allocatable:: expected(:,:)
+       real(sp),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -780,7 +780,7 @@ contains
        type(error_type), allocatable, intent(out) :: error
        integer, parameter :: n = 2
        real(dp) :: a(n,n)
-       real(dp),allocatable:: expected(:,:)
+       real(dp),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -799,7 +799,7 @@ contains
        type(error_type), allocatable, intent(out) :: error
        integer, parameter :: n = 2
        complex(sp) :: a(n,n)
-       complex(sp),allocatable:: expected(:,:)
+       complex(sp),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -817,7 +817,7 @@ contains
        type(error_type), allocatable, intent(out) :: error
        integer, parameter :: n = 2
        complex(dp) :: a(n,n)
-       complex(dp),allocatable:: expected(:,:)
+       complex(dp),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -835,7 +835,7 @@ contains
        type(error_type), allocatable, intent(out) :: error
        integer, parameter :: n = 2
        integer(int8) :: a(n,n)
-       integer(int8),allocatable:: expected(:,:)
+       integer(int8),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -853,7 +853,7 @@ contains
        type(error_type), allocatable, intent(out) :: error
        integer, parameter :: n = 2
        integer(int16) :: a(n,n)
-       integer(int16),allocatable:: expected(:,:)
+       integer(int16),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -871,7 +871,7 @@ contains
        type(error_type), allocatable, intent(out) :: error
        integer, parameter :: n = 2
        integer(int32) :: a(n,n)
-       integer(int32),allocatable:: expected(:,:)
+       integer(int32),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&
@@ -889,7 +889,7 @@ contains
        type(error_type), allocatable, intent(out) :: error
        integer, parameter :: n = 2
        integer(int64) :: a(n,n)
-       integer(int64),allocatable:: expected(:,:)
+       integer(int64),allocatable:: expected(:,:),diff(:,:)
 
        a=reshape([1,2,3,4],shape(a),order=[2,1])
        expected = reshape([&

From 334fb7d6f2c176b3215eddf4c9e2d84716477c31 Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Thu, 27 Oct 2022 18:06:42 +0800
Subject: [PATCH 13/14] Update CMakeLists.txt

---
 src/CMakeLists.txt | 1 +
 1 file changed, 1 insertion(+)

diff --git a/src/CMakeLists.txt b/src/CMakeLists.txt
index 0fb95a2d3..a056e791b 100644
--- a/src/CMakeLists.txt
+++ b/src/CMakeLists.txt
@@ -22,6 +22,7 @@ set(fppFiles
     stdlib_linalg.fypp
     stdlib_linalg_diag.fypp
     stdlib_linalg_outer_product.fypp
+    stdlib_linalg_repmat.fypp
     stdlib_optval.fypp
     stdlib_selection.fypp
     stdlib_sorting.fypp

From 06d866d7033ba7814f265107b4a92b57f8c4077d Mon Sep 17 00:00:00 2001
From: Euler-37 <64597797+Euler-37@users.noreply.github.com>
Date: Sun, 13 Nov 2022 09:42:49 +0800
Subject: [PATCH 14/14] Update test/linalg/test_linalg.fypp

Co-authored-by: Milan Curcic <caomaco@gmail.com>
---
 test/linalg/test_linalg.fypp | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/test/linalg/test_linalg.fypp b/test/linalg/test_linalg.fypp
index 6e906d2ec..f278345da 100644
--- a/test/linalg/test_linalg.fypp
+++ b/test/linalg/test_linalg.fypp
@@ -3,7 +3,7 @@
 module test_linalg
     use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
     use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64
-    use stdlib_linalg, only: diag, eye, trace, outer_product,repmat
+    use stdlib_linalg, only: diag, eye, trace, outer_product, repmat
 
     implicit none