2016-09-21 01:08:18 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2022-04-23 18:22:10 +05:30
|
|
|
|
!> @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
|
2014-10-10 18:38:34 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-12-18 19:49:04 +05:30
|
|
|
|
#define PETSC_MINOR_MIN 12
|
2023-04-13 23:43:01 +05:30
|
|
|
|
#define PETSC_MINOR_MAX 19
|
2019-05-28 15:36:21 +05:30
|
|
|
|
|
2022-04-24 08:13:44 +05:30
|
|
|
|
module CLI
|
2020-09-19 14:20:32 +05:30
|
|
|
|
use, intrinsic :: ISO_fortran_env
|
2020-01-23 14:05:41 +05:30
|
|
|
|
|
2019-05-28 15:36:21 +05:30
|
|
|
|
use PETScSys
|
|
|
|
|
|
2019-05-11 15:40:23 +05:30
|
|
|
|
use prec
|
2020-09-12 19:36:33 +05:30
|
|
|
|
use parallelization
|
2019-05-11 15:40:23 +05:30
|
|
|
|
use system_routines
|
2023-06-16 21:39:53 +05:30
|
|
|
|
use IO
|
2020-06-26 15:14:17 +05:30
|
|
|
|
|
2022-06-22 02:16:54 +05:30
|
|
|
|
implicit none(type,external)
|
2019-03-06 20:17:48 +05:30
|
|
|
|
private
|
2020-01-23 14:05:41 +05:30
|
|
|
|
integer, public, protected :: &
|
2022-04-23 18:22:10 +05:30
|
|
|
|
CLI_restartInc = 0 !< Increment at which calculation starts
|
2020-01-23 14:05:41 +05:30
|
|
|
|
character(len=:), allocatable, public, protected :: &
|
2022-04-23 18:22:10 +05:30
|
|
|
|
CLI_geomFile, & !< parameter given for geometry file
|
2023-06-05 19:37:47 +05:30
|
|
|
|
CLI_loadFile, & !< parameter given for load case file
|
|
|
|
|
CLI_materialFile
|
2019-03-06 20:17:48 +05:30
|
|
|
|
|
|
|
|
|
public :: &
|
|
|
|
|
getSolverJobName, &
|
2022-04-23 18:22:10 +05:30
|
|
|
|
CLI_init
|
2019-05-09 11:55:56 +05:30
|
|
|
|
|
2012-03-06 20:22:48 +05:30
|
|
|
|
contains
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
|
!> @brief initializes the solver by interpreting the command line arguments. Also writes
|
2012-06-15 21:40:21 +05:30
|
|
|
|
!! information on computation to screen
|
2012-03-06 20:22:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-23 02:24:20 +05:30
|
|
|
|
subroutine CLI_init()
|
2018-05-17 15:34:21 +05:30
|
|
|
|
#include <petsc/finclude/petscsys.h>
|
2018-10-15 08:33:53 +05:30
|
|
|
|
|
2019-04-03 18:19:16 +05:30
|
|
|
|
#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 ---
|
2018-05-17 15:34:21 +05:30
|
|
|
|
#endif
|
2018-10-15 08:33:53 +05:30
|
|
|
|
|
2023-06-23 02:14:19 +05:30
|
|
|
|
character(len=:), allocatable :: &
|
2023-06-23 02:24:20 +05:30
|
|
|
|
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
|
|
|
|
|
external :: &
|
|
|
|
|
quit
|
|
|
|
|
|
|
|
|
|
|
2023-06-16 21:39:53 +05:30
|
|
|
|
workingDirArg = getCWD()
|
|
|
|
|
|
2023-06-28 15:53:00 +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
|
2023-06-28 15:53:00 +05:30
|
|
|
|
print '(a)', achar(27)//'[31m'
|
|
|
|
|
print '(1x,a,/)', 'debug version - debug version - debug version - debug version - debug version'
|
2020-09-12 19:12:03 +05:30
|
|
|
|
#else
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(a)', achar(27)//'[94m'
|
2020-09-12 19:12:03 +05:30
|
|
|
|
#endif
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(1x,a)', ' _/_/_/ _/_/ _/ _/ _/_/ _/_/_/ _/ _/ _/_/_/'
|
|
|
|
|
print '(1x,a)', ' _/ _/ _/ _/ _/_/ _/_/ _/ _/ _/ _/ _/ _/'
|
|
|
|
|
print '(1x,a)', ' _/ _/ _/_/_/_/ _/ _/ _/ _/_/_/_/ _/_/ _/_/ _/_/'
|
|
|
|
|
print '(1x,a)', ' _/ _/ _/ _/ _/ _/ _/ _/ _/ _/ _/ _/'
|
|
|
|
|
print '(1x,a)', '_/_/_/ _/ _/ _/ _/ _/ _/ _/_/_/ _/ _/ _/_/_/'
|
2021-07-04 20:31:24 +05:30
|
|
|
|
#if defined(GRID)
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(1x,a)', 'Grid solver'
|
2021-07-08 21:26:49 +05:30
|
|
|
|
#elif defined(MESH)
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(1x,a)', 'Mesh solver'
|
2021-07-04 20:31:24 +05:30
|
|
|
|
#endif
|
2020-09-12 19:12:03 +05:30
|
|
|
|
#ifdef DEBUG
|
2023-06-28 15:53:00 +05:30
|
|
|
|
print '(/,1x,a)', 'debug version - debug version - debug version - debug version - debug version'
|
2020-09-12 19:12:03 +05:30
|
|
|
|
#endif
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(a)', achar(27)//'[0m'
|
2019-03-13 10:46:31 +05:30
|
|
|
|
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(1x,a)', 'F. Roters et al., Computational Materials Science 158:420–478, 2019'
|
|
|
|
|
print '(1x,a)', 'https://doi.org/10.1016/j.commatsci.2018.04.030'
|
2019-03-09 15:19:56 +05:30
|
|
|
|
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(/,1x,a)', 'Version: '//DAMASKVERSION
|
2019-03-06 20:17:48 +05:30
|
|
|
|
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(/,1x,a)', 'Compiled with: '//compiler_version()
|
|
|
|
|
print '(1x,a)', 'Compiled on: '//CMAKE_SYSTEM
|
|
|
|
|
print '(1x,a)', 'Compiler options: '//compiler_options()
|
2019-02-16 03:24:38 +05:30
|
|
|
|
|
2021-05-19 17:09:08 +05:30
|
|
|
|
! https://github.com/jeffhammond/HPCInfo/blob/master/docs/Preprocessor-Macros.md
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(/,1x,a)', 'Compiled on: '//__DATE__//' at '//__TIME__
|
2019-03-09 15:19:56 +05:30
|
|
|
|
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(/,1x,a,1x,i0,a,i0,a,i0)', &
|
|
|
|
|
'PETSc version:',PETSC_VERSION_MAJOR,'.',PETSC_VERSION_MINOR,'.',PETSC_VERSION_SUBMINOR
|
2020-11-14 19:06:10 +05:30
|
|
|
|
|
2019-03-09 15:19:56 +05:30
|
|
|
|
call date_and_time(values = dateAndTime)
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(/,1x,a,1x,2(i2.2,a),i4.4)', 'Date:',dateAndTime(3),'/',dateAndTime(2),'/',dateAndTime(1)
|
|
|
|
|
print '(1x,a,1x,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()
|
2023-06-23 02:14:19 +05:30
|
|
|
|
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')
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(/,1x,a)','#######################################################################'
|
|
|
|
|
print '(1x,a)', 'DAMASK Command Line Interface:'
|
|
|
|
|
print '(1x,a)', 'Düsseldorf Advanced Material Simulation Kit with PETSc-based solvers'
|
|
|
|
|
print '(1x,a,/)','#######################################################################'
|
|
|
|
|
print '(1x,a,/)','Valid command line switches:'
|
|
|
|
|
print '(1x,a)', ' --geom (-g, --geometry)'
|
|
|
|
|
print '(1x,a)', ' --load (-l, --loadcase)'
|
|
|
|
|
print '(1x,a)', ' --material (-m, --materialconfig)'
|
|
|
|
|
print '(1x,a)', ' --workingdir (-w, --wd, --workingdirectory)'
|
|
|
|
|
print '(1x,a)', ' --restart (-r, --rs)'
|
|
|
|
|
print '(1x,a)', ' --help (-h)'
|
|
|
|
|
print '(/,1x,a)','-----------------------------------------------------------------------'
|
|
|
|
|
print '(1x,a)', 'Mandatory arguments:'
|
|
|
|
|
print '(/,1x,a)',' --geom PathToGeomFile/NameOfGeom'
|
|
|
|
|
print '(1x,a)', ' Specifies the location of the geometry definition file.'
|
|
|
|
|
print '(/,1x,a)',' --load PathToLoadFile/NameOfLoadFile'
|
|
|
|
|
print '(1x,a)', ' Specifies the location of the load case definition file.'
|
|
|
|
|
print '(/,1x,a)',' --material PathToMaterialConfigurationFile/NameOfMaterialConfigurationFile'
|
|
|
|
|
print '(1x,a)', ' Specifies the location of the material configuration file.'
|
|
|
|
|
print '(/,1x,a)','-----------------------------------------------------------------------'
|
|
|
|
|
print '(1x,a)', 'Optional arguments:'
|
|
|
|
|
print '(/,1x,a)',' --workingdirectory PathToWorkingDirectory'
|
|
|
|
|
print '(1x,a)', ' Specifies the base directory of relative paths.'
|
|
|
|
|
print '(/,1x,a)',' --restart N'
|
|
|
|
|
print '(1x,a)', ' Reads in increment N and continues with calculating'
|
|
|
|
|
print '(1x,a)', ' increment N+1, N+2, ... based on this.'
|
|
|
|
|
print '(1x,a)', ' Appends to existing results file'
|
|
|
|
|
print '(1x,a)', ' "NameOfGeom_NameOfLoadFile_NameOfMaterialConfigurationFile.hdf5".'
|
|
|
|
|
print '(1x,a)', ' Works only if the restart information for increment N'
|
|
|
|
|
print '(1x,a)', ' is available in the base directory.'
|
|
|
|
|
print '(/,1x,a)','-----------------------------------------------------------------------'
|
|
|
|
|
print '(1x,a)', 'Help:'
|
|
|
|
|
print '(/,1x,a)',' --help'
|
|
|
|
|
print '(1x,a,/)',' Prints this message and exits'
|
2019-03-06 20:17:48 +05:30
|
|
|
|
call quit(0) ! normal Termination
|
|
|
|
|
case ('-l', '--load', '--loadcase')
|
2023-06-23 02:14:19 +05:30
|
|
|
|
loadCaseArg = getArg(i+1)
|
2019-03-06 20:17:48 +05:30
|
|
|
|
case ('-g', '--geom', '--geometry')
|
2023-06-23 02:14:19 +05:30
|
|
|
|
geometryArg = getArg(i+1)
|
2023-06-23 02:49:36 +05:30
|
|
|
|
case ('-m', '--material', '--materialconfig')
|
2023-06-23 02:14:19 +05:30
|
|
|
|
materialArg = getArg(i+1)
|
2020-04-26 12:06:16 +05:30
|
|
|
|
case ('-w', '--wd', '--workingdir', '--workingdirectory')
|
2023-06-23 02:14:19 +05:30
|
|
|
|
workingDirArg = getArg(i+1)
|
2019-03-06 20:17:48 +05:30
|
|
|
|
case ('-r', '--rs', '--restart')
|
2023-06-23 02:14:19 +05:30
|
|
|
|
arg = getArg(i+1)
|
2022-04-23 18:22:10 +05:30
|
|
|
|
read(arg,*,iostat=stat) CLI_restartInc
|
2023-06-23 08:29:44 +05:30
|
|
|
|
if (CLI_restartInc < 0 .or. stat /= 0) then
|
|
|
|
|
print'(/,1x,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
|
2022-06-09 02:36:01 +05:30
|
|
|
|
end do
|
2019-03-06 20:17:48 +05:30
|
|
|
|
|
2023-06-23 02:14:19 +05:30
|
|
|
|
if (.not. all([allocated(loadcaseArg),allocated(geometryArg),allocated(materialArg)])) then
|
2023-06-28 15:53:00 +05:30
|
|
|
|
print '(/,1x,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
|
|
|
|
|
2023-06-16 21:39:53 +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
|
|
|
|
|
2023-06-23 08:29:44 +05:30
|
|
|
|
commandLine = getArg(-1)
|
2019-03-06 20:17:48 +05:30
|
|
|
|
|
2023-06-28 15:53:00 +05:30
|
|
|
|
print '(/,1x,a)', 'Host name: '//getHostName()
|
|
|
|
|
print '(1x,a)', 'User name: '//getUserName()
|
2023-06-23 08:29:44 +05:30
|
|
|
|
|
2023-06-28 15:53:00 +05:30
|
|
|
|
print '(/,1x,a,/)', 'Command line call: '//trim(commandLine)
|
|
|
|
|
print '(1x,a)', 'Working directory: '//IO_glueDiffering(getCWD(),workingDirArg)
|
|
|
|
|
print '(1x,a)', 'Geometry: '//IO_glueDiffering(CLI_geomFile,geometryArg)
|
|
|
|
|
print '(1x,a)', 'Load case: '//IO_glueDiffering(CLI_loadFile,loadCaseArg)
|
|
|
|
|
print '(1x,a)', 'Material config: '//IO_glueDiffering(CLI_materialFile,materialArg)
|
|
|
|
|
print '(1x,a)', 'Solver job name: '//getSolverJobName()
|
2022-04-23 18:22:10 +05:30
|
|
|
|
if (CLI_restartInc > 0) &
|
2023-06-28 15:53:00 +05:30
|
|
|
|
print '(1x,a,i6.6)', 'Restart from increment: ', CLI_restartInc
|
2019-03-06 20:17:48 +05:30
|
|
|
|
|
2023-06-23 02:14:19 +05:30
|
|
|
|
|
2023-06-23 12:24:37 +05:30
|
|
|
|
end subroutine CLI_init
|
2023-06-23 02:14:19 +05:30
|
|
|
|
|
2023-06-23 12:24:37 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
|
!> @brief Get argument from command line.
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
|
function getArg(n)
|
2023-06-23 02:14:19 +05:30
|
|
|
|
|
2023-06-23 12:24:37 +05:30
|
|
|
|
integer, intent(in) :: n !< number of the argument
|
|
|
|
|
character(len=:), allocatable :: getArg
|
2023-06-23 02:14:19 +05:30
|
|
|
|
|
2023-06-23 12:24:37 +05:30
|
|
|
|
integer :: l,err
|
|
|
|
|
external :: quit
|
2023-06-23 02:14:19 +05:30
|
|
|
|
|
|
|
|
|
|
2023-06-23 12:24:37 +05:30
|
|
|
|
allocate(character(len=0)::getArg)
|
|
|
|
|
if (n<0) then
|
|
|
|
|
call get_command(getArg, length=l)
|
|
|
|
|
else
|
|
|
|
|
call get_command_argument(n,getArg,length=l)
|
|
|
|
|
endif
|
|
|
|
|
deallocate(getArg)
|
|
|
|
|
allocate(character(len=l)::getArg)
|
|
|
|
|
if (n<0) then
|
|
|
|
|
call get_command(getArg, status=err)
|
|
|
|
|
else
|
|
|
|
|
call get_command_argument(n,getArg,status=err)
|
|
|
|
|
endif
|
|
|
|
|
if (err /= 0) call quit(1)
|
2023-06-23 02:14:19 +05:30
|
|
|
|
|
2023-06-23 12:24:37 +05:30
|
|
|
|
end function getArg
|
2011-11-04 01:02:11 +05:30
|
|
|
|
|
2013-01-02 22:32:12 +05:30
|
|
|
|
|
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
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-08-21 02:44:34 +05:30
|
|
|
|
subroutine setWorkingDirectory(workingDirectoryArg)
|
2019-03-06 20:17:48 +05:30
|
|
|
|
|
2020-11-14 19:06:10 +05:30
|
|
|
|
character(len=*), intent(in) :: workingDirectoryArg !< working directory argument
|
|
|
|
|
character(len=:), allocatable :: workingDirectory
|
2023-06-23 12:24:37 +05:30
|
|
|
|
|
2019-03-06 20:17:48 +05:30
|
|
|
|
logical :: error
|
|
|
|
|
external :: quit
|
|
|
|
|
|
2023-06-23 12:24:37 +05:30
|
|
|
|
|
2019-03-06 20:17:48 +05:30
|
|
|
|
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
|
|
|
|
|
2023-06-23 02:24:20 +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
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(1x,a)', '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
|
2013-01-02 22:32:12 +05:30
|
|
|
|
|
2018-08-21 02:44:34 +05:30
|
|
|
|
end subroutine setWorkingDirectory
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2011-11-04 01:02:11 +05:30
|
|
|
|
|
2012-03-06 20:22:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-06-15 21:40:21 +05:30
|
|
|
|
!> @brief solver job name (no extension) as combination of geometry and load case name
|
2012-03-06 20:22:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-01-04 22:55:59 +05:30
|
|
|
|
function getSolverJobName()
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2020-01-04 22:55:59 +05:30
|
|
|
|
character(len=:), allocatable :: getSolverJobName
|
2023-06-23 02:24:20 +05:30
|
|
|
|
|
2019-03-06 20:17:48 +05:30
|
|
|
|
integer :: posExt,posSep
|
2012-02-21 21:34:16 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
|
2022-04-23 18:22:10 +05:30
|
|
|
|
posExt = scan(CLI_geomFile,'.',back=.true.)
|
|
|
|
|
posSep = scan(CLI_geomFile,'/',back=.true.)
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2022-04-23 18:22:10 +05:30
|
|
|
|
getSolverJobName = CLI_geomFile(posSep+1:posExt-1)
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2022-04-23 18:22:10 +05:30
|
|
|
|
posExt = scan(CLI_loadFile,'.',back=.true.)
|
|
|
|
|
posSep = scan(CLI_loadFile,'/',back=.true.)
|
2012-06-15 21:40:21 +05:30
|
|
|
|
|
2022-04-23 18:22:10 +05:30
|
|
|
|
getSolverJobName = getSolverJobName//'_'//CLI_loadFile(posSep+1:posExt-1)
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
|
end function getSolverJobName
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2011-02-07 20:05:42 +05:30
|
|
|
|
|
2012-03-06 20:22:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-23 02:14:19 +05:30
|
|
|
|
!> @brief Translate path as relative to CWD and check for existence.
|
2023-06-05 19:37:47 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-16 21:39:53 +05:30
|
|
|
|
function getPathRelCWD(path,fileType)
|
2023-06-05 19:37:47 +05:30
|
|
|
|
|
2023-06-16 21:39:53 +05:30
|
|
|
|
character(len=:), allocatable :: getPathRelCWD
|
|
|
|
|
character(len=*), intent(in) :: path
|
|
|
|
|
character(len=*), intent(in) :: fileType
|
2023-06-23 02:24:20 +05:30
|
|
|
|
|
2023-06-05 19:37:47 +05:30
|
|
|
|
logical :: file_exists
|
|
|
|
|
external :: quit
|
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
|
2023-06-16 21:39:53 +05:30
|
|
|
|
getPathRelCWD = trim(path)
|
|
|
|
|
if (scan(getPathRelCWD,'/') /= 1) getPathRelCWD = getCWD()//'/'//trim(getPathRelCWD)
|
2023-06-23 02:24:20 +05:30
|
|
|
|
getPathRelCWD = trim(relpath(getPathRelCWD,getCWD()))
|
2023-06-05 19:37:47 +05:30
|
|
|
|
|
2023-06-16 21:39:53 +05:30
|
|
|
|
inquire(file=getPathRelCWD, exist=file_exists)
|
2023-06-05 19:37:47 +05:30
|
|
|
|
if (.not. file_exists) then
|
2023-06-23 08:29:44 +05:30
|
|
|
|
print '(1x,a)', 'ERROR: '//fileType//' file does not exist: '//trim(getPathRelCWD)
|
2023-06-05 19:37:47 +05:30
|
|
|
|
call quit(1)
|
|
|
|
|
end if
|
|
|
|
|
|
2023-06-16 21:39:53 +05:30
|
|
|
|
end function getPathRelCWD
|
2023-06-05 19:37:47 +05:30
|
|
|
|
|
|
|
|
|
|
2012-03-06 20:22:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-23 02:14:19 +05:30
|
|
|
|
!> @brief Remove ../, /./, and // from path.
|
|
|
|
|
!> @details Works only if absolute path is given.
|
2012-03-06 20:22:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-23 02:24:20 +05:30
|
|
|
|
function normpath(path)
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2020-01-26 17:58:12 +05:30
|
|
|
|
character(len=*), intent(in) :: path
|
2023-06-23 02:24:20 +05:30
|
|
|
|
character(len=:), allocatable :: normpath
|
|
|
|
|
|
2019-03-06 20:17:48 +05:30
|
|
|
|
integer :: i,j,k,l
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
|
2013-05-13 19:40:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
|
! remove /./ from path
|
2023-06-23 02:24:20 +05:30
|
|
|
|
normpath = trim(path)
|
|
|
|
|
l = len_trim(normpath)
|
2019-03-06 20:17:48 +05:30
|
|
|
|
do i = l,3,-1
|
2023-06-23 02:24:20 +05:30
|
|
|
|
if (normpath(i-2:i) == '/./') normpath(i-1:l) = normpath(i+1:l)//' '
|
2022-06-09 02:36:01 +05:30
|
|
|
|
end do
|
2018-07-10 13:53:21 +05:30
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
|
! remove // from path
|
2023-06-23 02:24:20 +05:30
|
|
|
|
l = len_trim(normpath)
|
2019-03-06 20:17:48 +05:30
|
|
|
|
do i = l,2,-1
|
2023-06-23 02:24:20 +05:30
|
|
|
|
if (normpath(i-1:i) == '//') normpath(i-1:l) = normpath(i:l)//' '
|
2022-06-09 02:36:01 +05:30
|
|
|
|
end do
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2013-05-13 19:40:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-23 02:24:20 +05:30
|
|
|
|
! 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)
|
2023-06-23 02:24:20 +05:30
|
|
|
|
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
|
2023-06-23 02:24:20 +05:30
|
|
|
|
i = j+index(normpath(j+1:l),'../')
|
2022-06-09 02:36:01 +05:30
|
|
|
|
end do
|
2023-06-23 02:24:20 +05:30
|
|
|
|
if (len_trim(normpath) == 0) normpath = '/'
|
2011-08-01 23:40:55 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
normpath = trim(normpath)
|
2020-01-26 17:58:12 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
end function normpath
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2019-03-06 20:17:48 +05:30
|
|
|
|
|
2012-03-06 20:22:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-23 02:24:20 +05:30
|
|
|
|
!> @brief Determine relative path.
|
2012-03-06 20:22:48 +05:30
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-23 02:24:20 +05:30
|
|
|
|
function relpath(path,start)
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
character(len=*), intent(in) :: start,path
|
|
|
|
|
character(len=:), allocatable :: relpath
|
2023-06-23 02:14:19 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
character(len=:), allocatable :: start_cleaned,path_cleaned
|
2019-03-06 20:17:48 +05:30
|
|
|
|
integer :: i,posLastCommonSlash,remainingSlashes
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2023-06-23 02:14:19 +05:30
|
|
|
|
|
2019-03-06 20:17:48 +05:30
|
|
|
|
posLastCommonSlash = 0
|
|
|
|
|
remainingSlashes = 0
|
2023-06-23 02:24:20 +05:30
|
|
|
|
start_cleaned = normpath(trim(start)//'/')
|
|
|
|
|
path_cleaned = normpath(path)
|
2012-02-21 21:34:16 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
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
|
2023-06-23 02:24:20 +05:30
|
|
|
|
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
|
2018-07-10 13:53:21 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
relpath = repeat('..'//'/',remainingSlashes)//path_cleaned(posLastCommonSlash+1:len_trim(path_cleaned))
|
2011-08-01 23:40:55 +05:30
|
|
|
|
|
2023-06-23 02:24:20 +05:30
|
|
|
|
end function relpath
|
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
|
|
|
|
|
2022-04-24 08:13:44 +05:30
|
|
|
|
end module CLI
|