Skip to content

Commit

Permalink
HELIUM: pretty
Browse files Browse the repository at this point in the history
  • Loading branch information
cschran authored and hforbert committed Sep 12, 2019
1 parent d22b847 commit 4dc9290
Show file tree
Hide file tree
Showing 6 changed files with 1,605 additions and 1,955 deletions.
1,162 changes: 573 additions & 589 deletions src/motion/helium_interactions.F

Large diffs are not rendered by default.

14 changes: 6 additions & 8 deletions src/motion/helium_io.F
Original file line number Diff line number Diff line change
Expand Up @@ -471,14 +471,12 @@ SUBROUTINE helium_print_energy(helium_env)
CHARACTER(len=*), PARAMETER :: routineN = 'helium_print_energy', &
routineP = moduleN//':'//routineN
INTEGER :: handle, iteration, k, m, unit_nr
LOGICAL :: file_is_new, should_output
INTEGER :: handle, iteration, k, m, ntot, unit_nr
LOGICAL :: cepsample, file_is_new, should_output
REAL(KIND=dp) :: naccptd
REAL(KIND=dp), DIMENSION(:), POINTER :: my_energy
TYPE(cp_logger_type), POINTER :: logger
TYPE(section_vals_type), POINTER :: print_key
LOGICAL :: cepsample
INTEGER :: ntot
CALL timeset(routineN, handle)
Expand All @@ -502,16 +500,16 @@ SUBROUTINE helium_print_energy(helium_env)
IF (cepsample) THEN
ntot = 0
DO k = 1, SIZE(helium_env)
ntot = ntot + helium_env(1)%helium%iter_norot * helium_env(1)%helium%iter_rot
ntot = ntot+helium_env(1)%helium%iter_norot*helium_env(1)%helium%iter_rot
DO m = 1, helium_env(k)%helium%maxcycle
naccptd = naccptd+helium_env(k)%helium%num_accepted(helium_env(k)%helium%bisctlog2+2, m)
END DO
END DO
ELSE !(wormsample)
ntot = 0
DO k = 1, SIZE(helium_env)
naccptd = naccptd + helium_env(k)%helium%num_accepted(1, 1)
ntot = ntot + helium_env(k)%helium%num_accepted(2, 1)
naccptd = naccptd+helium_env(k)%helium%num_accepted(1, 1)
ntot = ntot+helium_env(k)%helium%num_accepted(2, 1)
END DO
END IF
CALL mp_sum(naccptd, helium_env(1)%comm)
Expand Down Expand Up @@ -542,7 +540,7 @@ SUBROUTINE helium_print_energy(helium_env)
WRITE (unit_nr, "(I9,7(1X,F20.9))") &
iteration, &
REAL(naccptd,dp)/REAL(ntot,dp), &
REAL(naccptd, dp)/REAL(ntot, dp), &
my_energy(e_id_potential), &
my_energy(e_id_kinetic), &
my_energy(e_id_thermo), &
Expand Down
26 changes: 10 additions & 16 deletions src/motion/helium_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -36,9 +36,9 @@ MODULE helium_methods
rho_moment_of_inertia, rho_num, rho_projected_area, rho_winding_cycle, rho_winding_number
USE input_constants, ONLY: helium_cell_shape_cube,&
helium_cell_shape_octahedron,&
helium_solute_intpot_none, &
helium_sampling_ceperley, &
helium_sampling_worm
helium_sampling_ceperley,&
helium_sampling_worm,&
helium_solute_intpot_none
USE input_section_types, ONLY: section_vals_get,&
section_vals_get_subs_vals,&
section_vals_type,&
Expand Down Expand Up @@ -109,7 +109,7 @@ SUBROUTINE helium_create(helium_env, input, solute)

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

CHARACTER(len=default_path_length) :: msg_str, msg_str2, potential_file_name
CHARACTER(len=default_path_length) :: msg_str, potential_file_name
INTEGER :: color_sub, handle, i, input_unit, isize, &
itmp, j, k, mepos, new_comm, nlines, &
ntab, num_env, pdx
Expand Down Expand Up @@ -193,9 +193,6 @@ SUBROUTINE helium_create(helium_env, input, solute)
helium_env(k)%helium%ltmp_atoms_1d, &
helium_env(k)%helium%itmp_atoms_np_1d, &
helium_env(k)%helium%pos, helium_env(k)%helium%work, &
#ifdef __FU_DEBUGWORM
helium_env(k)%helium%tmppos,&
#endif
helium_env(k)%helium%force_avrg, &
helium_env(k)%helium%force_inst, &
helium_env(k)%helium%rtmp_3_np_1d, &
Expand Down Expand Up @@ -395,7 +392,7 @@ SUBROUTINE helium_create(helium_env, input, solute)
CALL section_vals_val_get(helium_section, "SAMPLING_METHOD", &
i_val=helium_env(k)%helium%sampling_method)

SELECT CASE (helium_env(k)%helium%sampling_method)
SELECT CASE (helium_env (k)%helium%sampling_method)
CASE (helium_sampling_ceperley)
! check value of maxcycle
CALL section_vals_val_get(helium_section, "CEPERLEY%MAX_PERM_CYCLE", &
Expand Down Expand Up @@ -455,7 +452,7 @@ SUBROUTINE helium_create(helium_env, input, solute)
CALL section_vals_val_get(helium_section, "WORM%ALLOW_OPEN", &
l_val=helium_env(k)%helium%worm_allow_open)

IF (helium_env(k)%helium%worm_staging_l + 1 >= helium_env(k)%helium%beads) THEN
IF (helium_env(k)%helium%worm_staging_l+1 >= helium_env(k)%helium%beads) THEN
msg_str = "STAGING_L for worm sampling is to large"
CPABORT(msg_str)
ELSE IF (helium_env(k)%helium%worm_staging_l < 1) THEN
Expand All @@ -475,8 +472,8 @@ SUBROUTINE helium_create(helium_env, input, solute)
IF (helium_env(k)%helium%periodic) THEN
rtmp = rtmp*helium_env(k)%helium%density
ELSE
rtmp = rtmp*helium_env(k)%helium%atoms/&
(4.0_dp/3.0_dp*pi*helium_env(k)%helium%droplet_radius**3)
rtmp = rtmp*helium_env(k)%helium%atoms/ &
(4.0_dp/3.0_dp*pi*helium_env(k)%helium%droplet_radius**3)
END IF
helium_env(k)%helium%worm_ln_openclose_scale = LOG(rtmp)

Expand Down Expand Up @@ -586,9 +583,6 @@ SUBROUTINE helium_create(helium_env, input, solute)
i = helium_env(k)%helium%atoms
j = helium_env(k)%helium%beads
ALLOCATE (helium_env(k)%helium%pos(3, i, j))
#ifdef __FU_DEBUGWORM
ALLOCATE (helium_env(k)%helium%tmppos(3, i, j))
#endif
helium_env(k)%helium%pos = 0.0_dp
ALLOCATE (helium_env(k)%helium%work(3, i, j))
ALLOCATE (helium_env(k)%helium%ptable(helium_env(k)%helium%maxcycle+1))
Expand Down Expand Up @@ -934,7 +928,7 @@ SUBROUTINE helium_init(helium_env, pint_env)
CHARACTER(len=*), PARAMETER :: routineN = 'helium_init', routineP = moduleN//':'//routineN
INTEGER :: handle, i, k
INTEGER :: handle, k
LOGICAL :: coords_presampled, explicit, presample
REAL(KIND=dp) :: initkT, solute_radius
TYPE(cp_logger_type), POINTER :: logger
Expand Down Expand Up @@ -1011,7 +1005,7 @@ SUBROUTINE helium_init(helium_env, pint_env)
helium_env(k)%helium%worm_atom_idx = 0
helium_env(k)%helium%worm_bead_idx = 0
helium_env(k)%helium%work(:,:,:) = helium_env(k)%helium%pos(:,:,:)
helium_env(k)%helium%work(:, :, :) = helium_env(k)%helium%pos(:, :, :)
! init center of mass
IF (helium_env(k)%helium%solute_present) THEN
Expand Down
4 changes: 2 additions & 2 deletions src/motion/helium_sampling.F
Original file line number Diff line number Diff line change
Expand Up @@ -187,8 +187,8 @@ SUBROUTINE helium_sample(helium_env, pint_env)
CHARACTER(len=*), PARAMETER :: routineN = 'helium_sample', routineP = moduleN//':'//routineN

CHARACTER(len=default_string_length) :: msg_str
INTEGER :: i, ires, irot, iweight, k, nslices, &
nsteps, num_env, offset, sel_mp_source
INTEGER :: i, irot, iweight, k, nslices, nsteps, &
num_env, offset, sel_mp_source
REAL(KIND=dp) :: inv_num_env, inv_xn, rnd, rtmp, rweight
REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :) :: work_2d
TYPE(cp_logger_type), POINTER :: logger
Expand Down

0 comments on commit 4dc9290

Please sign in to comment.