47 lines
1.4 KiB
Fortran
47 lines
1.4 KiB
Fortran
|
!
|
||
|
!=======================================================================
|
||
|
!
|
||
|
MODULE CALL_CALC_7
|
||
|
!
|
||
|
USE ACCURACY_REAL
|
||
|
USE CALCULATORS_7
|
||
|
USE OUT_VALUES_7
|
||
|
!
|
||
|
! This module calls the subroutines of calculator 7 whenever necessary
|
||
|
!
|
||
|
CONTAINS
|
||
|
!
|
||
|
!=======================================================================
|
||
|
!
|
||
|
SUBROUTINE USE_CALC_7
|
||
|
!
|
||
|
IMPLICIT NONE
|
||
|
!
|
||
|
! Computing the exchange energy
|
||
|
!
|
||
|
IF(I_EX == 1) THEN !
|
||
|
CALL CALC_EXX !
|
||
|
END IF !
|
||
|
!
|
||
|
! Computing the exchange and correlation energy
|
||
|
!
|
||
|
IF(I_XC == 1) THEN !
|
||
|
CALL CALC_EXC !
|
||
|
END IF !
|
||
|
!
|
||
|
! Computing the correlation energy
|
||
|
!
|
||
|
IF(I_EC == 1) THEN !
|
||
|
CALL CALC_ECO !
|
||
|
END IF !
|
||
|
!
|
||
|
! Computing the kinetic energy
|
||
|
!
|
||
|
IF(I_EK == 1) THEN !
|
||
|
CALL CALC_KIN !
|
||
|
END IF !
|
||
|
!
|
||
|
END SUBROUTINE USE_CALC_7
|
||
|
!
|
||
|
END MODULE CALL_CALC_7
|