Statistiques
| Révision :

root / src / Check_step.f90

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

1
! This subroutine checks that the required step fulfills some conditions:
2
! v1.0
3
! Only valence angles are checked to remain in to 0:Pi range.
4

    
5
SUBROUTINE Check_step(Coord,Nat,NCoord,GeomOld,Step)
6

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

    
38
  Use Path_module, only : pi,ncart
39

    
40
  IMPLICIT NONE
41

    
42

    
43
  INTEGER, PARAMETER :: KINT=KIND(1)
44
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
45

    
46
  INTEGER(KINT), INTENT(IN) :: Nat,NCoord
47
  CHARACTER(32), INTENT(IN) :: Coord
48
  REAL(KREAL), INTENT(INOUT) :: Step(NCoord)
49
  REAL(KREAL), INTENT(IN) :: GeomOld(NCoord)
50

    
51
  ! As this subroutine is here for debugging, debug=T !
52
  LOGICAL, PARAMETER :: debug=.TRUE.
53

    
54

    
55
  ! Variables
56
  INTEGER(KINT) :: IBeg, Idx,Iat
57
  REAL(KREAL) ::  Fact
58

    
59
  ! Parameters
60
  REAL(KREAL),PARAMETER :: eps=1e-8
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
  if (.NOT.Valid("CheckStep")) RETURN
70

    
71
  if (nat.LE.2) THEN
72
     if (debug) WRITE(*,*) "Check-Step useless for 2 or less atoms !"
73
     return
74
  END IF
75

    
76
  if (debug) WRITE(*,*) "=========================== Entering Check_Step ===================="
77

    
78
  Fact=1.d0
79

    
80
  SELECT CASE(COORD)
81
  CASE ('ZMAT')
82
     Idx=3
83
     IF (STEP(Idx).GT.Eps) THEN
84
        If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
85
           Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
86
           WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
87
        END IF
88
        If (GeomOld(Idx)+Step(Idx).LE.0) THEN
89
           Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
90
           WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
91
        END IF
92
     END IF
93
     If (Nat.GT.3) THEN
94
        Idx=5
95
        IF (STEP(Idx).GE.Eps) THEN
96
           If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
97
              Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
98
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
99
           END IF
100
           If (GeomOld(Idx)+Step(Idx).LE.0) THEN
101
              Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
102
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
103
           END IF
104
        END IF
105
        DO Iat=5,Nat
106
           Idx=Idx+3
107
           IF (STEP(Idx).GE.Eps) THEN
108
              If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
109
                 Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
110
                 WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
111
              END IF
112
              If (GeomOld(Idx)+Step(Idx).LE.0) THEN
113
                 Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
114
                 WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx      
115
              END IF
116
           END IF
117
        END DO
118
     END IF
119

    
120
  CASE ('MIXED')
121
     SELECT CASE (NCart)
122
     CASE (1:2)
123
        Idx=3
124
        IF (STEP(Idx).GE.Eps) THEN
125
           If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
126
              Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
127
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
128
           END IF
129
           If (GeomOld(Idx)+Step(Idx).LE.0) THEN
130
              Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
131
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
132
           END IF
133
        END IF
134
        IF (Nat.GT.3) THEN
135
           Idx=5
136
           IF (STEP(Idx).GE.Eps) THEN
137
              If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
138
                 Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
139
                 WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
140
              END IF
141
              If (GeomOld(Idx)+Step(Idx).LE.0) THEN
142
                 Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
143
                 WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
144
              END IF
145
           END IF
146
        END IF
147
        IBeg=5
148
     CASE (3:)
149
        IBeg=NCart+1
150
        Idx=3*Ncart+2
151

    
152
     END SELECT
153
     DO Iat=5,Nat
154
        IF (STEP(Idx).GE.Eps) THEN
155
           If (GeomOld(Idx)+Step(Idx).GE.Pi) THEN
156
              Fact=min(Fact,0.999d0*(Pi-GeomOld(Idx))/Step(Idx))
157
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle >=180. Idx=",Idx
158
           END IF
159
           If (GeomOld(Idx)+Step(Idx).LE.0) THEN
160
              Fact=min(Fact,abs(0.999d0*GeomOld(Idx)/Step(Idx)))
161
              WRITE(*,*) "WARNING: Step reduced to prevent valence angle <=0. Idx=",Idx
162
           END IF
163
        END IF
164
        Idx=Idx+3
165
     END DO
166

    
167
  CASE ('CART','HYBRID','BAKER')
168
     if (debug) WRITE(*,*) "DBG Check_step:  Check useless for COORD=",TRIM(COORD)
169
  CASE DEFAULT
170
     WRITE(*,*) "COORD=",TRIM(COORD)," Not recognized in Check_step"
171
     STOP
172
  END SELECT
173

    
174
  If (debug) WRITE(*,*) "Check_Step: Fact=",Fact
175
  Step=Step*Fact
176

    
177
  if (debug) WRITE(*,*) "=========================== Exiting Check_Step ===================="
178

    
179
END SUBROUTINE Check_step