Skip to content
Merged
10 changes: 9 additions & 1 deletion STYLE_GUIDE.md
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,15 @@ focus on the semantics of the proposed changes rather than style and formatting.
```
When defining many arrays of the same dimension, `dimension` can be used as an exception if it makes the code less verbose.
* If the `optional` attribute is used to declare a dummy argument, it should follow the `intent` attribute.

* For module procedures, it is recommended to declare attributes before the module keyword for better retro compatibility (Projects using CMake versions lower than CMake 3.25.0 are concerned see [Spurious modules](https://gitlab.kitware.com/cmake/cmake/-/issues/18427#note_983426)).
Prefer the following pattern:
```
<attribute> <attribute> module <function/subroutine> <name>
```
instead of:
```
module <attribute> <attribute> <function/subroutine> <name>
```
## End <scope> block closing statements

Fortran allows certain block constructs or scopes to include the name of the program unit in the end statement.
Expand Down
8 changes: 4 additions & 4 deletions src/stdlib_linalg.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -154,13 +154,13 @@ module stdlib_linalg
! Vector to matrix
!
#:for k1, t1 in RCI_KINDS_TYPES
module pure function diag_${t1[0]}$${k1}$(v) result(res)
pure module function diag_${t1[0]}$${k1}$(v) result(res)
${t1}$, intent(in) :: v(:)
${t1}$ :: res(size(v),size(v))
end function diag_${t1[0]}$${k1}$
#:endfor
#:for k1, t1 in RCI_KINDS_TYPES
module pure function diag_${t1[0]}$${k1}$_k(v,k) result(res)
pure module function diag_${t1[0]}$${k1}$_k(v,k) result(res)
${t1}$, intent(in) :: v(:)
integer, intent(in) :: k
${t1}$ :: res(size(v)+abs(k),size(v)+abs(k))
Expand All @@ -171,13 +171,13 @@ module stdlib_linalg
! Matrix to vector
!
#:for k1, t1 in RCI_KINDS_TYPES
module pure function diag_${t1[0]}$${k1}$_mat(A) result(res)
pure module function diag_${t1[0]}$${k1}$_mat(A) result(res)
${t1}$, intent(in) :: A(:,:)
${t1}$ :: res(minval(shape(A)))
end function diag_${t1[0]}$${k1}$_mat
#:endfor
#:for k1, t1 in RCI_KINDS_TYPES
module pure function diag_${t1[0]}$${k1}$_mat_k(A,k) result(res)
pure module function diag_${t1[0]}$${k1}$_mat_k(A,k) result(res)
${t1}$, intent(in) :: A(:,:)
integer, intent(in) :: k
${t1}$ :: res(minval(shape(A))-abs(k))
Expand Down
8 changes: 4 additions & 4 deletions src/stdlib_linalg_diag.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ submodule (stdlib_linalg) stdlib_linalg_diag
contains

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


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

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

#:for k1, t1 in RCI_KINDS_TYPES
module pure function diag_${t1[0]}$${k1}$_mat_k(A,k) result(res)
pure module function diag_${t1[0]}$${k1}$_mat_k(A,k) result(res)
${t1}$, intent(in) :: A(:,:)
integer, intent(in) :: k
${t1}$ :: res(minval(shape(A))-abs(k))
Expand Down
6 changes: 3 additions & 3 deletions src/stdlib_system.F90
Original file line number Diff line number Diff line change
Expand Up @@ -500,7 +500,7 @@ end function run_sync_args
!!
!! @note The implementation relies on system-level process management capabilities.
!!
module logical function process_is_running(process) result(is_running)
logical module function process_is_running(process) result(is_running)
!> The process object to check.
class(process_type), intent(inout) :: process
!> Logical result: `.true.` if the process is still running, `.false.` otherwise.
Expand All @@ -524,7 +524,7 @@ end function process_is_running
!!
!! @note The implementation relies on system-level process management capabilities.
!!
module logical function process_is_completed(process) result(is_completed)
logical module function process_is_completed(process) result(is_completed)
!> The process object to check.
class(process_type), intent(inout) :: process
!> Logical result: `.true.` if the process has completed, `.false.` otherwise.
Expand Down Expand Up @@ -711,7 +711,7 @@ end subroutine process_callback
!!
!! @note This function relies on the `_WIN32` macro, which is defined in C compilers when targeting Windows.
!!
module logical function is_windows()
logical module function is_windows()
end function is_windows

module function process_get_ID(process) result(ID)
Expand Down
8 changes: 4 additions & 4 deletions src/stdlib_system_subprocess.F90
Original file line number Diff line number Diff line change
Expand Up @@ -331,7 +331,7 @@ subroutine launch_synchronous(process, args, stdin)
end subroutine launch_synchronous

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

real(RTICKS) :: ticks_per_second
Expand Down Expand Up @@ -511,7 +511,7 @@ subroutine save_completed_state(process,delete_files)
end subroutine save_completed_state

!> Live check if a process is running
module logical function process_is_running(process) result(is_running)
logical module function process_is_running(process) result(is_running)
class(process_type), intent(inout) :: process

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

!> Live check if a process has completed
module logical function process_is_completed(process) result(is_completed)
logical module function process_is_completed(process) result(is_completed)
class(process_type), intent(inout) :: process

! Each evaluation triggers a state update
Expand Down Expand Up @@ -600,7 +600,7 @@ end function assemble_cmd
!> Returns the file path of the null device for the current operating system.
!>
!> Version: Helper function.
module logical function is_windows()
logical module function is_windows()
is_windows = logical(process_is_windows())
end function is_windows

Expand Down
Loading