Statistiques
| Révision :

root / src / TestCart.f90 @ 1

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

1 1 pfleura2
SUBROUTINE TestCart(SetCart)
2 1 pfleura2
3 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4 1 pfleura2
  !
5 1 pfleura2
  ! This subroutines looks at the displacements for atoms between
6 1 pfleura2
  ! images. If the total displacement is less than the atomic radius
7 1 pfleura2
  ! then it might be a good idea to treat this atom as CART.
8 1 pfleura2
  !
9 1 pfleura2
  ! Input:
10 1 pfleura2
  !        SetCart : if True then Cart list is set by TestCart
11 1 pfleura2
  !              (Normal use : call TestCart with AutoCart as the argument)
12 1 pfleura2
  !
13 1 pfleura2
  ! Output:
14 1 pfleura2
  !        None
15 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
16 1 pfleura2
17 1 pfleura2
  Use Path_module
18 1 pfleura2
  Use Io_module
19 1 pfleura2
20 1 pfleura2
  IMPLICIT NONE
21 1 pfleura2
22 1 pfleura2
23 1 pfleura2
  LOGICAL, INTENT(IN) :: SetCart
24 1 pfleura2
25 1 pfleura2
  INTEGER(KINT) :: IGeom, I,J,K,Iat
26 1 pfleura2
  CHARACTER(SCHARS) :: Line,Line2
27 1 pfleura2
28 1 pfleura2
  REAL(KREAL) :: d
29 1 pfleura2
  LOGICAL, ALLOCATABLE :: TobeCart(:) ! Nat
30 1 pfleura2
  LOGICAL :: Debug
31 1 pfleura2
32 1 pfleura2
  INTERFACE
33 1 pfleura2
     function valid(string) result (isValid)
34 1 pfleura2
       CHARACTER(*), intent(in) :: string
35 1 pfleura2
       logical                  :: isValid
36 1 pfleura2
     END function VALID
37 1 pfleura2
  END INTERFACE
38 1 pfleura2
39 1 pfleura2
  debug=valid('testcart')
40 1 pfleura2
  if (debug) WRITE(*,*) "========================= Entering TestCart ==========="
41 1 pfleura2
42 1 pfleura2
  ALLOCATE(TobeCart(Nat))
43 1 pfleura2
44 1 pfleura2
  ToBeCart=.TRUE.
45 1 pfleura2
46 1 pfleura2
  ! We put first geometry as the reference
47 1 pfleura2
  DO I=1,NGeomI
48 1 pfleura2
     DO J=I+1,NGeomI
49 1 pfleura2
        DO K=1,Nat
50 1 pfleura2
           IF (ToBeCart(K)) THEN
51 1 pfleura2
                Iat=Atome(K)
52 1 pfleura2
              d=100.*sqrt((XyzGeomI(J,1,K)-XyzGeomI(I,1,K))**2+ &
53 1 pfleura2
                   (XyzGeomI(J,2,K)-XyzGeomI(I,2,K))**2+ &
54 1 pfleura2
                   (XyzGeomI(J,3,K)-XyzGeomI(I,3,K))**2)
55 1 pfleura2
              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)
56 1 pfleura2
              if ((d/r_cov(iat)).GE.0.5d0) ToBeCart(K)=.FALSE.
57 1 pfleura2
           END IF
58 1 pfleura2
        END DO
59 1 pfleura2
     END DO
60 1 pfleura2
  END DO
61 1 pfleura2
62 1 pfleura2
  If (Debug) THEN
63 1 pfleura2
     WRITE(*,*) "Atoms that might be described in CART"
64 1 pfleura2
     DO K=1,Nat
65 1 pfleura2
        IF (ToBeCart(K)) WRITE(*,'(I5)',ADVANCE="NO") K
66 1 pfleura2
     END DO
67 1 pfleura2
  END IF
68 1 pfleura2
69 1 pfleura2
  IF (SetCart) THEN
70 1 pfleura2
     WRITE(*,*) "AutoCART=T: Atoms that will be described in CART"
71 1 pfleura2
     K=1
72 1 pfleura2
     DO I=1,Nat
73 1 pfleura2
        If(ToBeCart(I)) THEN
74 1 pfleura2
           Cart(K)=I
75 1 pfleura2
           K=K+1
76 1 pfleura2
           WRITE(*,'(I5)',ADVANCE="NO") I
77 1 pfleura2
        END IF
78 1 pfleura2
     END DO
79 1 pfleura2
     Cart(K)=0
80 1 pfleura2
     Ncart=K-1
81 1 pfleura2
  END IF
82 1 pfleura2
83 1 pfleura2
  deallocate(tobecart)
84 1 pfleura2
85 1 pfleura2
if (debug) WRITE(*,*) "========================= Exiting TestCart ==========="
86 1 pfleura2
END SUBROUTINE TestCart
87 1 pfleura2
88 1 pfleura2
89 1 pfleura2
90 1 pfleura2
91 1 pfleura2