Statistiques
| Révision :

root / src / test_zmat.f90

Historique | Voir | Annoter | Télécharger (2,31 ko)

1 1 pfleura2
      FUNCTION test_zmat(na,ind_zmat)
2 1 pfleura2
3 12 pfleura2
! Test the validity of a z-matrix
4 12 pfleura2
5 12 pfleura2
!----------------------------------------------------------------------
6 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
7 12 pfleura2
!  Centre National de la Recherche Scientifique,
8 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
9 12 pfleura2
!
10 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
11 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
12 12 pfleura2
!
13 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
14 12 pfleura2
!  Contact: optnpath@gmail.com
15 12 pfleura2
!
16 12 pfleura2
! This file is part of "Opt'n Path".
17 12 pfleura2
!
18 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
19 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
20 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
21 12 pfleura2
!  or (at your option) any later version.
22 12 pfleura2
!
23 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
24 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
25 12 pfleura2
!
26 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
27 12 pfleura2
!  GNU Affero General Public License for more details.
28 12 pfleura2
!
29 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
30 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
31 12 pfleura2
!
32 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
33 12 pfleura2
! for commercial licensing opportunities.
34 12 pfleura2
!----------------------------------------------------------------------
35 12 pfleura2
36 1 pfleura2
      use Path_module
37 1 pfleura2
      use Io_module
38 1 pfleura2
39 1 pfleura2
      IMPLICIT NONE
40 1 pfleura2
41 1 pfleura2
      logical :: pos,test_zmat
42 1 pfleura2
      integer(KINT) :: i,na,n
43 1 pfleura2
      integer(KINT) :: ind_zmat(Na,5)
44 1 pfleura2
      integer(KINT), ALLOCATABLE :: ind_pos(:)
45 1 pfleura2
46 1 pfleura2
      ALLOCATE(ind_pos(Na))
47 1 pfleura2
       pos=.true.
48 1 pfleura2
49 1 pfleura2
      DO i=1,na
50 1 pfleura2
       ind_pos(ind_zmat(i,1))=i
51 1 pfleura2
      END DO
52 1 pfleura2
53 1 pfleura2
      DO i=2,na
54 1 pfleura2
        n=ind_zmat(i,2)
55 1 pfleura2
        IF (ind_pos(n) .GE. i) THEN
56 1 pfleura2
           pos=.false. .AND. pos
57 1 pfleura2
           write(IOOUT,*) 'Bond:',n,ind_pos(n),i,pos
58 1 pfleura2
        END IF
59 1 pfleura2
      END DO
60 1 pfleura2
61 1 pfleura2
      DO i=3,na
62 1 pfleura2
        n=ind_zmat(i,3)
63 1 pfleura2
        IF (ind_pos(n) .GE. i) THEN
64 1 pfleura2
           pos=.false. .AND. pos
65 1 pfleura2
           write(IOOUT,*) 'Angle:',n,ind_pos(n),i,pos
66 1 pfleura2
        END IF
67 1 pfleura2
      END DO
68 1 pfleura2
69 1 pfleura2
      DO i=4,na
70 1 pfleura2
        n=ind_zmat(i,4)
71 1 pfleura2
        IF (ind_pos(n) .GE. i) THEN
72 1 pfleura2
           pos=.false. .AND. pos
73 1 pfleura2
           write(IOOUT,*) 'Dihedral:',n,ind_pos(n),i,pos
74 1 pfleura2
        END IF
75 1 pfleura2
      END DO
76 1 pfleura2
77 1 pfleura2
      test_zmat=pos
78 1 pfleura2
      DEALLOCATE(ind_pos)
79 1 pfleura2
80 1 pfleura2
      END