Statistiques
| Révision :

root / utils / Xyz2Scan.f @ 2

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

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