2011-04-07 12:50:28 +05:30
! Copyright 2011 Max-Planck-Institut für Eisenforschung GmbH
2011-04-04 19:39:54 +05:30
!
! This file is part of DAMASK,
2012-03-06 20:22:48 +05:30
! the Düsseldorf Advanced Material Simulation Kit.
2011-04-04 19:39:54 +05:30
!
! DAMASK is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! DAMASK is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
!
2012-03-06 20:22:48 +05:30
!--------------------------------------------------------------------------------------------------
2010-09-23 13:35:50 +05:30
!* $Id$
2012-03-06 20:22:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Interfacing between the spectral solver and the material subroutines provided
!! by DAMASK
!--------------------------------------------------------------------------------------------------
module DAMASK_interface
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
implicit none
2012-03-06 20:22:48 +05:30
private
2012-03-09 01:55:28 +05:30
character ( len = 64 ) , parameter , public :: FEsolver = 'Spectral' !< Keyword for spectral solver
character ( len = 5 ) , parameter , public :: inputFileExtension = '.geom' !< File extension for geometry description
character ( len = 4 ) , parameter , public :: logFileExtension = '.log' !< Dummy variable as the spectral solver has no log
character ( len = 1024 ) , private :: geometryParameter , & !< Interpretated parameter given at command line
loadcaseParameter !< Interpretated parameter given at command line
2012-03-06 20:22:48 +05:30
2012-03-09 01:55:28 +05:30
public :: getSolverWorkingDirectoryName , & !< Interpretated parameter given at command line
2012-03-06 20:22:48 +05:30
getSolverJobName , &
getLoadCase , &
getLoadCaseName , &
getModelName , &
2012-04-11 22:58:08 +05:30
DAMASK_interface_init
2012-03-06 20:22:48 +05:30
private :: rectifyPath , &
makeRelativePath , &
getPathSep
contains
!--------------------------------------------------------------------------------------------------
2012-03-09 01:55:28 +05:30
!> @brief initializes the solver by interpreting the command line arguments. Also writes
2012-03-06 20:22:48 +05:30
!! information on computation on screen
!--------------------------------------------------------------------------------------------------
2012-04-11 22:58:08 +05:30
subroutine DAMASK_interface_init ( loadcaseParameterIn , geometryParameterIn )
2012-03-06 20:22:48 +05:30
use , intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
use prec , only : pInt
2011-11-04 01:02:11 +05:30
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
implicit none
2012-04-11 22:58:08 +05:30
character ( len = 1024 ) , optional , intent ( in ) :: &
loadcaseParameterIn , &
geometryParameterIn
character ( len = 1024 ) :: &
commandLine , & !< command line call as string
hostName , & !< name of computer
userName !< name of user calling the executable
integer :: &
i , &
start , &
length
integer , dimension ( 8 ) :: &
dateAndTime ! type default integer
write ( 6 , * )
write ( 6 , * ) '<<<+- DAMASK_spectral_interface init -+>>>'
write ( 6 , * ) '$Id$'
2012-02-01 00:48:55 +05:30
#include "compilation_info.f90"
2012-04-11 22:58:08 +05:30
if ( present ( loadcaseParameterIn ) . and . present ( geometryParameterIn ) ) then ! both mandatory parameters given in function call
geometryParameter = geometryParameterIn
loadcaseParameter = loadcaseParameterIn
commandLine = 'n/a'
start = 3_pInt
else if ( . not . ( present ( loadcaseParameterIn ) . and . present ( geometryParameterIn ) ) ) then ! none parameters given in function call, trying to get them from comman line
call get_command ( commandLine )
call date_and_time ( values = dateAndTime )
do i = 1 , len ( commandLine ) ! remove capitals
if ( 64 < iachar ( commandLine ( i : i ) ) . and . iachar ( commandLine ( i : i ) ) < 91 ) &
commandLine ( i : i ) = achar ( iachar ( commandLine ( i : i ) ) + 32 )
enddo
if ( index ( commandLine , ' -h ' , . true . ) > 0 . or . index ( commandLine , ' --help ' , . true . ) > 0 ) then ! search for ' -h ' or '--help'
write ( 6 , '(a)' ) '#############################################################'
write ( 6 , '(a)' ) 'DAMASK spectral:'
write ( 6 , '(a)' ) 'The spectral method boundary value problem solver for'
write ( 6 , '(a)' ) 'the Duesseldorf Advanced Material Simulation Kit'
write ( 6 , '(a)' ) '#############################################################'
write ( 6 , '(a)' ) 'Valid command line switches:'
write ( 6 , '(a)' ) ' --geom (-g, --geometry)'
write ( 6 , '(a)' ) ' --load (-l, --loadcase)'
write ( 6 , '(a)' ) ' --restart (-r)'
write ( 6 , '(a)' ) ' --help (-h)'
write ( 6 , '(a)' ) ' '
write ( 6 , '(a)' ) 'Mandatory Arguments:'
write ( 6 , '(a)' ) ' --load PathToLoadFile/NameOfLoadFile.load'
write ( 6 , '(a)' ) ' "PathToGeomFile" will be the working directory.'
write ( 6 , '(a)' ) ' Make sure the file "material.config" exists in the working'
write ( 6 , '(a)' ) ' directory'
write ( 6 , '(a)' ) ' For further configuration place "numerics.config"'
write ( 6 , '(a)' ) ' and "numerics.config" in that directory.'
write ( 6 , '(a)' ) ' '
write ( 6 , '(a)' ) ' --geom PathToGeomFile/NameOfGeom.geom'
write ( 6 , '(a)' ) ' '
write ( 6 , '(a)' ) 'Optional Argument:'
write ( 6 , '(a)' ) ' --restart XX'
write ( 6 , '(a)' ) ' Reads in total increment No. XX-1 and continous to'
write ( 6 , '(a)' ) ' calculate total increment No. XX.'
write ( 6 , '(a)' ) ' Attention: Overwrites existing results file '
write ( 6 , '(a)' ) ' "NameOfGeom_NameOfLoadFile_spectralOut".'
write ( 6 , '(a)' ) ' Works only if the restart information for total increment'
write ( 6 , '(a)' ) ' No. XX-1 is available in the working directory.'
write ( 6 , '(a)' ) 'Help:'
write ( 6 , '(a)' ) ' --help'
write ( 6 , '(a)' ) ' Prints this message and exits'
write ( 6 , '(a)' ) ' '
call quit ( 1_pInt ) ! normal Termination
endif
if ( . not . ( command_argument_count ( ) == 4 . or . command_argument_count ( ) == 6 ) ) then ! check for correct number of given arguments (no --help)
write ( 6 , '(a)' ) 'Wrong Nr. of Arguments. Run DAMASK_spectral.exe --help' ! Could not find valid keyword (position 0 +3). Functions from IO.f90 are not available
call quit ( 100_pInt ) ! abnormal termination
endif
start = index ( commandLine , '-g' , . true . ) + 3 ! search for '-g' and jump to first char of geometry
if ( index ( commandLine , '--geom' , . true . ) > 0 ) then ! if '--geom' is found, use that (contains '-g')
start = index ( commandLine , '--geom' , . true . ) + 7
endif
if ( index ( commandLine , '--geometry' , . true . ) > 0 ) then ! again, now searching for --geometry'
start = index ( commandLine , '--geometry' , . true . ) + 11
endif
if ( start == 3_pInt ) then ! Could not find valid keyword (position 0 +3). Functions from IO.f90 are not available
write ( 6 , '(a)' ) 'No Geometry specified'
call quit ( 100_pInt ) ! abnormal termination
endif
length = index ( commandLine ( start : len ( commandLine ) ) , ' ' , . false . )
call get_command ( commandLine ) ! may contain capitals
geometryParameter = '' ! should be empty
geometryParameter ( 1 : length ) = commandLine ( start : start + length )
do i = 1 , len ( commandLine ) ! remove capitals
if ( 64 < iachar ( commandLine ( i : i ) ) . and . iachar ( commandLine ( i : i ) ) < 91 ) commandLine ( i : i ) &
= achar ( iachar ( commandLine ( i : i ) ) + 32 )
enddo
start = index ( commandLine , '-l' , . true . ) + 3 ! search for '-l' and jump forward iby 3 to given name
if ( index ( commandLine , '--load' , . true . ) > 0 ) then ! if '--load' is found, use that (contains '-l')
start = index ( commandLine , '--load' , . true . ) + 7
endif
if ( index ( commandLine , '--loadcase' , . true . ) > 0 ) then ! again, now searching for --loadcase'
start = index ( commandLine , '--loadcase' , . true . ) + 11
endif
if ( start == 3_pInt ) then ! Could not find valid keyword (position 0 +3). Functions from IO.f90 are not available
write ( 6 , '(a)' ) 'No Loadcase specified'
call quit ( 100_pInt ) ! abnormal termination
endif
length = index ( commandLine ( start : len ( commandLine ) ) , ' ' , . false . )
call get_command ( commandLine ) ! may contain capitals
loadcaseParameter = '' ! should be empty
loadcaseParameter ( 1 : length ) = commandLine ( start : start + length )
do i = 1 , len ( commandLine ) ! remove capitals
if ( 64 < iachar ( commandLine ( i : i ) ) . and . iachar ( commandLine ( i : i ) ) < 91 ) commandLine ( i : i ) &
= achar ( iachar ( commandLine ( i : i ) ) + 32 )
enddo
start = index ( commandLine , '-r' , . true . ) + 3 ! search for '-r' and jump forward iby 3 to given name
if ( index ( commandLine , '--restart' , . true . ) > 0 ) then ! if '--restart' is found, use that (contains '-l')
start = index ( commandLine , '--restart' , . true . ) + 7
endif
length = index ( commandLine ( start : len ( commandLine ) ) , ' ' , . false . )
call get_command ( commandLine ) ! may contain capitals
else
write ( 6 , '(a)' ) 'Wrong Nr. of Arguments!' ! Function call with wrong No of arguments
call quit ( 100_pInt )
2012-02-21 21:34:16 +05:30
endif
2012-01-30 19:22:41 +05:30
call GET_ENVIRONMENT_VARIABLE ( 'HOST' , hostName )
call GET_ENVIRONMENT_VARIABLE ( 'USER' , userName )
2012-03-06 20:22:48 +05:30
write ( 6 , '(a,2(i2.2,a),i4.4)' ) ' Date: ' , dateAndTime ( 3 ) , '/' , &
dateAndTime ( 2 ) , '/' , &
dateAndTime ( 1 )
write ( 6 , '(a,2(i2.2,a),i2.2)' ) ' Time: ' , dateAndTime ( 5 ) , ':' , &
dateAndTime ( 6 ) , ':' , &
dateAndTime ( 7 )
2012-01-30 19:22:41 +05:30
write ( 6 , * ) 'Host Name: ' , trim ( hostName )
write ( 6 , * ) 'User Name: ' , trim ( userName )
2012-02-21 21:34:16 +05:30
write ( 6 , * ) 'Path Separator: ' , getPathSep ( )
2012-01-30 19:22:41 +05:30
write ( 6 , * ) 'Command line call: ' , trim ( commandLine )
2011-11-04 01:02:11 +05:30
write ( 6 , * ) 'Geometry Parameter: ' , trim ( geometryParameter )
write ( 6 , * ) 'Loadcase Parameter: ' , trim ( loadcaseParameter )
2012-01-30 19:22:41 +05:30
if ( start / = 3_pInt ) write ( 6 , * ) 'Restart Parameter: ' , trim ( commandLine ( start : start + length ) )
2011-11-04 01:02:11 +05:30
2012-03-06 20:22:48 +05:30
end subroutine DAMASK_interface_init
2011-11-04 01:02:11 +05:30
2012-03-06 20:22:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief extract working directory from loadcase file possibly based on current working dir
!--------------------------------------------------------------------------------------------------
2012-03-09 01:55:28 +05:30
character ( len = 1024 ) function getSolverWorkingDirectoryName ( )
2011-11-04 01:02:11 +05:30
implicit none
2012-03-09 01:55:28 +05:30
character ( len = 1024 ) :: cwd
character :: pathSep
2012-02-21 21:34:16 +05:30
pathSep = getPathSep ( )
2011-11-04 01:02:11 +05:30
2012-02-21 21:34:16 +05:30
if ( geometryParameter ( 1 : 1 ) == pathSep ) then ! absolute path given as command line argument
2011-11-04 01:02:11 +05:30
getSolverWorkingDirectoryName = geometryParameter ( 1 : scan ( geometryParameter , pathSep , 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
else
call getcwd ( cwd )
2012-02-21 21:34:16 +05:30
getSolverWorkingDirectoryName = trim ( cwd ) / / pathSep / / geometryParameter ( 1 : scan ( geometryParameter , pathSep , 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
endif
getSolverWorkingDirectoryName = rectifyPath ( getSolverWorkingDirectoryName )
2011-10-18 14:55:17 +05:30
2012-03-06 20:22:48 +05:30
end function getSolverWorkingDirectoryName
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
!--------------------------------------------------------------------------------------------------
!> @brief basename of geometry file from command line arguments
!--------------------------------------------------------------------------------------------------
character ( len = 1024 ) 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
2012-03-06 20:22:48 +05:30
implicit none
2011-02-21 20:07:38 +05:30
getSolverJobName = trim ( getModelName ( ) ) / / '_' / / trim ( getLoadCase ( ) )
2011-10-18 14:55:17 +05:30
2012-03-06 20:22:48 +05:30
end function getSolverJobName
2011-02-21 20:07:38 +05:30
2012-03-06 20:22:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief basename of geometry file from command line arguments
!--------------------------------------------------------------------------------------------------
character ( len = 1024 ) function getModelName ( )
2011-02-21 20:07:38 +05:30
use prec , only : pInt
implicit none
2012-03-06 20:22:48 +05:30
character ( len = 1024 ) :: cwd
2012-02-16 00:28:38 +05:30
integer :: posExt , posSep
2012-02-21 21:34:16 +05:30
character :: pathSep
pathSep = getPathSep ( )
2011-11-04 01:02:11 +05:30
posExt = scan ( geometryParameter , '.' , back = . true . )
posSep = scan ( geometryParameter , pathSep , 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
2012-02-21 21:34:16 +05:30
if ( posExt < = posSep ) posExt = len_trim ( geometryParameter ) + 1 ! no extension present
getModelName = geometryParameter ( 1 : posExt - 1_pInt ) ! path to geometry file (excl. extension)
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-02-21 21:34:16 +05:30
if ( scan ( getModelName , pathSep ) / = 1 ) then ! relative path given as command line argument
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
call getcwd ( cwd )
2011-02-21 20:07:38 +05:30
getModelName = rectifyPath ( trim ( cwd ) / / '/' / / getModelName )
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
else
2011-02-21 20:07:38 +05:30
getModelName = rectifyPath ( getModelName )
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
endif
2011-02-21 20:07:38 +05:30
getModelName = makeRelativePath ( getSolverWorkingDirectoryName ( ) , &
getModelName )
2011-10-18 14:55:17 +05:30
2012-03-06 20:22:48 +05:30
end function getModelName
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
!--------------------------------------------------------------------------------------------------
!> @brief name of load case file exluding extension
!--------------------------------------------------------------------------------------------------
character ( len = 1024 ) function getLoadCase ( )
2011-02-07 20:05:42 +05:30
2012-03-06 20:22:48 +05:30
implicit none
2012-02-16 00:28:38 +05:30
integer :: posExt , posSep
2012-02-21 21:34:16 +05:30
character :: pathSep
2011-02-07 20:05:42 +05:30
2012-02-21 21:34:16 +05:30
pathSep = getPathSep ( )
2011-11-04 01:02:11 +05:30
posExt = scan ( loadcaseParameter , '.' , back = . true . )
posSep = scan ( loadcaseParameter , pathSep , back = . true . )
2011-02-07 20:05:42 +05:30
2012-03-06 20:22:48 +05:30
if ( posExt < = posSep ) posExt = len_trim ( loadcaseParameter ) + 1 ! no extension present
getLoadCase = loadcaseParameter ( posSep + 1 : posExt - 1 ) ! name of load case file exluding extension
2011-02-07 20:05:42 +05:30
2012-03-06 20:22:48 +05:30
end function getLoadCase
2011-02-07 20:05:42 +05:30
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-03-06 20:22:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief relative path of loadcase from command line arguments
!--------------------------------------------------------------------------------------------------
character ( len = 1024 ) function getLoadcaseName ( )
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
implicit none
2012-03-06 20:22:48 +05:30
character ( len = 1024 ) :: cwd
2012-02-16 00:28:38 +05:30
integer :: posExt = 0 , posSep
2012-02-21 21:34:16 +05:30
character :: pathSep
pathSep = getPathSep ( )
2011-11-04 01:02:11 +05:30
getLoadcaseName = loadcaseParameter
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
posExt = scan ( getLoadcaseName , '.' , back = . true . )
posSep = scan ( getLoadcaseName , pathSep , back = . true . )
2012-03-06 20:22:48 +05:30
if ( posExt < = posSep ) getLoadcaseName = trim ( getLoadcaseName ) / / ( '.load' ) ! no extension present
if ( scan ( getLoadcaseName , pathSep ) / = 1 ) then ! relative path given as command line argument
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
call getcwd ( cwd )
2012-02-21 21:34:16 +05:30
getLoadcaseName = rectifyPath ( trim ( cwd ) / / pathSep / / getLoadcaseName )
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
else
getLoadcaseName = rectifyPath ( getLoadcaseName )
endif
getLoadcaseName = makeRelativePath ( getSolverWorkingDirectoryName ( ) , &
getLoadcaseName )
2012-03-06 20:22:48 +05:30
end function getLoadcaseName
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-03-06 20:22:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief remove ../ and ./ from 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
function rectifyPath ( path )
implicit none
2012-02-16 00:28:38 +05:30
character ( len = * ) :: path
character ( len = len_trim ( path ) ) :: rectifyPath
2012-02-21 21:34:16 +05:30
character :: pathSep
2012-02-16 00:28:38 +05:30
integer :: i , j , k , l !no pInt
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-02-21 21:34:16 +05:30
pathSep = getPathSep ( )
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
!remove ./ from path
l = len_trim ( path )
rectifyPath = path
2012-02-16 00:28:38 +05:30
do i = l , 3 , - 1
2012-02-21 21:34:16 +05:30
if ( rectifyPath ( i - 1 : i ) == '.' / / pathSep . and . rectifyPath ( i - 2 : i - 2 ) / = '.' ) &
2012-02-16 00:28:38 +05:30
rectifyPath ( i - 1 : l ) = rectifyPath ( i + 1 : 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
enddo
!remove ../ and corresponding directory from rectifyPath
l = len_trim ( rectifyPath )
2012-02-21 21:34:16 +05:30
i = index ( rectifyPath ( i : l ) , '..' / / pathSep )
2012-02-16 00:28:38 +05:30
j = 0
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
do while ( i > j )
2012-02-21 21:34:16 +05:30
j = scan ( rectifyPath ( 1 : i - 2 ) , pathSep , back = . true . )
2012-02-16 00:28:38 +05:30
rectifyPath ( j + 1 : l ) = rectifyPath ( i + 3 : l ) / / repeat ( ' ' , 2 + i - j )
2012-03-06 20:22:48 +05:30
if ( rectifyPath ( j + 1 : j + 1 ) == pathSep ) then !search for '//' that appear in case of XXX/../../XXX
2012-01-13 20:52:42 +05:30
k = len_trim ( rectifyPath )
2012-02-16 00:28:38 +05:30
rectifyPath ( j + 1 : k - 1 ) = rectifyPath ( j + 2 : k )
2012-01-13 20:52:42 +05:30
rectifyPath ( k : k ) = ' '
endif
2012-02-21 21:34:16 +05:30
i = j + index ( rectifyPath ( j + 1 : l ) , '..' / / pathSep )
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
enddo
2012-02-21 21:34:16 +05:30
if ( len_trim ( rectifyPath ) == 0 ) rectifyPath = pathSep
2011-08-01 23:40:55 +05:30
2012-03-06 20:22:48 +05:30
end function rectifyPath
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-03-06 20:22:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief relative path from absolute a to absolute b
!--------------------------------------------------------------------------------------------------
character ( len = 1024 ) function makeRelativePath ( a , b )
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
implicit none
character ( len = * ) :: a , b
2012-02-21 21:34:16 +05:30
character :: pathSep
2012-02-16 00:28:38 +05:30
integer :: i , posLastCommonSlash , remainingSlashes !no pInt
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-02-21 21:34:16 +05:30
pathSep = getPathSep ( )
2012-02-16 00:28:38 +05:30
posLastCommonSlash = 0
remainingSlashes = 0
2012-02-21 21:34:16 +05:30
2012-02-16 00:28:38 +05:30
do i = 1 , min ( 1024 , len_trim ( a ) , len_trim ( b ) )
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
if ( a ( i : i ) / = b ( i : i ) ) exit
2012-02-21 21:34:16 +05:30
if ( a ( i : i ) == pathSep ) posLastCommonSlash = i
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
enddo
2012-02-16 00:28:38 +05:30
do i = posLastCommonSlash + 1 , len_trim ( a )
2012-02-21 21:34:16 +05:30
if ( a ( i : i ) == pathSep ) remainingSlashes = remainingSlashes + 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
enddo
2012-02-21 21:34:16 +05:30
makeRelativePath = repeat ( '..' / / pathSep , remainingSlashes ) / / b ( posLastCommonSlash + 1 : len_trim ( b ) )
2011-08-01 23:40:55 +05:30
2012-03-06 20:22:48 +05:30
end function makeRelativePath
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-02-21 21:34:16 +05:30
2012-03-06 20:22:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief counting / and \ in $PATH System variable the character occuring more often is assumed
!! to be the path separator
!--------------------------------------------------------------------------------------------------
character function getPathSep ( )
2012-02-21 21:34:16 +05:30
use prec , only : pInt
2012-03-06 20:22:48 +05:30
2012-02-21 21:34:16 +05:30
implicit none
character ( len = 2048 ) path
integer ( pInt ) :: backslash = 0_pInt , slash = 0_pInt
integer :: i
call get_environment_variable ( 'PATH' , path )
do i = 1 , len ( trim ( path ) )
if ( path ( i : i ) == '/' ) slash = slash + 1_pInt
if ( path ( i : i ) == ' \ ' ) backslash = backslash + 1_pInt
enddo
if ( backslash > slash ) then
getPathSep = ' \ '
else
getPathSep = '/'
endif
end function
2012-03-06 20:22:48 +05:30
end module