Statistiques
| Révision :

root / src / CheckPeriodicBound.f90

Historique | Voir | Annoter | Télécharger (7,55 ko)

1
SUBROUTINE CheckPeriodicBound
2
  ! This subroutine is only for periodic systems
3
  ! it checks that the atoms do not change their
4
  ! positions from one side to the other during the simulations.
5
  ! This would ruin the interpolation.
6

    
7

    
8
!----------------------------------------------------------------------
9
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
10
!  Centre National de la Recherche Scientifique,
11
!  Université Claude Bernard Lyon 1. All rights reserved.
12
!
13
!  This work is registered with the Agency for the Protection of Programs 
14
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
15
!
16
!  Authors: P. Fleurat-Lessard, P. Dayal
17
!  Contact: optnpath@gmail.com
18
!
19
! This file is part of "Opt'n Path".
20
!
21
!  "Opt'n Path" is free software: you can redistribute it and/or modify
22
!  it under the terms of the GNU Affero General Public License as
23
!  published by the Free Software Foundation, either version 3 of the License,
24
!  or (at your option) any later version.
25
!
26
!  "Opt'n Path" is distributed in the hope that it will be useful,
27
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
28
!
29
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
30
!  GNU Affero General Public License for more details.
31
!
32
!  You should have received a copy of the GNU Affero General Public License
33
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
34
!
35
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
36
! for commercial licensing opportunities.
37
!----------------------------------------------------------------------
38

    
39
  Use Path_module
40
  Use Io_module
41

    
42
  IMPLICIT NONE
43

    
44

    
45
  INTEGER(KINT) :: IGeom, I,J,K
46
  REAL(KREAL), ALLOCATABLE :: GeomRef(:,:), GeomTmp(:,:) ! (3,Nat)
47

    
48
  REAL(KREAL) :: Latrloc(3,3),Bloc(3),Xt,Yt,Zt
49
  REAL(KREAL) :: NormA, NormB,Xrel,Yrel
50
  REAL(KREAL) :: Prod,LatrA(3),LatrB(3)
51
  REAL(KREAL) :: V(3)
52

    
53
  LOGICAL :: Debug
54

    
55
  INTERFACE
56
     function valid(string) result (isValid)
57
       CHARACTER(*), intent(in) :: string
58
       logical                  :: isValid
59
     END function VALID
60

    
61

    
62
    SUBROUTINE die(routine, msg, file, line, unit)
63

    
64
      Use VarTypes
65
      Use io_module
66

    
67
      implicit none
68
      character(len=*), intent(in)           :: routine, msg
69
      character(len=*), intent(in), optional :: file
70
      integer(KINT), intent(in), optional      :: line, unit
71

    
72
    END SUBROUTINE die
73

    
74
  END INTERFACE
75

    
76
  debug=valid('checkperiodicbound')
77
  if (debug) call header("Entering CheckPeriodicBound")
78

    
79
  ALLOCATE(GeomRef(3,Nat), GeomTmp(3,Nat))
80

    
81
  ! The test is easy in DIRECT space, so we will convert the geometries
82
  ! into this space. 
83

    
84
  SELECT CASE (Iper)
85
  CASE(1)
86
     NormA=DOT_PRODUCT(Lat_a,Lat_a)
87
     DO IGeom=2,NGeomI
88
        DO I=1,NAt
89
           DO J=1,3
90
              v(J)=XyzGeomI(IGeom,J,I)-XyzGeomI(1,J,I)
91
           END DO
92
           XRel=DOT_PRODUCT(Lat_a,v)/NormA
93
           if (abs(Xrel).GE.BoxTol) THEN
94
              If (debug) THEN
95
                 WRITE(*,'("Atom ",I5," moved because XRel=",F10.6)') I,XRel
96
                 WRITE(*,'("Ref: ",3(1X,F10.6))') XyzGeomI(1,1:3,I)
97
                 WRITE(*,'("Old: ",3(1X,F10.6))') XyzGeomI(IGeom,1:3,I)
98
                 WRITE(*,'("New: ",3(1X,F10.6))') XyzGeomI(IGeom,1:3,I)-Lat_a*Sign(1.0d0,XRel)
99
              END IF
100
              XyzGeomI(IGeom,1:3,I)=XyzGeomI(IGeom,1:3,I)-Lat_a*Sign(1.0d0,XRel)
101
           END IF
102
        END DO
103
     END DO
104
  CASE (2)
105
     NormA=DOT_PRODUCT(Lat_a,Lat_a)
106
     NormB=DOT_PRODUCT(Lat_b,Lat_b)
107
     Prod=DOT_PRODUCT(Lat_a,Lat_b)
108
     LatrA=(NormB*Lat_a-Prod*Lat_b)/(NormA*NormB-Prod**2)
109
     LatrB=(NormA*Lat_b-Prod*Lat_a)/(NormA*NormB-Prod**2)
110

    
111
     DO IGeom=2,NGeomI
112
        DO I=1,NAt
113
           DO J=1,3
114
              v(J)=XyzGeomI(IGeom,J,I)-XyzGeomI(1,J,I)
115
           END DO
116
           XRel=DOT_PRODUCT(Latra,v)
117
           YRel=DOT_PRODUCT(Latrb,v)
118
           if (abs(Xrel).GE.BoxTol) THEN
119
              If (debug) THEN
120
                 WRITE(*,'("Atom ",I5," moved because XRel=",F10.6)') I,XRel
121
                 WRITE(*,'("Ref: ",3(1X,F10.6))') XyzGeomI(1,1:3,I)
122
                 WRITE(*,'("Old: ",3(1X,F10.6))') XyzGeomI(IGeom,1:3,I)
123
                 WRITE(*,'("New: ",3(1X,F10.6))') XyzGeomI(IGeom,1:3,I)-Latra*Sign(1.0d0,XRel)
124
              END IF
125
              XyzGeomI(IGeom,1:3,I)=XyzGeomI(IGeom,1:3,I)-Latra*Sign(1.0d0,XRel)
126
           END IF
127
           if (abs(Yrel).GE.BoxTol) THEN
128
              If (debug) THEN
129
                 WRITE(*,'("Atom ",I5," moved because YRel=",F10.6)') I,YRel
130
                 WRITE(*,'("Ref: ",3(1X,F10.6))') XyzGeomI(1,1:3,I)
131
                 WRITE(*,'("Old: ",3(1X,F10.6))') XyzGeomI(IGeom,1:3,I)
132
                 WRITE(*,'("New: ",3(1X,F10.6))') XyzGeomI(IGeom,1:3,I)-Latrb*Sign(1.0d0,YRel)
133
              END IF
134
              XyzGeomI(IGeom,1:3,I)=XyzGeomI(IGeom,1:3,I)-Latrb*Sign(1.0d0,YRel)
135
           END IF
136
        END DO
137
     END DO
138

    
139
  CASE(3)
140

    
141

    
142

    
143
!      if (debug) THEN
144
!         WRITE(*,'(1X,A,3(1X,F10.6))') "Lat_a:",Lat_a
145
!         WRITE(*,'(1X,A,3(1X,F10.6))') "Lat_b:",Lat_b
146
!         WRITE(*,'(1X,A,3(1X,F10.6))') "Lat_c:",Lat_c
147
!         WRITE(*,'(1X,A,3(1X,F10.6))') "BocTol:",BoxTol
148

    
149
!      NormA=DOT_PRODUCT(Lat_a,Lat_a)
150
!      NormB=DOT_PRODUCT(Lat_b,Lat_b)
151
!      Prod=DOT_PRODUCT(Lat_a,Lat_b)
152
!      LatrA=(NormB*Lat_a-Prod*Lat_b)/(NormA*NormB-Prod**2)
153
!      LatrB=(NormA*Lat_b-Prod*Lat_a)/(NormA*NormB-Prod**2)
154
! !     NormA=DOT_PRODUCT(Latra,Latra)
155
! !     NormB=DOT_PRODUCT(Latrb,Latrb)
156

    
157
!         DO IGeom=2,NGeomI
158
!            DO I=1,NAt
159
!               DO J=1,3
160
!                  v(J)=XyzGeomI(IGeom,J,I)-XyzGeomI(1,J,I)
161
!               END DO
162
!               XRel=DOT_PRODUCT(Latra,v)
163
!               YRel=DOT_PRODUCT(Latrb,v)
164
!               If (abs(XRel).GT.BoxTol)  WRITE(*,*) "Xrel too big:",IGeom,I,Xrel
165
!               If (abs(YRel).GT.BoxTol)  WRITE(*,*) "Yrel too big:",IGeom,I,Yrel
166
! !               WRITE(*,*) "Xrel :",IGeom,I,Xrel
167
! !               WRITE(*,*) "Yrel :",IGeom,I,Yrel
168
! !               WRITE(*,*) "Zrel :",IGeom,I,Zrel
169

    
170
!            END DO
171
!         END DO
172
!      END IF
173

    
174
     Latrloc(1:3,1)=Lat_a
175
     Latrloc(1:3,2)=Lat_b
176
     Latrloc(1:3,3)=Lat_c
177
     Bloc=1.
178
     ! TODO: Replace by LAPACK subroutine
179
     CALL Gaussj(Latrloc,3,3,Bloc,1,1)
180

    
181
     ! We put first geometry as the reference
182
     GeomRef=0.
183
     DO I=1,Nat
184
        DO K=1,3
185
           DO J=1,3
186
              GeomRef(K,I)=GeomRef(K,I)+XyzGeomI(1,J,I)*LatrLoc(K,J)
187
           END DO
188
        END DO
189
     END DO
190

    
191
     DO IGeom=2,NGeomI
192
        GeomTmp=0.
193
        DO I=1,Nat
194
           DO K=1,3
195
              DO J=1,3
196
                 GeomTmp(K,I)=GeomTmp(K,I)+XyzGeomI(IGeom,J,I)*LatrLoc(K,J)
197
              END DO
198
              if (abs(GeomTmp(K,I)-GeomRef(K,I)).GE.BoxTol) THEN
199
                 If (debug) & 
200
                      WRITE(*,'("Coord ",I1," has been changed for atom ",I5," by ",F4.0," ref:",F9.6," old:",F9.6," new:",F9.6)') &
201
                      K,I,Sign(1.d0,GeomRef(K,I)-GeomTmp(K,I)),& 
202
                      GeomRef(K,I),GeomTmp(K,I), &
203
                      GeomTmp(K,I)+Sign(1.d0,GeomRef(K,I)-GeomTmp(K,I))
204

    
205
                 GeomTmp(K,I)=GeomTmp(K,I)+Sign(1.d0,GeomRef(K,I)-GeomTmp(K,I))
206
              END IF
207
           END DO
208
           Xt=GeomTmp(1,I)
209
           Yt=GeomTmp(2,I)
210
           Zt=GeomTmp(3,I)
211
           XyzGeomI(IGeom,1,I)=Xt*lat_a(1)+Yt*lat_b(1)+Zt*lat_c(1)
212
           XyzGeomI(IGeom,2,I)=Xt*lat_a(2)+Yt*lat_b(2)+Zt*lat_c(2)
213
           XyzGeomI(IGeom,3,I)=Xt*lat_a(3)+Yt*lat_b(3)+Zt*lat_c(3)
214
        END DO
215
     END DO
216

    
217
  CASE DEFAULT
218
     Call Die("CheckPeriodicBound"," Iper unknown")
219
  END SELECT
220

    
221

    
222
  if (debug) WRITE(*,*) "========================= Exiting CheckPeriodicBound ==========="
223
END SUBROUTINE CheckPeriodicBound
224

    
225

    
226
 
227

    
228

    
229