root / src / TestCart.f90
Historique | Voir | Annoter | Télécharger (3,48 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 |
!---------------------------------------------------------------------- |
18 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
19 |
! Centre National de la Recherche Scientifique, |
20 |
! Université Claude Bernard Lyon 1. All rights reserved. |
21 |
! |
22 |
! This work is registered with the Agency for the Protection of Programs |
23 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
24 |
! |
25 |
! Authors: P. Fleurat-Lessard, P. Dayal |
26 |
! Contact: optnpath@gmail.com |
27 |
! |
28 |
! This file is part of "Opt'n Path". |
29 |
! |
30 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
31 |
! it under the terms of the GNU Affero General Public License as |
32 |
! published by the Free Software Foundation, either version 3 of the License, |
33 |
! or (at your option) any later version. |
34 |
! |
35 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
36 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
37 |
! |
38 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
39 |
! GNU Affero General Public License for more details. |
40 |
! |
41 |
! You should have received a copy of the GNU Affero General Public License |
42 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
43 |
! |
44 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
45 |
! for commercial licensing opportunities. |
46 |
!---------------------------------------------------------------------- |
47 |
|
48 |
Use Path_module |
49 |
Use Io_module |
50 |
|
51 |
IMPLICIT NONE |
52 |
|
53 |
|
54 |
LOGICAL, INTENT(IN) :: SetCart |
55 |
|
56 |
INTEGER(KINT) :: I, J, K, Iat |
57 |
|
58 |
REAL(KREAL) :: d |
59 |
LOGICAL, ALLOCATABLE :: TobeCart(:) ! Nat |
60 |
LOGICAL :: Debug |
61 |
|
62 |
INTERFACE |
63 |
function valid(string) result (isValid) |
64 |
CHARACTER(*), intent(in) :: string |
65 |
logical :: isValid |
66 |
END function VALID |
67 |
END INTERFACE |
68 |
|
69 |
debug=valid('testcart') |
70 |
if (debug) WRITE(*,*) "========================= Entering TestCart ===========" |
71 |
|
72 |
ALLOCATE(TobeCart(Nat)) |
73 |
|
74 |
ToBeCart=.TRUE. |
75 |
|
76 |
! We put first geometry as the reference |
77 |
DO I=1,NGeomI |
78 |
DO J=I+1,NGeomI |
79 |
DO K=1,Nat |
80 |
IF (ToBeCart(K)) THEN |
81 |
Iat=Atome(K) |
82 |
d=100.*sqrt((XyzGeomI(J,1,K)-XyzGeomI(I,1,K))**2+ & |
83 |
(XyzGeomI(J,2,K)-XyzGeomI(I,2,K))**2+ & |
84 |
(XyzGeomI(J,3,K)-XyzGeomI(I,3,K))**2) |
85 |
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) |
86 |
if ((d/r_cov(iat)).GE.0.5d0) ToBeCart(K)=.FALSE. |
87 |
END IF |
88 |
END DO |
89 |
END DO |
90 |
END DO |
91 |
|
92 |
If (Debug) THEN |
93 |
WRITE(*,*) "Atoms that might be described in CART" |
94 |
DO K=1,Nat |
95 |
IF (ToBeCart(K)) WRITE(*,'(I5)',ADVANCE="NO") K |
96 |
END DO |
97 |
END IF |
98 |
|
99 |
IF (SetCart) THEN |
100 |
WRITE(*,*) "AutoCART=T: Atoms that will be described in CART" |
101 |
K=1 |
102 |
DO I=1,Nat |
103 |
If(ToBeCart(I)) THEN |
104 |
Cart(K)=I |
105 |
K=K+1 |
106 |
WRITE(*,'(I5)',ADVANCE="NO") I |
107 |
END IF |
108 |
END DO |
109 |
Cart(K)=0 |
110 |
Ncart=K-1 |
111 |
END IF |
112 |
|
113 |
deallocate(tobecart) |
114 |
|
115 |
if (debug) WRITE(*,*) "========================= Exiting TestCart ===========" |
116 |
END SUBROUTINE TestCart |
117 |
|
118 |
|
119 |
|
120 |
|
121 |
|
122 |
|