MsSpec-DFM/New_libraries/DFM_library/UTILITIES_LIBRARY/utilities_4.f90

243 lines
5.6 KiB
Fortran
Raw Normal View History

2022-02-02 16:19:10 +01:00
!
!=======================================================================
!
MODULE UTILITIES_4
!
USE ACCURACY_REAL
!
! It contains the following functions/subroutines:
!
! * SUBROUTINE TAU_TO_D(TAU,DC)
! * SUBROUTINE D_TO_TAU(DC,TAU)
! * SUBROUTINE ETA_TO_D(ETA,DC,T,RD,D)
! * SUBROUTINE D_TO_ETA(ETA,DC,T,RD,D)
! * SUBROUTINE TAU_TO_ETA(TAU,RS,T,ETA)
!
!
CONTAINS
!
!
!=======================================================================
!
SUBROUTINE TAU_TO_D(TAU,DC)
!
! This subroutine computes the diffusion coefficient from the
! knowledge of the relaxation time using the relation:
!
!
! v_F^2 * TAU
! DC = ---------------- where d is the dimensionality
! d
!
!
! Input parameters:
!
! * TAU : relaxation time (in SI)
!
!
! Output parameters:
!
! * DC : diffusion coefficient (in SI)
!
!
! Author : D. Sébilleau
!
! Last modified : 25 Jun 2020
!
!
USE MATERIAL_PROP, ONLY : DMN
USE FERMI_SI, ONLY : VF_SI
USE UTILITIES_1, ONLY : D
!
IMPLICIT NONE
!
REAL (WP), INTENT(IN) :: TAU
REAL (WP) :: DC
!
DC=VF_SI*VF_SI*TAU/D(DMN) !
!
END SUBROUTINE TAU_TO_D
!
!=======================================================================
!
SUBROUTINE D_TO_TAU(DC,TAU)
!
! This subroutine computes the relaxation time from the
! knowledge of the diffusion coefficient using the relation:
!
!
! v_F^2 * TAU
! DC = ---------------- where d is the dimensionality
! d
!
!
! Input parameters:
!
! * DC : diffusion coefficient (in SI)
!
!
! Output parameters:
!
! * TAU : relaxation time (in SI)
!
!
!
! Author : D. Sébilleau
!
! Last modified : 23 Oct 2020
!
!
USE MATERIAL_PROP, ONLY : DMN
USE FERMI_SI, ONLY : VF_SI
USE UTILITIES_1, ONLY : D
!
IMPLICIT NONE
!
REAL (WP), INTENT(IN) :: DC
REAL (WP), INTENT(OUT) :: TAU
!
TAU = DC * D(DMN) / (VF_SI * VF_SI) !
!
END SUBROUTINE D_TO_TAU
!
!=======================================================================
!
SUBROUTINE ETA_TO_D(ETA,T,RD,DC)
!
! This subroutine computes the shear viscosity from the
! knowledge of the diffusion coefficient using the relation:
!
!
! k_B * T
! DC = ----------------
! 6*pi * ETA* RD
!
!
! Input parameters:
!
! * ETA : viscosity in SI
! * T : temperature in SI
! * RD : sphere radius in SI
!
!
! Output parameters:
!
! * DC : diffusion coefficient (in SI)
!
!
! Author : D. Sébilleau
!
! Last modified : 25 Jun 2020
!
!
USE REAL_NUMBERS, ONLY : SIXTH
USE CONSTANTS_P1, ONLY : K_B
USE PI_ETC, ONLY : PI_INV
!
IMPLICIT NONE
!
REAL (WP), INTENT(IN) :: ETA,T,RD
REAL (WP), INTENT(OUT) :: DC
!
DC = K_B * T * SIXTH * PI_INV / (ETA * RD) !
!
END SUBROUTINE ETA_TO_D
!
!=======================================================================
!
SUBROUTINE D_TO_ETA(DC,T,RD,ETA)
!
! This subroutine computes the diffusion coefficient from the
! knowledge of the shear viscosity using the relation:
!
!
! k_B * T
! DC = ----------------
! 6*pi * ETA* RD
!
!
! Input parameters:
!
! * DC : diffusion coefficient (in SI)
! * T : temperature in SI
! * RD : sphere radius in SI
!
!
! Output parameters:
!
! * ETA : viscosity in SI
!
!
! Author : D. Sébilleau
!
! Last modified : 25 Jun 2020
!
!
USE REAL_NUMBERS, ONLY : SIXTH
USE CONSTANTS_P1, ONLY : K_B
USE PI_ETC, ONLY : PI_INV
!
IMPLICIT NONE
!
REAL (WP),INTENT(IN) :: DC,T,RD
REAL (WP),INTENT(OUT) :: ETA
!
ETA = K_B * T * SIXTH * PI_INV / (DC * RD) !
!
END SUBROUTINE D_TO_ETA
!
!=======================================================================
!
SUBROUTINE TAU_TO_ETA(TAU,RS,T,ETA)
!
! This subroutine computes the shear viscosity from the
! knowledge of the relaxation using the relation:
!
! References: (1) R. Kishore and K. N. Pathak,
! Phys. Rev. 183, 672-674 (1069)
!
!
! 2
! ETA = --- * N0 * mu * TAU
! 5
!
! This formula is valid in the low-temperature limit k_B*T << mu
! for 3D systems
!
!
! Input parameters:
!
! * TAU : relaxation time (in SI)
! * RS : Wigner-Seitz radius (in units of a_0)
! * T : temperature in SI
!
!
! Output parameters:
!
! * ETA : shear viscosity (in SI)
!
!
! Author : D. Sébilleau
!
! Last modified : 25 Jun 2020
!
!
USE MATERIAL_PROP, ONLY : DMN
USE REAL_NUMBERS, ONLY : TWO,FIFTH
USE UTILITIES_1, ONLY : RS_TO_N0
USE CHEMICAL_POTENTIAL, ONLY : MU
!
REAL (WP), INTENT(IN) :: TAU,RS,T
REAL (WP), INTENT(OUT) :: ETA
REAL (WP) :: N0,MU0
!
N0 = RS_TO_N0('3D',RS) !
!
MU0 = MU('3D',T) !
!
ETA = TWO * FIFTH * N0 * MU0 * TAU !
!
END SUBROUTINE TAU_TO_ETA
!
END MODULE UTILITIES_4