Statistiques
| Révision :

root / src / CalcBMat_int.f90

Historique | Voir | Annoter | Télécharger (4,06 ko)

1
subroutine CalcBmat_int(natoms, xyzatm, indzmat, dzdc)
2

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

    
34
  use Io_module
35
  use Path_module, only :  atome
36

    
37
  IMPLICIT NONE
38

    
39

    
40
  integer(KINT), INTENT(IN) :: natoms, indzmat(natoms,5)
41
  real(KREAL), INTENT(IN)   :: xyzatm(3,natoms)
42
  real(KREAL), INTENT(OUT)   :: dzdc(3*natoms,3*natoms)
43

    
44

    
45
!!!!!!!!!!!!!!!!!!!!!
46
!
47
! This routine computes the derivatives of the internal coordinates
48
! with respect to the cartesian coordinates.
49
! This is what is called the B matrix in Baker coordinates :
50
! B(i,j)=dz_i/dx_j
51
!
52
! it uses the same routines as Calc_baker
53
!
54
!!!!!!!!!!!!!!!!!!!!!!
55
!
56
! Input:
57
! natoms: number of atoms
58
! xyzatm(3,natoms): cartesian geometry
59
! indzmat(natoms,5): index of the Z-matrix definition
60
! atmass(natoms): mass of the atoms
61
! atome(natoms): ??
62
!
63
! Output:
64
! dzdc(3*natoms,3*natoms): B matrix
65
!
66
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
67

    
68

    
69
  INTERFACE
70
     function valid(string) result (isValid)
71
       CHARACTER(*), intent(in) :: string
72
       logical                  :: isValid
73
     END function VALID
74
  END INTERFACE
75

    
76
  LOGICAL :: debug
77
  INTEGER(KINT) :: i,j,k,iat
78
  INTEGER(KINT) :: iat1, iat2, iat3, iat4
79

    
80

    
81
  ! ======================================================================
82

    
83

    
84
  debug=valid('CalcBmat_int').OR.valid('CalcBMat')
85
  if (debug) Call Header('Entering CalcBmat_int')
86

    
87
  if (debug) THEN
88
     WRITE(*,*) 'DBG CALCBMAT_INT Xyzatm '
89
     DO iat=1,natoms
90
        write(*,'(1X,I5,3(1X,F15.6))') atome(iat), xyzatm(1:3,iat)
91
     END DO
92
     WRITE(*,*) 'DBG CALCBMAT_INT IndZmat'
93
     DO iat=1,natoms
94
        write(*,'(6(1X,I5))') iat, indzmat(iat,1:4)
95
     END DO
96
  END IF
97

    
98
  dzdc=0.d0
99
  if (natoms.ge.2) THEN
100
     iat1=indzmat(2,1)
101
     iat2=indzmat(2,2)
102
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,4))
103
   END IF
104
  if (natoms.ge.3) THEN
105
     iat1=indzmat(3,1)
106
     iat2=indzmat(3,2)
107
     iat3=indzmat(3,3)
108
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,7))
109
     CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,8))
110
  END IF
111
  k=10
112
  DO I=4, Natoms
113
     iat1=indzmat(i,1)
114
     iat2=indzmat(i,2)
115
     iat3=indzmat(i,3)
116
     iat4=indzmat(i,4)
117
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,k))
118
     k=k+1
119
     CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,k))
120
     k=k+1
121
     CALL CONSTRAINTS_TORSION_DER2(Natoms,iat1,iat2,iat3,iat4, xyzatm, dzdc(1,k)) 
122
     k=k+1
123
  END DO
124

    
125

    
126
  if (debug) THEN
127
     WRITE(*,*) 'DBG CALCBMAT_INT dzdc '
128
     k=min(3*natoms,12)
129
     DO iat=1,natoms
130
        DO j=1,3
131
           write(*,'(1X,I5,12(1X,F12.6))') 3*iat-3+j, dzdc(1:k,3*iat-3+j)
132
        END DO
133
     END DO
134
  END IF             
135

    
136
  if (debug) Call Header('CalcBmat_int Over')
137
  ! ======================================================================
138

    
139
end subroutine CalcBmat_int