Statistiques
| Révision :

root / src / Add2indzmat.f90 @ 12

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

1 1 pfleura2
SUBROUTINE  add2indzmat(na,izm,n1,n2,n3,n4,ind_zmat,x,y,z)
2 1 pfleura2
  ! This subroutine adds the description of atom n1
3 1 pfleura2
  ! into ind_zmat at position izm
4 1 pfleura2
  ! it checks that atoms n1 n2 n3 are not aligned
5 1 pfleura2
  ! and if so, it describes n1 as n1 n2 n4 n3 instead of n1 n2 n3 n4.
6 1 pfleura2
  ! As n2 n3 n4 are not aligned, this is sufficient to ensure that the description
7 1 pfleura2
  ! of n1 is ok.
8 12 pfleura2
9 12 pfleura2
!----------------------------------------------------------------------
10 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
11 12 pfleura2
!  Centre National de la Recherche Scientifique,
12 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
13 12 pfleura2
!
14 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
15 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
16 12 pfleura2
!
17 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
18 12 pfleura2
!  Contact: optnpath@gmail.com
19 12 pfleura2
!
20 12 pfleura2
! This file is part of "Opt'n Path".
21 12 pfleura2
!
22 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
23 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
24 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
25 12 pfleura2
!  or (at your option) any later version.
26 12 pfleura2
!
27 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
28 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
29 12 pfleura2
!
30 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
31 12 pfleura2
!  GNU Affero General Public License for more details.
32 12 pfleura2
!
33 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
34 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
35 12 pfleura2
!
36 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
37 12 pfleura2
! for commercial licensing opportunities.
38 12 pfleura2
!----------------------------------------------------------------------
39 12 pfleura2
40 1 pfleura2
  IMPLICIT NONE
41 1 pfleura2
42 1 pfleura2
  INTEGER, PARAMETER :: KINT=KIND(1)
43 1 pfleura2
  INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
44 1 pfleura2
45 1 pfleura2
46 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: na,izm,n1,n2
47 1 pfleura2
  INTEGER(KINT), INTENT(INOUT) :: n3,n4
48 1 pfleura2
  INTEGER(KINT) :: ind_zmat(na,5),n0
49 1 pfleura2
  REAL(KREAL) :: x(na), y(na), z(na)
50 1 pfleura2
51 1 pfleura2
  real(KREAL) :: vx1,vy1,vz1,norm1
52 1 pfleura2
  real(KREAL) :: vx2,vy2,vz2,norm2
53 1 pfleura2
  real(KREAL) :: vx3,vy3,vz3,norm3
54 1 pfleura2
  REAL(KREAL) :: pi
55 1 pfleura2
56 1 pfleura2
  LOGICAL :: debug
57 1 pfleura2
58 1 pfleura2
59 1 pfleura2
  REAL(KREAL) :: Ang123,Ang234,sangle
60 1 pfleura2
61 1 pfleura2
  INTERFACE
62 1 pfleura2
     function valid(string) result (isValid)
63 1 pfleura2
       CHARACTER(*), intent(in) :: string
64 1 pfleura2
       logical                  :: isValid
65 1 pfleura2
     END function VALID
66 1 pfleura2
67 1 pfleura2
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
68 1 pfleura2
       use Path_module, only :  Pi,KINT, KREAL
69 1 pfleura2
       real(KREAL) ::  v1x,v1y,v1z,norm1
70 1 pfleura2
       real(KREAL) ::  v2x,v2y,v2z,norm2
71 1 pfleura2
       real(KREAL) ::  angle
72 1 pfleura2
     END FUNCTION ANGLE
73 1 pfleura2
74 1 pfleura2
  END INTERFACE
75 1 pfleura2
76 1 pfleura2
  debug=valid("add2indzmat")
77 1 pfleura2
  pi=acos(-1.d0)
78 1 pfleura2
79 1 pfleura2
  if (debug) WRITE(*,*) "Entering Add2IndZmat with izm,n1,n2,n3,n4",izm,n1,n2,n3,n4
80 1 pfleura2
  Call vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
81 1 pfleura2
  Call vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
82 1 pfleura2
  Call vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
83 1 pfleura2
84 1 pfleura2
  Ang123=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)/180.*pi
85 1 pfleura2
  Ang234=angle(vx2,vy2,vz2,norm2,vx3,vy3,vz3,norm3)/180.*pi
86 1 pfleura2
87 1 pfleura2
  sangle=sin(ang123)
88 1 pfleura2
  if (sangle.LE.0.09d0) THEN
89 1 pfleura2
     sangle=sin(ang234)
90 1 pfleura2
     if (sangle.LE.0.09d0) THEN
91 1 pfleura2
        WRITE(*,*) "ERROR in Add2IndZmat : all four atoms aligned"
92 1 pfleura2
        WRITE(*,*) n1,n2,n3,n4
93 1 pfleura2
        STOP
94 1 pfleura2
     END IF
95 1 pfleura2
     n0=n3
96 1 pfleura2
     n3=n4
97 1 pfleura2
     n4=n0
98 1 pfleura2
  END IF
99 1 pfleura2
  ind_zmat(izm,1)=n1
100 1 pfleura2
  ind_zmat(izm,2)=n2
101 1 pfleura2
  ind_zmat(izm,3)=n3
102 1 pfleura2
  ind_zmat(izm,4)=n4
103 1 pfleura2
104 1 pfleura2
  RETURN
105 1 pfleura2
END SUBROUTINE add2indzmat