DAMASK_EICMD/src/DAMASK_interface.f90

470 lines
20 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 Interfacing between the PETSc-based solvers and the material subroutines provided
!! by DAMASK
!> @details Interfacing between the PETSc-based solvers and the material subroutines provided
2020-06-26 15:14:17 +05:30
!> by DAMASK. Interpreting the command line arguments to get load case, geometry file,
2018-08-05 14:11:01 +05:30
!> and working directory.
!--------------------------------------------------------------------------------------------------
2019-04-03 11:55:42 +05:30
#define PETSC_MAJOR 3
#define PETSC_MINOR_MIN 12
2020-10-06 10:42:04 +05:30
#define PETSC_MINOR_MAX 14
module DAMASK_interface
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
2020-06-26 15:14:17 +05:30
2019-03-06 20:17:48 +05:30
implicit none
private
logical, volatile, public, protected :: &
interface_SIGTERM, & !< termination signal
interface_SIGUSR1, & !< 1. user-defined signal
interface_SIGUSR2 !< 2. user-defined signal
integer, public, protected :: &
2019-03-06 20:17:48 +05:30
interface_restartInc = 0 !< Increment at which calculation starts
character(len=:), allocatable, public, protected :: &
interface_geomFile, & !< parameter given for geometry file
interface_loadFile !< parameter given for load case file
2019-03-06 20:17:48 +05:30
public :: &
getSolverJobName, &
DAMASK_interface_init, &
interface_setSIGTERM, &
interface_setSIGUSR1, &
interface_setSIGUSR2
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
!--------------------------------------------------------------------------------------------------
2019-05-03 09:51:43 +05:30
subroutine DAMASK_interface_init
#include <petsc/finclude/petscsys.h>
#if PETSC_VERSION_MAJOR!=3 || PETSC_VERSION_MINOR<PETSC_MINOR_MIN || PETSC_VERSION_MINOR>PETSC_MINOR_MAX
2018-08-20 21:27:15 +05:30
===================================================================================================
-- WRONG PETSc VERSION --- WRONG PETSc VERSION --- WRONG PETSc VERSION --- WRONG PETSc VERSION --
2018-08-20 21:27:15 +05:30
===================================================================================================
#endif
character(len=pPathLen*3+pStringLen) :: &
commandLine !< command line call as string
character(len=pPathLen) :: &
2019-03-24 15:18:46 +05:30
arg, & !< individual argument
loadCaseArg = '', & !< -l argument given to the executable
2019-03-06 20:17:48 +05:30
geometryArg = '', & !< -g 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
print'(/,a)', ' <<<+- DAMASK_interface init -+>>>'
2019-03-06 20:17:48 +05:30
2020-09-29 12:52:15 +05:30
if(worldrank == 0) open(OUTPUT_UNIT, encoding='UTF-8') ! for special characters in output
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*, ' _/_/_/ _/ _/ _/ _/ _/ _/ _/_/_/ _/ _/ _/_/_/'
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
2020-09-19 11:50:29 +05:30
print*, 'Roters et al., Computational Materials Science 158:420478, 2019'
print*, 'https://doi.org/10.1016/j.commatsci.2018.04.030'
print'(/,a)', ' Version: '//DAMASKVERSION
2019-03-06 20:17:48 +05:30
! https://github.com/jeffhammond/HPCInfo/blob/master/docs/Preprocessor-Macros.md
#if defined(__PGI)
print'(/,a,i4.4,a,i8.8)', ' Compiled with PGI fortran version :', __PGIC__,&
'.', __PGIC_MINOR__
#else
print'(/,a)', ' Compiled with: '//compiler_version()
print'(a)', ' Compiler options: '//compiler_options()
2019-02-16 03:24:38 +05:30
#endif
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()
2020-05-14 10:29:30 +05:30
call get_command_argument(i,arg,status=err)
if (err /= 0) call quit(1)
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)', ' --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)',' -----------------------------------------------------------------------'
print'(a)', ' Optional arguments:'
print'(/,a)',' --workingdirectory PathToWorkingDirectory'
print'(a)', ' Specifies the working directory and overwrites the default ./'
print'(a)', ' Make sure the file "material.config" exists in the working'
print'(a)', ' directory.'
print'(a)', ' For further configuration place "numerics.config"'
print'(a)',' and "debug.config" in that directory.'
print'(/,a)',' --restart N'
print'(a)', ' Reads in increment N and continues with calculating'
print'(a)', ' increment N+1 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')
2020-05-16 22:02:30 +05:30
call get_command_argument(i+1,loadCaseArg,status=err)
2019-03-06 20:17:48 +05:30
case ('-g', '--geom', '--geometry')
2020-05-16 22:02:30 +05:30
call get_command_argument(i+1,geometryArg,status=err)
case ('-w', '--wd', '--workingdir', '--workingdirectory')
2020-05-16 22:02:30 +05:30
call get_command_argument(i+1,workingDirArg,status=err)
2019-03-06 20:17:48 +05:30
case ('-r', '--rs', '--restart')
2020-05-16 22:02:30 +05:30
call get_command_argument(i+1,arg,status=err)
2019-03-24 15:18:46 +05:30
read(arg,*,iostat=stat) interface_restartInc
if (interface_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)
2019-03-06 20:17:48 +05:30
endif
end select
2020-05-14 10:29:30 +05:30
if (err /= 0) call quit(1)
2019-03-06 20:17:48 +05:30
enddo
if (len_trim(loadcaseArg) == 0 .or. len_trim(geometryArg) == 0) then
print'(/,a)', ' ERROR: Please specify geometry AND load case (-h for help)'
2019-03-06 20:17:48 +05:30
call quit(1)
endif
if (len_trim(workingDirArg) > 0) call setWorkingDirectory(trim(workingDirArg))
interface_geomFile = getGeometryFile(geometryArg)
interface_loadFile = getLoadCaseFile(loadCaseArg)
2019-03-06 20:17:48 +05:30
2019-03-24 15:18:46 +05:30
call get_command(commandLine)
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)
2020-01-26 23:01:56 +05:30
if (len_trim(workingDirArg) > 0) &
print'(a)', ' Working dir argument: '//trim(workingDirArg)
print'(a)', ' Geometry argument: '//trim(geometryArg)
print'(a)', ' Loadcase argument: '//trim(loadcaseArg)
print'(/,a)', ' Working directory: '//getCWD()
print'(a)', ' Geometry file: '//interface_geomFile
print'(a)', ' Loadcase file: '//interface_loadFile
print'(a)', ' Solver job name: '//getSolverJobName()
2019-03-06 20:17:48 +05:30
if (interface_restartInc > 0) &
print'(a,i6.6)', ' Restart from increment: ', interface_restartInc
2019-03-06 20:17:48 +05:30
2020-12-14 13:44:03 +05:30
call signalterm_c(c_funloc(catchSIGTERM))
call signalusr1_c(c_funloc(catchSIGUSR1))
call signalusr2_c(c_funloc(catchSIGUSR2))
call interface_setSIGTERM(.false.)
call interface_setSIGUSR1(.false.)
call interface_setSIGUSR2(.false.)
end subroutine DAMASK_interface_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
endif absolutePath
workingDirectory = trim(rectifyPath(workingDirectory))
error = setCWD(trim(workingDirectory))
if(error) then
print*, 'ERROR: Invalid Working directory: '//trim(workingDirectory)
2019-03-06 20:17:48 +05:30
call quit(1)
endif
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(interface_geomFile,'.',back=.true.)
posSep = scan(interface_geomFile,'/',back=.true.)
getSolverJobName = interface_geomFile(posSep+1:posExt-1)
posExt = scan(interface_loadFile,'.',back=.true.)
posSep = scan(interface_loadFile,'/',back=.true.)
getSolverJobName = getSolverJobName//'_'//interface_loadFile(posSep+1:posExt-1)
end function getSolverJobName
!--------------------------------------------------------------------------------------------------
!> @brief basename of geometry file with extension from command line arguments
!--------------------------------------------------------------------------------------------------
function getGeometryFile(geometryParameter)
character(len=:), allocatable :: getGeometryFile
character(len=*), intent(in) :: geometryParameter
logical :: file_exists
external :: quit
2019-03-06 20:17:48 +05:30
getGeometryFile = trim(geometryParameter)
if (scan(getGeometryFile,'/') /= 1) getGeometryFile = getCWD()//'/'//trim(getGeometryFile)
getGeometryFile = trim(makeRelativePath(getCWD(), getGeometryFile))
inquire(file=getGeometryFile, exist=file_exists)
2019-03-06 20:17:48 +05:30
if (.not. file_exists) then
print*, 'ERROR: Geometry file does not exists: '//trim(getGeometryFile)
2019-03-06 20:17:48 +05:30
call quit(1)
endif
end function getGeometryFile
!--------------------------------------------------------------------------------------------------
2020-06-26 15:14:17 +05:30
!> @brief relative path of load case from command line arguments
!--------------------------------------------------------------------------------------------------
function getLoadCaseFile(loadCaseParameter)
character(len=:), allocatable :: getLoadCaseFile
character(len=*), intent(in) :: loadCaseParameter
logical :: file_exists
external :: quit
2019-03-06 20:17:48 +05:30
getLoadCaseFile = trim(loadCaseParameter)
if (scan(getLoadCaseFile,'/') /= 1) getLoadCaseFile = getCWD()//'/'//trim(getLoadCaseFile)
getLoadCaseFile = trim(makeRelativePath(getCWD(), getLoadCaseFile))
inquire(file=getLoadCaseFile, exist=file_exists)
2019-03-06 20:17:48 +05:30
if (.not. file_exists) then
print*, 'ERROR: Load case file does not exists: '//trim(getLoadCaseFile)
2019-03-06 20:17:48 +05:30
call quit(1)
endif
2018-09-15 18:24:56 +05:30
end function getLoadCaseFile
!--------------------------------------------------------------------------------------------------
!> @brief remove ../, /./, and // from path.
!> @details works only if absolute path is given
!--------------------------------------------------------------------------------------------------
function rectifyPath(path)
2020-01-26 17:58:12 +05:30
character(len=*), intent(in) :: path
character(len=:), allocatable :: rectifyPath
2019-03-06 20:17:48 +05:30
integer :: i,j,k,l
!--------------------------------------------------------------------------------------------------
! remove /./ from path
2019-03-06 20:17:48 +05:30
rectifyPath = trim(path)
l = len_trim(rectifyPath)
do i = l,3,-1
if (rectifyPath(i-2:i) == '/./') rectifyPath(i-1:l) = rectifyPath(i+1:l)//' '
enddo
!--------------------------------------------------------------------------------------------------
! remove // from path
2019-03-06 20:17:48 +05:30
l = len_trim(rectifyPath)
do i = l,2,-1
if (rectifyPath(i-1:i) == '//') rectifyPath(i-1:l) = rectifyPath(i:l)//' '
enddo
!--------------------------------------------------------------------------------------------------
! remove ../ and corresponding directory from rectifyPath
2019-03-06 20:17:48 +05:30
l = len_trim(rectifyPath)
i = index(rectifyPath(i:l),'../')
j = 0
do while (i > j)
j = scan(rectifyPath(1:i-2),'/',back=.true.)
rectifyPath(j+1:l) = rectifyPath(i+3:l)//repeat(' ',2+i-j)
if (rectifyPath(j+1:j+1) == '/') then !search for '//' that appear in case of XXX/../../XXX
k = len_trim(rectifyPath)
rectifyPath(j+1:k-1) = rectifyPath(j+2:k)
rectifyPath(k:k) = ' '
endif
i = j+index(rectifyPath(j+1:l),'../')
enddo
if(len_trim(rectifyPath) == 0) rectifyPath = '/'
2020-01-26 17:58:12 +05:30
rectifyPath = trim(rectifyPath)
end function rectifyPath
2019-03-06 20:17:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Determine relative path from absolute a to absolute b
!--------------------------------------------------------------------------------------------------
2020-01-26 17:58:12 +05:30
function makeRelativePath(a,b)
character(len=*), intent(in) :: a,b
character(len=pPathLen) :: a_cleaned,b_cleaned
2020-01-26 17:58:12 +05:30
character(len=:), allocatable :: makeRelativePath
2019-03-06 20:17:48 +05:30
integer :: i,posLastCommonSlash,remainingSlashes
2019-03-06 20:17:48 +05:30
posLastCommonSlash = 0
remainingSlashes = 0
a_cleaned = rectifyPath(trim(a)//'/')
b_cleaned = rectifyPath(b)
2020-09-19 14:26:41 +05:30
do i = 1, min(len_trim(a_cleaned),len_trim(rectifyPath(b_cleaned)))
2019-03-06 20:17:48 +05:30
if (a_cleaned(i:i) /= b_cleaned(i:i)) exit
if (a_cleaned(i:i) == '/') posLastCommonSlash = i
enddo
do i = posLastCommonSlash+1,len_trim(a_cleaned)
if (a_cleaned(i:i) == '/') remainingSlashes = remainingSlashes + 1
enddo
2019-03-06 20:17:48 +05:30
makeRelativePath = repeat('..'//'/',remainingSlashes)//b_cleaned(posLastCommonSlash+1:len_trim(b_cleaned))
end function makeRelativePath
2019-03-06 20:17:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Set global variable interface_SIGTERM to .true.
!> @details This function can be registered to catch signals send to the executable.
!--------------------------------------------------------------------------------------------------
subroutine catchSIGTERM(signal) bind(C)
integer(C_INT), value :: signal
2021-01-18 02:26:19 +05:30
print'(a,i0)', ' received signal ',signal
call interface_setSIGTERM(.true.)
end subroutine catchSIGTERM
!--------------------------------------------------------------------------------------------------
2021-01-18 02:26:19 +05:30
!> @brief Set global variable interface_SIGUSR1 to .true.
!> @details This function can be registered to catch signals send to the executable.
!--------------------------------------------------------------------------------------------------
2021-01-18 02:26:19 +05:30
subroutine catchSIGUSR1(signal) bind(C)
2021-01-18 02:26:19 +05:30
integer(C_INT), value :: signal
2021-01-18 02:26:19 +05:30
print'(a,i0)', ' received signal ',signal
call interface_setSIGUSR1(.true.)
end subroutine catchSIGUSR1
!--------------------------------------------------------------------------------------------------
2021-01-18 02:26:19 +05:30
!> @brief Set global variable interface_SIGUSR2 to .true.
!> @details This function can be registered to catch signals send to the executable.
!--------------------------------------------------------------------------------------------------
2021-01-18 02:26:19 +05:30
subroutine catchSIGUSR2(signal) bind(C)
2019-03-06 20:17:48 +05:30
integer(C_INT), value :: signal
2021-01-18 02:26:19 +05:30
print'(a,i0,a)', ' received signal ',signal
call interface_setSIGUSR2(.true.)
end subroutine catchSIGUSR2
!--------------------------------------------------------------------------------------------------
2021-01-18 02:26:19 +05:30
!> @brief Set global variable interface_SIGTERM.
!--------------------------------------------------------------------------------------------------
2021-01-18 02:26:19 +05:30
subroutine interface_setSIGTERM(state)
logical, intent(in) :: state
2021-01-18 02:26:19 +05:30
interface_SIGTERM = state
print*, 'set SIGTERM to',state
end subroutine interface_setSIGTERM
2019-03-06 20:17:48 +05:30
!--------------------------------------------------------------------------------------------------
2021-01-18 02:26:19 +05:30
!> @brief Set global variable interface_SIGUSR.
!--------------------------------------------------------------------------------------------------
2021-01-18 02:26:19 +05:30
subroutine interface_setSIGUSR1(state)
2021-01-18 02:26:19 +05:30
logical, intent(in) :: state
2019-03-06 20:17:48 +05:30
2021-01-18 02:26:19 +05:30
interface_SIGUSR1 = state
print*, 'set SIGUSR1 to',state
end subroutine interface_setSIGUSR1
!--------------------------------------------------------------------------------------------------
!> @brief Set global variable interface_SIGUSR2.
!--------------------------------------------------------------------------------------------------
subroutine interface_setSIGUSR2(state)
logical, intent(in) :: state
2021-01-18 02:26:19 +05:30
interface_SIGUSR2 = state
2021-01-18 02:26:19 +05:30
print*, 'set SIGUSR2 to',state
end subroutine interface_setSIGUSR2
2019-02-16 03:24:38 +05:30
end module