Statistiques
| Révision :

root / src / TestCart.f90 @ 5

Historique | Voir | Annoter | Télécharger (2,18 ko)

1
SUBROUTINE TestCart(SetCart)
2

    
3
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4
  !
5
  ! This subroutines looks at the displacements for atoms between
6
  ! images. If the total displacement is less than the atomic radius
7
  ! then it might be a good idea to treat this atom as CART.
8
  !
9
  ! Input:
10
  !        SetCart : if True then Cart list is set by TestCart
11
  !              (Normal use : call TestCart with AutoCart as the argument)  
12
  !
13
  ! Output:
14
  !        None
15
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
16

    
17
  Use Path_module
18
  Use Io_module
19

    
20
  IMPLICIT NONE
21

    
22

    
23
  LOGICAL, INTENT(IN) :: SetCart
24

    
25
  INTEGER(KINT) :: I, J, K, Iat
26

    
27
  REAL(KREAL) :: d
28
  LOGICAL, ALLOCATABLE :: TobeCart(:) ! Nat
29
  LOGICAL :: Debug
30

    
31
  INTERFACE
32
     function valid(string) result (isValid)
33
       CHARACTER(*), intent(in) :: string
34
       logical                  :: isValid
35
     END function VALID
36
  END INTERFACE
37

    
38
  debug=valid('testcart')
39
  if (debug) WRITE(*,*) "========================= Entering TestCart ==========="
40

    
41
  ALLOCATE(TobeCart(Nat))
42

    
43
  ToBeCart=.TRUE.
44

    
45
  ! We put first geometry as the reference
46
  DO I=1,NGeomI
47
     DO J=I+1,NGeomI
48
        DO K=1,Nat
49
           IF (ToBeCart(K)) THEN
50
                Iat=Atome(K)
51
              d=100.*sqrt((XyzGeomI(J,1,K)-XyzGeomI(I,1,K))**2+ &
52
                   (XyzGeomI(J,2,K)-XyzGeomI(I,2,K))**2+ &
53
                   (XyzGeomI(J,3,K)-XyzGeomI(I,3,K))**2) 
54
              if (debug) WRITe(*,'(4(1X,I5),10(1X,F12.8))') k,i,j,iat,d,r_cov(iat),r_cov(iat)*fact,d/r_cov(iat)
55
              if ((d/r_cov(iat)).GE.0.5d0) ToBeCart(K)=.FALSE.
56
           END IF
57
        END DO
58
     END DO
59
  END DO
60

    
61
  If (Debug) THEN
62
     WRITE(*,*) "Atoms that might be described in CART"
63
     DO K=1,Nat
64
        IF (ToBeCart(K)) WRITE(*,'(I5)',ADVANCE="NO") K
65
     END DO
66
  END IF
67

    
68
  IF (SetCart) THEN
69
     WRITE(*,*) "AutoCART=T: Atoms that will be described in CART"
70
     K=1
71
     DO I=1,Nat
72
        If(ToBeCart(I)) THEN
73
           Cart(K)=I
74
           K=K+1
75
           WRITE(*,'(I5)',ADVANCE="NO") I
76
        END IF
77
     END DO
78
     Cart(K)=0
79
     Ncart=K-1
80
  END IF
81

    
82
  deallocate(tobecart)
83

    
84
if (debug) WRITE(*,*) "========================= Exiting TestCart ==========="
85
END SUBROUTINE TestCart
86

    
87

    
88
 
89

    
90

    
91