MsSpec-DFM/New_libraries/DFM_library/CALCULATORS_LIBRARY/call_calc_3.f90

156 lines
5.7 KiB
Fortran

!
!=======================================================================
!
MODULE CALL_CALC_3
!
USE ACCURACY_REAL
USE CALCULATORS_3
USE OUT_VALUES_3
!
! This module calls the subroutines of calculator 3 whenever necessary
!
CONTAINS
!
!=======================================================================
!
SUBROUTINE USE_CALC_3(IQ,X)
!
!
!
! Input parameters:
!
! * IQ : q index
! * X : dimensionless factor --> X = q / (2 * k_F)
!
!
!
!
! Author : D. Sébilleau
!
! Last modified : 28 Jan 2021
!
!
IMPLICIT NONE
!
INTEGER :: IQ
!
REAL (WP) :: X
!
! Computing the local-field corrections G(q,omega)
!
IF(I_LF == 1) THEN !
CALL CALC_LFC(X) !
END IF !
!
! Computing the I(q) function = G(q,inf)
!
IF(I_IQ == 1) THEN !
CALL CALC_IQF(X) !
END IF !
!
! Computing the structure factor S(q,omega)
!
IF(I_SF == 1) THEN !
CALL CALC_SFC(X) !
END IF !
!
IF(IQ == 1) THEN !
!
! Computing the pair correlation/distribution functions
!
IF(I_PC == 1) THEN !
CALL CALC_PCF !
END IF !
IF(I_P2 == 1) THEN !
CALL CALC_PDF !
END IF !
END IF !
!
! Computing the vertex function Gamma(q,omega)
!
IF(I_DC == 1) THEN !
CALL CALC_VTX(X) !
END IF !
!
! Computing the plasmon damping from eps(q,omega)
!
IF(I_VX == 1) THEN !
CALL CALC_DMP(IQ,X) !
END IF !
!
! Computing the q bounds
!
IF(I_QC == 1) THEN !
CALL CALC_QBD !
END IF !
!
! Computing the relaxation time
!
IF(I_RL == 1) THEN !
CALL CALC_RLX(X) !
END IF !
!
! Computing the screening vector
!
IF(I_KS == 1) THEN !
CALL CALC_SCR(X) !
END IF !
!
! Computing the omega = q * v_F file
!
!
IF(I_OQ == 1) THEN !
CALL CALC_QVF(X) !
END IF !
!
! Computing the moments of Im[ epsilon ]
!
IF(I_ME == 1) THEN !
CALL CALC_MEP(X) !
END IF !
!
! Computing the moments of the dynamical structure factor
!
IF(I_MS == 1) THEN !
CALL CALC_MSF(X) !
END IF !
!
! Computing the moments of the loss function
!
IF(I_ML == 1) THEN !
CALL CALC_MLO(X) !
END IF !
!
! Computing the zeros of Re[ eps(q,omega) ]
!
IF(I_ZE == 1) THEN !
CALL CALC_RE0(X) !
END IF !
!
! Computing the inelastic mean free path
!
IF(IQ == 1) THEN !
IF(I_MF == 1) THEN !
CALL CALC_MFP !
END IF !
END IF !
!
! Computing the Fourier-space Nevalinna/memory function
!
IF(I_NV == 1) THEN !
CALL CALC_NEV(X) !
END IF !
!
! Computing the time-domain memory function
!
IF(IQ == 1) THEN !
IF(I_MT == 1) THEN !
CALL CALC_MEM !
END IF !
END IF !
!
END SUBROUTINE USE_CALC_3
!
END MODULE CALL_CALC_3