Révision 1

utils/AnaPathrel (revision 1)
1
#!/bin/bash
2
if [ $# -lt 4 ]; then
3
 echo "Use: $0 File.out MaxCyc PathName NGeomF"
4
 exit
5
fi
6

  
7
Fout=$1
8
ItMax=$2
9
Nom=$3
10
NGeomF=$4
11

  
12
export LANG=C
13

  
14
echo "#ItMax=$ItMax"
15
echo "#Nom=$Nom"
16
echo "#NGeomF"=$NGeomF
17

  
18
if [ -s ${Nom}_cart.0 ]; then
19
 Ext=_cart
20
elif [ -s ${Nom}.0 ]; then
21
 Ext=""
22
else
23
 echo "Cannot find ${Nom}.0 nor ${Nom}_cart.0: ERROR"
24
 exit
25
fi
26
 echo "Using files ${Nom}${Ext}.XX"
27

  
28
if [ -s $Nom.datl ]; then
29
 it=1
30
 while [ -s $Nom.datl_${it} ]
31
  do
32
 let it=it+1
33
 done
34
 echo "Moving $Nom.datl into $Nom.datl_${it}"
35
 mv $Nom.datl $Nom.datl_${it}
36
fi
37
echo "Creating $Nom.datl"
38

  
39
for i in `seq 0 $ItMax`
40
 do
41
  xyz2path  ${Nom}${Ext}.$i 
42
 cat Scan.dat >> $Nom.datl
43
 echo " " >> $Nom.datl
44
 echo " " >> $Nom.datl
45
done 
46

  
47
E0=`head -1 Scan.dat | awk '{print $NF}' `
48

  
49
cat << EOF > ${Nom}_l.gplot
50
#!/usr/bin/gnuplot -persist
51
 set pointsize 2
52
 Eref=$E0
53
 Conv=627.51
54
EOF
55

  
56
for i in `seq 1 $ItMax`
57
do
58
 echo "plot \"$Nom.datl\" i 0 u 1:(\$2-Eref)*Conv w lp " >> ${Nom}_l.gplot
59
 echo "replot \"$Nom.datl\" i $i u 1:(\$2-Eref)*Conv w lp " >> ${Nom}_l.gplot
60
 echo "pause -1" >> ${Nom}_l.gplot
61
done
62
 echo "pause -1" >> ${Nom}_l.gplot
63

  
64
cat << EOF > ${Nom}_l2.gplot
65
#!/usr/bin/gnuplot -persist
66
 set pointsize 2
67
 Eref=$E0
68
 Conv=627.51
69
EOF
70

  
71
 echo "plot \"$Nom.datl\" i 0 u 1:(\$2-Eref)*Conv w lp " >>  ${Nom}_l2.gplot
72
for i in `seq 1 $ItMax`
73
do
74
 echo "replot \"$Nom.datl\" i $i u 1:(\$2-Eref)*Conv w lp " >>  ${Nom}_l2.gplot
75
done
76

  
77
cat << EOF > ${Nom}_l3.gplot
78
#!/usr/bin/gnuplot -persist
79
 set pointsize 2
80
 Eref=$E0
81
 Conv=627.51
82
EOF
83

  
84
 echo "plot \"$Nom.datl\" i 0 u 0:(\$2-Eref)*Conv w lp " >>  ${Nom}_l3.gplot
85
for i in `seq 1 $ItMax`
86
do
87
 echo "replot \"$Nom.datl\" i $i u 0:(\$2-Eref)*Conv w lp " >>  ${Nom}_l3.gplot
88
done
89

  
90
chmod u+x ${Nom}_l.gplot ${Nom}_l2.gplot ${Nom}_l3.gplot
0 91

  
utils/Xyz2Scan.f (revision 1)
1
          program Xyz2irc
2
! This programs reads a XYZ file and converts it into distances,
3
! valence angle and dihedral angles.
4
! It prints them as a function of the irc distance...
5
!-----------------------------------------------
6
! Input: name of the ROOT file of PAW
7
! it also needs a file call list which has the following structure:
8
! the first line gives the time when you want to start your analysis
9
! one line contains the type of the value you want to follow, it can be
10
! b  for a Bond distance
11
! a for an angle
12
! d for a dihedral
13
! this descriptor is followed by the number of the atoms involved !
14
! a typical file can be:
15
! 3.
16
! b  1  2
17
! b 2  3
18
! a 1 2 3
19
!----------------------------------------------
20
! Ouput: A files call Scan.dat
21
! wich contains in the first lines the input file (as a reminder)
22
! and then for each step the wanted values
23
!------------------------------------------------
24
! Second version also reads the energy (as to be written after E= on
25
! the comment line)
26
!------------------------------------------------
27
! Third version contains a new command: c for Center of Mass
28
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
29
! v 3.1 the c command now creates the center of mass... and allows
30
! people to do whatever they want with it...
31
! Syntax: c NbAt ListAt
32
!!
33
! v 3.2
34
! Added the p command that gives the oriented angle between two planes
35
! Syntax: p At1 At2 At3 At4 At5 At6
36
! At1, At2, At3 define the first plane
37
! At4, At5, At6 define the second plane
38
! How it works: gives the angles between the normal of the two planes, defined by
39
! the cross produc At2-At1 x At2-At3 etc.
40
!!!!
41

  
42

  
43
          IMPLICIT NONE
44
          INTEGER*4 maxnat,MaxList
45
          Parameter (MaxNat=10000,MaxList=100)
46
          character*120 f1
47
          REAL*8   geos(3,maxnat)
48
          character*33 fmt
49
          character*3 atoms(maxnat)
50
          character*5 Type
51
          Character*120 line
52
          INTEGER*4 NbPrint
53
          REAL*8   AU2PS,Pi
54
! Mass is not used for now.
55
!          REAL*8  Mass(MaxNat)
56
          REAL*8 Ener, Conv
57
          INTEGER*4 At1,At2,At3,At4,At5,At6,IOOUT
58
          INTEGER*4  IArg, I, NNN, Ng, J
59

  
60
          INTEGER*4 Nat,NbDist, NbAngle, NbDie,NbP,NbCOM
61
          INTEGER*4 At1B(MaxList),At2B(MaxList)
62
          INTEGER*4 At1A(MaxList),At2A(MaxList),At3A(MaxList)
63
          INTEGER*4 At1D(MaxList),At2D(MaxList),At3D(MaxList),
64
     $              At4D(MaxList)
65
          INTEGER*4 At1p(MaxList),At2p(MaxList),At3p(MaxList),
66
     $              At4p(MaxList),At5p(MaxList),At6p(MaxList) 
67
          INTEGER*4 AtCom(0:MaxList,MaxList)
68
          REAL*8    VB(MaxList),VA(MaxList),VD(MaxList),VCOM(MaxList)
69
          REAL*8    Vp(MaxList)
70
          LOGICAL FExist
71

  
72
c          INTEGER*4 iargc
73
c          external iargc
74

  
75
          COMMON /Indices/Nat,NbDist,NbAngle,NbDie,NbP,NbCom, At1B,At2B,
76
     &         At1A,At2A,At3A,At1D,At2D,At3D,At4D,AtCom,
77
     &         At1p,At2p,At3p,At4p,At5p,At6p
78
          COMMON /Values/VB,VA,VD,Vp,VCom
79
          COMMON /Const/AU2ps,Pi
80

  
81
          AU2PS=1./41341.37
82
          NbPrint=100
83
          Pi=dacos(-1.d0)
84
          IOOUT=13
85
          Conv=1.
86
          iarg=iargc()
87
          if (iarg.lt.1) then
88
             WRITE(*,*) "=============================================="
89
             WRITE(*,*) "==                                          =="
90
             WRITE(*,*) "==   Xyz2Scan: Xyz file to scan file        =="
91
             WRITE(*,*) "==                                          =="
92
             WRITE(*,*) "=============================================="
93
             WRITE(*,*) "Usage: xyz2scan XYZ_file "
94
             WRITE(*,*) "The XYZ file should follow the 'usual' format:"
95
             WRITE(*,*) "Number of atoms on the first line "
96
             WRITE(*,*) "Comment on the second line"
97
             WRITE(*,*) "The geometry is given in cartesian coordinates"
98
             WRITE(*,*) "with atom symbol and three coordinates:"
99
             WRITE(*,*) " C   0. 1. 0."
100
             WRITE(*,*) ""
101
             WRITE(*,*) " xyz2scan also needs a file called 'list' "
102
             WRITE(*,*) "which has the following structure:"
103
             WRITE(*,*) "Each line contains the type of the value you"
104
             WRITE(*,*) "want to follow, it can be:"
105
             WRITE(*,*) " - b  for a Bond distance"
106
             WRITE(*,*) " - a for an angle"
107
             WRITE(*,*) " - d for a dihedral"
108
             WRITE(*,*) " - p for the oriented angle between two planes"
109
             WRITE(*,*) "This descriptor is followed by the number of"
110
             WRITE(*,*) "the atoms involved"
111
             WRITE(*,*) "One can also create 'barycenter' atoms that"
112
             WRITE(*,*) "can then be used as normal atoms."
113
             WRITE(*,*) "the descriptor is 'c' followed by the number"
114
             WRITE(*,*) "of atoms and the list of atoms:"
115
             WRITE(*,*) " c 2  1 5"
116
             WRITE(*,*) "A typical file can be:"
117
             WRITE(*,*) " b  1  2"
118
             WRITE(*,*) " b 2  3"
119
             WRITE(*,*) " a 1 2 3"
120
             WRITE(*,*) "     "
121
             WRITE(*,*) "=============================================="
122
             write(*,*) 'XYZ filename:'
123
              read(*,'(a)') f1
124
            else
125
              call getarg(1,f1)
126
          endif
127

  
128
          open(13,file='Scan.dat')
129

  
130
          INQUIRE(File='list',Exist=FExist)
131
          if (.NOT.FExist) THEN
132
             WRITE(*,*) "File *list* is missing"
133
             STOP
134
          END IF
135

  
136
          open(11,file=f1)
137
          READ(11,*) nnn
138
          close(11)
139

  
140
          if (nnn.GT.MaxNat) THEN
141
             WRITE(*,*) "Sorry but your system has too many atoms"
142
             WRITE(*,*) "Change the value of MaxNat in the source file"
143
             WRITE(*,*) "and then recompile."
144
             WRITE(*,*) "For information, now MaxNat=",MaxNat
145
             WRITE(*,*) "and you have ",nnn," atoms."
146
             STOP
147
          END IF
148

  
149
         open(14,file='list')
150
         Type="d"
151
         DO WHILE (Type.ne."E")
152
          CALL READLINE(14,Type,Line)
153
!          WRITE(*,*) Line,Type
154
          if (Type.eq."b") THEN
155
             NbDist=NbDist+1
156
             READ(Line,*) At1,At2
157
             At1B(NbDist)=At1
158
             At2B(NbDist)=At2
159
          END IF
160
          if (Type.eq."a") THEN
161
             NbAngle=NbAngle+1
162
             READ(Line,*) At1,At2,At3
163
             At1A(NbAngle)=At1
164
             At2A(NbAngle)=At2
165
             At3A(NbAngle)=At3
166
          END IF
167
          if (Type.eq."d") THEN
168
             NbDie=NbDie+1
169
             READ(Line,*) At1,At2,At3,At4
170
             At1D(NbDie)=At1
171
             At2D(NbDie)=At2
172
             At3D(NbDie)=At3
173
             At4D(NbDie)=At4
174
!            WRITE(13,'("# d ",4(A3,I3))') Atoms(At1),At1,Atoms(At2),At2,  
175
!     &          Atoms(At3),At3,Atoms(At4),At4
176
!            WRITE(*,'("# d ",4(A3,I3))') Atoms(At1),At1,Atoms(At2),At2,   
177
!     &          Atoms(At3),At3,Atoms(At4),At4
178

  
179
          END IF
180
          if (Type.eq."p") THEN
181
             NbP=NbP+1
182
             READ(Line,*) At1,At2,At3,At4,At5,At6
183
             At1p(NbP)=At1
184
             At2p(NbP)=At2
185
             At3p(NbP)=At3
186
             At4p(NbP)=At4
187
             At5p(NbP)=At5
188
             At6p(NbP)=At6
189
          END IF
190

  
191
          if (Type.eq."c") THEN
192
            NbCOM=NbCOM+1
193
            READ(Line,*) At1,(AtCom(j,NbCOM),j=1,At1)
194
            AtCom(0,NbCOM)=At1
195
            Atoms(nat+NbCom)="G"
196
          END IF
197

  
198
         END DO
199

  
200
         CLOSE(14)
201

  
202
! We read one geoetry to get the atoms name
203
         open(11,file=f1)
204
          call rtraitem(11,nnn,ener,geos,atoms)
205
         close(11)
206

  
207

  
208
! We write things
209
! First NbCom
210
         if (NbCom.GE.1) THEN
211
            WRITE(*,*) "# Added center of mass"
212
            WRITE(IOOUT,*) "# Added center of mass"
213
            DO J=1,NbCom
214
            WRITE(IOOUT,'("# c ",I4,20(A3,I3))') AtCom(0,J),                  
215
     &          (Atoms(AtCom(i,J)),AtCom(i,J),i=1,At1)
216
            WRITE(*,'("# c ",I4,20(A3,I3))') AtCom(0,J),                   
217
     &          (Atoms(AtCom(i,J)),AtCom(i,J),i=1,At1)
218
            END DO
219
         END IF
220

  
221
! Distances
222
         if (NbDist.GE.1) THEN
223
            WRITE(*,*) "# Bonds"
224
            WRITE(IOOUT,*) "# Bonds"
225
            DO J=1,NbDist
226
               At1= At1B(J)
227
               At2=At2B(J)
228
             WRITE(IOOUT,'("# b ",2(A3,I3))') Atoms(At1),At1,
229
     $              Atoms(At2),At2
230
             WRITE(*,'("# b ",2(A3,I3))') Atoms(At1),At1,Atoms(At2),At2
231
            END DO
232
         END IF
233

  
234
! Angles
235
         if (NbAngle.GE.1) THEN
236
            WRITE(*,*) "# Angles"
237
            WRITE(IOOUT,*) "# Angles"
238
            DO J=1,NbAngle
239
            At1= At1A(J)
240
            At2= At2A(J)
241
            At3= At3A(J)
242
            WRITE(IOOUT,'("# a ",3(A3,I3))') Atoms(At1),At1,Atoms(At2),
243
     &            At2, Atoms(At3),At3
244
            WRITE(*,'("# a ",3(A3,I3))') Atoms(At1),At1,Atoms(At2),
245
     &           At2, Atoms(At3),At3
246

  
247
            END DO
248
         END IF
249

  
250

  
251
! Dihedrals 
252
         if (NbDie.GE.1) THEN
253
            WRITE(*,*) "# Dihedrals"
254
            WRITE(IOOUT,*) "# Dihedrals"
255
            DO J=1,NbDie
256
            At1= At1D(J)
257
            At2= At2D(J)
258
            At3= At3D(J)
259
            At4= At4D(J)
260
            WRITE(IOOUT,'("# d ",4(A3,I3))') Atoms(At1),At1,Atoms(At2)
261
     &          ,At2,Atoms(At3),At3,Atoms(At4),At4
262
            WRITE(*,'("# d ",4(A3,I3))') Atoms(At1),At1,Atoms(At2),At2,   
263
     &          Atoms(At3),At3,Atoms(At4),At4
264
            END DO
265
         END IF
266

  
267
! Planar angles
268
         if (NbP.GE.1) THEN
269
            WRITE(*,*) "# Planes angles"
270
            WRITE(IOOUT,*) "# Planes angles"
271
            DO J=1,NbP
272
            At1= At1p(J)
273
            At2= At2p(J)
274
            At3= At3p(J)
275
            At4= At4p(J)
276
            At5= At5p(J)
277
            At6= At6p(J)
278
            WRITE(IOOUT,'("# p ",8(A3,I3))') Atoms(At1),At1,Atoms(At2)
279
     &          ,At2,Atoms(At3),At3,Atoms(At4),At4
280
     &          ,Atoms(At5),At5,Atoms(At6),At6
281
            WRITE(*,'("# p ",8(A3,I3))') Atoms(At1),At1,Atoms(At2),At2,   
282
     &          Atoms(At3),At3,Atoms(At4),At4
283
     &          ,Atoms(At5),At5,Atoms(At6),At6
284
            END DO
285
         END IF
286

  
287

  
288
          fmt='(   (1X,F12.5),1X,F15.6)'
289
          write(fmt(2:4),'(i3)') NbDist+NbAngle+NbDie+NbP
290
!           write(*,*) nat3
291
!          write(*,*) 'fmt:',fmt
292

  
293
          ng=1
294

  
295
          open(11,file=f1)
296

  
297
10           call rtraitem(11,nnn,ener,geos,atoms)
298
!           WRITE(*,*) nnn
299

  
300
           if (nnn.gt.0) then
301
! We convert coordinates in a0 into Angstroem
302
!              write(*,*) "Analyse !"
303
            Call Analyse(geos)
304

  
305
             write(IOOUT,fmt) (VB(j)/Conv,j=1,NbDist),
306
     &            (VA(j),j=1,NbAngle),
307
     &            (VD(j),j=1,NbDie),(Vp(j),j=1,NbP),ener
308
             write(*,fmt) (VB(j)/Conv,j=1,NbDist),
309
     &            (VA(j),j=1,NbAngle),
310
     &            (VD(j),j=1,NbDie),(Vp(j),j=1,NbP),ener
311

  
312
           ng=ng+1
313
            goto 10
314
           endif
315
           WRITE(*,*) 'Found ',ng-1,' geometries'
316
           close(11)
317
         end
318

  
319
!--------------------------------------------------------------
320
          subroutine rtraitem(ifil,nnn,E,tab,atoms)
321
!           implicit real*8 (a-h,o-z)
322
            IMPLICIT NONE
323
           character*120 line
324
           character*3 Atoms(*)
325
           integer*4 nnn, IFil, Idx, I, J
326
           REAL*8  Tab(3,*), E
327

  
328

  
329
           read(ifil,*,err=99,end=99) nnn
330
           read(ifil,'(A)') line
331
           idx=index(line,'E')
332
!           WRITE(*,*) 'idx,line',idx,line
333
           if (idx/=0) THEN
334
             line=line(idx+2:)
335
              idx=index(line,"=")
336
              if (idx/=0) line=line(idx+1:)
337
              idx=index(line,":")
338
              if (idx/=0) line=line(idx+1:)
339
              read(line,*) E
340
           ELSE
341
             E=0.
342
           END IF
343
           
344
!           write(*,*) 'coucou',line
345
           do i=1,nnn
346
              read(ifil,'(A)',err=99,end=99) Line
347
              do while (line(1:1)==' ')
348
                 line=line(2:)
349
              end do
350
              atoms(i)=line(1:3)
351
!            write(*,*) 'coucou atoms',atoms(i)
352
              do while (line(1:1).ne.' ')
353
                 line=line(2:)
354
              end do
355
!              WRITE(*,*) 'coucou2:',i,line
356
              read(line,*) (tab(j,i),j=1,3)
357
           end do
358
!           WRITE(*,*) 'coucou:',nnn,tab(1,1)
359
           return
360
99           nnn=0
361
!             WRITE(*,*) 'Erreur lecture',ifil,nnn
362
             return
363
          end
364

  
365
!--------------------------------------------------------------
366

  
367
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
368
! READLINE
369
! This subroutine reads a line for a file, and converts
370
! the first field into a character variable, and the rest into 4 integers
371
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
372

  
373
      SUBROUTINE READLINE(IOIN,Type,Line)
374
        
375
       IMPLICIT NONE
376
      CHARACTER Type*5,LINE*120
377
      INTEGER i,IOIN
378
      READ(IOIN,'(A120)',ERR=999,END=999) LINE
379
!      WRITE(*,*) Line
380
      DO WHILE (LINE(1:1).eq.' ')
381
         LINE=LINE(2:)
382
      END DO
383

  
384
      i=1
385
      DO WHILE (LINE(i:i).ne.' ')
386
         i=i+1
387
      END DO
388
      
389
      if (i.ge.6) THEN
390
         WRITE(*,*) 'Pb with READLINE:',LINE
391
         GOTO 999
392
      END IF
393
      Type=LINE(1:i-1)
394
      LINE=LINE(i:120) // " 0 0 0 0"
395

  
396
      RETURN
397
 999  Type="E"
398
      END
399

  
400

  
401

  
402
      SUBROUTINE Analyse(geos)
403

  
404
      IMPLICIT NONE
405
      INTEGER*4 MaxNat,MaxList
406
      parameter (maxnat=10000,MaxList=100)
407
      REAL*8 geos(3,maxnat)
408
      REAL*8 AU2PS,Pi
409
      INTEGER*4 i,j,k
410
      REAL*8 V1x,V1y,V1z,V2x,V2y,V2z,V3x,V3y,V3z
411
      REAL*8 d1,d2,ca,sa
412
      REAL*8 V4x,v4y,v4z,v5x,v5y,v5z
413
      REAL*8 COG(3)
414

  
415
          INTEGER*4 Nat,NbDist, NbAngle, NbDie,NbP,NbCOM
416
          INTEGER*4 At1B(MaxList),At2B(MaxList)
417
          INTEGER*4 At1A(MaxList),At2A(MaxList),At3A(MaxList)
418
          INTEGER*4 At1D(MaxList),At2D(MaxList),At3D(MaxList),
419
     $              At4D(MaxList)
420
          INTEGER*4 At1p(MaxList),At2p(MaxList),At3p(MaxList),
421
     $              At4p(MaxList),At5p(MaxList),At6p(MaxList)
422
          INTEGER*4 AtCom(0:MaxList,MaxList)
423
          REAL*8    VB(MaxList),VA(MaxList),VD(MaxList),VCOM(MaxList)
424
          REAL*8    Vp(MaxList)
425

  
426
          COMMON /Indices/Nat,NbDist,NbAngle,NbDie,NbP,NbCom, At1B,At2B,
427
     &         At1A,At2A,At3A,At1D,At2D,At3D,At4D,AtCom,
428
     &         At1p,At2p,At3p,At4p,At5p,At6p
429
          COMMON /Values/VB,VA,VD,Vp,VCom
430
          COMMON /Const/AU2ps,Pi
431

  
432
          DO I=1,Nat
433
             WRITE(*,'(1X,I3,3(1X,F15.6))') i,(geos(j,i),j=1,3)
434
          END DO
435

  
436
! First, we create the Centre of Mass atoms
437
            DO i=1,NbCOM
438
              COG(1)=0.
439
              COG(2)=0.
440
              COG(3)=0.
441
              DO j=1,AtCOm(0,i)
442
                 DO k=1,3
443
                    COG(k)=COG(k)+geos(k,AtCom(j,i))
444
                 END DO
445
              END DO
446
              DO k=1,3
447
                 COG(k)=COG(k)/AtCOM(0,i)
448
                 geos(k,Nat+i)=COG(k)
449
              END DO
450
            END DO
451

  
452

  
453
            DO i=1,NbDist
454
               VB(i)=sqrt((geos(1,At1B(i))-geos(1,At2B(i)))**2+  
455
     &      (geos(2,At1B(i))-geos(2,At2B(i)))**2+                     
456
     &      (geos(3,At1B(i))-geos(3,At2B(i)))**2)
457
            END DO
458
            DO i=1,NbAngle
459
               v1x=geos(1,At1A(i))-geos(1,At2A(i))
460
               v1y=geos(2,At1A(i))-geos(2,At2A(i))
461
               v1z=geos(3,At1A(i))-geos(3,At2A(i))
462
               d1=sqrt(v1x**2+v1y**2+v1z**2)
463
               v2x=geos(1,At3A(i))-geos(1,At2A(i))
464
               v2y=geos(2,At3A(i))-geos(2,At2A(i))
465
               v2z=geos(3,At3A(i))-geos(3,At2A(i))
466
               d2=sqrt(v2x**2+v2y**2+v2z**2)
467
               VA(i)=acos((v1x*v2x+v1y*v2y+v1z*v2z)/(d1*d2))*180./Pi
468
            END DO
469
            DO i=1,NbDie
470
!               WRITE(*,*) At1D(i),At2D(i),At3D(i),At4D(i)
471
!              WRITE(*,*) geos(1,At1D(i)),geos(2,At1D(i)),geos(3,At1D(i))
472
!              WRITE(*,*) geos(1,At2D(i)),geos(2,At2D(i)),geos(3,At2D(i))
473
               v1x=geos(1,At1D(i))-geos(1,At2D(i))
474
               v1y=geos(2,At1D(i))-geos(2,At2D(i))
475
               v1z=geos(3,At1D(i))-geos(3,At2D(i))
476
               v2x=geos(1,At3D(i))-geos(1,At2D(i))
477
               v2y=geos(2,At3D(i))-geos(2,At2D(i))
478
               v2z=geos(3,At3D(i))-geos(3,At2D(i))
479
               v3x=geos(1,At4D(i))-geos(1,At3D(i))
480
               v3y=geos(2,At4D(i))-geos(2,At3D(i))
481
               v3z=geos(3,At4D(i))-geos(3,At3D(i))
482
          
483
               v4x=v1y*v2z-v1z*v2y
484
               v4y=v1z*v2x-v1x*v2z
485
               v4z=v1x*v2y-v1y*v2x
486
               d1=sqrt(v4x**2+v4y**2+v4z**2)
487
               v5x=-v2y*v3z+v2z*v3y
488
               v5y=-v2z*v3x+v2x*v3z
489
               v5z=-v2x*v3y+v2y*v3x
490
               d2=sqrt(v5x**2+v5y**2+v5z**2)
491
               if (d1<=1e-12) THEN
492
                  WRITE(*,*) "WARNING: Dihedral, d1=0"
493
                  ca=-1.
494
                  sa=0.
495
               END IF
496
               if (d2<=1e-12) THEN
497
                  WRITE(*,*) "WARNING: Dihedral, d2=0"
498
                  ca=-1.
499
                  sa=0.
500
               END IF
501
               ca=(v4x*v5x+v4y*v5y+v4z*v5z)/(d1*d2)
502
               sa=v1x*v5x+v1y*v5y+v1z*v5z
503
               if (abs(ca)>1.) ca=sign(1.d0,ca)
504
               VD(i)=acos(ca)*180./Pi
505
               if (sa<0.) VD(i)=-VD(i)
506
!               WRITE(*,*) "Dihe",v5x,v5y,v5z,v4x,v4y,v4z,d1,d2,
507
!     &(v4x*v5x+v4y*v5y+v4z*v5z)/(d1*d2),pi
508
!                WRITE(*,*) "Dihe ca,sa,d1,d2",ca,sa,d1,d2,acos(ca)
509

  
510
               
511
!!!!!!!!! Another solution, more elegant ?
512
!               norm2=sqrt(v2x**2+v2y**2+v2z**2)
513
!               sa=(v4x*(v5y*v2z-v5z*v2y) 
514
!     *            -v4y*(v5x*v2z-v5z*v2x) 
515
!     *            +v4z*(v5x*v2y-v5y*v2x))
516
!     *       /(d1*norm2*d2)
517
!               angle_d=datan2(sa,ca)*180./Pi
518
!               WRITE(*,*) sa,ca,angle_d,d1,d2,norm2
519
!               WRITE(*,*) VD(i),angle_d
520
            END DO
521

  
522
            DO i=1,NbP
523
! v1= At2-At1
524
               v1x=geos(1,At1p(i))-geos(1,At2p(i))
525
               v1y=geos(2,At1p(i))-geos(2,At2p(i))
526
               v1z=geos(3,At1p(i))-geos(3,At2p(i))
527
! v2=At2-At3
528
               v2x=geos(1,At3p(i))-geos(1,At2p(i))
529
               v2y=geos(2,At3p(i))-geos(2,At2p(i))
530
               v2z=geos(3,At3p(i))-geos(3,At2p(i))
531
! v4 = v1 x v2
532
               v4x=v1y*v2z-v1z*v2y
533
               v4y=v1z*v2x-v1x*v2z
534
               v4z=v1x*v2y-v1y*v2x
535
               d1=sqrt(v4x**2+v4y**2+v4z**2)
536

  
537
! v3= At5-At4
538
               v3x=geos(1,At4p(i))-geos(1,At5p(i))
539
               v3y=geos(2,At4p(i))-geos(2,At5p(i))
540
               v3z=geos(3,At4p(i))-geos(3,At5p(i))
541
! v2=At5-At6
542
               v2x=geos(1,At6p(i))-geos(1,At5p(i))
543
               v2y=geos(2,At6p(i))-geos(2,At5p(i))
544
               v2z=geos(3,At6p(i))-geos(3,At5p(i))
545

  
546
! v5 = v3 x v2
547
               v5x=v3y*v2z-v3z*v2y
548
               v5y=v3z*v2x-v3x*v2z
549
               v5z=v3x*v2y-v3y*v2x
550
               d2=sqrt(v5x**2+v5y**2+v5z**2)
551

  
552
               ca=(v4x*v5x+v4y*v5y+v4z*v5z)/(d1*d2)
553
               sa=v1x*v5x+v1y*v5y+v1z*v5z
554
               Vp(i)=acos(ca)*180./Pi
555
               if (sa<0.) Vp(i)=-Vp(i)
556
!               WRITE(*,*) "Dihe",v5x,v5y,v5z,v4x,v4y,v4z,d1,d2,
557
!     &(v4x*v5x+v4y*v5y+v4z*v5z)/(d1*d2),pi
558
!!!!!!!!! Another solution, more elegant ?
559
! See Dihedral routine
560
            END DO
561

  
562

  
563
        END
0 564

  
utils/Xyz2Path.param (revision 1)
1
       INTEGER*4 MaxNAt
2
       PARAMETER (MaxNat=500)
utils/AnaPath (revision 1)
1
#!/bin/bash
2
if [ $# -lt 4 ]; then
3
 echo "Use: $0 File.out MaxCyc PathName NGeomF [x column]"
4
 exit
5
fi
6

  
7
Fout=$1
8
ItMax=$2
9
Nom=$3
10
NGeomF=$4
11

  
12
xcol=1
13
if [ $# -eq 5 ]; then
14
xcol=$5
15
fi
16

  
17
export LANG=C
18

  
19
echo "#ItMax=$ItMax"
20
echo "#Nom=$Nom"
21
echo "#NGeomF"=$NGeomF
22

  
23
if [ -s ${Nom}_cart.0 ]; then
24
 Ext=_cart
25
elif [ -s ${Nom}.0 ]; then
26
 Ext=""
27
else
28
 echo "Cannot find ${Nom}.0 nor ${Nom}_cart.0 -- ERROR"
29
 exit
30
fi
31
 echo "Using files ${Nom}${Ext}.XX"
32

  
33
if [ -s $Nom.datl ]; then
34
 it=1
35
 while [ -s $Nom.datl_${it} ]
36
  do
37
 let it=it+1
38
 done
39
 echo "Moving $Nom.datl into $Nom.datl_${it}"
40
 mv $Nom.datl $Nom.datl_${it}
41
fi
42
echo "Creating $Nom.datl"
43

  
44
for i in `seq 0 $ItMax`
45
 do
46
  xyz2path  ${Nom}${Ext}.$i 
47
 cat Scan.dat >> $Nom.datl
48
 echo " " >> $Nom.datl
49
 echo " " >> $Nom.datl
50
done 
51

  
52
icol=`tail -1 Scan.dat | wc -w`
53

  
54
cat << EOF > ${Nom}_l.gplot
55
#!/usr/bin/gnuplot -persist
56
 set pointsize 2
57
 xcol=$xcol
58
EOF
59

  
60

  
61
for i in `seq 1 $ItMax`
62
do
63
 echo "plot \"$Nom.datl\" i 0 u xcol:$icol w lp " >> ${Nom}_l.gplot
64
 echo "replot \"$Nom.datl\" i $i u xcol:$icol w lp " >> ${Nom}_l.gplot
65
 echo "pause -1" >> ${Nom}_l.gplot
66
done
67
 echo "pause -1" >> ${Nom}_l.gplot
68

  
69

  
70
chmod u+x  ${Nom}_l.gplot
71

  
72
cat << EOF > ${Nom}_l2.gplot
73
#!/usr/bin/gnuplot -persist
74
 set pointsize 2
75
 xcol=$xcol
76
EOF
77

  
78
echo "plot \"$Nom.datl\" i 0 u xcol:$icol w lp " >>  ${Nom}_l2.gplot
79
for i in `seq 1 $ItMax`
80
do
81
 echo "replot \"$Nom.datl\" i $i u xcol:$icol w lp " >>  ${Nom}_l2.gplot
82
done
83

  
84
chmod u+x  ${Nom}_l2.gplot
85

  
86
cat << EOF > ${Nom}_l3.gplot
87
#!/usr/bin/gnuplot -persist
88
 set pointsize 2
89
EOF
90

  
91
 echo "plot \"$Nom.datl\" i 0 u 0:$icol w lp " >>  ${Nom}_l3.gplot
92
for i in `seq 1 $ItMax`
93
do
94
 echo "replot \"$Nom.datl\" i $i u 0:$icol w lp " >>  ${Nom}_l3.gplot
95
done
96

  
97
chmod u+x  ${Nom}_l3.gplot
0 98

  
utils/Makefile (revision 1)
1
link ../src/Makefile
0 2

  
utils/Xyz2Path.f (revision 1)
1
          program Xyz2Path
2
! This programs reads a XYZ file and converts it into distances,
3
! valence angle and dihedral angles.
4
! It prints them as a function of the irc distance...
5
!-----------------------------------------------
6
! Input: name of the XYZ File
7
! it also needs a file call list which has the following structure:
8
! one line contains the type of the value you want to follow, it can be
9
! b  for a Bond distance
10
! a for an angle
11
! d for a dihedral
12
! this descriptor is followed by the number of the atoms involved !
13
! a typical file can be:
14
! b  1  2
15
! b 2  3
16
! a 1 2 3
17
!----------------------------------------------
18
! Ouput: A files call Scan.dat
19
! wich contains in the first lines the input file (as a reminder)
20
! and then for each step the wanted values
21
!------------------------------------------------
22
! Second version also reads the energy (as to be written after E= on
23
! the comment line)
24
!------------------------------------------------
25
! Third version contains a new command: c for Center of Mass
26
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
27
! v 3.1 the c command now creates the center of mass... and allows
28
! people to do whatever they want with it...
29
! Syntax: c NbAt ListAt
30

  
31

  
32
          IMPLICIT NONE
33

  
34
          INCLUDE "Xyz2Path.param"
35

  
36
          character*40 f1
37
          REAL*8   geos(3,maxnat), geos1(3,maxnat)
38
          character*33 fmt
39
          character*3 atoms(maxnat)
40
          character*5 Type
41
          Character*120 line
42
          INTEGER*4 NbPrint
43
          REAL*8   AU2PS,Pi
44
          REAL*8  Mass(MaxNat), Ener, Conv, Ds, s
45
          REAL*8  MassAt(0:86)
46
          INTEGER*4 At1,At2,At3,At4,IOOUT,Iat
47
          INTEGER*4  IArg, I, NNN, Ng, J
48

  
49
          INTEGER*4 Nat,NbDist, NbAngle, NbDie,NbCOM
50
          INTEGER*4 At1B(MaxNat),At2B(MaxNat)
51
          INTEGER*4 At1A(MaxNat),At2A(MaxNat),At3A(MaxNat)
52
          INTEGER*4 At1D(MaxNat),At2D(MaxNat),At3D(MaxNat),At4D(MaxNat)
53
          INTEGER*4 AtCom(0:MaxNat,MaxNat)
54
          REAL*8    VB(MaxNat),VA(MaxNat),VD(MaxNat),VCOM(MaxNat)
55

  
56
          REAL*8 MRot(3,3), Rmsd
57
          LOGICAL FExist,FRot,FAlign,Debug
58

  
59
          INTEGER*4 ConvertNumAt
60
          external ConvertNumAt
61

  
62
          COMMON /Indices/Nat,NbDist,NbAngle,NbDie,NbCom, At1B,At2B,
63
     &         At1A,At2A,At3A,At1D,At2D,At3D,At4D,AtCom
64
          COMMON /Values/VB,VA,VD,VCom
65
          COMMON /Const/AU2ps,Pi
66
 
67
          DATA MassAt/0.0D0,                                             
68
     $           1.0078D0,                      4.0026D0,                
69
     $            7.0160D0, 9.0122D0,11.0093D0,                          
70
     $           12.0000D0,14.0031D0,15.9949D0,18.9984D0,19.9924D0,      
71
     $           22.9898D0,23.9850D0,26.9815D0,                          
72
     $           27.9769D0,30.9738D0,31.9721D0,34.9688D0,39.9624D0,      
73
     $           39.0983D0,40.08D0,                                      
74
     $             44.9559D0, 47.88D0, 50.9415D0, 51.996D0, 54.9380D0,   
75
     $             55.847D0, 58.9332D0, 58.69D0, 63.546D0, 65.39D0,      
76
     $           69.72D0,72.59D0,74.9216D0,78.96D0,79.904D0,83.80D0,     
77
     $           85.4678D0,87.62D0,88.9059D0,91.224D0,92.9064D0,         
78
     $   95.94D0,98D0,101.07D0,102.906D0,106.42D0,107.868D0,112.41D0,    
79
     $   114.82D0,118.71D0,121.75D0,127.60D0,126.905D0,131.29D0,          
80
!     6           'CS','BA',
81
     $           132.905,137.34,                                          
82
!     6       'LA',
83
!               'CE','PR','ND','PM','SM','EU','GD',
84
!               'TB','DY','HO', 'ER','TM','YB','LU',
85
     $      138.91,                                                       
86
     $       140.12, 130.91, 144.24,147.,150.35, 151.96,157.25,           
87
     $       158.924, 162.50, 164.93, 167.26,168.93,173.04,174.97,        
88
!     6                'HF','TA',' W','RE','OS','IR','PT',
89
!                      'AU','HG',
90
!     6                                 'TL','PB','BI','PO','AT','RN'/
91
     $       178.49, 180.95, 183.85, 186.2, 190.2, 192.2, 195.09,         
92
     $       196.97, 200.59,                                              
93
     $       204.37, 207.19,208.98,210.,210.,222. /
94

  
95

  
96
          AU2PS=1./41341.37
97
          NbPrint=100
98
          Pi=dacos(-1.d0)
99
          IOOUT=13
100
          Conv=1.
101
          FRot=.TRUE.
102
          FAlign=.TRUE.
103
          Debug=.FALSE.
104
          NbDist=0
105
          NbAngle=0
106
          NbDie=0
107

  
108
          iarg=command_argument_count()
109
          if (iarg.lt.1) then
110
                 write(*,*) 'XYZ filename:'
111
              read(*,'(a)') f1
112
            else
113
              call getarg(1,f1)
114
          endif
115

  
116
          open(13,file='Scan.dat')
117

  
118
          INQUIRE(File='list',Exist=FExist)
119
          if (.NOT.FExist) THEN
120
             WRITE(*,*) "No file 'list', just printing Energy"
121
          END IF
122

  
123
          open(11,file=f1)
124
          call rtraitem(11,nnn,ener,geos1,atoms)
125
          close(11)
126

  
127
         DO I=1,nnn
128
            Iat=ConvertNumAt(atoms(I))
129
            Mass(I)=MassAt(Iat)
130
!           write(*,*) I,Atoms(I),Mass(I),geos1(:,I)
131
         END DO
132

  
133
         if (FExist) THEN
134
         open(14,file='list')
135
         Type="d"
136
         DO WHILE (Type.ne."E")
137
          CALL READLINE(14,Type,Line)
138
!          WRITE(*,*) Line,Type
139
          if (Type.eq."b") THEN
140
             NbDist=NbDist+1
141
             READ(Line,*) At1,At2
142
             At1B(NbDist)=At1
143
             At2B(NbDist)=At2
144
             WRITE(13,'("# b ",2(A3,I3))') Atoms(At1),At1,Atoms(At2),At2
145
             WRITE(*,'("# b ",2(A3,I3))') Atoms(At1),At1,Atoms(At2),At2
146
          END IF
147
          if (Type.eq."a") THEN
148
             NbAngle=NbAngle+1
149
             READ(Line,*) At1,At2,At3
150
             At1A(NbAngle)=At1
151
             At2A(NbAngle)=At2
152
             At3A(NbAngle)=At3
153
            WRITE(13,'("# a ",3(A3,I3))') Atoms(At1),At1,Atoms(At2),
154
     &            At2, Atoms(At3),At3
155
            WRITE(*,'("# a ",3(A3,I3))') Atoms(At1),At1,Atoms(At2),
156
     &           At2, Atoms(At3),At3
157
          END IF
158
          if (Type.eq."d") THEN
159
             NbDie=NbDie+1
160
             READ(Line,*) At1,At2,At3,At4
161
             At1D(NbDie)=At1
162
             At2D(NbDie)=At2
163
             At3D(NbDie)=At3
164
             At4D(NbDie)=At4
165
            WRITE(13,'("# d ",4(A3,I3))') Atoms(At1),At1,Atoms(At2),At2,  
166
     &          Atoms(At3),At3,Atoms(At4),At4
167
            WRITE(*,'("# d ",4(A3,I3))') Atoms(At1),At1,Atoms(At2),At2,   
168
     &          Atoms(At3),At3,Atoms(At4),At4
169

  
170
          END IF
171
          if (Type.eq."c") THEN
172
            NbCOM=NbCOM+1
173
            READ(Line,*) At1,(AtCom(j,NbCOM),j=1,At1)
174
            AtCom(0,NbCOM)=At1
175
            Atoms(nat+NbCom)="G"
176
            WRITE(13,'("# c ",I4,20(A3,I3))') At1,                  
177
     &          (Atoms(AtCom(i,NbCoM)),AtCom(i,NbCOM),i=1,At1)
178
            WRITE(*,'("# c ",I4,20(A3,I3))') At1,                   
179
     &          (Atoms(AtCom(i,NbCoM)),AtCom(i,NbCOM),i=1,At1)
180
          END IF
181

  
182
         END DO
183
         END IF
184

  
185

  
186

  
187
          fmt='(   (1X,F12.5),1X,F15.6)'
188
          write(fmt(2:4),'(i3)') NbDist+NbAngle+NbDie+1
189
!           write(*,*) nat3
190
!          write(*,*) 'fmt:',fmt
191

  
192
          ng=1
193

  
194
         s=0.
195

  
196
          open(11,file=f1)
197

  
198
10           call rtraitem(11,nnn,ener,geos,atoms)
199
!           WRITE(*,*) nnn
200
           if (nnn.gt.0) then
201

  
202
          call CalcRmsd(nnn, geos1, geos,MRot,rmsd,FRot,FAlign,debug)
203
         ds=0.
204
           DO I=1,nnn
205
             DO J=1,3
206
             ds=ds+mass(I)*(geos(J,I)-geos1(J,I))**2
207
!            write(*,*) I,J,geos(J,I),Geos1(J,I),ds
208
             geos1(J,I)=Geos(J,I)
209
              END DO
210
            END DO
211
           s=s+sqrt(ds)
212

  
213
! We convert coordinates in a0 into Angstroem
214
!              write(*,*) "Analyse !"
215
            if (FExist) THEN
216
            Call Analyse(geos)
217

  
218
             write(IOOUT,fmt) s,(VB(j)/Conv,j=1,NbDist),
219
     &            (VA(j),j=1,NbAngle),
220
     &            (VD(j),j=1,NbDie),ener
221
             write(*,fmt) s,(VB(j)/Conv,j=1,NbDist),
222
     &            (VA(j),j=1,NbAngle),
223
     &            (VD(j),j=1,NbDie),ener
224
             ELSE
225
                        write(IOOUT,fmt) s,ener
226
             write(*,fmt) s,ener
227
            END IF 
228
           ng=ng+1
229
            goto 10
230
           endif
231
           WRITE(*,*) 'Found ',ng-1,' geometries'
232
           close(11)
233
         end
234

  
235
!--------------------------------------------------------------
236
          subroutine rtraitem(ifil,nnn,E,tab,atoms)
237
!           implicit real*8 (a-h,o-z)
238
            IMPLICIT NONE
239
           character*120 line
240
           character*3 Atoms(*)
241
           integer*4 nnn, IFil, Idx, I, J
242
           REAL*8  Tab(3,*), E
243

  
244

  
245
           read(ifil,*,err=99,end=99) nnn
246
           read(ifil,'(A)') line
247
           idx=index(line,'E')
248
!           WRITE(*,*) 'idx,line',idx,line
249
           if (idx/=0) THEN
250
             line=line(idx+2:)
251
              idx=index(line,"=")
252
              if (idx/=0) line=line(idx+1:)
253
              idx=index(line,":")
254
              if (idx/=0) line=line(idx+1:)
255
              read(line,*) E
256
           ELSE
257
             E=0.
258
           END IF
259
           
260
!           write(*,*) 'coucou',line
261
           do i=1,nnn
262
              read(ifil,'(A)',err=99,end=99) Line
263
              do while (line(1:1)==' ')
264
                 line=line(2:)
265
              end do
266
              atoms(i)=line(1:3)
267
!            write(*,*) 'coucou atoms',atoms(i)
268
              do while (line(1:1).ne.' ')
269
                 line=line(2:)
270
              end do
271
!              WRITE(*,*) 'coucou2:',i,line
272
              read(line,*) (tab(j,i),j=1,3)
273
           end do
274
!           WRITE(*,*) 'coucou:',nnn,tab(1,1)
275
           return
276
99           nnn=0
277
!             WRITE(*,*) 'Erreur lecture',ifil,nnn
278
             return
279
          end
280

  
281
!--------------------------------------------------------------
282

  
283
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
284
! READLINE
285
! This subroutine reads a line for a file, and converts
286
! the first field into a character variable, and the rest into 4 integers
287
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
288

  
289
      SUBROUTINE READLINE(IOIN,Type,Line)
290
        
291
       IMPLICIT NONE
292
      CHARACTER Type*5,LINE*120
293
      INTEGER i,IOIN
294
      READ(IOIN,'(A120)',ERR=999,END=999) LINE
295
!      WRITE(*,*) Line
296
      DO WHILE (LINE(1:1).eq.' ')
297
         LINE=LINE(2:)
298
      END DO
299

  
300
      i=1
301
      DO WHILE (LINE(i:i).ne.' ')
302
         i=i+1
303
      END DO
304
      
305
      if (i.ge.6) THEN
306
         WRITE(*,*) 'Pb with READLINE:',LINE
307
         GOTO 999
308
      END IF
309
      Type=LINE(1:i-1)
310
      LINE=LINE(i:120) // " 0 0 0 0"
311

  
312
      RETURN
313
 999  Type="E"
314
      END
315

  
316

  
317

  
318
      SUBROUTINE Analyse(geos)
319

  
320
      IMPLICIT NONE
321
          INCLUDE "Xyz2Path.param"
322

  
323
      REAL*8 geos(3,maxnat)
324
      REAL*8 AU2PS,Pi
325
      INTEGER*4 i,j,k
326
      REAL*8 V1x,V1y,V1z,V2x,V2y,V2z,V3x,V3y,V3z
327
      REAL*8 d1,d2,ca,sa
328
      REAL*8 V4x,v4y,v4z,v5x,v5y,v5z
329
      REAL*8 COG(3)
330

  
331
      INTEGER*4 Nat,NbDist, NbAngle, NbDie,NbCOM
332
      INTEGER*4 At1B(MaxNat),At2B(MaxNat)
333
      INTEGER*4 At1A(MaxNat),At2A(MaxNat),At3A(MaxNat)
334
      INTEGER*4 At1D(MaxNat),At2D(MaxNat),At3D(MaxNat),At4D(MaxNat)
335
      INTEGER*4 AtCom(0:MaxNat,MaxNat)
336
      REAL*8    VB(MaxNat),VA(MaxNat),VD(MaxNat),VCOM(MaxNat)
337

  
338
      COMMON /Indices/Nat,NbDist,NbAngle,NbDie,NbCom,   
339
     &      At1B,At2B,At1A,At2A,At3A,At1D,At2D,At3D,At4D,AtCom
340
      COMMON /Values/VB,VA,VD,VCom
341
      COMMON /Const/AU2ps,Pi
342

  
343
          DO I=1,Nat
344
             WRITE(*,'(1X,I3,3(1X,F15.6))') i,(geos(j,i),j=1,3)
345
          END DO
346

  
347
! First, we create the Centre of Mass atoms
348
            DO i=1,NbCOM
349
              COG(1)=0.
350
              COG(2)=0.
351
              COG(3)=0.
352
              DO j=1,AtCOm(0,i)
353
                 DO k=1,3
354
                    COG(k)=COG(k)+geos(k,AtCom(j,i))
355
                 END DO
356
              END DO
357
              DO k=1,3
358
                 COG(k)=COG(k)/AtCOM(0,i)
359
                 geos(k,Nat+i)=COG(k)
360
              END DO
361
            END DO
362

  
363

  
364
            DO i=1,NbDist
365
               VB(i)=sqrt((geos(1,At1B(i))-geos(1,At2B(i)))**2+  
366
     &      (geos(2,At1B(i))-geos(2,At2B(i)))**2+                     
367
     &      (geos(3,At1B(i))-geos(3,At2B(i)))**2)
368
            END DO
369
            DO i=1,NbAngle
370
               v1x=geos(1,At1A(i))-geos(1,At2A(i))
371
               v1y=geos(2,At1A(i))-geos(2,At2A(i))
372
               v1z=geos(3,At1A(i))-geos(3,At2A(i))
373
               d1=sqrt(v1x**2+v1y**2+v1z**2)
374
               v2x=geos(1,At3A(i))-geos(1,At2A(i))
375
               v2y=geos(2,At3A(i))-geos(2,At2A(i))
376
               v2z=geos(3,At3A(i))-geos(3,At2A(i))
377
               d2=sqrt(v2x**2+v2y**2+v2z**2)
378
               VA(i)=acos((v1x*v2x+v1y*v2y+v1z*v2z)/(d1*d2))*180./Pi
379
            END DO
380
            DO i=1,NbDie
381
!               WRITE(*,*) At1D(i),At2D(i),At3D(i),At4D(i)
382
!              WRITE(*,*) geos(1,At1D(i)),geos(2,At1D(i)),geos(3,At1D(i))
383
!              WRITE(*,*) geos(1,At2D(i)),geos(2,At2D(i)),geos(3,At2D(i))
384
               v1x=geos(1,At1D(i))-geos(1,At2D(i))
385
               v1y=geos(2,At1D(i))-geos(2,At2D(i))
386
               v1z=geos(3,At1D(i))-geos(3,At2D(i))
387
               v2x=geos(1,At3D(i))-geos(1,At2D(i))
388
               v2y=geos(2,At3D(i))-geos(2,At2D(i))
389
               v2z=geos(3,At3D(i))-geos(3,At2D(i))
390
               v3x=geos(1,At4D(i))-geos(1,At3D(i))
391
               v3y=geos(2,At4D(i))-geos(2,At3D(i))
392
               v3z=geos(3,At4D(i))-geos(3,At3D(i))
393
          
394
               v4x=v1y*v2z-v1z*v2y
395
               v4y=v1z*v2x-v1x*v2z
396
               v4z=v1x*v2y-v1y*v2x
397
               d1=sqrt(v4x**2+v4y**2+v4z**2)
398
               v5x=-v2y*v3z+v2z*v3y
399
               v5y=-v2z*v3x+v2x*v3z
400
               v5z=-v2x*v3y+v2y*v3x
401
               d2=sqrt(v5x**2+v5y**2+v5z**2)
402
               ca=(v4x*v5x+v4y*v5y+v4z*v5z)/(d1*d2)
403
               sa=v1x*v5x+v1y*v5y+v1z*v5z
404
               VD(i)=acos(ca)*180./Pi
405
               if (sa<0.) VD(i)=-VD(i)
406
!               WRITE(*,*) "Dihe",v5x,v5y,v5z,v4x,v4y,v4z,d1,d2,
407
!     &(v4x*v5x+v4y*v5y+v4z*v5z)/(d1*d2),pi
408
!!!!!!!!! Another solution, more elegant ?
409
!               norm2=sqrt(v2x**2+v2y**2+v2z**2)
410
!               sa=(v4x*(v5y*v2z-v5z*v2y) 
411
!     *            -v4y*(v5x*v2z-v5z*v2x) 
412
!     *            +v4z*(v5x*v2y-v5y*v2x))
413
!     *       /(d1*norm2*d2)
414
!               angle_d=datan2(sa,ca)*180./Pi
415
!               WRITE(*,*) sa,ca,angle_d,d1,d2,norm2
416
!               WRITE(*,*) VD(i),angle_d
417
            END DO
418

  
419
        END
420

  
421
C================================================================
422
C    Convertit un nom d'atome (2 lettres) en nombre de masse (entier)
423
C cette fonction a ete modifiee pour pouvoir convertir un nom
424
C d'atome avec un numero a la fin...
425
C================================================================
426

  
427
        FUNCTION ConvertNumAt(ATOM)
428

  
429

  
430
        IMPLICIT NONE 
431

  
432
        INTEGER*4 I,Long,ConvertNumAt,IC
433
        character*2 ATOM*2,ATOME*3,L_Atom*2
434
        INTEGER*4  Max_Z
435
        PARAMETER (Max_Z=86)
436
        CHARACTER*2  Nom(0:Max_Z)
437

  
438
       DATA NOM/ ' X',' H',                                    'HE',
439
     $          'LI','BE',            ' B',' C',' N',' O',' F','NE',
440
     $          'NA','MG',            'AL','SI',' P',' S','CL','AR',
441
     $          ' K','CA',
442
     $      'SC','TI',' V','CR','MN','FE','CO','NI','CU','ZN',
443
     $                                'GA','GE','AS','SE','BR','KR',
444
     $          'RB','SR',
445
     $      ' Y','ZR','NB','MO','TC','RU','RH','PD','AG','CD',
446
     $                                'IN','SN','SB','TE',' I','XE',
447
     $          'CS','BA',
448
     $      'LA',
449
     $        'CE','PR','ND','PM','SM','EU','GD','TB','DY','HO',
450
     $        'ER','TM','YB','LU',
451
     $               'HF','TA',' W','RE','OS','IR','PT','AU','HG',
452
     $                                'TL','PB','BI','PO','AT','RN'/
453

  
454

  
455
C Verifie qu'il n'y a que des lettres et des espaces dans ATOM
456
!        WRITE(*,*) 'DBG CNVNUMAT, ATOM:',ATOM
457

  
458
        L_atom=Atom
459
        IF (ATOM(1:1).LT.'A') L_ATOM(1:1)=' '
460
        IC=Ichar(ATOM(1:1))
461
        IF ((ic.le.123).AND.(ic.ge.97)) L_ATOM(1:1)=CHAr(IC-32)
462
        IF (ATOM(2:2).LT.'A') L_ATOM(2:2)=' '
463
        IC=Ichar(ATOM(2:2))
464
        IF ((ic.le.123).AND.(ic.ge.97)) L_ATOM(2:2)=CHAr(IC-32)
465
C Justifie le nom sur la droite (et non sur la gauche comme souvent...)
466
         Long=INDEX(L_ATOM,' ')-1
467
         ATOME=' ' // L_ATOM
468
        IF (Long.EQ.1) L_ATOM=ATOME(1:2)
469
!        WRITE(*,*) 'DBG CNVNUMAT, L_ATOM:',L_ATOM
470
        I=max_Z
471
        DO WHILE ((nom(I).NE.L_ATOM) .AND. (I.GT.0))
472
         I=I-1
473
        END DO
474
        ConvertNumAT=I
475
        END
476
! This subroutine calculates RMSD using quaternions.
477
! It is based on the F90 routine bu E. Coutsias
478
! http://www.math.unm.edu/~vageli/homepage.html
479
! I (PFL) have just translated it, and I have changed the diagonalization
480
! subroutine.
481
! I also made some changes to make it suitable for Cart package.
482
!----------------------------------------------------------------------
483
!----------------------------------------------------------------------
484
! Copyright (C) 2004, 2005 Chaok Seok, Evangelos Coutsias and Ken Dill
485
!      UCSF, Univeristy of New Mexico, Seoul National University
486
! Witten by Chaok Seok and Evangelos Coutsias 2004.
487
                                                                                
488
! This library is free software; you can redistribute it and/or
489
! modify it under the terms of the GNU Lesser General Public
490
! License as published by the Free Software Foundation; either
491
! version 2.1 of the License, or (at your option) any later version.
492
!
493
                                                                                
494
! This library is distributed in the hope that it will be useful,
495
! but WITHOUT ANY WARRANTY; without even the implied warranty of
496
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
497
! Lesser General Public License for more details.
498
!
499
                                                                                
500
! You should have received a copy of the GNU Lesser General Public
501
! License along with this library; if not, write to the Free Software
502
! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
503
!----------------------------------------------------------------------------
504

  
505
      subroutine CalcRmsd(na, geom,geom2,U,rmsd,FRot,FAlign,debug)
506
!-----------------------------------------------------------------------
507
!  This subroutine calculates the least square rmsd of two coordinate
508
!  sets coord1(3,n) and coord2(3,n) using a method based on quaternion.
509
!  It then calculate the  rotation matrix U and the centers of coord, and uses
510
! them to align the two molecules.
511
!-----------------------------------------------------------------------
512

  
513

  
514
      IMPLICIT NONE
515

  
516
      INCLUDE "Xyz2Path.param"
517

  
518
      INTEGER*4 IOIN, IOOUT, IOSCRN, IOPRNT, IOTAMP
519
      COMMON/IODEFS/IOIN,IOOUT,IOSCRN,IOPRNT,IOTAMP
520

  
521
      integer*4 na
522
      real*8  geom(3,MaxNAt), Geom2(3,MaxNAt)
523
      real*8  U(3,3), rmsd
524
      LOGICAL  FRot,FAlign,Debug
525

  
526
      REAL*8 Coord1(3,MaxNAt), Coord2(3,MaxNAt)
527
      real*8  xc1,yc1,zc1, xc2,yc2,zc2
528
      
529

  
530
      integer*4 i, j,  ia
531
      real*8 x_norm, y_norm, lambda
532
      real*8 Rmatrix(3,3)
533
      real*8 S(4,4)
534
      real*8 EigVec(4,4), EigVal(4)
535

  
536

  
537

  
538
  ! calculate the barycenters, centroidal coordinates, and the norms
539
      x_norm = 0.0d0
540
      y_norm = 0.0d0
541
      xc1=0.
542
      yc1=0.
543
      zc1=0.
544
      xc2=0.
545
      yc2=0.
546
      zc2=0.
547
      do ia=1,na
548
         xc1=xc1+geom(1,ia)
549
         xc2=xc2+geom2(1,ia)
550
         yc1=yc1+geom(2,ia)
551
         yc2=yc2+geom2(2,ia)
552
         zc1=zc1+geom(3,ia)
553
         zc2=zc2+geom2(3,ia)
554
!         if (debug) WRITE(*,'(A,I5,4(1X,F10.4))') 'ia...',ia,x(ia),
555
!     &                        x2(ia),xc1,xc2
556
      END DO
557
      xc1=xc1/dble(na)
558
      yc1=yc1/dble(na)
559
      zc1=zc1/dble(na)
560
      xc2=xc2/dble(na)
561
      yc2=yc2/dble(na)
562
      zc2=zc2/dble(na)
563

  
564
      IF (debug) WRITE(*,'(1X,A,3(1X,F10.4))') 'Center1',xc1,yc1,zc1
565
      IF (debug) WRITE(*,'(1X,A,3(1X,F10.4))') 'Center2',xc2,yc2,zc2
566
      do i=1,na
567
         Coord1(1,i)=geom(1,i)-xc1
568
         Coord1(2,i)=geom(2,i)-yc1
569
         Coord1(3,i)=geom(3,i)-zc1
570
         Coord2(1,i)=geom2(1,i)-xc2
571
         Coord2(2,i)=geom2(2,i)-yc2
572
         Coord2(3,i)=geom2(3,i)-zc2
573
         x_norm=x_norm+Coord1(1,i)**2+Coord1(2,i)**2+Coord1(3,i)**2
574
         y_norm=y_norm+Coord2(1,i)**2+Coord2(2,i)**2+Coord2(3,i)**2
575
      end do
576

  
577
      IF (debug) THEN
578
         WRITE(*,*) "R matrix"
579
         DO I=1,3
580
            WRITE(*,*) (RMatrix(I,j),j=1,3)
581
         END DO
582
      END IF
583

  
584
  ! calculate the R matrix
585
      do i = 1, 3
586
         do j = 1, 3
587
            Rmatrix(i,j)=0.
588
            do ia=1,na
589
               Rmatrix(i,j) = Rmatrix(i,j)+Coord1(i,ia)*Coord2(j,ia)
590
            END DO
591
         end do
592
      end do
593

  
594
      IF (debug) THEN
595
         WRITE(*,*) "R matrix"
596
         DO I=1,3
597
            WRITE(*,*) (RMatrix(I,j),j=1,3)
598
         END DO
599
      END IF
600

  
601

  
602
  ! S matrix
603
      S(1, 1) = Rmatrix(1, 1) + Rmatrix(2, 2) + Rmatrix(3, 3)
604
      S(2, 1) = Rmatrix(2, 3) - Rmatrix(3, 2)
605
      S(3, 1) = Rmatrix(3, 1) - Rmatrix(1, 3)
606
      S(4, 1) = Rmatrix(1, 2) - Rmatrix(2, 1)
607

  
608
      S(1, 2) = S(2, 1)
609
      S(2, 2) = Rmatrix(1, 1) - Rmatrix(2, 2) - Rmatrix(3, 3)
610
      S(3, 2) = Rmatrix(1, 2) + Rmatrix(2, 1)
611
      S(4, 2) = Rmatrix(1, 3) + Rmatrix(3, 1)
612

  
613
      S(1, 3) = S(3, 1)
614
      S(2, 3) = S(3, 2)
615
      S(3, 3) =-Rmatrix(1, 1) + Rmatrix(2, 2) - Rmatrix(3, 3)
616
      S(4, 3) = Rmatrix(2, 3) + Rmatrix(3, 2)
617

  
618
      S(1, 4) = S(4, 1)
619
      S(2, 4) = S(4, 2)
620
      S(3, 4) = S(4, 3)
621
      S(4, 4) =-Rmatrix(1, 1) - Rmatrix(2, 2) + Rmatrix(3, 3) 
622

  
623

  
624
! PFL : I use my usual Jacobi diagonalisation
625
  ! Calculate eigenvalues and eigenvectors, and 
626
  ! take the maximum eigenvalue lambda and the corresponding eigenvector q.
627

  
628
      IF (debug) THEN
629
         WRITE(*,*) "S matrix"
630
         DO I=1,4
631
            WRITE(*,*) (S(I,j),j=1,4)
632
         END DO
633
      END IF
634

  
635
      Call Jacobi(S,4,EigVal,EigVec,4)
636

  
637
      Call Trie(4,EigVal,EigVec,4)
638

  
639
      Lambda=EigVal(4)
640

  
641
! RMS Deviation
642
       rmsd=sqrt(max(0.0d0,((x_norm+y_norm)-2.0d0*lambda))/dble(na))
643

  
644
      if (FRot.OR.FAlign) Call rotation_matrix(EigVec(1,4),U)
645
      IF (FAlign) THEN
646
         DO I=1,na
647
            geom2(1,i)=Coord2(1,i)*U(1,1)+Coord2(2,i)*U(2,1)
648
     &           +Coord2(3,i)*U(3,1) +xc1
649
            geom2(2,i)=Coord2(1,i)*U(1,2)+Coord2(2,i)*U(2,2)
650
     &           +Coord2(3,i)*U(3,2) +yc1
651
            geom2(3,i)=Coord2(1,i)*U(1,3)+Coord2(2,i)*U(2,3)
652
     &           +Coord2(3,i)*U(3,3) +zc1
653
         END DO
654
      END IF
655

  
656
      END
657

  
658

  
659
!-----------------------------------------------------------------------
660
      subroutine rotation_matrix(q, U)
661
!-----------------------------------------------------------------------
662
! This subroutine constructs rotation matrix U from quaternion q.
663
!-----------------------------------------------------------------------
664
! This subroutine calculates RMSD using quaternions.
665
! It is based on the F90 routine bu E. Coutsias
666
! http://www.math.unm.edu/~vageli/homepage.html
667
! I (PFL) have just translated it, and I have changed the diagonalization
668
! subroutine.
669
! I also made some changes to make it suitable for Cart package.
670
!----------------------------------------------------------------------
671
!----------------------------------------------------------------------
672
! Copyright (C) 2004, 2005 Chaok Seok, Evangelos Coutsias and Ken Dill
673
!      UCSF, Univeristy of New Mexico, Seoul National University
674
! Witten by Chaok Seok and Evangelos Coutsias 2004.
675
                                                                                
676
! This library is free software; you can redistribute it and/or
677
! modify it under the terms of the GNU Lesser General Public
678
! License as published by the Free Software Foundation; either
679
! version 2.1 of the License, or (at your option) any later version.
680
!
681
                                                                                
682
! This library is distributed in the hope that it will be useful,
683
! but WITHOUT ANY WARRANTY; without even the implied warranty of
684
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
685
! Lesser General Public License for more details.
686
!
687
                                                                                
688
! You should have received a copy of the GNU Lesser General Public
689
! License along with this library; if not, write to the Free Software
690
! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
691
!----------------------------------------------------------------------------
692

  
693
      real*8 q(4)
... Ce différentiel a été tronqué car il excède la taille maximale pouvant être affichée.

Formats disponibles : Unified diff