Skip to content

Commit

Permalink
Add some initializers, fix dashboard (#2652)
Browse files Browse the repository at this point in the history
  • Loading branch information
fstein93 committed Mar 6, 2023
1 parent b951fa5 commit f26eaef
Show file tree
Hide file tree
Showing 27 changed files with 800 additions and 1,035 deletions.
957 changes: 421 additions & 536 deletions src/aobasis/basis_set_types.F

Large diffs are not rendered by default.

7 changes: 4 additions & 3 deletions src/aobasis/orbital_transformation_matrices.F
Original file line number Diff line number Diff line change
Expand Up @@ -40,10 +40,11 @@ MODULE orbital_transformation_matrices
CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'orbital_transformation_matrices'

TYPE orbtramat_type
REAL(KIND=dp), DIMENSION(:, :), POINTER :: c2s, slm, slm_inv, s2c
REAL(KIND=dp), DIMENSION(:, :), POINTER :: c2s => NULL(), slm => NULL(), &
slm_inv => NULL(), s2c => NULL()
END TYPE orbtramat_type

TYPE(orbtramat_type), DIMENSION(:), POINTER :: orbtramat
TYPE(orbtramat_type), DIMENSION(:), POINTER :: orbtramat => NULL()

INTEGER, SAVE :: current_maxl = -1

Expand Down Expand Up @@ -323,7 +324,7 @@ END SUBROUTINE init_spherical_harmonics
! **************************************************************************************************
SUBROUTINE write_matrix(matrix, l, lunit, headline)

REAL(KIND=dp), DIMENSION(:, :), POINTER :: matrix
REAL(KIND=dp), DIMENSION(:, :), INTENT(IN) :: matrix
INTEGER, INTENT(IN) :: l, lunit
CHARACTER(LEN=*), INTENT(IN) :: headline

Expand Down
4 changes: 1 addition & 3 deletions src/aobasis/paw_basis_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ MODULE paw_basis_types
! **************************************************************************************************
SUBROUTINE get_paw_basis_info(basis_1c, o2nindex, n2oindex, nsatbas)

TYPE(gto_basis_set_type), POINTER :: basis_1c
TYPE(gto_basis_set_type), INTENT(IN) :: basis_1c
INTEGER, DIMENSION(:), OPTIONAL, POINTER :: o2nindex, n2oindex
INTEGER, INTENT(OUT), OPTIONAL :: nsatbas

Expand All @@ -47,8 +47,6 @@ SUBROUTINE get_paw_basis_info(basis_1c, o2nindex, n2oindex, nsatbas)
INTEGER, DIMENSION(:), POINTER :: lmax, lmin, npgf
LOGICAL :: n2o, nsa, o2n

CPASSERT(ASSOCIATED(basis_1c))

o2n = PRESENT(o2nindex)
n2o = PRESENT(n2oindex)
nsa = PRESENT(nsatbas)
Expand Down
150 changes: 75 additions & 75 deletions src/arnoldi/arnoldi_types.F

Large diffs are not rendered by default.

4 changes: 2 additions & 2 deletions src/common/cp_files.F
Original file line number Diff line number Diff line change
Expand Up @@ -40,8 +40,8 @@ MODULE cp_files

TYPE preconnection_type
PRIVATE
CHARACTER(LEN=default_path_length) :: file_name
INTEGER :: unit_number
CHARACTER(LEN=default_path_length) :: file_name = ""
INTEGER :: unit_number = -1
END TYPE preconnection_type

TYPE(preconnection_type), DIMENSION(max_preconnections) :: preconnected
Expand Down
100 changes: 34 additions & 66 deletions src/common/cp_iter_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -73,13 +73,13 @@ MODULE cp_iter_types
!> \author fawzi
! **************************************************************************************************
TYPE cp_iteration_info_type
INTEGER :: ref_count
INTEGER :: print_level, n_rlevel
INTEGER, DIMENSION(:), POINTER :: iteration
LOGICAL, DIMENSION(:), POINTER :: last_iter
CHARACTER(len=default_string_length) :: project_name
INTEGER :: ref_count = -1
INTEGER :: print_level = -1, n_rlevel = -1
INTEGER, DIMENSION(:), POINTER :: iteration => NULL()
LOGICAL, DIMENSION(:), POINTER :: last_iter => NULL()
CHARACTER(len=default_string_length) :: project_name = ""
CHARACTER(LEN=default_string_length), &
DIMENSION(:), POINTER :: level_name
DIMENSION(:), POINTER :: level_name => NULL()
END TYPE cp_iteration_info_type

CONTAINS
Expand All @@ -90,38 +90,19 @@ MODULE cp_iter_types
!> \param project_name name of the project, used to create the filenames
!> \author fawzi
! **************************************************************************************************
SUBROUTINE cp_iteration_info_create(iteration_info, project_name)
PURE SUBROUTINE cp_iteration_info_create(iteration_info, project_name)
TYPE(cp_iteration_info_type), POINTER :: iteration_info
CHARACTER(len=*), INTENT(in) :: project_name

CHARACTER(len=*), PARAMETER :: routineN = 'cp_iteration_info_create', &
routineP = moduleN//':'//routineN

INTEGER :: stat

ALLOCATE (iteration_info, stat=stat)
IF (stat /= 0) &
CPABORT(routineP//" could not allocate iteration_info")
ALLOCATE (iteration_info)

iteration_info%ref_count = 1
iteration_info%print_level = 2
iteration_info%n_rlevel = 1
iteration_info%project_name = project_name
NULLIFY (iteration_info%iteration)
NULLIFY (iteration_info%level_name)
NULLIFY (iteration_info%last_iter)
ALLOCATE (iteration_info%iteration(iteration_info%n_rlevel), stat=stat)
IF (stat /= 0) THEN
CPABORT(routineP//" iteration_info%iteration allocation")
END IF
ALLOCATE (iteration_info%level_name(iteration_info%n_rlevel), stat=stat)
IF (stat /= 0) THEN
CPABORT(routineP//" iteration_info%level_name allocation")
END IF
ALLOCATE (iteration_info%last_iter(iteration_info%n_rlevel), stat=stat)
IF (stat /= 0) THEN
CPABORT(routineP//" iteration_info%last_iter allocation")
END IF
ALLOCATE (iteration_info%iteration(iteration_info%n_rlevel))
ALLOCATE (iteration_info%level_name(iteration_info%n_rlevel))
ALLOCATE (iteration_info%last_iter(iteration_info%n_rlevel))
iteration_info%iteration(iteration_info%n_rlevel) = 1
iteration_info%level_name(iteration_info%n_rlevel) = "__ROOT__"
iteration_info%last_iter(iteration_info%n_rlevel) = .FALSE.
Expand All @@ -134,14 +115,11 @@ END SUBROUTINE cp_iteration_info_create
!> \author fawzi
! **************************************************************************************************
SUBROUTINE cp_iteration_info_retain(iteration_info)
TYPE(cp_iteration_info_type), POINTER :: iteration_info
TYPE(cp_iteration_info_type), INTENT(INOUT) :: iteration_info

CHARACTER(len=*), PARAMETER :: routineN = 'cp_iteration_info_retain', &
routineP = moduleN//':'//routineN

IF (.NOT. ASSOCIATED(iteration_info)) THEN
CPABORT(routineP//" iteration_info not associated")
END IF
IF (iteration_info%ref_count <= 0) THEN
CPABORT(routineP//" iteration_info%ref_counf<=0")
END IF
Expand Down Expand Up @@ -186,44 +164,34 @@ END SUBROUTINE cp_iteration_info_release
!> \author Teodoro Laino [tlaino]
! **************************************************************************************************
SUBROUTINE cp_iteration_info_copy_iter(iteration_info_in, iteration_info_out)
TYPE(cp_iteration_info_type), POINTER :: iteration_info_in, iteration_info_out
TYPE(cp_iteration_info_type), INTENT(INOUT) :: iteration_info_in, iteration_info_out

CHARACTER(len=*), PARAMETER :: routineN = 'cp_iteration_info_copy_iter', &
routineP = moduleN//':'//routineN

INTEGER :: i, stat
INTEGER :: i

IF (ASSOCIATED(iteration_info_in)) THEN
IF (iteration_info_in%ref_count <= 0) THEN
CPABORT(routineP//" iteration_info_in%ref_counf<=0")
END IF

iteration_info_out%n_rlevel = iteration_info_in%n_rlevel

DEALLOCATE (iteration_info_out%iteration)
i = SIZE(iteration_info_in%iteration)
ALLOCATE (iteration_info_out%iteration(i), stat=stat)
IF (stat /= 0) &
CPABORT(routineP//" could not allocate iteration_info%iteration")
iteration_info_out%iteration = iteration_info_in%iteration

DEALLOCATE (iteration_info_out%last_iter)
i = SIZE(iteration_info_in%last_iter)
ALLOCATE (iteration_info_out%last_iter(i), stat=stat)
IF (stat /= 0) &
CPABORT(routineP//" could not allocate iteration_info%last_iter")
iteration_info_out%last_iter = iteration_info_in%last_iter

DEALLOCATE (iteration_info_out%level_name)
i = SIZE(iteration_info_in%level_name)
ALLOCATE (iteration_info_out%level_name(i), stat=stat)
IF (stat /= 0) &
CPABORT(routineP//" could not allocate iteration_info%level_name")
iteration_info_out%level_name = iteration_info_in%level_name

ELSE
CPABORT(routineP//" iteration_info_in not associated!")
IF (iteration_info_in%ref_count <= 0) THEN
CPABORT(routineP//" iteration_info_in%ref_counf<=0")
END IF

iteration_info_out%n_rlevel = iteration_info_in%n_rlevel

DEALLOCATE (iteration_info_out%iteration)
i = SIZE(iteration_info_in%iteration)
ALLOCATE (iteration_info_out%iteration(i))
iteration_info_out%iteration = iteration_info_in%iteration

DEALLOCATE (iteration_info_out%last_iter)
i = SIZE(iteration_info_in%last_iter)
ALLOCATE (iteration_info_out%last_iter(i))
iteration_info_out%last_iter = iteration_info_in%last_iter

DEALLOCATE (iteration_info_out%level_name)
i = SIZE(iteration_info_in%level_name)
ALLOCATE (iteration_info_out%level_name(i))
iteration_info_out%level_name = iteration_info_in%level_name

END SUBROUTINE cp_iteration_info_copy_iter

END MODULE cp_iter_types
Expand Down
74 changes: 18 additions & 56 deletions src/common/cp_log_handling.F
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,8 @@ MODULE cp_log_handling
USE machine, ONLY: default_output_unit,&
m_getpid,&
m_hostnm
USE message_passing, ONLY: mp_para_env_type
USE message_passing, ONLY: mp_para_env_release,&
mp_para_env_type
USE string_utilities, ONLY: compress
USE timings, ONLY: print_stack
#include "../base/base_uses.f90"
Expand Down Expand Up @@ -137,15 +138,15 @@ MODULE cp_log_handling
!> \author Fawzi Mohamed
! **************************************************************************************************
TYPE cp_logger_type
INTEGER :: ref_count
INTEGER :: print_level
INTEGER :: default_local_unit_nr
INTEGER :: default_global_unit_nr
LOGICAL :: close_local_unit_on_dealloc, close_global_unit_on_dealloc
CHARACTER(len=default_string_length) :: suffix
CHARACTER(len=default_path_length) :: local_filename, global_filename
TYPE(mp_para_env_type), POINTER :: para_env
TYPE(cp_iteration_info_type), POINTER :: iter_info
INTEGER :: ref_count = -1
INTEGER :: print_level = -1
INTEGER :: default_local_unit_nr = -1
INTEGER :: default_global_unit_nr = -1
LOGICAL :: close_local_unit_on_dealloc = .FALSE., close_global_unit_on_dealloc = .FALSE.
CHARACTER(len=default_string_length) :: suffix = ""
CHARACTER(len=default_path_length) :: local_filename = "", global_filename = ""
TYPE(mp_para_env_type), POINTER :: para_env => NULL()
TYPE(cp_iteration_info_type), POINTER :: iter_info => NULL()
END TYPE cp_logger_type

TYPE cp_logger_p_type
Expand Down Expand Up @@ -184,7 +185,7 @@ END FUNCTION cp_default_logger_stack_size
!> available within the program
! **************************************************************************************************
SUBROUTINE cp_add_default_logger(logger)
TYPE(cp_logger_type), POINTER :: logger
TYPE(cp_logger_type), INTENT(INOUT), TARGET :: logger

CHARACTER(len=*), PARAMETER :: routineN = 'cp_add_default_logger', &
routineP = moduleN//':'//routineN
Expand Down Expand Up @@ -295,11 +296,7 @@ SUBROUTINE cp_logger_create(logger, para_env, print_level, &
CHARACTER(len=*), PARAMETER :: routineN = 'cp_logger_create', &
routineP = moduleN//':'//routineN

INTEGER :: stat

ALLOCATE (logger, stat=stat)
IF (stat /= 0) &
CPABORT(routineP//" could not ALLOCATE a logger")
ALLOCATE (logger)

NULLIFY (logger%para_env)
NULLIFY (logger%iter_info)
Expand Down Expand Up @@ -405,13 +402,11 @@ END SUBROUTINE cp_logger_create
!> \author Fawzi Mohamed
! **************************************************************************************************
SUBROUTINE cp_logger_retain(logger)
TYPE(cp_logger_type), POINTER :: logger
TYPE(cp_logger_type), INTENT(INOUT) :: logger

CHARACTER(len=*), PARAMETER :: routineN = 'cp_logger_retain', &
routineP = moduleN//':'//routineN

IF (.NOT. ASSOCIATED(logger)) &
CPABORT(routineP//" logger not associated")
IF (logger%ref_count < 1) &
CPABORT(routineP//" logger%ref_count<1")
logger%ref_count = logger%ref_count + 1
Expand Down Expand Up @@ -447,7 +442,7 @@ SUBROUTINE cp_logger_release(logger)
logger%close_local_unit_on_dealloc = .FALSE.
logger%default_local_unit_nr = -1
END IF
CALL my_mp_para_env_release(logger%para_env)
CALL mp_para_env_release(logger%para_env)
CALL cp_iteration_info_release(logger%iter_info)
DEALLOCATE (logger)
END IF
Expand Down Expand Up @@ -546,14 +541,12 @@ END FUNCTION cp_logger_get_default_io_unit
!> \author Fawzi Mohamed
! **************************************************************************************************
SUBROUTINE cp_logger_set_log_level(logger, level)
TYPE(cp_logger_type), POINTER :: logger
TYPE(cp_logger_type), INTENT(INOUT) :: logger
INTEGER, INTENT(in) :: level

CHARACTER(len=*), PARAMETER :: routineN = 'cp_logger_set_log_level', &
routineP = moduleN//':'//routineN

IF (.NOT. ASSOCIATED(logger)) &
CPABORT(routineP//" logger not associated")
IF (logger%ref_count < 1) &
CPABORT(routineP//" logger%ref_count<1")
logger%print_level = level
Expand Down Expand Up @@ -664,33 +657,6 @@ RECURSIVE FUNCTION cp_logger_get_default_unit_nr(logger, local, skip_not_ionode)
END IF
END FUNCTION cp_logger_get_default_unit_nr

! **************************************************************************************************
!> \brief releases the para object (to be called when you don't want anymore
!> the shared copy of this object)
!> \param para_env the new group
!> \par History
!> 08.2002 created [fawzi]
!> \author Fawzi Mohamed
!> \note
!> local private version to avoid circular dependencies
!> (see cp_para_env:mp_para_env_release)!
! **************************************************************************************************
SUBROUTINE my_mp_para_env_release(para_env)
TYPE(mp_para_env_type), POINTER :: para_env
CHARACTER(len=*), PARAMETER :: routineN = 'my_mp_para_env_release', &
routineP = moduleN//':'//routineN
IF (ASSOCIATED(para_env)) THEN
IF (.NOT. para_env%is_valid()) THEN
CPABORT(routineP//" para_env%ref_count<1")
END IF
CALL para_env%free()
IF (.NOT. para_env%is_valid()) DEALLOCATE (para_env)
END IF
NULLIFY (para_env)
END SUBROUTINE my_mp_para_env_release
! **************************************************************************************************
!> \brief generates a unique filename (ie adding eventual suffixes and
!> process ids)
Expand Down Expand Up @@ -748,13 +714,9 @@ END SUBROUTINE cp_logger_generate_filename
!> \author Fawzi Mohamed
! **************************************************************************************************
SUBROUTINE cp_logger_set(logger, local_filename, global_filename)
TYPE(cp_logger_type), POINTER :: logger
TYPE(cp_logger_type), INTENT(INOUT) :: logger
CHARACTER(len=*), INTENT(in), OPTIONAL :: local_filename, global_filename

CHARACTER(len=*), PARAMETER :: routineN = 'cp_logger_set', routineP = moduleN//':'//routineN
IF (.NOT. ASSOCIATED(logger)) &
CPABORT(routineP//" unassociated logger")
IF (PRESENT(local_filename)) logger%local_filename = local_filename
IF (PRESENT(global_filename)) logger%global_filename = global_filename
END SUBROUTINE cp_logger_set
Expand Down Expand Up @@ -832,7 +794,7 @@ END FUNCTION cp_real_dp_to_string
!> \return ...
!> \author fawzi
! **************************************************************************************************
FUNCTION cp_logical_to_string(val) RESULT(res)
ELEMENTAL FUNCTION cp_logical_to_string(val) RESULT(res)
LOGICAL, INTENT(in) :: val
CHARACTER(len=1) :: res

Expand Down
12 changes: 6 additions & 6 deletions src/common/cp_min_heap.F
Original file line number Diff line number Diff line change
Expand Up @@ -23,18 +23,18 @@ MODULE cp_min_heap
INTEGER, PARAMETER :: valt = int_8

TYPE cp_heap_node
INTEGER(KIND=keyt) :: key
INTEGER(KIND=valt) :: value
INTEGER(KIND=keyt) :: key = -1_keyt
INTEGER(KIND=valt) :: value = -1_valt
END TYPE cp_heap_node

TYPE cp_heap_node_e
TYPE(cp_heap_node) :: node
TYPE(cp_heap_node) :: node = cp_heap_node()
END TYPE cp_heap_node_e

TYPE cp_heap_type
INTEGER :: n
INTEGER, DIMENSION(:), POINTER :: index
TYPE(cp_heap_node_e), DIMENSION(:), POINTER :: nodes
INTEGER :: n = -1
INTEGER, DIMENSION(:), POINTER :: index => NULL()
TYPE(cp_heap_node_e), DIMENSION(:), POINTER :: nodes => NULL()
END TYPE cp_heap_type

CONTAINS
Expand Down

0 comments on commit f26eaef

Please sign in to comment.