Statistiques
| Révision :

root / src / Add2indzmat.f90

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

1
SUBROUTINE  add2indzmat(na,izm,n1,n2,n3,n4,ind_zmat,x,y,z)
2
  ! This subroutine adds the description of atom n1
3
  ! into ind_zmat at position izm
4
  ! it checks that atoms n1 n2 n3 are not aligned
5
  ! and if so, it describes n1 as n1 n2 n4 n3 instead of n1 n2 n3 n4.
6
  ! As n2 n3 n4 are not aligned, this is sufficient to ensure that the description
7
  ! of n1 is ok.
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
  IMPLICIT NONE
41

    
42
  INTEGER, PARAMETER :: KINT=KIND(1)
43
  INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
44

    
45

    
46
  INTEGER(KINT), INTENT(IN) :: na,izm,n1,n2
47
  INTEGER(KINT), INTENT(INOUT) :: n3,n4
48
  INTEGER(KINT) :: ind_zmat(na,5),n0
49
  REAL(KREAL) :: x(na), y(na), z(na)
50

    
51
  real(KREAL) :: vx1,vy1,vz1,norm1
52
  real(KREAL) :: vx2,vy2,vz2,norm2
53
  real(KREAL) :: vx3,vy3,vz3,norm3
54
  REAL(KREAL) :: pi
55

    
56
  LOGICAL :: debug
57

    
58

    
59
  REAL(KREAL) :: Ang123,Ang234,sangle
60

    
61
  INTERFACE
62
     function valid(string) result (isValid)
63
       CHARACTER(*), intent(in) :: string
64
       logical                  :: isValid
65
     END function VALID
66

    
67
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
68
       use Path_module, only :  Pi,KINT, KREAL
69
       real(KREAL) ::  v1x,v1y,v1z,norm1
70
       real(KREAL) ::  v2x,v2y,v2z,norm2
71
       real(KREAL) ::  angle
72
     END FUNCTION ANGLE
73

    
74
  END INTERFACE
75

    
76
  debug=valid("add2indzmat")
77
  pi=acos(-1.d0)
78

    
79
  if (debug) WRITE(*,*) "Entering Add2IndZmat with izm,n1,n2,n3,n4",izm,n1,n2,n3,n4
80
  Call vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
81
  Call vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
82
  Call vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
83

    
84
  Ang123=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)/180.*pi
85
  Ang234=angle(vx2,vy2,vz2,norm2,vx3,vy3,vz3,norm3)/180.*pi
86

    
87
  sangle=sin(ang123)
88
  if (sangle.LE.0.09d0) THEN
89
     sangle=sin(ang234) 
90
     if (sangle.LE.0.09d0) THEN
91
        WRITE(*,*) "ERROR in Add2IndZmat : all four atoms aligned"
92
        WRITE(*,*) n1,n2,n3,n4
93
        STOP
94
     END IF
95
     n0=n3
96
     n3=n4
97
     n4=n0
98
  END IF
99
  ind_zmat(izm,1)=n1
100
  ind_zmat(izm,2)=n2
101
  ind_zmat(izm,3)=n3
102
  ind_zmat(izm,4)=n4
103

    
104
  RETURN
105
END SUBROUTINE add2indzmat
106