Statistiques
| Révision :

root / src / TestCart.f90 @ 12

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