module mode_calc !This mode is used to calculate various quantities based on input information use parameters use io use subroutines use elements use box character(len=100) :: calc_opt real(kind=dp), allocatable :: calculated(:) public contains subroutine calc(arg_pos) !Main calling subroutine for mode_create integer, intent(out) :: arg_pos print *, '------------------------Mode Calc----------------------------' !First parse command call parse(arg_pos) print *, "Calculating ", trim(adjustl(calc_opt)), " for ", ele_num, " elements and ", atom_num, " atoms." !Now call the correct calc function based on calc_opt select case(trim(adjustl(calc_opt))) case('tot_virial') allocate(calculated(6)) call calc_tot_virial case('tot_energy') allocate(calculated(1)) call calc_tot_energy case default print *, trim(adjustl(calc_opt)), " is not accepted as a calc option in mode_calc" stop 3 end select end subroutine calc subroutine parse(arg_pos) !This parses the mode calc options integer, intent(out) :: arg_pos character(len = 100) :: infile integer:: arglen real(kind=dp) :: temp_box_bd(6) call get_command_argument(2, infile, arglen) if (arglen == 0 ) stop "Missing calc option in mode calc" call get_in_file(infile) call read_in(1, (/0.0_dp, 0.0_dp, 0.0_dp /), temp_box_bd) call grow_box(temp_box_bd) call get_command_argument(3, calc_opt, arglen) if (arglen == 0 ) stop "Missing calc option in mode calc" arg_pos = 4 end subroutine parse subroutine calc_tot_virial !Calculate the the total box pressure in GPa integer :: i, j, ibasis, inod real(kind=dp) :: avg_virial(6) !First check to make sure that the virial was set for the atoms/elements if(.not.vflag) then print *, "Virial data has not been sent/may not be available with your current input file " stop 3 end if !Sum the atom virials calculated = 0 do i = 1, atom_num do j = 1, 6 calculated(j) = calculated(j) - virial_atom(j, i) end do end do !Sum the nodal virials do i = 1, ele_num do inod = 1, ng_node(lat_ele(i)) do ibasis = 1, basisnum(lat_ele(i)) do j = 1,6 calculated(j) = calculated(j) - virial_node(j,ibasis,inod,i)*(size_ele(i)**3)/ng_node(lat_ele(i)) end do end do end do end do !Now calculate the total box virial and convert to GPa calculated = evtogp(calculated)/box_volume() print *, "Total virial is calculated as : (v11, v22, v33, v32, v31, v21)" print *, calculated end subroutine calc_tot_virial subroutine calc_tot_energy integer :: i, inod, ibasis, j calculated=0 !Sum atom energies do i = 1, atom_num calculated(1) = calculated(1) + energy_atom(i) end do !Sum element energies do i =1, ele_num do inod=1, ng_node(lat_ele(i)) do ibasis=1, basisnum(lat_ele(i)) calculated(1) = calculated(1) + energy_node(ibasis, inod, i)*(size_ele(i)**3)/ng_node(lat_ele(i)) end do end do end do print *, 'Total energy in eV is:' print *, calculated(1) end subroutine calc_tot_energy end module mode_calc