31#include "../base/base_uses.f90" 
   35   CHARACTER(len=*), 
PARAMETER, 
PRIVATE :: moduleN = 
'neb_types' 
   48      INTEGER       :: number_of_replica = 0, nsize_xyz = 0, nsize_int = 0
 
   49      INTEGER       :: nsteps_it = 0, istep = 0
 
   50      INTEGER       :: nr_he_image = 0
 
   51      LOGICAL       :: rotate_frames = .false., align_frames = .false.
 
   52      LOGICAL       :: optimize_end_points = .false.
 
   53      LOGICAL       :: use_colvar = .false.
 
   54      LOGICAL       :: reparametrize_frames = .false.
 
   55      INTEGER       :: spline_order = 0
 
   56      REAL(kind=
dp) :: k = 0.0_dp, spring_energy = 0.0_dp, avg_distance = 0.0_dp
 
   57      REAL(kind=
dp) :: smoothing = 0.0_dp
 
   58      CHARACTER(LEN=default_string_length) :: opt_type_label = 
"" 
 
   70      REAL(kind=
dp), 
DIMENSION(:, :), 
POINTER  :: xyz => null(), int => null(), wrk => null()
 
   71      REAL(kind=
dp), 
DIMENSION(:, :, :), 
POINTER  :: mmatrix => null()
 
 
   86      LOGICAL, 
INTENT(IN), 
OPTIONAL                      :: full_allocation
 
   88      INTEGER                                            :: neb_nr_replica
 
   89      LOGICAL                                            :: allocate_all
 
   91      cpassert(.NOT. 
ASSOCIATED(neb_var))
 
   92      allocate_all = .false.
 
   93      IF (
PRESENT(full_allocation)) allocate_all = full_allocation
 
   94      neb_nr_replica = neb_env%number_of_replica
 
   96      NULLIFY (neb_var%xyz, neb_var%int, neb_var%wrk, neb_var%Mmatrix)
 
   97      IF (allocate_all) 
THEN 
   98         ALLOCATE (neb_var%xyz(neb_env%nsize_xyz, neb_nr_replica))
 
  101      IF (neb_env%use_colvar) 
THEN 
  103         cpassert(neb_env%nsize_int > 0)
 
  104         ALLOCATE (neb_var%int(neb_env%nsize_int, neb_nr_replica))
 
  106         neb_var%wrk => neb_var%int
 
  109         IF (.NOT. allocate_all) 
THEN 
  110            ALLOCATE (neb_var%xyz(neb_env%nsize_xyz, neb_nr_replica))
 
  113         neb_var%wrk => neb_var%xyz
 
  115      neb_var%size_wrk(1) = 
SIZE(neb_var%wrk, 1)
 
  116      neb_var%size_wrk(2) = 
SIZE(neb_var%wrk, 2)
 
 
  129      cpassert(
ASSOCIATED(neb_var))
 
  130      IF (
ASSOCIATED(neb_var%xyz)) 
THEN 
  131         DEALLOCATE (neb_var%xyz)
 
  134         DEALLOCATE (neb_var%int)
 
  136      NULLIFY (neb_var%wrk)
 
 
Interface for the force calculations.
 
Defines the basic variable types.
 
integer, parameter, public dp
 
integer, parameter, public default_string_length
 
Typo for Nudged Elastic Band Calculation.
 
subroutine, public neb_var_release(neb_var)
Releases a variable type for BAND calculation.
 
subroutine, public neb_var_create(neb_var, neb_env, full_allocation)
Creates a variable type for BAND calculation.
 
wrapper to abstract the force evaluation of the various methods