DAMASK_EICMD/src/CLI.f90

375 lines
16 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
!> @author Jaeyong Jung, Max-Planck-Institut für Eisenforschung GmbH
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Parse command line interface for PETSc-based solvers
!--------------------------------------------------------------------------------------------------
#define PETSC_MINOR_MIN 12
2023-04-13 23:43:01 +05:30
#define PETSC_MINOR_MAX 19
2022-04-24 08:13:44 +05:30
module CLI
2020-09-19 14:20:32 +05:30
use, intrinsic :: ISO_fortran_env
use PETScSys
2019-05-11 15:40:23 +05:30
use prec
use parallelization
2019-05-11 15:40:23 +05:30
use system_routines
use IO
2020-06-26 15:14:17 +05:30
implicit none(type,external)
2019-03-06 20:17:48 +05:30
private
integer, public, protected :: &
CLI_restartInc = 0 !< Increment at which calculation starts
character(len=:), allocatable, public, protected :: &
CLI_geomFile, & !< parameter given for geometry file
CLI_loadFile, & !< parameter given for load case file
CLI_materialFile
2019-03-06 20:17:48 +05:30
public :: &
getSolverJobName, &
CLI_init
2019-05-09 11:55:56 +05:30
contains
!--------------------------------------------------------------------------------------------------
!> @brief initializes the solver by interpreting the command line arguments. Also writes
!! information on computation to screen
!--------------------------------------------------------------------------------------------------
subroutine CLI_init()
#include <petsc/finclude/petscsys.h>
#if PETSC_VERSION_MAJOR!=3 || PETSC_VERSION_MINOR<PETSC_MINOR_MIN || PETSC_VERSION_MINOR>PETSC_MINOR_MAX
2021-04-25 11:36:52 +05:30
-- UNSUPPORTED PETSc VERSION --- UNSUPPORTED PETSc VERSION --- UNSUPPORTED PETSc VERSION ---
#endif
character(len=:), allocatable :: &
commandLine, & !< command line call as string
arg, & !< individual argument
loadCaseArg, & !< -l argument given to the executable
geometryArg, & !< -g argument given to the executable
materialArg, & !< -m argument given to the executable
workingDirArg !< -w argument given to the executable
2019-03-06 20:17:48 +05:30
integer :: &
2019-03-24 15:18:46 +05:30
stat, &
2020-09-13 13:49:38 +05:30
i
2019-03-06 20:17:48 +05:30
integer, dimension(8) :: &
dateAndTime
2020-05-14 10:29:30 +05:30
integer :: err
2019-03-06 20:17:48 +05:30
external :: &
quit
workingDirArg = getCWD()
2022-04-24 08:13:44 +05:30
print'(/,1x,a)', '<<<+- CLI init -+>>>'
2020-09-13 13:49:38 +05:30
2020-09-12 19:12:03 +05:30
! http://patorjk.com/software/taag/#p=display&f=Lean&t=DAMASK%203
#ifdef DEBUG
print*, achar(27)//'[31m'
print'(a,/)', ' debug version - debug version - debug version - debug version - debug version'
2020-09-12 19:12:03 +05:30
#else
print*, achar(27)//'[94m'
2020-09-12 19:12:03 +05:30
#endif
print*, ' _/_/_/ _/_/ _/ _/ _/_/ _/_/_/ _/ _/ _/_/_/'
print*, ' _/ _/ _/ _/ _/_/ _/_/ _/ _/ _/ _/ _/ _/'
print*, ' _/ _/ _/_/_/_/ _/ _/ _/ _/_/_/_/ _/_/ _/_/ _/_/'
print*, ' _/ _/ _/ _/ _/ _/ _/ _/ _/ _/ _/ _/'
print*, ' _/_/_/ _/ _/ _/ _/ _/ _/ _/_/_/ _/ _/ _/_/_/'
#if defined(GRID)
print*, ' Grid solver'
2021-07-08 21:26:49 +05:30
#elif defined(MESH)
print*, ' Mesh solver'
#endif
2020-09-12 19:12:03 +05:30
#ifdef DEBUG
print'(/,a)', ' debug version - debug version - debug version - debug version - debug version'
2020-09-12 19:12:03 +05:30
#endif
print*, achar(27)//'[0m'
2019-03-13 10:46:31 +05:30
2021-03-18 20:06:40 +05:30
print*, 'F. Roters et al., Computational Materials Science 158:420478, 2019'
2020-09-19 11:50:29 +05:30
print*, 'https://doi.org/10.1016/j.commatsci.2018.04.030'
print'(/,a)', ' Version: '//DAMASKVERSION
2019-03-06 20:17:48 +05:30
print'(/,a)', ' Compiled with: '//compiler_version()
print'(a)', ' Compiled on: '//CMAKE_SYSTEM
print'(a)', ' Compiler options: '//compiler_options()
2019-02-16 03:24:38 +05:30
! https://github.com/jeffhammond/HPCInfo/blob/master/docs/Preprocessor-Macros.md
print'(/,a)', ' Compiled on: '//__DATE__//' at '//__TIME__
print'(/,a,i0,a,i0,a,i0)', &
' PETSc version: ',PETSC_VERSION_MAJOR,'.',PETSC_VERSION_MINOR,'.',PETSC_VERSION_SUBMINOR
call date_and_time(values = dateAndTime)
print'(/,a,2(i2.2,a),i4.4)', ' Date: ',dateAndTime(3),'/',dateAndTime(2),'/', dateAndTime(1)
print'(a,2(i2.2,a),i2.2)', ' Time: ',dateAndTime(5),':', dateAndTime(6),':', dateAndTime(7)
2019-03-06 20:17:48 +05:30
2019-03-24 15:18:46 +05:30
do i = 1, command_argument_count()
arg = getArg(i)
2019-03-24 15:18:46 +05:30
select case(trim(arg)) ! extract key
2019-03-06 20:17:48 +05:30
case ('-h','--help')
2020-11-16 02:46:44 +05:30
print'(/,a)',' #######################################################################'
print'(a)', ' DAMASK Command Line Interface:'
2020-11-16 02:46:44 +05:30
print'(a)', ' Düsseldorf Advanced Material Simulation Kit with PETSc-based solvers'
print'(a,/)',' #######################################################################'
print'(a,/)',' Valid command line switches:'
print'(a)', ' --geom (-g, --geometry)'
print'(a)', ' --load (-l, --loadcase)'
print'(a)', ' --material (-m, --materialConfig)'
print'(a)', ' --workingdir (-w, --wd, --workingdirectory)'
print'(a)', ' --restart (-r, --rs)'
print'(a)', ' --help (-h)'
print'(/,a)',' -----------------------------------------------------------------------'
print'(a)', ' Mandatory arguments:'
print'(/,a)',' --geom PathToGeomFile/NameOfGeom'
print'(a)', ' Specifies the location of the geometry definition file.'
print'(/,a)',' --load PathToLoadFile/NameOfLoadFile'
print'(a)', ' Specifies the location of the load case definition file.'
print'(/,a)',' --material PathToMaterialConfigurationFile/NameOfMaterialConfigurationFile'
print'(a)', ' Specifies the location of the material configuration file.'
print'(/,a)',' -----------------------------------------------------------------------'
print'(a)', ' Optional arguments:'
print'(/,a)',' --workingdirectory PathToWorkingDirectory'
print'(a)', ' Specifies the working directory and overwrites the default ./'
2021-07-27 20:14:52 +05:30
print'(a)', ' Make sure the file "material.yaml" exists in the working'
print'(a)', ' directory.'
2021-07-27 20:14:52 +05:30
print'(a)', ' For further configuration place "numerics.yaml"'
print'(a)',' in that directory.'
print'(/,a)',' --restart N'
print'(a)', ' Reads in increment N and continues with calculating'
print'(a)', ' increment N+1, N+2, ... based on this.'
print'(a)', ' Appends to existing results file'
print'(a)', ' "NameOfGeom_NameOfLoadFile.hdf5".'
print'(a)', ' Works only if the restart information for increment N'
print'(a)', ' is available in the working directory.'
print'(/,a)',' -----------------------------------------------------------------------'
print'(a)', ' Help:'
print'(/,a)',' --help'
print'(a,/)',' Prints this message and exits'
2019-03-06 20:17:48 +05:30
call quit(0) ! normal Termination
case ('-l', '--load', '--loadcase')
loadCaseArg = getArg(i+1)
2019-03-06 20:17:48 +05:30
case ('-g', '--geom', '--geometry')
geometryArg = getArg(i+1)
case ('-m', '--material', '--materialConfig')
materialArg = getArg(i+1)
case ('-w', '--wd', '--workingdir', '--workingdirectory')
workingDirArg = getArg(i+1)
2019-03-06 20:17:48 +05:30
case ('-r', '--rs', '--restart')
arg = getArg(i+1)
read(arg,*,iostat=stat) CLI_restartInc
if (CLI_restartInc < 0 .or. stat /=0) then
print'(/,a)', ' ERROR: Could not parse restart increment: '//trim(arg)
2019-03-24 15:18:46 +05:30
call quit(1)
2022-06-09 02:36:01 +05:30
end if
2019-03-06 20:17:48 +05:30
end select
2020-05-14 10:29:30 +05:30
if (err /= 0) call quit(1)
2022-06-09 02:36:01 +05:30
end do
2019-03-06 20:17:48 +05:30
if (.not. all([allocated(loadcaseArg),allocated(geometryArg),allocated(materialArg)])) then
print'(/,a)', ' ERROR: Please specify geometry AND load case AND material configuration (-h for help)'
2019-03-06 20:17:48 +05:30
call quit(1)
2022-06-09 02:36:01 +05:30
end if
2019-03-06 20:17:48 +05:30
call setWorkingDirectory(trim(workingDirArg))
CLI_geomFile = getPathRelCWD(geometryArg,'geometry')
CLI_loadFile = getPathRelCWD(loadCaseArg,'load case')
CLI_materialFile = getPathRelCWD(materialArg,'material configuration')
2019-03-06 20:17:48 +05:30
commandLine = getArg(0)
print'(/,a)', ' Host name: '//getHostName()
print'(a)', ' User name: '//getUserName()
2019-03-06 20:17:48 +05:30
print'(/a/)', ' Command line call: '//trim(commandLine)
print'(a)', ' Working directory: '//IO_glueDiffering(getCWD(),workingDirArg)
print'(a)', ' Geometry: '//IO_glueDiffering(CLI_geomFile,geometryArg)
print'(a)', ' Load case: '//IO_glueDiffering(CLI_loadFile,loadCaseArg)
print'(a)', ' Material config: '//IO_glueDiffering(CLI_materialFile,materialArg)
print'(a)', ' Solver job name: '//getSolverJobName()
if (CLI_restartInc > 0) &
print'(a,i6.6)', ' Restart from increment: ', CLI_restartInc
2019-03-06 20:17:48 +05:30
contains
!------------------------------------------------------------------------------------------------
!> @brief Get argument from command line.
!------------------------------------------------------------------------------------------------
function getArg(n)
integer, intent(in) :: n !< number of the argument
character(len=:), allocatable :: getArg
integer :: l,err
allocate(character(len=0)::getArg)
call get_command_argument(n,getArg,length=l)
deallocate(getArg)
allocate(character(len=l)::getArg)
call get_command_argument(n,getArg,status=err)
if (err /= 0) call quit(1)
end function getArg
end subroutine CLI_init
2018-06-18 19:49:03 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief extract working directory from given argument or from location of geometry file,
!! possibly converting relative arguments to absolut path
!--------------------------------------------------------------------------------------------------
subroutine setWorkingDirectory(workingDirectoryArg)
2019-03-06 20:17:48 +05:30
character(len=*), intent(in) :: workingDirectoryArg !< working directory argument
character(len=:), allocatable :: workingDirectory
2019-03-06 20:17:48 +05:30
logical :: error
external :: quit
absolutePath: if (workingDirectoryArg(1:1) == '/') then
workingDirectory = workingDirectoryArg
else absolutePath
workingDirectory = getCWD()
workingDirectory = trim(workingDirectory)//'/'//workingDirectoryArg
2022-06-09 02:36:01 +05:30
end if absolutePath
2019-03-06 20:17:48 +05:30
workingDirectory = trim(normpath(workingDirectory))
2019-03-06 20:17:48 +05:30
error = setCWD(trim(workingDirectory))
2022-12-07 22:59:03 +05:30
if (error) then
print*, 'ERROR: Invalid Working directory: '//trim(workingDirectory)
2019-03-06 20:17:48 +05:30
call quit(1)
2022-06-09 02:36:01 +05:30
end if
end subroutine setWorkingDirectory
!--------------------------------------------------------------------------------------------------
!> @brief solver job name (no extension) as combination of geometry and load case name
!--------------------------------------------------------------------------------------------------
function getSolverJobName()
character(len=:), allocatable :: getSolverJobName
2019-03-06 20:17:48 +05:30
integer :: posExt,posSep
posExt = scan(CLI_geomFile,'.',back=.true.)
posSep = scan(CLI_geomFile,'/',back=.true.)
getSolverJobName = CLI_geomFile(posSep+1:posExt-1)
posExt = scan(CLI_loadFile,'.',back=.true.)
posSep = scan(CLI_loadFile,'/',back=.true.)
getSolverJobName = getSolverJobName//'_'//CLI_loadFile(posSep+1:posExt-1)
end function getSolverJobName
!--------------------------------------------------------------------------------------------------
!> @brief Translate path as relative to CWD and check for existence.
!--------------------------------------------------------------------------------------------------
function getPathRelCWD(path,fileType)
character(len=:), allocatable :: getPathRelCWD
character(len=*), intent(in) :: path
character(len=*), intent(in) :: fileType
logical :: file_exists
external :: quit
getPathRelCWD = trim(path)
if (scan(getPathRelCWD,'/') /= 1) getPathRelCWD = getCWD()//'/'//trim(getPathRelCWD)
getPathRelCWD = trim(relpath(getPathRelCWD,getCWD()))
inquire(file=getPathRelCWD, exist=file_exists)
if (.not. file_exists) then
print*, 'ERROR: '//fileType//' file does not exist: '//trim(getPathRelCWD)
call quit(1)
end if
end function getPathRelCWD
!--------------------------------------------------------------------------------------------------
!> @brief Remove ../, /./, and // from path.
!> @details Works only if absolute path is given.
!--------------------------------------------------------------------------------------------------
function normpath(path)
2020-01-26 17:58:12 +05:30
character(len=*), intent(in) :: path
character(len=:), allocatable :: normpath
2019-03-06 20:17:48 +05:30
integer :: i,j,k,l
!--------------------------------------------------------------------------------------------------
! remove /./ from path
normpath = trim(path)
l = len_trim(normpath)
2019-03-06 20:17:48 +05:30
do i = l,3,-1
if (normpath(i-2:i) == '/./') normpath(i-1:l) = normpath(i+1:l)//' '
2022-06-09 02:36:01 +05:30
end do
!--------------------------------------------------------------------------------------------------
! remove // from path
l = len_trim(normpath)
2019-03-06 20:17:48 +05:30
do i = l,2,-1
if (normpath(i-1:i) == '//') normpath(i-1:l) = normpath(i:l)//' '
2022-06-09 02:36:01 +05:30
end do
!--------------------------------------------------------------------------------------------------
! remove ../ and corresponding directory from path
l = len_trim(normpath)
i = index(normpath(i:l),'../')
2019-03-06 20:17:48 +05:30
j = 0
do while (i > j)
j = scan(normpath(1:i-2),'/',back=.true.)
normpath(j+1:l) = normpath(i+3:l)//repeat(' ',2+i-j)
if (normpath(j+1:j+1) == '/') then !search for '//' that appear in case of XXX/../../XXX
k = len_trim(normpath)
normpath(j+1:k-1) = normpath(j+2:k)
normpath(k:k) = ' '
2022-06-09 02:36:01 +05:30
end if
i = j+index(normpath(j+1:l),'../')
2022-06-09 02:36:01 +05:30
end do
if (len_trim(normpath) == 0) normpath = '/'
normpath = trim(normpath)
2020-01-26 17:58:12 +05:30
end function normpath
2019-03-06 20:17:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Determine relative path.
!--------------------------------------------------------------------------------------------------
function relpath(path,start)
character(len=*), intent(in) :: start,path
character(len=:), allocatable :: relpath
character(len=:), allocatable :: start_cleaned,path_cleaned
2019-03-06 20:17:48 +05:30
integer :: i,posLastCommonSlash,remainingSlashes
2019-03-06 20:17:48 +05:30
posLastCommonSlash = 0
remainingSlashes = 0
start_cleaned = normpath(trim(start)//'/')
path_cleaned = normpath(path)
do i = 1, min(len_trim(start_cleaned),len_trim(path_cleaned))
if (start_cleaned(i:i) /= path_cleaned(i:i)) exit
if (start_cleaned(i:i) == '/') posLastCommonSlash = i
2022-06-09 02:36:01 +05:30
end do
do i = posLastCommonSlash+1,len_trim(start_cleaned)
if (start_cleaned(i:i) == '/') remainingSlashes = remainingSlashes + 1
2022-06-09 02:36:01 +05:30
end do
relpath = repeat('..'//'/',remainingSlashes)//path_cleaned(posLastCommonSlash+1:len_trim(path_cleaned))
end function relpath
2022-04-24 08:13:44 +05:30
end module CLI