Statistiques
| Révision :

root / src / bib_oper.f90

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

1
!----------------------------------------------------------------------
2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
3
!  Centre National de la Recherche Scientifique,
4
!  Université Claude Bernard Lyon 1. All rights reserved.
5
!
6
!  This work is registered with the Agency for the Protection of Programs 
7
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
8
!
9
!  Authors: P. Fleurat-Lessard, P. Dayal
10
!  Contact: optnpath@gmail.com
11
!
12
! This file is part of "Opt'n Path".
13
!
14
!  "Opt'n Path" is free software: you can redistribute it and/or modify
15
!  it under the terms of the GNU Affero General Public License as
16
!  published by the Free Software Foundation, either version 3 of the License,
17
!  or (at your option) any later version.
18
!
19
!  "Opt'n Path" is distributed in the hope that it will be useful,
20
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
21
!
22
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
23
!  GNU Affero General Public License for more details.
24
!
25
!  You should have received a copy of the GNU Affero General Public License
26
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
27
!
28
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
29
! for commercial licensing opportunities.
30
!----------------------------------------------------------------------
31

    
32
!================================================================
33
!       vecteur
34
!================================================================
35

    
36
         SUBROUTINE vecteur(n1,n2,x,y,z,vx,vy,vz,norm)
37

    
38
        use Path_module, only : NAt, KINT, KREAL
39

    
40

    
41
        integer(KINT) :: n1,n2
42
        real(KREAL) ::  x(Nat),y(Nat),z(Nat)
43
        real(KREAL) ::  vx,vy,vz,norm
44

    
45
        vx=x(n2)-x(n1)
46
        vy=y(n2)-y(n1)
47
        vz=z(n2)-z(n1)
48

    
49
        !norm=dsqrt( vx*vx + vy*vy + vz*vz )
50
            norm=sqrt( vx*vx + vy*vy + vz*vz )
51

    
52
!       write(6,*)
53
!       write(6,*) vx,vy,vz,norm
54
!       write(6,*)
55

    
56
      RETURN
57
      END
58

    
59
!================================================================
60
!       angle
61
!================================================================
62

    
63
         FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
64

    
65

    
66
        use Path_module, only :  Pi,KREAL
67

    
68
        real(KREAL) ::  v1x,v1y,v1z,norm1
69
        real(KREAL) ::  v2x,v2y,v2z,norm2
70
        real(KREAL) ::  angle,ps
71

    
72
!       write(6,*)
73
!       write(6,*) v1x,v1y,v1z,norm1
74
!       write(6,*) v2x,v2y,v2z,norm2
75
!       write(6,*)
76
        IF (abs(norm1) .LT. 1.D-4) THEN
77
            STOP 'Angle: norm1 egale 0'
78
        ELSE IF (abs(norm2) .LT. 1.D-4) THEN
79
            STOP 'Angle: norm2 egale 0'
80
        ELSE
81
          ps=v1x*v2x+v1y*v2y+v1z*v2z
82
          angle=dacos(ps/(norm1*norm2))*180./Pi
83
        ENDIF
84

    
85
      RETURN
86
      END
87

    
88

    
89
!================================================================
90
!       angle oriente (dihedre)
91
!================================================================
92

    
93
         FUNCTION angle_d(v1x,v1y,v1z,norm1, &
94
                          v2x,v2y,v2z,norm2, &
95
                          v3x,v3y,v3z,norm3)
96

    
97
        use Path_module, only :  Pi, KREAL
98

    
99
        real(KREAL) ::  v1x,v1y,v1z,norm1
100
        real(KREAL) ::  v2x,v2y,v2z,norm2
101
        real(KREAL) ::  v3x,v3y,v3z,norm3
102
        real(KREAL) ::  angle_d,ca,sa
103

    
104
!       write(6,*)
105
!       write(6,*) v1x,v1y,v1z,norm1
106
!       write(6,*) v2x,v2y,v2z,norm2
107
!       write(6,*) v3x,v3y,v3z,norm3
108
!       write(6,*)
109
        !Print *, 'Inside angle_d'
110
        IF (abs(norm1) .LT. 1.D-4) THEN
111
            STOP 'Angle_d: norm1 egale 0'
112
         ELSE IF (abs(norm2) .LT. 1.D-4) THEN
113
            STOP 'Angle_d: norm2 egale 0'
114
        ELSE IF (abs(norm3) .LT. 1.D-4) THEN
115
            STOP 'Angle_d: norm3 egale 0'
116
        ELSE
117
          ca=(v1x*v2x+v1y*v2y+v1z*v2z)/(norm1*norm2)
118
          sa=(v1x*(v2y*v3z-v2z*v3y) &
119
             -v1y*(v2x*v3z-v2z*v3x) &
120
             +v1z*(v2x*v3y-v2y*v3x)) &
121
             /(norm1*norm2*norm3)
122
           angle_d=datan2(sa,ca)*180./Pi
123
!         write(*,*) sa,ca,angle_d,norm1,norm2,norm3
124
        ENDIF
125
        !Print *, 'End of angle_d'
126
      RETURN
127
      END
128

    
129
!================================================================
130
!       produit vectoriel
131
!================================================================
132

    
133
       SUBROUTINE produit_vect(v1x,v1y,v1z, &
134
                               v2x,v2y,v2z, &
135
                               v3x,v3y,v3z,norm3)
136

    
137
        use Path_module, only :   KREAL
138

    
139
        real(KREAL) ::  v1x,v1y,v1z ! what do you do with norm1, norm2???
140
        real(KREAL) ::  v2x,v2y,v2z
141
        real(KREAL) ::  v3x,v3y,v3z,norm3
142

    
143
        v3x= v1y*v2z-v1z*v2y
144
        v3y=-v1x*v2z+v1z*v2x
145
            v3z= v1x*v2y-v1y*v2x
146

    
147
        norm3=dsqrt( v3x*v3x + v3y*v3y + v3z*v3z )
148

    
149

    
150
      RETURN
151
      END
152

    
153
!================================================================
154
!       rotation suivant l axe x de phi tq a11=cos(phi) a12=sin(phi)
155
!================================================================
156

    
157
       SUBROUTINE rota_x(v1x,v1y,v1z,a11,a12)
158

    
159
        use Path_module, only :  KREAL
160

    
161
        real(KREAL) ::  v1x,v1y,v1z
162
        real(KREAL) ::  v2x,v2y,v2z
163
        real(KREAL) ::  a11,a12
164

    
165
        v2x=  v1x
166
        v2y=  a11*v1y - a12*v1z
167
        v2z=  a12*v1y + a11*v1z
168

    
169

    
170
        v1x=v2x
171
        v1y=v2y
172
        v1z=v2z
173

    
174

    
175
      RETURN
176
      END
177

    
178

    
179
!================================================================
180
!       rotation suivant l axe y de phi tq a11=cos(phi) a12=sin(phi)
181
!================================================================
182

    
183
       SUBROUTINE rota_y(v1x,v1y,v1z,a11,a12)
184

    
185
        use Path_module, only :   KREAL
186

    
187
        real(KREAL) ::  v1x,v1y,v1z
188
        real(KREAL) ::  v2x,v2y,v2z
189
        real(KREAL) ::  a11,a12
190

    
191
        v2x=  a11*v1x - a12*v1z
192
        v2y=  v1y
193
        v2z=  a12*v1x + a11*v1z
194

    
195

    
196
        v1x=v2x
197
        v1y=v2y
198
        v1z=v2z
199

    
200

    
201
        RETURN
202
        END
203

    
204

    
205
!================================================================
206
!       rotation suivant l axe z de phi tq a11=cos(phi) a12=sin(phi)
207
!================================================================
208

    
209
       SUBROUTINE rota_z(v1x,v1y,v1z,a11,a12)
210

    
211
        use Path_module, only :   KREAL
212

    
213
        real(KREAL) ::  v1x,v1y,v1z
214
        real(KREAL) ::  v2x,v2y,v2z
215
        real(KREAL) ::  a11,a12
216

    
217
        v2x=  a11*v1x - a12*v1y
218
        v2y=  a12*v1x + a11*v1y
219
        v2z=  v1z
220

    
221

    
222
        v1x=v2x
223
        v1y=v2y
224
        v1z=v2z
225

    
226
        RETURN
227
        END