Skip to content

Commit

Permalink
Add INTENT attributes
Browse files Browse the repository at this point in the history
  • Loading branch information
mkrack committed Oct 26, 2021
1 parent ab39009 commit 61af418
Showing 1 changed file with 18 additions and 15 deletions.
33 changes: 18 additions & 15 deletions src/common/cp_result_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -59,8 +59,8 @@ MODULE cp_result_methods
! **************************************************************************************************
SUBROUTINE put_result_r1(results, description, values)
TYPE(cp_result_type), POINTER :: results
CHARACTER(LEN=default_string_length) :: description
REAL(KIND=dp), DIMENSION(:) :: values
CHARACTER(LEN=default_string_length), INTENT(IN) :: description
REAL(KIND=dp), DIMENSION(:), INTENT(IN) :: values

INTEGER :: isize, jsize
LOGICAL :: check
Expand Down Expand Up @@ -93,8 +93,8 @@ END SUBROUTINE put_result_r1
! **************************************************************************************************
SUBROUTINE put_result_r2(results, description, values)
TYPE(cp_result_type), POINTER :: results
CHARACTER(LEN=default_string_length) :: description
REAL(KIND=dp), DIMENSION(:, :) :: values
CHARACTER(LEN=default_string_length), INTENT(IN) :: description
REAL(KIND=dp), DIMENSION(:, :), INTENT(IN) :: values

INTEGER :: isize, jsize
LOGICAL :: check
Expand Down Expand Up @@ -126,7 +126,7 @@ END SUBROUTINE put_result_r2
! **************************************************************************************************
FUNCTION test_for_result(results, description) RESULT(res_exist)
TYPE(cp_result_type), POINTER :: results
CHARACTER(LEN=default_string_length) :: description
CHARACTER(LEN=default_string_length), INTENT(IN) :: description
LOGICAL :: res_exist

INTEGER :: i, nlist
Expand Down Expand Up @@ -159,9 +159,10 @@ END FUNCTION test_for_result
! **************************************************************************************************
SUBROUTINE get_result_r1(results, description, values, nval, n_rep, n_entries)
TYPE(cp_result_type), POINTER :: results
CHARACTER(LEN=default_string_length) :: description
REAL(KIND=dp), DIMENSION(:) :: values
INTEGER, OPTIONAL :: nval, n_rep, n_entries
CHARACTER(LEN=default_string_length), INTENT(IN) :: description
REAL(KIND=dp), DIMENSION(:), INTENT(OUT) :: values
INTEGER, INTENT(IN), OPTIONAL :: nval
INTEGER, INTENT(OUT), OPTIONAL :: n_rep, n_entries

INTEGER :: i, k, nlist, nrep, size_res, size_values

Expand Down Expand Up @@ -231,9 +232,10 @@ END SUBROUTINE get_result_r1
! **************************************************************************************************
SUBROUTINE get_result_r2(results, description, values, nval, n_rep, n_entries)
TYPE(cp_result_type), POINTER :: results
CHARACTER(LEN=default_string_length) :: description
REAL(KIND=dp), DIMENSION(:, :) :: values
INTEGER, OPTIONAL :: nval, n_rep, n_entries
CHARACTER(LEN=default_string_length), INTENT(IN) :: description
REAL(KIND=dp), DIMENSION(:, :), INTENT(OUT) :: values
INTEGER, INTENT(IN), OPTIONAL :: nval
INTEGER, INTENT(OUT), OPTIONAL :: n_rep, n_entries

INTEGER :: i, k, nlist, nrep, size_res, size_values

Expand Down Expand Up @@ -302,8 +304,8 @@ END SUBROUTINE get_result_r2
! **************************************************************************************************
SUBROUTINE get_nreps(results, description, n_rep, n_entries, type_in_use)
TYPE(cp_result_type), POINTER :: results
CHARACTER(LEN=default_string_length) :: description
INTEGER, OPTIONAL :: n_rep, n_entries, type_in_use
CHARACTER(LEN=default_string_length), INTENT(IN) :: description
INTEGER, INTENT(OUT), OPTIONAL :: n_rep, n_entries, type_in_use

INTEGER :: I, nlist

Expand Down Expand Up @@ -359,8 +361,9 @@ END SUBROUTINE get_nreps
! **************************************************************************************************
SUBROUTINE cp_results_erase(results, description, nval)
TYPE(cp_result_type), POINTER :: results
CHARACTER(LEN=default_string_length), OPTIONAL :: description
INTEGER, OPTIONAL :: nval
CHARACTER(LEN=default_string_length), INTENT(IN), &
OPTIONAL :: description
INTEGER, INTENT(IN), OPTIONAL :: nval

INTEGER :: entry_deleted, i, k, new_size, nlist, &
nrep
Expand Down

0 comments on commit 61af418

Please sign in to comment.