update
This commit is contained in:
@ -15,7 +15,7 @@
|
||||
|
||||
module TPMLib !*************************************************************************************
|
||||
!
|
||||
! TMD Library: Basic constants, types, and mathematical functions
|
||||
! Basic constants, types, and mathematical functions.
|
||||
!
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
!
|
||||
@ -41,20 +41,20 @@ implicit none
|
||||
! Physical unit constants
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
|
||||
real(c_double), parameter :: K_AMU = 1.66056E-27 ! a.m.u. (atomic mass unit, Dalton)
|
||||
real(c_double), parameter :: K_EV = 1.60217646e-19 ! eV (electron-volt)
|
||||
real(c_double), parameter :: K_AMU = 1.66056E-27 ! a.m.u. (atomic mass unit, Dalton)
|
||||
real(c_double), parameter :: K_EV = 1.60217646e-19 ! eV (electron-volt)
|
||||
|
||||
real(c_double), parameter :: K_MDLU = 1.0E-10 ! MD length unit (m)
|
||||
real(c_double), parameter :: K_MDEU = K_EV ! MD energy unit (J)
|
||||
real(c_double), parameter :: K_MDMU = K_AMU ! MD mass unit (kg)
|
||||
real(c_double), parameter :: K_MDFU = K_MDEU / K_MDLU ! MD force unit (N)
|
||||
real(c_double), parameter :: K_MDCU = K_MDEU / K_MDMU ! MD specific heat unit (J/(kg*K))
|
||||
real(c_double), parameter :: K_MDLU = 1.0E-10 ! MD length unit (m)
|
||||
real(c_double), parameter :: K_MDEU = K_EV ! MD energy unit (J)
|
||||
real(c_double), parameter :: K_MDMU = K_AMU ! MD mass unit (kg)
|
||||
real(c_double), parameter :: K_MDFU = K_MDEU / K_MDLU ! MD force unit (N)
|
||||
real(c_double), parameter :: K_MDCU = K_MDEU / K_MDMU ! MD specific heat unit (J/(kg*K))
|
||||
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
! Global variables
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
|
||||
integer(c_int) :: StdUID = 31
|
||||
integer(c_int) :: StdUID = 31
|
||||
|
||||
contains !******************************************************************************************
|
||||
|
||||
@ -62,19 +62,19 @@ contains !**********************************************************************
|
||||
! Simple mathematical functions
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
|
||||
real(c_double) function rad ( X ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double) function rad ( X ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double), intent(in) :: X
|
||||
!-------------------------------------------------------------------------------------------
|
||||
rad = X * M_PI_180
|
||||
end function rad !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
|
||||
real(c_double) function sqr ( X ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double) function sqr ( X ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double), intent(in) :: X
|
||||
!-------------------------------------------------------------------------------------------
|
||||
sqr = X * X
|
||||
end function sqr !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
|
||||
integer(c_int) function signum ( X ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
integer(c_int) function signum ( X ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double), intent(in) :: X
|
||||
!-------------------------------------------------------------------------------------------
|
||||
if ( X > 0 ) then
|
||||
@ -90,27 +90,25 @@ contains !**********************************************************************
|
||||
! Vector & matrix functions
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
|
||||
real(c_double) function S_V3xx ( V ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double) function S_V3xx ( V ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double), dimension(0:2), intent(in) :: V
|
||||
!-------------------------------------------------------------------------------------------
|
||||
S_V3xx = V(0) * V(0) + V(1) * V(1) + V(2) * V(2)
|
||||
end function S_V3xx !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
|
||||
real(c_double) function S_V3xV3 ( V1, V2 ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double) function S_V3xV3 ( V1, V2 ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double), dimension(0:2), intent(in) :: V1, V2
|
||||
!-------------------------------------------------------------------------------------------
|
||||
S_V3xV3 = V1(0) * V2(0) + V1(1) * V2(1) + V1(2) * V2(2)
|
||||
end function S_V3xV3 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
|
||||
real(c_double) function S_V3norm3 ( V ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double) function S_V3norm3 ( V ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
real(c_double), dimension(0:2), intent(in) :: V
|
||||
!-------------------------------------------------------------------------------------------
|
||||
S_V3norm3 = dsqrt ( V(0) * V(0) + V(1) * V(1) + V(2) * V(2) )
|
||||
end function S_V3norm3 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
|
||||
subroutine V3_ort ( V ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
! Vector production
|
||||
!-------------------------------------------------------------------------------------------
|
||||
real(c_double), dimension(0:2), intent(inout) :: V
|
||||
!-------------------------------------------------------------------------------------------
|
||||
real(c_double) :: Vabs
|
||||
@ -122,8 +120,6 @@ contains !**********************************************************************
|
||||
end subroutine V3_ort !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
|
||||
subroutine V3_V3xxV3 ( V, V1, V2 ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
! Vector production
|
||||
!-------------------------------------------------------------------------------------------
|
||||
real(c_double), dimension(0:2), intent(out) :: V
|
||||
real(c_double), dimension(0:2), intent(in) :: V1, V2
|
||||
!-------------------------------------------------------------------------------------------
|
||||
@ -175,10 +171,10 @@ contains !**********************************************************************
|
||||
end subroutine EulerAngles !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
! File inout and output
|
||||
! File input and output
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
|
||||
integer(c_int) function OpenFile ( Name, Params, Path ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
integer(c_int) function OpenFile ( Name, Params, Path ) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
character*(*), intent(in) :: Name, Params, Path
|
||||
!-------------------------------------------------------------------------------------------
|
||||
integer(c_int) :: Fuid
|
||||
|
||||
Reference in New Issue
Block a user