root / src / WriteMixed_Gaussian.f90
Historique | Voir | Annoter | Télécharger (4,16 ko)
1 |
SUBROUTINE WriteMixed_Gaussian(na,atome,NCart,ind_zmat,val_zmat) |
---|---|
2 |
!---------------------------------------------------------------------- |
3 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
4 |
! Centre National de la Recherche Scientifique, |
5 |
! Université Claude Bernard Lyon 1. All rights reserved. |
6 |
! |
7 |
! This work is registered with the Agency for the Protection of Programs |
8 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
9 |
! |
10 |
! Authors: P. Fleurat-Lessard, P. Dayal |
11 |
! Contact: optnpath@gmail.com |
12 |
! |
13 |
! This file is part of "Opt'n Path". |
14 |
! |
15 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
16 |
! it under the terms of the GNU Affero General Public License as |
17 |
! published by the Free Software Foundation, either version 3 of the License, |
18 |
! or (at your option) any later version. |
19 |
! |
20 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
21 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
22 |
! |
23 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
24 |
! GNU Affero General Public License for more details. |
25 |
! |
26 |
! You should have received a copy of the GNU Affero General Public License |
27 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
28 |
! |
29 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
30 |
! for commercial licensing opportunities. |
31 |
!---------------------------------------------------------------------- |
32 |
|
33 |
Use Path_module, only : Nom |
34 |
Use Io_module |
35 |
|
36 |
IMPLICIT NONE |
37 |
! Parameters of the subroutine |
38 |
! na: number of atoms in the system |
39 |
integer(KINT), INTENT(IN) :: na |
40 |
! atome: Mass number of the atoms of the system |
41 |
integer(KINT), INTENT(IN) :: atome(na) |
42 |
! nCart: number of atoms described in cartesian |
43 |
integer(KINT), INTENT(IN) :: NCart |
44 |
! ind_zmat: for "zmat" atoms contains the indices of reference atoms |
45 |
integer(KINT), INTENT(IN) :: ind_zmat(Na,5) |
46 |
! val_zmat: for "zmat" atoms contains the values from reference atoms |
47 |
real(KREAL), INTENT(IN) :: val_zmat(Na,3) |
48 |
|
49 |
character(6) :: at1, at2, at3, at4, d, a, dh |
50 |
Character(6) :: x,y,z |
51 |
character(SCHARS), ALLOCATABLE :: tab(:) ! 3*na |
52 |
character(LCHARS) :: ligne |
53 |
|
54 |
INTEGER(KINT) :: i,n1,n2,n3,n4, NZmat,ITab |
55 |
|
56 |
ALLOCATE(tab(3*na)) |
57 |
|
58 |
! We first write the Cartesian atoms |
59 |
|
60 |
DO I=1,NCart |
61 |
! Name of the atom |
62 |
n1=ind_zmat(i,1) |
63 |
write(at1,11) nom(atome(n1)),n1 |
64 |
Call CleanString(at1,' ') |
65 |
! x |
66 |
write(x,11) 'x',i |
67 |
Call CleanString(x,' ') |
68 |
|
69 |
write(tab(3*i-2),'(A,1X,F12.8)') trim(x),val_zmat(i,1) |
70 |
! y |
71 |
write(y,11) 'y',i |
72 |
Call CleanString(y,' ') |
73 |
write(tab(3*i-1),'(A,1X,F12.8)') trim(y),val_zmat(i,2) |
74 |
! z |
75 |
write(z,11) 'z',i |
76 |
Call CleanString(z,' ') |
77 |
write(tab(3*i),'(A,1X,F12.8)') trim(z),val_zmat(i,3) |
78 |
! write the line |
79 |
write(ligne,'(1X,A,1X,A,1X,A,1X,A)') Trim(at1),x,y,z |
80 |
write(IOOUT,*) TRIM(ligne) |
81 |
END DO |
82 |
|
83 |
NZmat=na-NCart |
84 |
ITab=3*NCart+1 |
85 |
|
86 |
DO i=NCart+1,NZmat |
87 |
IF (i .GE. 1) THEN |
88 |
n1=ind_zmat(i,1) |
89 |
write(at1,11) nom(atome(n1)),n1 |
90 |
11 format(a2,i3) |
91 |
Call CleanString(at1,' ') |
92 |
write(ligne,4) at1 |
93 |
END IF |
94 |
IF (i .GE. 2) THEN |
95 |
n2=ind_zmat(i,2) |
96 |
write(at2,11) nom(atome(n2)),n2 |
97 |
Call CleanString(At2,' ') |
98 |
write(d,11) 'R',i-1 |
99 |
Call CleanString(D,' ') |
100 |
write(ligne,4) at1,at2,d |
101 |
write(tab(ITab),12) d,val_zmat(i,1) |
102 |
ITab=ITab+1 |
103 |
12 format(a8,f8.4) |
104 |
END IF |
105 |
IF (i .GE. 3) THEN |
106 |
n3=ind_zmat(i,3) |
107 |
write(at3,11) nom(atome(n3)),n3 |
108 |
Call CleanString(At3,' ') |
109 |
write(a,11) 'A',na+i-3 |
110 |
Call CleanString(A,' ') |
111 |
write(ligne,4) at1,at2,d,at3,a |
112 |
write(tab(ITab),13) a,val_zmat(i,2) |
113 |
ITab=ITab+1 |
114 |
13 format(a8,f8.3) |
115 |
END IF |
116 |
IF (i .GE. 4) THEN |
117 |
n4=ind_zmat(i,4) |
118 |
write(at4,11) nom(atome(n4)),n4 |
119 |
Call CleanString(At4,' ') |
120 |
write(dh,11) 'DH',na+na+i-6 |
121 |
Call CleanString(dh,' ') |
122 |
write(ligne,4) at1,at2,d,at3,a,at4,dh |
123 |
4 format(7a6) |
124 |
write(tab(ITab),13) dh,val_zmat(i,3) |
125 |
ITab=ITab+1 |
126 |
END IF |
127 |
write(IOOUT,*) TRIM(ligne) |
128 |
END DO |
129 |
|
130 |
write(IOOUT,*) |
131 |
DO i=1,ITab |
132 |
write(IOOUT,*) TRIM(tab(i)) |
133 |
END DO |
134 |
write(IOOUT,*) |
135 |
|
136 |
DEALLOCATE(Tab) |
137 |
|
138 |
END SUBROUTINE WriteMixed_Gaussian |