root / src / TestCart.f90 @ 4
Historique | Voir | Annoter | Télécharger (2,22 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) :: IGeom, I,J,K,Iat |
26 |
CHARACTER(SCHARS) :: Line,Line2 |
27 |
|
28 |
REAL(KREAL) :: d |
29 |
LOGICAL, ALLOCATABLE :: TobeCart(:) ! Nat |
30 |
LOGICAL :: Debug |
31 |
|
32 |
INTERFACE |
33 |
function valid(string) result (isValid) |
34 |
CHARACTER(*), intent(in) :: string |
35 |
logical :: isValid |
36 |
END function VALID |
37 |
END INTERFACE |
38 |
|
39 |
debug=valid('testcart') |
40 |
if (debug) WRITE(*,*) "========================= Entering TestCart ===========" |
41 |
|
42 |
ALLOCATE(TobeCart(Nat)) |
43 |
|
44 |
ToBeCart=.TRUE. |
45 |
|
46 |
! We put first geometry as the reference |
47 |
DO I=1,NGeomI |
48 |
DO J=I+1,NGeomI |
49 |
DO K=1,Nat |
50 |
IF (ToBeCart(K)) THEN |
51 |
Iat=Atome(K) |
52 |
d=100.*sqrt((XyzGeomI(J,1,K)-XyzGeomI(I,1,K))**2+ & |
53 |
(XyzGeomI(J,2,K)-XyzGeomI(I,2,K))**2+ & |
54 |
(XyzGeomI(J,3,K)-XyzGeomI(I,3,K))**2) |
55 |
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 |
if ((d/r_cov(iat)).GE.0.5d0) ToBeCart(K)=.FALSE. |
57 |
END IF |
58 |
END DO |
59 |
END DO |
60 |
END DO |
61 |
|
62 |
If (Debug) THEN |
63 |
WRITE(*,*) "Atoms that might be described in CART" |
64 |
DO K=1,Nat |
65 |
IF (ToBeCart(K)) WRITE(*,'(I5)',ADVANCE="NO") K |
66 |
END DO |
67 |
END IF |
68 |
|
69 |
IF (SetCart) THEN |
70 |
WRITE(*,*) "AutoCART=T: Atoms that will be described in CART" |
71 |
K=1 |
72 |
DO I=1,Nat |
73 |
If(ToBeCart(I)) THEN |
74 |
Cart(K)=I |
75 |
K=K+1 |
76 |
WRITE(*,'(I5)',ADVANCE="NO") I |
77 |
END IF |
78 |
END DO |
79 |
Cart(K)=0 |
80 |
Ncart=K-1 |
81 |
END IF |
82 |
|
83 |
deallocate(tobecart) |
84 |
|
85 |
if (debug) WRITE(*,*) "========================= Exiting TestCart ===========" |
86 |
END SUBROUTINE TestCart |
87 |
|
88 |
|
89 |
|
90 |
|
91 |
|
92 |
|