Statistiques
| Révision :

root / src / Check_step.f90

Historique | Voir | Annoter | Télécharger (6,18 ko)

1 1 pfleura2
! This subroutine checks that the required step fulfills some conditions:
2 1 pfleura2
! v1.0
3 1 pfleura2
! Only valence angles are checked to remain in to 0:Pi range.
4 1 pfleura2
5 2 pfleura2
SUBROUTINE Check_step(Coord,Nat,NCoord,GeomOld,Step)
6 1 pfleura2
7 12 pfleura2
!----------------------------------------------------------------------
8 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
9 12 pfleura2
!  Centre National de la Recherche Scientifique,
10 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
11 12 pfleura2
!
12 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
13 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
14 12 pfleura2
!
15 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
16 12 pfleura2
!  Contact: optnpath@gmail.com
17 12 pfleura2
!
18 12 pfleura2
! This file is part of "Opt'n Path".
19 12 pfleura2
!
20 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
21 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
22 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
23 12 pfleura2
!  or (at your option) any later version.
24 12 pfleura2
!
25 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
26 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
27 12 pfleura2
!
28 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
29 12 pfleura2
!  GNU Affero General Public License for more details.
30 12 pfleura2
!
31 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
32 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
33 12 pfleura2
!
34 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
35 12 pfleura2
! for commercial licensing opportunities.
36 12 pfleura2
!----------------------------------------------------------------------
37 12 pfleura2
38 1 pfleura2
  Use Path_module, only : pi,ncart
39 1 pfleura2
40 1 pfleura2
  IMPLICIT NONE
41 1 pfleura2
42 1 pfleura2
43 1 pfleura2
  INTEGER, PARAMETER :: KINT=KIND(1)
44 1 pfleura2
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
45 1 pfleura2
46 2 pfleura2
  INTEGER(KINT), INTENT(IN) :: Nat,NCoord
47 1 pfleura2
  CHARACTER(32), INTENT(IN) :: Coord
48 1 pfleura2
  REAL(KREAL), INTENT(INOUT) :: Step(NCoord)
49 1 pfleura2
  REAL(KREAL), INTENT(IN) :: GeomOld(NCoord)
50 1 pfleura2
51 1 pfleura2
  ! As this subroutine is here for debugging, debug=T !
52 1 pfleura2
  LOGICAL, PARAMETER :: debug=.TRUE.
53 1 pfleura2
54 2 pfleura2
55 1 pfleura2
  ! Variables
56 1 pfleura2
  INTEGER(KINT) :: IBeg, Idx,Iat
57 1 pfleura2
  REAL(KREAL) ::  Fact
58 1 pfleura2
59 1 pfleura2
  ! Parameters
60 1 pfleura2
  REAL(KREAL),PARAMETER :: eps=1e-8
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
  if (.NOT.Valid("CheckStep")) RETURN
70 1 pfleura2
71 1 pfleura2
  if (nat.LE.2) THEN
72 1 pfleura2
     if (debug) WRITE(*,*) "Check-Step useless for 2 or less atoms !"
73 1 pfleura2
     return
74 1 pfleura2
  END IF
75 1 pfleura2
76 1 pfleura2
  if (debug) WRITE(*,*) "=========================== Entering Check_Step ===================="
77 1 pfleura2
78 1 pfleura2
  Fact=1.d0
79 1 pfleura2
80 1 pfleura2
  SELECT CASE(COORD)
81 1 pfleura2
  CASE ('ZMAT')
82 1 pfleura2
     Idx=3
83 1 pfleura2
     IF (STEP(Idx).GT.Eps) THEN
84 1 pfleura2
        If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
85 1 pfleura2
           Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
86 1 pfleura2
           WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
87 1 pfleura2
        END IF
88 1 pfleura2
        If (GeomOld(Idx)+Step(Idx).LE.0) THEN
89 1 pfleura2
           Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
90 1 pfleura2
           WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
91 1 pfleura2
        END IF
92 1 pfleura2
     END IF
93 1 pfleura2
     If (Nat.GT.3) THEN
94 1 pfleura2
        Idx=5
95 1 pfleura2
        IF (STEP(Idx).GE.Eps) THEN
96 1 pfleura2
           If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
97 1 pfleura2
              Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
98 1 pfleura2
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
99 1 pfleura2
           END IF
100 1 pfleura2
           If (GeomOld(Idx)+Step(Idx).LE.0) THEN
101 1 pfleura2
              Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
102 1 pfleura2
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
103 1 pfleura2
           END IF
104 1 pfleura2
        END IF
105 1 pfleura2
        DO Iat=5,Nat
106 1 pfleura2
           Idx=Idx+3
107 1 pfleura2
           IF (STEP(Idx).GE.Eps) THEN
108 1 pfleura2
              If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
109 1 pfleura2
                 Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
110 1 pfleura2
                 WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
111 1 pfleura2
              END IF
112 1 pfleura2
              If (GeomOld(Idx)+Step(Idx).LE.0) THEN
113 1 pfleura2
                 Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
114 1 pfleura2
                 WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
115 1 pfleura2
              END IF
116 1 pfleura2
           END IF
117 1 pfleura2
        END DO
118 1 pfleura2
     END IF
119 1 pfleura2
120 1 pfleura2
  CASE ('MIXED')
121 1 pfleura2
     SELECT CASE (NCart)
122 1 pfleura2
     CASE (1:2)
123 1 pfleura2
        Idx=3
124 1 pfleura2
        IF (STEP(Idx).GE.Eps) THEN
125 1 pfleura2
           If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
126 1 pfleura2
              Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
127 1 pfleura2
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
128 1 pfleura2
           END IF
129 1 pfleura2
           If (GeomOld(Idx)+Step(Idx).LE.0) THEN
130 1 pfleura2
              Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
131 1 pfleura2
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
132 1 pfleura2
           END IF
133 1 pfleura2
        END IF
134 1 pfleura2
        IF (Nat.GT.3) THEN
135 1 pfleura2
           Idx=5
136 1 pfleura2
           IF (STEP(Idx).GE.Eps) THEN
137 1 pfleura2
              If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
138 1 pfleura2
                 Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
139 1 pfleura2
                 WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
140 1 pfleura2
              END IF
141 1 pfleura2
              If (GeomOld(Idx)+Step(Idx).LE.0) THEN
142 1 pfleura2
                 Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
143 1 pfleura2
                 WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
144 1 pfleura2
              END IF
145 1 pfleura2
           END IF
146 1 pfleura2
        END IF
147 1 pfleura2
        IBeg=5
148 1 pfleura2
     CASE (3:)
149 1 pfleura2
        IBeg=NCart+1
150 1 pfleura2
        Idx=3*Ncart+2
151 1 pfleura2
152 1 pfleura2
     END SELECT
153 1 pfleura2
     DO Iat=5,Nat
154 1 pfleura2
        IF (STEP(Idx).GE.Eps) THEN
155 1 pfleura2
           If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
156 1 pfleura2
              Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
157 1 pfleura2
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
158 1 pfleura2
           END IF
159 1 pfleura2
           If (GeomOld(Idx)+Step(Idx).LE.0) THEN
160 1 pfleura2
              Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
161 1 pfleura2
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
162 1 pfleura2
           END IF
163 1 pfleura2
        END IF
164 1 pfleura2
        Idx=Idx+3
165 1 pfleura2
     END DO
166 1 pfleura2
167 1 pfleura2
  CASE ('CART','HYBRID','BAKER')
168 1 pfleura2
     if (debug) WRITE(*,*) "DBG Check_step:  Check useless for COORD=",TRIM(COORD)
169 1 pfleura2
  CASE DEFAULT
170 1 pfleura2
     WRITE(*,*) "COORD=",TRIM(COORD)," Not recognized in Check_step"
171 1 pfleura2
     STOP
172 1 pfleura2
  END SELECT
173 1 pfleura2
174 1 pfleura2
  If (debug) WRITE(*,*) "Check_Step: Fact=",Fact
175 1 pfleura2
  Step=Step*Fact
176 1 pfleura2
177 1 pfleura2
  if (debug) WRITE(*,*) "=========================== Exiting Check_Step ===================="
178 1 pfleura2
179 1 pfleura2
END SUBROUTINE Check_step