Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
85 changes: 85 additions & 0 deletions .codee-format
Original file line number Diff line number Diff line change
@@ -0,0 +1,85 @@
---
AlignAmpersandToColumnLimit: false
AlignAssignmentOperators: true
AlignUseItems:
Kind: OneItemPerLine
FirstLineFit: FitIfPossible
BreakBeforeBinaryOperators: true
Casing:
Identifiers: Preserve
Keywords: Lowercase
LogicalConstants: Lowercase
LogicalOperators: Lowercase
RelationalOperators: Lowercase
UserDefinedOperators: Lowercase
ColumnLimit: 132
CommentDirectivePrefixes: []
DisabledDirectivePrefixes: []
IndentSize: 2
IndentExceptions:
ModuleContains: IndentBeforeAndAfter
Comments: Indent
FixedFormLabelAlignment: Right
ContinuationIndentSize: DoubleIndentSize
DoubleColonSeparator: AddAlways
EndOfLineNormalization: Autodetect
EndStatementFormat: EndStructureAndName
EndStatementSeparation:
EndAssociate: Separated
EndBlockConstruct: Separated
EndBlockData: Separated
EndCritical: Separated
EndTeam: Separated
EndDoLoop: Separated
EndEnum: Separated
EndEnumerationType: Separated
EndForall: Separated
EndFunction: Separated
EndIf: Separated
EndInterface: Separated
EndModule: Separated
EndModuleProcedure: Separated
EndProgram: Separated
EndSelect: Separated
EndSubmodule: Separated
EndSubroutine: Separated
EndType: Separated
EndWhere: Separated
EnsureNewlineAtEOF: true
ConsecutiveEmptyLines:
MaxToKeep: 1
BetweenProcedures: 1
RemoveAtStartOfFile: true
RemoveAtEndOfFile: true
KindKeywordPrefix: RemoveAlways
MacroIdentifiers: []
RelationalOperators: UseSymbols
SpacesAroundOperators:
LeftParenthesisExpression: NoTrailing
LeftParenthesisGeneric: NoSpaces
LeftParenthesisKeyword: OnlyLeading
RightParenthesisExpression: NoLeading
RightParenthesisGeneric: NoLeading
RightParenthesisKeyword: NoLeading
Assignment: Both
Association: Both
ControlFlowAssignment: Both
KeywordAssignment: NoSpaces
ParameterAssignment: NoSpaces
BinaryArithmetic: Both
Exponentiation: NoSpaces
DefinedBinary: Both
DefinedUnary: NoTrailing
Relational: Both
RelationalLegacy: Both
LogicalBinary: Both
LogicalNot: NoTrailing
UnaryPlusMinus: NoTrailing
Comma: OnlyTrailing
Concat: Both
DoubleColon: Both
RemoveConsecutiveWhitespace: true
RemoveSemicolons: true
RemoveTrailingWhitespace: true
SeparateMultipleInlineStatements: true
...
23 changes: 23 additions & 0 deletions .github/workflows/CI-Fortran-format.yml
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
name: CI-Fortran-format

on:
pull_request:
branches: [ "master" ]

jobs:
format:
runs-on: ubuntu-latest
strategy:
fail-fast: false

steps:
- uses: actions/checkout@v4
- uses: foxtran/setup-codee@v1

- name: Run Fortran formatter
run: |
codee format . --verbose

- name: Check for uncommitted changes
run: |
git diff --exit-code
20 changes: 10 additions & 10 deletions examples/Fortran/example.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,16 +19,16 @@ program main
do
if (.not.lb%get_range(bot, top)) exit
do j = bot, top
block
real(8), allocatable :: a(:,:), b(:,:), c(:,:)
i = 3 * (100 - j) + 200
allocate(a(i,i),b(i,i),c(i,i))
call random_number(a)
call random_number(b)
c = matmul(a,b)
write(7,'(I6,ES15.8)') j, sum(c)
deallocate(a,b,c)
end block
block
real(8), allocatable :: a(:, :), b(:, :), c(:, :)
i = 3 * (100 - j) + 200
allocate(a(i, i), b(i, i), c(i, i))
call random_number(a)
call random_number(b)
c = matmul(a, b)
write(7, '(I6,ES15.8)') j, sum(c)
deallocate(a, b, c)
end block
end do
end do
print '(A)', "Done!"
Expand Down
40 changes: 20 additions & 20 deletions src/Fortran/abstract_load_balancer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -15,20 +15,20 @@ module SLB4MPI_abstract_load_balancer_m

type, abstract :: load_balancer_t
integer(MPI_INTEGER_KIND) :: communicator !< MPI communicator
integer(MPI_INTEGER_KIND) :: rank !< Rank of the process
integer(MPI_INTEGER_KIND) :: root = 0 !< Rank of the root process
integer(MPI_INTEGER_KIND) :: nranks !< Number of processes (group size)
integer(8) :: lower_bound !< Lower bound of range
integer(8) :: upper_bound !< Upper bound of range
integer(8) :: min_chunk_size !< Minimal chunk size for job
integer(8) :: max_chunk_size !< Maximal chunk size for job
contains
integer(MPI_INTEGER_KIND) :: rank !< Rank of the process
integer(MPI_INTEGER_KIND) :: root = 0 !< Rank of the root process
integer(MPI_INTEGER_KIND) :: nranks !< Number of processes (group size)
integer(8) :: lower_bound !< Lower bound of range
integer(8) :: upper_bound !< Upper bound of range
integer(8) :: min_chunk_size !< Minimal chunk size for job
integer(8) :: max_chunk_size !< Maximal chunk size for job
contains
procedure(initialize), deferred, public :: initialize
procedure(get_range), deferred, public :: get_range
procedure(clean), deferred, public :: clean
procedure(get_range), deferred, public :: get_range
procedure(clean), deferred, public :: clean

procedure :: default_initialize
end type
end type load_balancer_t

abstract interface

Expand All @@ -44,10 +44,10 @@ module SLB4MPI_abstract_load_balancer_m
!>
subroutine initialize(lb, communicator, lower_bound, upper_bound, min_chunk_size, max_chunk_size)
import load_balancer_t, MPI_INTEGER_KIND
class(load_balancer_t), intent(inout) :: lb
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size
class(load_balancer_t), intent(inout) :: lb
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size
end subroutine initialize

!>
Expand All @@ -64,7 +64,7 @@ end subroutine initialize
logical function get_range(lb, lower_bound, upper_bound)
import load_balancer_t
class(load_balancer_t), intent(inout) :: lb
integer(8), intent(out) :: lower_bound, upper_bound
integer(8), intent(out) :: lower_bound, upper_bound
end function get_range

!>
Expand Down Expand Up @@ -94,10 +94,10 @@ end subroutine clean
!> @param[in] max_chunk_size - maximal size of chank that can be associated with job, default: upper_bound - lower_bound + 1
!>
subroutine default_initialize(lb, communicator, lower_bound, upper_bound, min_chunk_size, max_chunk_size)
class(load_balancer_t), intent(inout) :: lb
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size
class(load_balancer_t), intent(inout) :: lb
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size

integer(MPI_INTEGER_KIND) :: ierr

Expand Down
12 changes: 6 additions & 6 deletions src/Fortran/dynamic_load_balancer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,15 +8,15 @@ module SLB4MPI_dynamic_load_balancer_m

type, extends(load_balancer_t) :: dynamic_load_balancer_t
#ifdef SLB4MPI_WITH_MPI
integer(MPI_INTEGER_KIND) :: window !< sync window
integer(MPI_INTEGER_KIND) :: window !< sync window
#else
integer(MPI_INTEGER_KIND) :: counter !< evaluation index
#endif
contains
contains
procedure :: initialize
procedure :: get_range
procedure :: clean
end type
end type dynamic_load_balancer_t

interface

Expand All @@ -38,9 +38,9 @@ module SLB4MPI_dynamic_load_balancer_m
subroutine initialize(lb, communicator, lower_bound, upper_bound, min_chunk_size, max_chunk_size)
use, intrinsic :: iso_c_binding, only: c_ptr, c_f_pointer
class(dynamic_load_balancer_t), intent(inout) :: lb
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size

integer(MPI_ADDRESS_KIND) :: size
integer(MPI_INTEGER_KIND) :: disp_unit, ierr
Expand Down
15 changes: 8 additions & 7 deletions src/Fortran/guided_load_balancer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,15 +8,15 @@ module SLB4MPI_guided_load_balancer_m

type, extends(load_balancer_t) :: guided_load_balancer_t
#ifdef SLB4MPI_WITH_MPI
integer(MPI_INTEGER_KIND) :: window !< sync window
integer(MPI_INTEGER_KIND) :: window !< sync window
#else
integer(MPI_INTEGER_KIND) :: counter !< evaluation index
#endif
contains
contains
procedure :: initialize
procedure :: get_range
procedure :: clean
end type
end type guided_load_balancer_t

interface

Expand All @@ -38,9 +38,9 @@ module SLB4MPI_guided_load_balancer_m
subroutine initialize(lb, communicator, lower_bound, upper_bound, min_chunk_size, max_chunk_size)
use, intrinsic :: iso_c_binding, only: c_ptr, c_f_pointer
class(guided_load_balancer_t), intent(inout) :: lb
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size

integer(MPI_ADDRESS_KIND) :: size
integer(MPI_INTEGER_KIND) :: disp_unit, ierr
Expand Down Expand Up @@ -89,7 +89,8 @@ logical function get_range(lb, lower_bound, upper_bound) result(to_compute)

#ifdef SLB4MPI_WITH_MPI
call MPI_Win_lock(MPI_LOCK_EXCLUSIVE, lb%root, 0_MPI_INTEGER_KIND, lb%window, ierr)
call MPI_Get(root_counter, 1_MPI_INTEGER_KIND, MPI_INTEGER8, lb%root, 0_MPI_ADDRESS_KIND, 1_MPI_INTEGER_KIND, MPI_INTEGER8, lb%window, ierr)
call MPI_Get(root_counter, 1_MPI_INTEGER_KIND, MPI_INTEGER8, lb%root, 0_MPI_ADDRESS_KIND, 1_MPI_INTEGER_KIND, MPI_INTEGER8, &
lb%window, ierr)
call MPI_Win_flush(lb%root, lb%window, ierr)
associated_tasks = min(max((lb%upper_bound - root_counter) / lb%nranks, lb%min_chunk_size), lb%max_chunk_size)
call MPI_Fetch_and_op(associated_tasks, lower_bound, MPI_INTEGER8, lb%root, 0_MPI_ADDRESS_KIND, MPI_SUM, lb%window, ierr)
Expand Down
24 changes: 12 additions & 12 deletions src/Fortran/local_static_load_balancer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,11 +6,11 @@ module SLB4MPI_local_static_load_balancer_m
type, extends(load_balancer_t) :: local_static_load_balancer_t
private
integer(8) :: counter
contains
contains
procedure :: initialize
procedure :: get_range
procedure :: clean
end type
end type local_static_load_balancer_t

interface

Expand All @@ -31,9 +31,9 @@ module SLB4MPI_local_static_load_balancer_m
!>
subroutine initialize(lb, communicator, lower_bound, upper_bound, min_chunk_size, max_chunk_size)
class(local_static_load_balancer_t), intent(inout) :: lb
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size
integer(MPI_INTEGER_KIND), intent(in) :: communicator
integer(8), intent(in) :: lower_bound, upper_bound
integer(8), optional, intent(in) :: min_chunk_size, max_chunk_size
!
integer(8) :: n_tasks, extra_tasks

Expand All @@ -42,16 +42,16 @@ subroutine initialize(lb, communicator, lower_bound, upper_bound, min_chunk_size
n_tasks = (upper_bound - lower_bound + 1) / lb%nranks
extra_tasks = mod(upper_bound - lower_bound + 1, lb%nranks)
if (n_tasks < min_chunk_size) then
n_tasks = min_chunk_size
extra_tasks = 0
n_tasks = min_chunk_size
extra_tasks = 0
end if

if (lb%rank < extra_tasks) then
lb%lower_bound = lb%rank * (n_tasks + 1) + lower_bound
lb%upper_bound = (lb%rank + 1) * (n_tasks + 1) + lower_bound - 1
lb%lower_bound = lb%rank * (n_tasks + 1) + lower_bound
lb%upper_bound = (lb%rank + 1) * (n_tasks + 1) + lower_bound - 1
else
lb%lower_bound = lb%rank * n_tasks + extra_tasks + lower_bound
lb%upper_bound = (lb%rank + 1) * n_tasks + extra_tasks + lower_bound - 1
lb%lower_bound = lb%rank * n_tasks + extra_tasks + lower_bound
lb%upper_bound = (lb%rank + 1) * n_tasks + extra_tasks + lower_bound - 1
end if

lb%lower_bound = min(lb%lower_bound, upper_bound + 1)
Expand All @@ -74,7 +74,7 @@ end subroutine initialize
!>
logical function get_range(lb, lower_bound, upper_bound) result(to_compute)
class(local_static_load_balancer_t), intent(inout) :: lb
integer(8), intent(out) :: lower_bound, upper_bound
integer(8), intent(out) :: lower_bound, upper_bound

to_compute = .true.

Expand Down
Loading