! !======================================================================= ! MODULE CALCULATORS_5 ! ! This module contains the subroutines allowing to compute ! various Fermi properties of the electron/plasma liquids: ! ! * Fermi energy : CALC_EFF ! * Fermi momentum : CALC_KFF ! * Fermi velocity : CALC_VFF ! * Fermi temperature : CALC_TFF ! * Fermi density of states : CALC_NFF ! ! USE ACCURACY_REAL ! CONTAINS ! !======================================================================= ! SUBROUTINE CALC_EFF ! ! This subroutine computes the Fermi energy and writes it into a file ! ! ! ! Author : D. Sébilleau ! ! Last modified : 16 Sep 2020 ! ! USE FERMI_SI, ONLY : EF_SI USE ENE_CHANGE, ONLY : EV ! USE OUT_VALUES_5, ONLY : I_EF USE PRINT_FILES, ONLY : IO_EF ! IMPLICIT NONE ! IF(I_EF == 1) THEN ! WRITE(IO_EF,*) EF_SI / EV ! END IF ! ! END SUBROUTINE CALC_EFF ! !======================================================================= ! SUBROUTINE CALC_KFF ! ! This subroutine computes the Fermi momentum and writes it into a file ! ! ! ! Author : D. Sébilleau ! ! Last modified : 16 Sep 2020 ! ! USE FERMI_SI, ONLY : KF_SI USE ENE_CHANGE, ONLY : ANG ! USE OUT_VALUES_5, ONLY : I_KF USE PRINT_FILES, ONLY : IO_KF ! IMPLICIT NONE ! IF(I_KF == 1) THEN ! WRITE(IO_KF,*) KF_SI * ANG ! END IF ! ! END SUBROUTINE CALC_KFF ! !======================================================================= ! SUBROUTINE CALC_VFF ! ! This subroutine computes the Fermi velocity and writes it into a file ! ! ! ! Author : D. Sébilleau ! ! Last modified : 16 Sep 2020 ! ! USE FERMI_SI, ONLY : VF_SI ! USE OUT_VALUES_5, ONLY : I_VF USE PRINT_FILES, ONLY : IO_VF ! IMPLICIT NONE ! IF(I_VF == 1) THEN ! WRITE(IO_VF,*) VF_SI ! END IF ! ! END SUBROUTINE CALC_VFF ! !======================================================================= ! SUBROUTINE CALC_TFF ! ! This subroutine computes the Fermi temperature and writes it into a file ! ! ! ! Author : D. Sébilleau ! ! Last modified : 16 Sep 2020 ! ! USE FERMI_SI, ONLY : TF_SI ! USE OUT_VALUES_5, ONLY : I_TE USE PRINT_FILES, ONLY : IO_TE ! IMPLICIT NONE ! IF(I_TE == 1) THEN ! WRITE(IO_TE,*) TF_SI ! END IF ! ! END SUBROUTINE CALC_TFF ! !======================================================================= ! SUBROUTINE CALC_NFF ! ! This subroutine computes the Fermi density of states ! and writes it into a file ! ! ! ! Author : D. Sébilleau ! ! Last modified : 16 Sep 2020 ! ! USE FERMI_SI, ONLY : NF_SI USE ENE_CHANGE, ONLY : EV ! USE OUT_VALUES_5, ONLY : I_DL USE PRINT_FILES, ONLY : IO_DL ! IMPLICIT NONE ! IF(I_DL == 1) THEN ! WRITE(IO_DL,*) NF_SI * EV ! END IF ! ! END SUBROUTINE CALC_NFF ! END MODULE CALCULATORS_5