Statistiques
| Révision :

root / src / test_zmat.f90

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

1
      FUNCTION test_zmat(na,ind_zmat)
2

    
3
! Test the validity of a z-matrix 
4

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

    
36
      use Path_module
37
      use Io_module
38

    
39
      IMPLICIT NONE
40

    
41
      logical :: pos,test_zmat
42
      integer(KINT) :: i,na,n
43
      integer(KINT) :: ind_zmat(Na,5)
44
      integer(KINT), ALLOCATABLE :: ind_pos(:)
45

    
46
      ALLOCATE(ind_pos(Na))
47
       pos=.true.
48

    
49
      DO i=1,na
50
       ind_pos(ind_zmat(i,1))=i
51
      END DO
52

    
53
      DO i=2,na
54
        n=ind_zmat(i,2)
55
        IF (ind_pos(n) .GE. i) THEN
56
           pos=.false. .AND. pos
57
           write(IOOUT,*) 'Bond:',n,ind_pos(n),i,pos
58
        END IF
59
      END DO
60

    
61
      DO i=3,na
62
        n=ind_zmat(i,3)
63
        IF (ind_pos(n) .GE. i) THEN
64
           pos=.false. .AND. pos
65
           write(IOOUT,*) 'Angle:',n,ind_pos(n),i,pos
66
        END IF
67
      END DO
68

    
69
      DO i=4,na
70
        n=ind_zmat(i,4)
71
        IF (ind_pos(n) .GE. i) THEN
72
           pos=.false. .AND. pos
73
           write(IOOUT,*) 'Dihedral:',n,ind_pos(n),i,pos
74
        END IF
75
      END DO
76

    
77
      test_zmat=pos
78
      DEALLOCATE(ind_pos)
79

    
80
      END