Skip to content

Commit fb7c9f5

Browse files
committed
submodule procedures declaration made compatible with older cmake versions
1 parent eb46153 commit fb7c9f5

File tree

4 files changed

+15
-15
lines changed

4 files changed

+15
-15
lines changed

src/stdlib_linalg.fypp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -154,13 +154,13 @@ module stdlib_linalg
154154
! Vector to matrix
155155
!
156156
#:for k1, t1 in RCI_KINDS_TYPES
157-
module pure function diag_${t1[0]}$${k1}$(v) result(res)
157+
pure module function diag_${t1[0]}$${k1}$(v) result(res)
158158
${t1}$, intent(in) :: v(:)
159159
${t1}$ :: res(size(v),size(v))
160160
end function diag_${t1[0]}$${k1}$
161161
#:endfor
162162
#:for k1, t1 in RCI_KINDS_TYPES
163-
module pure function diag_${t1[0]}$${k1}$_k(v,k) result(res)
163+
pure module function diag_${t1[0]}$${k1}$_k(v,k) result(res)
164164
${t1}$, intent(in) :: v(:)
165165
integer, intent(in) :: k
166166
${t1}$ :: res(size(v)+abs(k),size(v)+abs(k))
@@ -171,13 +171,13 @@ module stdlib_linalg
171171
! Matrix to vector
172172
!
173173
#:for k1, t1 in RCI_KINDS_TYPES
174-
module pure function diag_${t1[0]}$${k1}$_mat(A) result(res)
174+
pure module function diag_${t1[0]}$${k1}$_mat(A) result(res)
175175
${t1}$, intent(in) :: A(:,:)
176176
${t1}$ :: res(minval(shape(A)))
177177
end function diag_${t1[0]}$${k1}$_mat
178178
#:endfor
179179
#:for k1, t1 in RCI_KINDS_TYPES
180-
module pure function diag_${t1[0]}$${k1}$_mat_k(A,k) result(res)
180+
pure module function diag_${t1[0]}$${k1}$_mat_k(A,k) result(res)
181181
${t1}$, intent(in) :: A(:,:)
182182
integer, intent(in) :: k
183183
${t1}$ :: res(minval(shape(A))-abs(k))

src/stdlib_linalg_diag.fypp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ submodule (stdlib_linalg) stdlib_linalg_diag
77
contains
88

99
#:for k1, t1 in RCI_KINDS_TYPES
10-
module pure function diag_${t1[0]}$${k1}$(v) result(res)
10+
pure module function diag_${t1[0]}$${k1}$(v) result(res)
1111
${t1}$, intent(in) :: v(:)
1212
${t1}$ :: res(size(v),size(v))
1313
integer :: i
@@ -20,7 +20,7 @@ contains
2020

2121

2222
#:for k1, t1 in RCI_KINDS_TYPES
23-
module pure function diag_${t1[0]}$${k1}$_k(v,k) result(res)
23+
pure module function diag_${t1[0]}$${k1}$_k(v,k) result(res)
2424
${t1}$, intent(in) :: v(:)
2525
integer, intent(in) :: k
2626
${t1}$ :: res(size(v)+abs(k),size(v)+abs(k))
@@ -44,7 +44,7 @@ contains
4444
#:endfor
4545

4646
#:for k1, t1 in RCI_KINDS_TYPES
47-
module pure function diag_${t1[0]}$${k1}$_mat(A) result(res)
47+
pure module function diag_${t1[0]}$${k1}$_mat(A) result(res)
4848
${t1}$, intent(in) :: A(:,:)
4949
${t1}$ :: res(minval(shape(A)))
5050
integer :: i
@@ -55,7 +55,7 @@ contains
5555
#:endfor
5656

5757
#:for k1, t1 in RCI_KINDS_TYPES
58-
module pure function diag_${t1[0]}$${k1}$_mat_k(A,k) result(res)
58+
pure module function diag_${t1[0]}$${k1}$_mat_k(A,k) result(res)
5959
${t1}$, intent(in) :: A(:,:)
6060
integer, intent(in) :: k
6161
${t1}$ :: res(minval(shape(A))-abs(k))

src/stdlib_system.F90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -500,7 +500,7 @@ end function run_sync_args
500500
!!
501501
!! @note The implementation relies on system-level process management capabilities.
502502
!!
503-
module logical function process_is_running(process) result(is_running)
503+
logical module function process_is_running(process) result(is_running)
504504
!> The process object to check.
505505
class(process_type), intent(inout) :: process
506506
!> Logical result: `.true.` if the process is still running, `.false.` otherwise.
@@ -524,7 +524,7 @@ end function process_is_running
524524
!!
525525
!! @note The implementation relies on system-level process management capabilities.
526526
!!
527-
module logical function process_is_completed(process) result(is_completed)
527+
logical module function process_is_completed(process) result(is_completed)
528528
!> The process object to check.
529529
class(process_type), intent(inout) :: process
530530
!> Logical result: `.true.` if the process has completed, `.false.` otherwise.
@@ -711,7 +711,7 @@ end subroutine process_callback
711711
!!
712712
!! @note This function relies on the `_WIN32` macro, which is defined in C compilers when targeting Windows.
713713
!!
714-
module logical function is_windows()
714+
logical module function is_windows()
715715
end function is_windows
716716

717717
module function process_get_ID(process) result(ID)

src/stdlib_system_subprocess.F90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -331,7 +331,7 @@ subroutine launch_synchronous(process, args, stdin)
331331
end subroutine launch_synchronous
332332

333333
!> Return the current (or total) process lifetime, in seconds
334-
module real(RTICKS) function process_lifetime(process) result(delta_t)
334+
real(RTICKS) module function process_lifetime(process) result(delta_t)
335335
class(process_type), intent(in) :: process
336336

337337
real(RTICKS) :: ticks_per_second
@@ -511,7 +511,7 @@ subroutine save_completed_state(process,delete_files)
511511
end subroutine save_completed_state
512512

513513
!> Live check if a process is running
514-
module logical function process_is_running(process) result(is_running)
514+
logical module function process_is_running(process) result(is_running)
515515
class(process_type), intent(inout) :: process
516516

517517
! Each evaluation triggers a state update
@@ -522,7 +522,7 @@ module logical function process_is_running(process) result(is_running)
522522
end function process_is_running
523523

524524
!> Live check if a process has completed
525-
module logical function process_is_completed(process) result(is_completed)
525+
logical module function process_is_completed(process) result(is_completed)
526526
class(process_type), intent(inout) :: process
527527

528528
! Each evaluation triggers a state update
@@ -600,7 +600,7 @@ end function assemble_cmd
600600
!> Returns the file path of the null device for the current operating system.
601601
!>
602602
!> Version: Helper function.
603-
module logical function is_windows()
603+
logical module function is_windows()
604604
is_windows = logical(process_is_windows())
605605
end function is_windows
606606

0 commit comments

Comments
 (0)