DAMASK_EICMD/src/system_routines.f90

187 lines
5.8 KiB
Fortran
Raw Normal View History

2016-05-05 16:30:46 +05:30
!--------------------------------------------------------------------------------------------------
2020-06-26 15:14:17 +05:30
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Wrappers to C routines for system operations
2016-05-05 16:30:46 +05:30
!--------------------------------------------------------------------------------------------------
2016-03-12 01:29:14 +05:30
module system_routines
2019-05-11 01:18:43 +05:30
use, intrinsic :: ISO_C_Binding
2020-06-26 15:14:17 +05:30
use prec
implicit none
2020-06-26 15:14:17 +05:30
public :: &
signalterm_C, &
signalusr1_C, &
signalusr2_C, &
isDirectory, &
getCWD, &
getHostName, &
setCWD
2020-06-26 15:14:17 +05:30
interface
2020-06-26 15:14:17 +05:30
function isDirectory_C(path) bind(C)
use, intrinsic :: ISO_C_Binding, only: &
C_INT, &
C_CHAR
2020-01-26 16:49:36 +05:30
use prec
2020-06-26 15:14:17 +05:30
integer(C_INT) :: isDirectory_C
2020-01-26 16:49:36 +05:30
character(kind=C_CHAR), dimension(pPathLen), intent(in) :: path ! C string is an array
2020-07-25 02:14:41 +05:30
end function isDirectory_C
2020-06-26 15:14:17 +05:30
2020-01-26 16:49:36 +05:30
subroutine getCurrentWorkDir_C(path, stat) bind(C)
use, intrinsic :: ISO_C_Binding, only: &
C_INT, &
C_CHAR
2020-01-26 16:49:36 +05:30
use prec
2020-06-26 15:14:17 +05:30
2020-01-26 16:49:36 +05:30
character(kind=C_CHAR), dimension(pPathLen), intent(out) :: path ! C string is an array
integer(C_INT), intent(out) :: stat
2020-07-25 02:14:41 +05:30
end subroutine getCurrentWorkDir_C
2020-06-26 15:14:17 +05:30
subroutine getHostName_C(str, stat) bind(C)
use, intrinsic :: ISO_C_Binding, only: &
C_INT, &
C_CHAR
2020-01-26 16:49:36 +05:30
use prec
2020-06-26 15:14:17 +05:30
2020-01-26 16:49:36 +05:30
character(kind=C_CHAR), dimension(pStringLen), intent(out) :: str ! C string is an array
integer(C_INT), intent(out) :: stat
2020-07-25 02:14:41 +05:30
end subroutine getHostName_C
2020-06-26 15:14:17 +05:30
function chdir_C(path) bind(C)
use, intrinsic :: ISO_C_Binding, only: &
C_INT, &
C_CHAR
2020-01-26 16:49:36 +05:30
use prec
2020-06-26 15:14:17 +05:30
integer(C_INT) :: chdir_C
2020-01-26 16:49:36 +05:30
character(kind=C_CHAR), dimension(pPathLen), intent(in) :: path ! C string is an array
end function chdir_C
2020-06-26 15:14:17 +05:30
subroutine signalterm_C(handler) bind(C)
use, intrinsic :: ISO_C_Binding, only: &
C_FUNPTR
2020-06-26 15:14:17 +05:30
type(C_FUNPTR), intent(in), value :: handler
end subroutine signalterm_C
2020-06-26 15:14:17 +05:30
subroutine signalusr1_C(handler) bind(C)
use, intrinsic :: ISO_C_Binding, only: &
C_FUNPTR
2020-06-26 15:14:17 +05:30
type(C_FUNPTR), intent(in), value :: handler
end subroutine signalusr1_C
2020-06-26 15:14:17 +05:30
subroutine signalusr2_C(handler) bind(C)
use, intrinsic :: ISO_C_Binding, only: &
C_FUNPTR
2020-06-26 15:14:17 +05:30
type(C_FUNPTR), intent(in), value :: handler
end subroutine signalusr2_C
2020-06-26 15:14:17 +05:30
end interface
2016-03-12 01:29:14 +05:30
contains
2016-05-05 16:30:46 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief figures out if a given path is a directory (and not an ordinary file)
!--------------------------------------------------------------------------------------------------
logical function isDirectory(path)
2019-05-11 01:18:43 +05:30
character(len=*), intent(in) :: path
2020-01-26 16:49:36 +05:30
character(kind=C_CHAR), dimension(pPathLen) :: strFixedLength ! C string as array
2020-06-26 15:14:17 +05:30
integer :: i
2019-05-11 01:18:43 +05:30
strFixedLength = repeat(C_NULL_CHAR,len(strFixedLength))
do i=1,len(path) ! copy array components
strFixedLength(i)=path(i:i)
enddo
isDirectory=merge(.True.,.False.,isDirectory_C(strFixedLength) /= 0_C_INT)
2016-03-12 01:29:14 +05:30
2016-05-05 16:30:46 +05:30
end function isDirectory
2016-03-12 01:29:14 +05:30
2016-05-05 16:30:46 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief gets the current working directory
!--------------------------------------------------------------------------------------------------
function getCWD()
2020-01-26 16:49:36 +05:30
character(kind=C_CHAR), dimension(pPathLen) :: charArray ! C string is an array
character(len=:), allocatable :: getCWD
2019-05-11 01:18:43 +05:30
integer(C_INT) :: stat
integer :: i
2020-06-26 15:14:17 +05:30
2019-05-11 01:18:43 +05:30
call getCurrentWorkDir_C(charArray,stat)
2020-06-26 15:14:17 +05:30
2019-05-11 01:18:43 +05:30
if (stat /= 0_C_INT) then
getCWD = 'Error occured when getting currend working directory'
else
2020-01-26 16:49:36 +05:30
allocate(character(len=pPathLen)::getCWD)
2019-05-11 01:18:43 +05:30
arrayToString: do i=1,len(getCWD)
if (charArray(i) /= C_NULL_CHAR) then
getCWD(i:i)=charArray(i)
else
getCWD = getCWD(:i-1)
2019-05-11 01:18:43 +05:30
exit
endif
enddo arrayToString
endif
2016-03-12 01:29:14 +05:30
2016-05-05 16:30:46 +05:30
end function getCWD
2016-03-12 01:29:14 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief gets the current host name
!--------------------------------------------------------------------------------------------------
function getHostName()
2019-05-09 11:55:56 +05:30
2020-01-26 16:49:36 +05:30
character(kind=C_CHAR), dimension(pPathLen) :: charArray ! C string is an array
character(len=:), allocatable :: getHostName
2019-05-11 01:18:43 +05:30
integer(C_INT) :: stat
integer :: i
2020-06-26 15:14:17 +05:30
2019-05-11 01:18:43 +05:30
call getHostName_C(charArray,stat)
2019-05-11 01:18:43 +05:30
if (stat /= 0_C_INT) then
getHostName = 'Error occured when getting host name'
else
2020-01-26 16:49:36 +05:30
allocate(character(len=pPathLen)::getHostName)
2019-05-11 01:18:43 +05:30
arrayToString: do i=1,len(getHostName)
if (charArray(i) /= C_NULL_CHAR) then
getHostName(i:i)=charArray(i)
else
getHostName = getHostName(:i-1)
2019-05-11 01:18:43 +05:30
exit
endif
enddo arrayToString
endif
end function getHostName
2018-05-26 02:52:32 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief changes the current working directory
!--------------------------------------------------------------------------------------------------
logical function setCWD(path)
2019-05-09 11:55:56 +05:30
2019-05-11 01:18:43 +05:30
character(len=*), intent(in) :: path
2020-01-26 16:49:36 +05:30
character(kind=C_CHAR), dimension(pPathLen) :: strFixedLength ! C string is an array
2019-05-11 01:18:43 +05:30
integer :: i
2020-06-26 15:14:17 +05:30
2019-05-11 01:18:43 +05:30
strFixedLength = repeat(C_NULL_CHAR,len(strFixedLength))
do i=1,len(path) ! copy array components
strFixedLength(i)=path(i:i)
enddo
setCWD=merge(.True.,.False.,chdir_C(strFixedLength) /= 0_C_INT)
2018-05-26 02:52:32 +05:30
end function setCWD
2016-03-12 01:29:14 +05:30
end module system_routines