module mode_merge !This module contains the code needed for merging several .mb files together use parameters use atoms use io use subroutines use elements character(len=4) :: dim integer :: in_num public contains subroutine merge(arg_pos) integer, intent(out) :: arg_pos integer :: i real(kind=dp) :: displace(3), temp_box_bd(6) !First we parse the merge command call parse_command(arg_pos) !Now loop over all files and stack them do i = 1, in_num displace(:) = 0.0_dp if ((i==1).or.(trim(adjustl(dim)) == 'none')) then call read_in(i, displace, temp_box_bd) call grow_box(temp_box_bd) else select case(trim(adjustl(dim))) case('x') displace(1) = box_bd(2) case('y') displace(2) = box_bd(4) case('z') displace(3) = box_bd(6) end select call read_in(i, displace, temp_box_bd) call grow_box(temp_box_bd) end if end do return end subroutine merge subroutine parse_command(arg_pos) integer, intent(out) :: arg_pos character(len=100) :: textholder integer :: i, stat, arglen !Get dimension to concatenate along call get_command_argument(2, dim, arglen) if (arglen == 0) STOP "Missing dim in mode_merge command" select case(trim(adjustl(dim))) case('x','y','z','none') continue case default print *, dim, " not accepted as a dimension in mode_merge" stop 3 end select !Get number of files to read in call get_command_argument(3, textholder, arglen) if (arglen == 0) STOP "Number of files to read missing in mode_merge command" read(textholder, *, iostat = stat) in_num if (stat > 0) STOP "Error reading number of files in, must be integer" !Now loop and pull out all files do i = 1, in_num call get_command_argument(3+i, textholder, arglen) if (arglen == 0) STOP "Fewer files to read in then specified" !Make sure this file is readable call get_in_file(textholder) end do !Set argpos accordingly arg_pos = 3+in_num+1 !Now options loop !Check for optional keywords do while(.true.) if(arg_pos > command_argument_count()) exit !Pull out the next argument which should either be a keyword or an option call get_command_argument(arg_pos, textholder) textholder=adjustl(textholder) arg_pos=arg_pos+1 !Choose what to based on what the option string is select case(trim(textholder)) case default !If it isn't an available option to mode merge then we just exit exit end select end do end subroutine parse_command end module mode_merge