Statistiques
| Révision :

root / utils / Xyz2Path.f @ 2

Historique | Voir | Annoter | Télécharger (27,96 ko)

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)
694
      real*8 U(3,3)
695
      real*8 q0,q1,q2,q3,b0,b1,b2,b3,q00,q01,q02,q03
696
      REAL*8 q11,q12,q13,q22,q23,q33
697

    
698
      q0 = q(1)
699
      q1 = q(2)
700
      q2 = q(3)
701
      q3 = q(4)
702

    
703
      b0 = 2.0d0*q0
704
      b1 = 2.0d0*q1
705
      b2 = 2.0d0*q2
706
      b3 = 2.0d0*q3
707

    
708
      q00 = b0*q0-1.0d0
709
      q01 = b0*q1
710
      q02 = b0*q2
711
      q03 = b0*q3
712

    
713
      q11 = b1*q1
714
      q12 = b1*q2
715
      q13 = b1*q3  
716
      
717
      q22 = b2*q2
718
      q23 = b2*q3
719
      
720
      q33 = b3*q3 
721
      
722
      U(1,1) = q00+q11
723
      U(1,2) = q12-q03
724
      U(1,3) = q13+q02
725
      
726
      U(2,1) = q12+q03
727
      U(2,2) = q00+q22
728
      U(2,3) = q23-q01
729
      
730
      U(3,1) = q13-q02
731
      U(3,2) = q23+q01
732
      U(3,3) = q00+q33
733
      
734
      end 
735
      
736
c============================================================
737
c
738
c ++  diagonalisation par jacobi
739
c     vecteur propre i : V(i,i)
740
c     valeur propre i : D(i)
741
c
742
c============================================================
743
c 
744
      SUBROUTINE JACOBI(A,N,D,V,max_N)
745
      IMPLICIT REAL*8 (A-H,O-Z)
746
      parameter (max_it=500)
747
      DIMENSION A(max_N,max_N),B(max_N),Z(max_N)
748
      DIMENSION V(max_N,max_N),D(max_N)
749

    
750

    
751
      DO 12 IP=1,N
752
        DO 11 IQ=1,N
753
          V(IP,IQ)=0.
754
11      CONTINUE
755
        V(IP,IP)=1.
756
12    CONTINUE
757
      DO 13 IP=1,N
758
        B(IP)=A(IP,IP)
759
        D(IP)=B(IP)
760
        Z(IP)=0.
761
13    CONTINUE
762
      NROT=0
763
      DO 24 I=1,max_it
764
        SM=0.
765
        DO 15 IP=1,N-1
766
          DO 14 IQ=IP+1,N
767
            SM=SM+ABS(A(IP,IQ))
768
14        CONTINUE
769
15      CONTINUE
770
        IF(SM.EQ.0.)RETURN
771
        IF(I.LT.4)THEN
772
          TRESH=0.2*SM/N**2
773
        ELSE
774
          TRESH=0.
775
        ENDIF
776
        DO 22 IP=1,N-1
777
          DO 21 IQ=IP+1,N
778
            G=100.*ABS(A(IP,IQ))
779
            IF((I.GT.4).AND.(ABS(D(IP))+G.EQ.ABS(D(IP)))
780
     *         .AND.(ABS(D(IQ))+G.EQ.ABS(D(IQ))))THEN
781
              A(IP,IQ)=0.
782
            ELSE IF(ABS(A(IP,IQ)).GT.TRESH)THEN
783
              H=D(IQ)-D(IP)
784
              IF(ABS(H)+G.EQ.ABS(H))THEN
785
                T=A(IP,IQ)/H
786
              ELSE
787
                THETA=0.5*H/A(IP,IQ)
788
                T=1./(ABS(THETA)+SQRT(1.+THETA**2))
789
                IF(THETA.LT.0.)T=-T
790
              ENDIF
791
              C=1./SQRT(1+T**2)
792
              S=T*C
793
              TAU=S/(1.+C)
794
              H=T*A(IP,IQ)
795
              Z(IP)=Z(IP)-H
796
              Z(IQ)=Z(IQ)+H
797
              D(IP)=D(IP)-H
798
              D(IQ)=D(IQ)+H
799
              A(IP,IQ)=0.
800
              DO 16 J=1,IP-1
801
                G=A(J,IP)
802
                H=A(J,IQ)
803
                A(J,IP)=G-S*(H+G*TAU)
804
                A(J,IQ)=H+S*(G-H*TAU)
805
16            CONTINUE
806
              DO 17 J=IP+1,IQ-1
807
                G=A(IP,J)
808
                H=A(J,IQ)
809
                A(IP,J)=G-S*(H+G*TAU)
810
                A(J,IQ)=H+S*(G-H*TAU)
811
17            CONTINUE
812
              DO 18 J=IQ+1,N
813
                G=A(IP,J)
814
                H=A(IQ,J)
815
                A(IP,J)=G-S*(H+G*TAU)
816
                A(IQ,J)=H+S*(G-H*TAU)
817
18            CONTINUE
818
              DO 19 J=1,N
819
                G=V(J,IP)
820
                H=V(J,IQ)
821
                V(J,IP)=G-S*(H+G*TAU)
822
                V(J,IQ)=H+S*(G-H*TAU)
823
19            CONTINUE
824
              NROT=NROT+1
825
            ENDIF
826
21        CONTINUE
827
22      CONTINUE
828
        DO 23 IP=1,N
829
          B(IP)=B(IP)+Z(IP)
830
          D(IP)=B(IP)
831
          Z(IP)=0.
832
23      CONTINUE
833
24    CONTINUE
834
      write(6,*) max_it,' iterations should never happen'
835
      STOP
836
      RETURN
837
      END
838
c
839
c============================================================
840
c
841
c ++  trie des vecteur dans l'ordre croissant
842
c
843
c============================================================
844
c
845
        SUBROUTINE trie(nb_niv,ene,psi,max_niv)
846
        integer i,j,k,nb_niv,max_niv
847
        real*8 ene(max_niv),psi(max_niv,max_niv)
848
        real*8 a
849

    
850
        DO i=1,nb_niv
851
          DO j=i+1,nb_niv
852
            IF (ene(i) .GT. ene(j)) THEN
853
c              permutation
854
              a=ene(i)
855
              ene(i)=ene(j)
856
              ene(j)=a
857
              DO k=1,nb_niv
858
                 a=psi(k,i)
859
                 psi(k,i)=psi(k,j)
860
                 psi(k,j)=a
861
              END DO
862
            END IF
863
          END DO
864
        END DO
865

    
866
        END
867