!-----------------------------------------------------------------------------------! ! Bader charge density analysis program ! Module for specifying input options !-----------------------------------------------------------------------------------! MODULE options_mod USE kind_mod , ONLY : q2 IMPLICIT NONE TYPE :: options_obj CHARACTER(LEN=128) :: chargefile, refchgfile REAL(q2) :: badertol, stepsize, vacval INTEGER :: out_opt, out_auto = 0, out_cube = 1, out_chgcar4 = 2, out_chgcar5 = 3 INTEGER :: in_opt, in_auto = 0, in_cube = 1, in_chgcar = 2, in_chgcar4 = 3,in_chgcar5 = 4 INTEGER :: bader_opt, bader_offgrid = 0, bader_ongrid = 1, bader_neargrid = 2, bader_weight = 3 INTEGER :: quit_opt, quit_max = 0, quit_known = 1 INTEGER :: refine_edge_itrs ! refine_edge_itrs=-1 check points around the reassigned points during refinement ! refine_edge_itrs=-2 check every edge point during refinement INTEGER :: selanum, selbnum, sumanum, sumbnum INTEGER,ALLOCATABLE,DIMENSION(:) :: selavol, selbvol,sumavol,sumbvol LOGICAL :: vac_flag LOGICAL :: bader_flag, voronoi_flag, dipole_flag, ldos_flag LOGICAL :: print_all_bader, print_all_atom LOGICAL :: print_sel_bader, print_sel_atom LOGICAL :: print_sum_bader, print_sum_atom LOGICAL :: print_bader_index, print_atom_index LOGICAL :: verbose_flag, ref_flag, find_critpoints_flag LOGICAL :: print_surfaces_atoms REAL(q2) :: par_tem, par_gradfloor REAL(q2) :: cp_min_distance REAL(q2) :: par_newtonr, cp_search_radius LOGICAL :: ismolecule LOGICAL :: iscrystal LOGICAL :: debugMode LOGICAL :: dohes LOGICAL :: enableDensityDescend,enableCHGCARSmoothening LOGICAL :: gradMode !gradMode enables the gradient descend subroutine to replace the Newton's Method subroutine LOGICAL :: GD_magMode LOGICAL :: autocp_flag ! Turns on heuristic features LOGICAL :: static_search ! Only initiate searches from coordinates read LOGICAL :: static_check ! reads in a list of CPs and runs through checks. LOGICAL :: aflow_sym ! Reads aflow.fgroup.relax.out to get symmetry info LOGICAL :: ignore_cp_conflict ! This forces ReduceCP to always finish. END TYPE options_obj PRIVATE PUBLIC :: get_options, options_obj CONTAINS !-----------------------------------------------------------------------------------! ! get_options: Read any input flags and the charge density file name !-----------------------------------------------------------------------------------! SUBROUTINE get_options(opts) TYPE(options_obj) :: opts LOGICAL :: existflag LOGICAL :: readchgflag INTEGER :: n, i, ip, m, it INTEGER :: sel, itmp, istart, iend CHARACTER(LEN=128) :: p CHARACTER*128 :: inc INTEGER :: COMMAND_ARGUMENT_COUNT ! Default values opts%par_tem = 0 opts%cp_search_radius = 3 opts%cp_min_distance = 1.5 ! cp_min_distance is the criteria for determine if two points are identical ! due to spacial proximity. This is in lattice units. opts%par_newtonr = 0.1 opts%par_gradfloor = 0.1 ! opts%par_GDgradfloor = 0.2 opts%ismolecule = .FALSE. opts%iscrystal = .FALSE. opts%dohes = .FALSE. opts%out_opt = opts%out_chgcar4 opts%in_opt = opts%in_auto opts%debugMode = .FALSE. ! print options opts%vac_flag = .FALSE. ! opts%vac_flag = .TRUE. opts%vacval = 1E-3 opts%print_all_atom = .FALSE. opts%print_all_bader = .FALSE. opts%print_sel_atom = .FALSE. opts%print_sel_bader = .FALSE. opts%print_sum_atom = .FALSE. opts%print_sum_bader = .FALSE. opts%print_bader_index = .FALSE. opts%print_atom_index = .FALSE. ! end of print options opts%bader_opt = opts%bader_neargrid opts%quit_opt = opts%quit_known opts%refine_edge_itrs = -1 opts%bader_flag = .TRUE. opts%voronoi_flag = .FALSE. opts%dipole_flag = .FALSE. opts%ldos_flag = .FALSE. opts%verbose_flag = .FALSE. opts%badertol = 1E-3 opts%stepsize = 0.0_q2 opts%ref_flag = .FALSE. opts%find_critpoints_flag = .FALSE. opts%autocp_flag = .FALSE. opts%print_surfaces_atoms = .FALSE. opts%enableDensityDescend = .FALSE. opts%enableCHGCARSmoothening = .FALSE. opts%gradMode = .FALSE. opts%GD_magMode = .TRUE. opts%static_search = .FALSE. opts%aflow_sym = .FALSE. opts%ignore_cp_conflict = .FALSE. ! n=IARGC() n=COMMAND_ARGUMENT_COUNT() IF (n == 0) THEN call write_options() STOP END IF ! Loop over all arguments m=0 readchgflag = .FALSE. readopts: DO WHILE(m' WRITE(*,*) ' -c | -n < bader | voronoi >' WRITE(*,*) ' Turn on [-c] or off [-n] the following calculations' WRITE(*,*) ' bader: Bader atoms in molecules (default)' WRITE(*,*) ' voronoi: population analysis based on distance' ! WRITE(*,*) ' dipole: multiple moments in Bader volumes' ! WRITE(*,*) ' ldos: local density of states in Bader volumes' WRITE(*,*) '' WRITE(*,*) ' -b < neargrid | ongrid | weight >' WRITE(*,*) ' Use the default near-grid bader partitioning, the' WRITE(*,*) ' original on-grid based algorithm, or the weight method' WRITE(*,*) ' of Yu and Trinkle' WRITE(*,*) '' ! WRITE(*,*) ' -s < stepsiz >' ! WRITE(*,*) ' Steepest ascent trajectory step size. This parameter is' ! WRITE(*,*) ' (only) used for the default offgrid Bader analysis. If' ! WRITE(*,*) ' not specified, the stepsize is set to the minimum distance' ! WRITE(*,*) ' between charge density grid points.' ! WRITE(*,*) '' WRITE(*,*) ' -r < refine_edge_method >' WRITE(*,*) ' By default (-r -1) , only the points around reassigned' WRITE(*,*) ' points are checked during refinements. The old method, ' WRITE(*,*) ' which checks every edge point during each refinement, can' WRITE(*,*) ' be enabled using the -r -2 switch:' WRITE(*,*) ' bader -r -2 CHGCAR' WRITE(*,*) '' WRITE(*,*) ' -ref < reference_charge >' WRITE(*,*) ' Use a reference charge file to do the Bader partitioning.' WRITE(*,*) ' This is the recommended way to analyze vasp output files:' WRITE(*,*) ' bader CHGCAR -ref CHGCAR_total' WRITE(*,*) ' where CHGCAR_total is the sum of AECCAR0 and AECCAR2.' WRITE(*,*) '' WRITE(*,*) ' -vac < off | auto | vacuum_density >' WRITE(*,*) ' Assign low density points to vacuum.' WRITE(*,*) ' auto: vacuum density cutoff is 1E-3 e/Ang^3 by default' WRITE(*,*) ' off: do not assign low density points to a vacuum volume' WRITE(*,*) ' vacuum_density: maximum density assigned to a vacuum volume' WRITE(*,*) '' WRITE(*,*) ' -m < known | max >' WRITE(*,*) ' Determines how trajectories terminate' WRITE(*,*) ' known: stop when a point is surrounded by known points' WRITE(*,*) ' max: stop only when a charge density maximum is reached ' WRITE(*,*) '' WRITE(*,*) ' -p < all_atom | all_bader >' WRITE(*,*) ' Print calculated Bader volumes' WRITE(*,*) ' all_atom: all atomic volumes' WRITE(*,*) ' all_bader: all Bader volumes' WRITE(*,*) '' WRITE(*,*) ' -p < sel_atom | sel_bader > ' WRITE(*,*) ' Print calculated Bader volumes' WRITE(*,*) ' sel_atom: atomic volume(s) around the selected atom(s)' WRITE(*,*) ' sel_bader: selected Bader volumes' WRITE(*,*) '' WRITE(*,*) ' -p < sum_atom | sum_bader > ' WRITE(*,*) ' Print calculated Bader volumes' WRITE(*,*) ' sum_atom: sum of atomic volume(s) around the selected atom(s)' WRITE(*,*) ' sum_bader: sum of selected Bader volumes' WRITE(*,*) '' WRITE(*,*) ' -p < atom_index | bader_index >' WRITE(*,*) ' Print index of atomic or Bader volumes' WRITE(*,*) ' atom_index: print atomic volume indicies' WRITE(*,*) ' bader_index: print Bader volume indicies' WRITE(*,*) '' WRITE(*,*) ' -p < surfaces_atoms >' WRITE(*,*) ' Print a file with a list of surfaces coordinates and atoms' WRITE(*,*) ' forming this surface' WRITE(*,*) '' WRITE(*,*) ' -i < cube | chgcar >' WRITE(*,*) ' Input charge density file type. If not specified, the' WRITE(*,*) ' program will try to determine the charge density file type' WRITE(*,*) ' automatically.' WRITE(*,*) '' WRITE(*,*) ' -h' WRITE(*,*) ' Help.' WRITE(*,*) '' WRITE(*,*) ' -v' WRITE(*,*) ' Verbose output.' WRITE(*,*) '' WRITE(*,*) ' -cp' WRITE(*,*) ' Find critical points of the charge density' WRITE(*,*) ' Calculate eigenvalues and eigenvectors at those points' WRITE(*,*) ' Store results in file named CPF##.dat' WRITE(*,*) '' !WRITE(*,*) ' -parnewtonr' !WRITE(*,*) ' Criteria for stopping Newton Raphson method trajectory for & ! small stepsize. Default values should be OK.' !WRITE(*,*) ' -pargradfloor ' !WRITE(*,*) ' Criterial for stopping Newtons method for small & ! gradient. Default values should be OK.' !WRITE(*,*) ' -partem ' !WRITE(*,*) ' Proximity criteria for initializing Newtons method & ! trajectory. Default values should be OK.' !WRITE(*,*) ' -pardistance ' !WRITE(*,*) ' Proximity criteria in Angstrom for declaring two CP & ! duplicates of each other. Default values shoud & ! be OK.' !WRITE(*,*) ' -parsr' !WRITE(*,*) ' Search radius. If a Newton Rhapson trajectory & ! initiated at a point, no more trajectory will & ! initiate within this radius. Default is 0. Higher & ! values will improve performance. Value higher than & ! 3 will likely cause inaccurate results.' END SUBROUTINE write_help !-----------------------------------------------------------------------------------! END module options_mod