Statistiques
| Révision :

root / src / CalcTangent.f90

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

1 1 pfleura2
!This programs reads a set of geometries, and print the tangent
2 1 pfleura2
! to the path they form
3 1 pfleura2
4 1 pfleura2
SUBROUTINE CalcTangent(XgeomF,NGeomS,XGeom,Coef)
5 1 pfleura2
6 12 pfleura2
!----------------------------------------------------------------------
7 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
8 12 pfleura2
!  Centre National de la Recherche Scientifique,
9 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
10 12 pfleura2
!
11 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
12 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
13 12 pfleura2
!
14 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
15 12 pfleura2
!  Contact: optnpath@gmail.com
16 12 pfleura2
!
17 12 pfleura2
! This file is part of "Opt'n Path".
18 12 pfleura2
!
19 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
20 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
21 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
22 12 pfleura2
!  or (at your option) any later version.
23 12 pfleura2
!
24 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
25 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
26 12 pfleura2
!
27 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
28 12 pfleura2
!  GNU Affero General Public License for more details.
29 12 pfleura2
!
30 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
31 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
32 12 pfleura2
!
33 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
34 12 pfleura2
! for commercial licensing opportunities.
35 12 pfleura2
!----------------------------------------------------------------------
36 12 pfleura2
37 1 pfleura2
  use Path_module, only: IntCoordI, Nat, Coord, XyzGeomI, Atome, Order, &
38 1 pfleura2
                         OrderInv, IndZmat, NMaxPtPath, IntTangent, XyzTangent, &
39 1 pfleura2
             NGeomF, NCoord
40 1 pfleura2
  use Io_module, ONly : IoTmp,PathName, Kint,KReal
41 1 pfleura2
  use VarTypes
42 1 pfleura2
43 1 pfleura2
  IMPLICIT NONE
44 1 pfleura2
  ! NGeomS: number of geometries.
45 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: NGeomS
46 1 pfleura2
  REAL(KREAL), INTENT(IN) :: XGeomF(NGeomF),Xgeom(NGeomS),Coef(NGeomS,NCoord)
47 1 pfleura2
48 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: Path(:,:) ! NGeomS,NCoord
49 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: PathTan(:,:) ! NGeomF,NCoord
50 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: DbgTgt(:),GeomTmp(:) ! NCoord
51 1 pfleura2
52 2 pfleura2
  INTEGER(KINT) :: i, j, n3at, k
53 1 pfleura2
  INTEGER(KINT), SAVE :: icall=-1
54 1 pfleura2
  INTEGER(KINT) :: NMaxPt
55 2 pfleura2
!  REAL(KREAL), PARAMETER :: Inf=1e32, h=0.001d0
56 1 pfleura2
  CHARACTER(120) :: Line,File
57 1 pfleura2
  CHARACTER(LCHARS) :: TITLE
58 1 pfleura2
  LOGICAL :: Debug=.False.
59 2 pfleura2
  REAL(KREAL) :: utmp
60 1 pfleura2
61 1 pfleura2
  LOGICAL, EXTERNAL :: valid
62 1 pfleura2
63 1 pfleura2
  debug=valid('calctangent')
64 1 pfleura2
65 1 pfleura2
  if (debug) WRITE(*,*) "======================================== Entering CalcTangen ============================"
66 1 pfleura2
  n3at=3*nat
67 1 pfleura2
68 1 pfleura2
  ALLOCATE(Path(NGeomS,Ncoord),PathTan(NGeomF,NCoord),GeomTMP(NCoord))
69 1 pfleura2
70 1 pfleura2
 icall=icall+2
71 1 pfleura2
 write(Line,'(I5)') icall
72 1 pfleura2
 File=TRIM(adjustl(PathName)) // '_dbgtgt_' // TRIM(adjustl(Line)) // '.dat'
73 1 pfleura2
 OPEN(IOTMP,File=File)
74 1 pfleura2
75 1 pfleura2
  ! We construct path, depending on COORD:
76 1 pfleura2
  ! Path(NGeomS,Ncoord), NGeoms is equal to NGeomI
77 1 pfleura2
  ! IntCoordI(:,:) ! (NGeomI,3*Nat-6)
78 1 pfleura2
 SELECT CASE(Coord)
79 1 pfleura2
    CASE ('ZMAT','MIXED')
80 1 pfleura2
     Path(:,:)=IntCoordI(:,:)
81 1 pfleura2
  CASE ('CART','HYBRID')
82 1 pfleura2
     Path=reshape(XyzGeomI,(/NGeomS,NCoord/))
83 1 pfleura2
  CASE ('BAKER')
84 1 pfleura2
   Path(:,:)=IntCoordI(:,:)
85 1 pfleura2
  CASE DEFAULT
86 1 pfleura2
     WRITE(*,*) "Coord=",TRIM(COORD)," not recognized in CalcTangent. STOP"
87 1 pfleura2
     STOP
88 1 pfleura2
  END SELECT
89 1 pfleura2
90 1 pfleura2
91 1 pfleura2
  if (debug) THEN
92 1 pfleura2
     WRITE(*,*) 'DBG CalcTangent. Geometries from Path'
93 1 pfleura2
     DO I=1,NGeomS
94 1 pfleura2
        GeomTmp=Path(I,1:NCoord)
95 1 pfleura2
        WRITE(Title,"('Geometry ',I3,'/',I3,' for iteration ',I3)") I,NgeomS
96 1 pfleura2
        Call PrintGeom(Title,Nat,Ncoord,GeomTmp,Coord,6,Atome,Order,OrderInv,IndZmat)
97 1 pfleura2
!         IF (COORD.EQ.'ZMAT') THEN
98 1 pfleura2
!            WRITE(*,"('Geometry ',I3,'/',I3,' for iteration ',I3)") I,NgeomS
99 1 pfleura2
!            WRITE(*,'(1X,A5,3(1X,A4,1X,F11.6))') Nom(Atome(OrderInv(indzmat(1,1))))
100 1 pfleura2
!            WRITE(*,'(1X,A5,3(1X,A4,1X,F11.6))') Nom(Atome(OrderInv(indzmat(2,1)))), &
101 1 pfleura2
!                 Nom(Atome(OrderInv(indzmat(2,2)))),Path(I,1)
102 1 pfleura2
!            WRITE(*,'(1X,A5,3(1X,A4,1X,F11.6))') Nom(Atome(OrderInv(indzmat(3,1)))), &
103 1 pfleura2
!                 Nom(Atome(OrderInv(indzmat(3,2)))),Path(I,2), &
104 1 pfleura2
!                 Nom(Atome(OrderInv(indzmat(3,3)))),Path(I,3)
105 1 pfleura2
!            Idx=4
106 1 pfleura2
!            DO Iat=4,Nat
107 1 pfleura2
!               WRITE(*,'(1X,A5,3(1X,A4,1X,F11.6))') Nom(Atome(OrderInv(indzmat(iat,1)))), &
108 1 pfleura2
!                    Nom(Atome(OrderInv(indzmat(iat,2)))),Path(I,Idx), &
109 1 pfleura2
!                    Nom(Atome(OrderInv(indzmat(iat,3)))),Path(I,Idx+1), &
110 1 pfleura2
!                    Nom(Atome(OrderInv(indzmat(iat,4)))),Path(I,Idx+2)
111 1 pfleura2
!               Idx=Idx+3
112 1 pfleura2
!            END DO
113 1 pfleura2
!         ELSE
114 1 pfleura2
!            WRITE(*,*) Nat
115 1 pfleura2
!            WRITE(*,"('Geometry ',I3,'/',I3,' for iteration ',I3)") I,NgeomF
116 1 pfleura2
!            DO Iat=1,Nat
117 1 pfleura2
!               WRITE(*,'(1X,A5,3(1X,F11.6))') Nom(Atome(OrderInv(indzmat(iat,1)))), &
118 1 pfleura2
!                    Path(I,3*Iat-2:3*Iat)
119 1 pfleura2
!            END DO
120 1 pfleura2
!         END IF
121 1 pfleura2
     END DO
122 1 pfleura2
  END IF
123 1 pfleura2
124 1 pfleura2
!Debug info
125 1 pfleura2
 IF (debug.AND.(COORD.EQ.'ZMAT')) THEN
126 1 pfleura2
     ALLOCATE(DbgTgt(NCoord))
127 1 pfleura2
     WRITE(*,*) 'DBG CalcTangent. Path written in ' // TRIM(File)
128 1 pfleura2
     WRITE(*,'(A,12(1X,F10.5))') "DBG CalcTangent, XgeomF:",XGeomF
129 1 pfleura2
130 1 pfleura2
     NMaxPt=min(200,NMaxPtPath)-1
131 1 pfleura2
    DO K=0,NMaxPt
132 1 pfleura2
       utmp=K*Xgeom(NGeomS)/NMaxPt
133 1 pfleura2
       DO J=1,NCoord
134 1 pfleura2
       Call Splint(utmp,DbgTgt(J),NGeomS,Xgeom,Path(1,J),Coef(1,J))
135 1 pfleura2
       END DO
136 1 pfleura2
       WRITE(IOTMP,'(12(1X,F10.5))') utmp,DbgTgt
137 1 pfleura2
    END DO
138 1 pfleura2
    DEALLOCATE(DbgTgt)
139 1 pfleura2
 END IF
140 1 pfleura2
141 1 pfleura2
!We construct the derivatives
142 1 pfleura2
DO I=1,NGeomF
143 1 pfleura2
  DO J=1,NCoord
144 1 pfleura2
        Call SplinDer(XgeomF(I),PathTan(I,J),NGeomS,Xgeom,Path(1,J),Coef(1,J))
145 1 pfleura2
  END DO
146 1 pfleura2
END DO
147 1 pfleura2
148 1 pfleura2
 SELECT CASE(Coord)
149 1 pfleura2
    CASE ('ZMAT','MIXED')
150 1 pfleura2
     IntTangent=PathTan
151 1 pfleura2
  CASE ('CART','HYBRID')
152 1 pfleura2
     XyzTangent=Pathtan
153 1 pfleura2
  END SELECT
154 1 pfleura2
155 1 pfleura2
156 1 pfleura2
  if (debug) THEN
157 1 pfleura2
     WRITE(*,*) 'DBG CalcTangent. Tangents'
158 1 pfleura2
     DO I=1,NGeomF
159 1 pfleura2
        GeomTmp=PathTan(I,1:NCoord)
160 1 pfleura2
        WRITE(Title,"('Tangents for geometry ',I3,'/',I3,' for iteration ',I3)") I,NgeomF
161 1 pfleura2
        Call PrintGeom(Title,Nat,Ncoord,GeomTmp,Coord,6,Atome,Order,OrderInv,IndZmat)
162 1 pfleura2
163 1 pfleura2
        WRITe(*,'(A,12(1X,F10.6))') "Test:",GeomTmp(1:NCoord)
164 1 pfleura2
165 1 pfleura2
!         IF (COORD.EQ.'ZMAT') THEN
166 1 pfleura2
!            WRITE(*,"('Tangent for Geometry ',I3,'/',I3,' for iteration ',I3)") I,NgeomF
167 1 pfleura2
!            WRITE(*,'(1X,A5,3(1X,A4,1X,F11.6))') Nom(Atome(OrderInv(indzmat(1,1))))
168 1 pfleura2
!            WRITE(*,'(1X,A5,3(1X,A4,1X,F11.6))') Nom(Atome(OrderInv(indzmat(2,1)))), &
169 1 pfleura2
!                 Nom(Atome(OrderInv(indzmat(2,2)))),IntTangent(I,1)
170 1 pfleura2
!            WRITE(*,'(1X,A5,3(1X,A4,1X,F11.6))') Nom(Atome(OrderInv(indzmat(3,1)))), &
171 1 pfleura2
!                 Nom(Atome(OrderInv(indzmat(3,2)))),IntTangent(I,2), &
172 1 pfleura2
!                 Nom(Atome(OrderInv(indzmat(3,3)))),IntTangent(I,3)
173 1 pfleura2
!            Idx=4
174 1 pfleura2
!            DO Iat=4,Nat
175 1 pfleura2
!               WRITE(*,'(1X,A5,3(1X,A4,1X,F11.6))') Nom(Atome(OrderInv(indzmat(iat,1)))), &
176 1 pfleura2
!                    Nom(Atome(OrderInv(indzmat(iat,2)))),IntTangent(I,Idx), &
177 1 pfleura2
!                    Nom(Atome(OrderInv(indzmat(iat,3)))),IntTangent(I,Idx+1), &
178 1 pfleura2
!                    Nom(Atome(OrderInv(indzmat(iat,4)))),IntTangent(I,Idx+2)
179 1 pfleura2
!               Idx=Idx+3
180 1 pfleura2
!            END DO
181 1 pfleura2
!         ELSE
182 1 pfleura2
!            WRITE(*,*) Nat
183 1 pfleura2
!            WRITE(*,"('Tangent for Geometry ',I3,'/',I3,' for iteration ',I3)") I,NgeomF
184 1 pfleura2
!            DO Iat=1,Nat
185 1 pfleura2
!               WRITE(*,'(1X,A5,3(1X,F11.6))') Nom(Atome(OrderInv(indzmat(iat,1)))), &
186 1 pfleura2
!                    XyzTangent(I,3*Iat-2:3*Iat)
187 1 pfleura2
!            END DO
188 1 pfleura2
!         END IF
189 1 pfleura2
     END DO
190 1 pfleura2
  END IF
191 1 pfleura2
192 1 pfleura2
193 1 pfleura2
DeALLOCATE(Path)
194 1 pfleura2
195 1 pfleura2
 CLOSE(IOTMP)
196 1 pfleura2
  if (debug) WRITE(*,*) "======================================== Ending CalcTangent ============================"
197 1 pfleura2
198 1 pfleura2
END SUBROUTINE CalcTangent