Statistiques
| Révision :

root / src / ConvertZmat_cart_3.f90

Historique | Voir | Annoter | Télécharger (3,56 ko)

1
!C================================================================
2
!C       Converti les positions Zmat en coordonnes cartesiennes
3
!C This version deals with the third atoms in A B C
4
!C  Used in Mix to Cart.
5
!C================================================================
6

    
7
        SUBROUTINE ConvertZmat_cart_3(iat,ind_zmat,d,a_val,x,y,z)
8

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

    
40
        use Path_module, only : Nat, KINT, KREAL
41

    
42
        IMPLICIT NONE
43

    
44
        integer(KINT) :: iat, n1, n2
45
        real(KREAL)    :: x(nat),y(nat),z(nat)
46
        real(KREAL) ::  d,a_val
47
        integer(KINT) :: ind_zmat(Nat,5)
48

    
49
        real(KREAL) ::  vx1,vy1,vz1,norm1
50
        real(KREAL) ::  vvx1,vvy1,vvz1,normv1
51
        real(KREAL) ::  vx4, vy4, vz4
52
        real(KREAL) ::  a11_z1,a12_z1
53
        real(KREAL) ::  a11_y,a12_y
54

    
55

    
56

    
57
!C ind_zmat(1) contient le numero de l'atome, (2) celui par rapport auquel on definit la distance...
58

    
59
          n1=ind_zmat(iat,2)
60
          n2=ind_zmat(iat,3)
61

    
62
!          WRITE(*,*) iat,n1,n2
63

    
64
!          WRITE(*,*) "d,val,di",d,a_val,a_dih,a_val*180./3.141592654
65

    
66
          CALL vecteur(n1,n2,x,y,z,vx1,vy1,vz1,norm1)
67

    
68
          vvx1=vx1
69
          vvy1=vy1
70
          vvz1=vz1
71

    
72
!c rotation autour de z de v1 de phi (a11_z1=cos(phi) et a12_z1=sin(phi) ) tq
73
!C  v1 soit dans le plan xOz
74

    
75
          normv1=dsqrt(vvx1*vvx1+vvy1*vvy1)
76

    
77
          IF (normv1 .GE. 1.D-6) THEN
78
             a11_z1 = vvx1/normv1
79
             a12_z1 = vvy1/normv1
80
           ELSE
81
             a11_z1 = 1
82
             a12_z1 = 0
83
          END IF
84

    
85
             CALL rota_z(vx1,vy1,vz1,a11_z1,-a12_z1)
86

    
87
!c rotation autour de y de v1 de theta (a11_y=cos(theta) et a12_y=sin(theta) ) tq
88
!C  v1 soit sur l'axe Ox
89

    
90

    
91
          IF (norm1 .GE. 1.D-8) THEN
92
             a11_y = vz1/norm1
93
             a12_y = vx1/norm1
94
          ELSE
95
             a11_y = 1
96
             a12_y = 0
97
          END IF
98

    
99
             CALL rota_y(vx1,vy1,vz1,a11_y,a12_y)
100

    
101

    
102
!c calcul le vecteur de l atome dans la nouvelle orientation
103

    
104
          vx4=d*sin(a_val)
105
          vy4=0.
106
           vz4=d*cos(a_val)
107

    
108
!c calcul le vecteur de l atome
109
!c on tourne en sens invers
110
          CALL rota_y(vx4,vy4,vz4,a11_y ,-a12_y )
111
          CALL rota_z(vx4,vy4,vz4,a11_z1, a12_z1)
112

    
113
!c calcul l atome a partir de v4
114
          x(iat)=vx4+x(n1)
115
          y(iat)=vy4+y(n1)
116
          z(iat)=vz4+z(n1)
117

    
118
        END
119

    
120