Skip to content

Commit

Permalink
Fix / suppress uninitialized variables
Browse files Browse the repository at this point in the history
  • Loading branch information
oschuett committed Aug 18, 2021
1 parent ef60d10 commit 67237a2
Show file tree
Hide file tree
Showing 9 changed files with 40 additions and 12 deletions.
14 changes: 13 additions & 1 deletion src/colvar_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -3040,7 +3040,6 @@ SUBROUTINE torsion_colvar(colvar, cell, subsys, particles, no_riemann_sheet_op)
dedxia = zcb*dedyt - ycb*dedzt
dedyia = xcb*dedzt - zcb*dedxt
dedzia = ycb*dedxt - xcb*dedyt
dedzia = ycb*dedxt - xcb*dedyt
dedxib = yca*dedzt - zca*dedyt + zdc*dedyu - ydc*dedzu
dedyib = zca*dedxt - xca*dedzt + xdc*dedzu - zdc*dedxu
dedzib = xca*dedyt - yca*dedxt + ydc*dedxu - xdc*dedyu
Expand All @@ -3050,6 +3049,19 @@ SUBROUTINE torsion_colvar(colvar, cell, subsys, particles, no_riemann_sheet_op)
dedxid = zcb*dedyu - ycb*dedzu
dedyid = xcb*dedzu - zcb*dedxu
dedzid = ycb*dedxu - xcb*dedyu
ELSE
dedxia = 0.0_dp
dedyia = 0.0_dp
dedzia = 0.0_dp
dedxib = 0.0_dp
dedyib = 0.0_dp
dedzib = 0.0_dp
dedxic = 0.0_dp
dedyic = 0.0_dp
dedzic = 0.0_dp
dedxid = 0.0_dp
dedyid = 0.0_dp
dedzid = 0.0_dp
ENDIF
!
colvar%ss = e
Expand Down
3 changes: 3 additions & 0 deletions src/fist_nonbond_force.F
Original file line number Diff line number Diff line change
Expand Up @@ -338,6 +338,8 @@ SUBROUTINE force_nonbond(fist_nonbond_env, ewald_env, particle_set, cell, &
rab_list(1:3, 2) = 0.0_dp
rab_list(1:3, 3) = 0.0_dp
rab_list(1:3, 4) = rab_ss(1:3) + cell_v(1:3)
ELSE
rab_list(:, :) = 0.0_dp
END IF
! Compute the term only if all the pairs (cc,cs,sc,ss) are within the cut-off
Check_terms: DO i = 1, 4
Expand All @@ -354,6 +356,7 @@ SUBROUTINE force_nonbond(fist_nonbond_env, ewald_env, particle_set, cell, &
rab_com = rab_cc
shell_a = 0
shell_b = 0
rab_list(:, :) = 0.0_dp
END IF
rab_com = rab_com + cell_v
rab2_com = rab_com(1)**2 + rab_com(2)**2 + rab_com(3)**2
Expand Down
2 changes: 2 additions & 0 deletions src/force_fields_input.F
Original file line number Diff line number Diff line change
Expand Up @@ -1099,6 +1099,8 @@ SUBROUTINE read_b4_section(nonbonded, section, start)
! Get the 6 coefficients of the 5th-order polynomial -> x(1:6)
! and the 4 coefficients of the 3rd-order polynomial -> x(7:10)
x(:) = MATMUL(p_inv(:, :), v(:))
ELSE
x(:) = 0.0_dp
END IF
CALL section_vals_val_get(section, "RCUT", i_rep_section=isec, r_val=rcut)
Expand Down
2 changes: 2 additions & 0 deletions src/moments_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -98,6 +98,7 @@ SUBROUTINE get_reference_point(rpoint, drpoint, qs_env, fist_env, reference, ref
CASE (use_mom_ref_com)
rpoint = 0._dp
mtot = 0._dp
center(:) = 0._dp
IF (do_molecule) THEN
mass_low = -HUGE(mass_low)
! fold the molecule around the heaviest atom in the molecule
Expand Down Expand Up @@ -141,6 +142,7 @@ SUBROUTINE get_reference_point(rpoint, drpoint, qs_env, fist_env, reference, ref
CASE (use_mom_ref_coac)
rpoint = 0._dp
ztot = 0._dp
center(:) = 0._dp
IF (do_molecule) THEN
mass_low = -HUGE(mass_low)
! fold the molecule around the heaviest atom in the molecule
Expand Down
4 changes: 2 additions & 2 deletions src/mulliken.F
Original file line number Diff line number Diff line change
Expand Up @@ -524,8 +524,8 @@ SUBROUTINE mulliken_charges_akp(p_matrix_kp, s_matrix_kp, para_env, particle_set
CPASSERT(ASSOCIATED(p_matrix_kp))
CPASSERT(ASSOCIATED(s_matrix_kp))

nspin = SIZE(p_matrix)
CALL dbcsr_get_info(s_matrix, nblkrows_total=nblock)
nspin = SIZE(p_matrix_kp, 1)
CALL dbcsr_get_info(s_matrix_kp(1, 1)%matrix, nblkrows_total=nblock)
ALLOCATE (charges(nblock, nspin), charges_im(nblock, nspin))
charges = 0.0_dp

Expand Down
3 changes: 3 additions & 0 deletions src/pw/dct.F
Original file line number Diff line number Diff line change
Expand Up @@ -1104,6 +1104,9 @@ SUBROUTINE expansion_bounds(pw_grid, neumann_directions, srcs_expand, flipg_stat
CASE (neumannZ)
maxn_sendrecv = 1
shf_yesno = (/0, 0, 1/)
CASE DEFAULT
CPABORT("Unknown neumann direction")
shf_yesno = (/0, 0, 0/)
END SELECT
ALLOCATE (pcs_bnds(2, 3, maxn_sendrecv))
Expand Down
2 changes: 2 additions & 0 deletions src/qs_grid_atom.F
Original file line number Diff line number Diff line change
Expand Up @@ -474,6 +474,8 @@ SUBROUTINE initialize_atomic_grid(int_grid, nr, na, rmax, quadrature, iunit)
rm(2) = SUM(int_grid%batch(ig)%rco(2, 1:np))
rm(3) = SUM(int_grid%batch(ig)%rco(3, 1:np))
rm(1:3) = rm(1:3)/REAL(np, KIND=dp)
ELSE
rm(:) = 0.0_dp
END IF
int_grid%batch(ig)%rcenter(1:3) = rm(1:3)
dmax = 0.0_dp
Expand Down
14 changes: 7 additions & 7 deletions src/qs_tddfpt2_subgroups.F
Original file line number Diff line number Diff line change
Expand Up @@ -139,19 +139,19 @@ MODULE qs_tddfpt2_subgroups
! **************************************************************************************************
TYPE mgrid_saved_parameters
!> create commensurate grids
LOGICAL :: commensurate_mgrids
LOGICAL :: commensurate_mgrids = .FALSE.
!> create real-space grids
LOGICAL :: realspace_mgrids
LOGICAL :: realspace_mgrids = .FALSE.
!> do not perform load balancing
LOGICAL :: skip_load_balance
LOGICAL :: skip_load_balance = .FALSE.
!> cutoff value at the finest grid level
REAL(KIND=dp) :: cutoff
REAL(KIND=dp) :: cutoff = 0.0_dp
!> inverse scale factor
REAL(KIND=dp) :: progression_factor
REAL(KIND=dp) :: progression_factor = 0.0_dp
!> relative cutoff
REAL(KIND=dp) :: relative_cutoff
REAL(KIND=dp) :: relative_cutoff = 0.0_dp
!> list of explicitly given cutoff values
REAL(KIND=dp), DIMENSION(:), POINTER :: e_cutoff
REAL(KIND=dp), DIMENSION(:), POINTER :: e_cutoff => NULL()
END TYPE mgrid_saved_parameters

CONTAINS
Expand Down
8 changes: 6 additions & 2 deletions tools/conventions/conventions.supp
Original file line number Diff line number Diff line change
Expand Up @@ -56,14 +56,18 @@ dumpdcd.F: Found STOP statement in procedure "abort_program"
dumpdcd.F: Found STOP statement in procedure "dumpdcd"
dumpdcd.F: Found WRITE statement with hardcoded unit in "abort_program"
dumpdcd.F: Found WRITE statement with hardcoded unit in "print_help"
dumpdcd.F: 'MEM[(struct array02_real(kind=8) &)&r_pbc].dim[0].ubound' is used uninitialized [-Wuninitialized]
dumpdcd.F: 'MEM[(struct array02_real(kind=8) &)&r_pbc].dim[1].stride' is used uninitialized [-Wuninitialized]
dumpdcd.F: 'MEM[(struct array02_real(kind=8) &)&s].dim[0].ubound' is used uninitialized [-Wuninitialized]
dumpdcd.F: 'MEM[(struct array02_real(kind=8) &)&s_pbc].dim[0].ubound' is used uninitialized [-Wuninitialized]
dumpdcd.F: 'MEM[(struct array02_real(kind=8) &)&s_pbc].dim[1].stride' is used uninitialized [-Wuninitialized]
dumpdcd.F: 's.dim[1].stride' is used uninitialized [-Wuninitialized]
eip_silicon.F: Found OPEN statement in procedure "eip_bazant_silicon"
eip_silicon.F: Found OPEN statement in procedure "eip_lenosky_silicon"
eip_silicon.F: Found WRITE statement with hardcoded unit in "eip_bazant_silicon"
eip_silicon.F: Found WRITE statement with hardcoded unit in "eip_lenosky_silicon"
eip_silicon.F: Found WRITE statement with hardcoded unit in "subfeniat_b"
eip_silicon.F: Found WRITE statement with hardcoded unit in "subfeniat_l"
eri_mme_lattice_summation.F: '__var_14_matmul.dim[0].lbound' is used uninitialized in this function [-Wuninitialized]
eri_mme_lattice_summation.F: '__var_14_matmul.dim[0].ubound' is used uninitialized in this function [-Wuninitialized]
et_coupling_proj.F: Routine INFOG2L called with an implicit interface.
extended_system_init.F: Found WRITE statement with hardcoded unit in "init_barostat_variables"
farming_methods.F: Found CLOSE statement in procedure "farming_parse_input"
Expand Down

0 comments on commit 67237a2

Please sign in to comment.