Statistiques
| Révision :

root / src / CalcBMat_mixed.f90

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

1
subroutine CalcBMat_mixed (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 : NCart
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
! Here, it is used for mixed Cart+Z-mat system
55
!
56
!!!!!!!!!!!!!!!!!!!!!!
57
!
58
! Input:
59
! natoms: number of atoms
60
! xyzatm(3,natoms): cartesian geometry
61
! indzmat(natoms,5): index of the Z-matrix definition
62
! atmass(natoms): mass of the atoms
63
! atome(natoms): ??
64
!
65
! Output:
66
! dzdc(3*natoms,3*natoms): B matrix
67
!
68
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
69

    
70

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

    
78
  LOGICAL :: debug
79
  INTEGER(KINT) :: i,j,k,iat, istart
80
  INTEGER(KINT) :: iat1, iat2, iat3, iat4
81

    
82

    
83

    
84
  ! ======================================================================
85

    
86
  debug=valid('CalcBMat').OR.valid('CalcBMat_mixed')
87

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

    
100
  dzdc=0.d0
101
  do i = 1, NCart
102
     iat=indzmat(i,1)
103
     do j=1,3
104
        k=(iat-1)*3+j
105
        dzdc(k,k)=1.d0
106
     END DO
107
  END DO
108

    
109
    IF (NCart.EQ.1) THEN
110
       if (natoms.ge.2) THEN
111
          iat1=indzmat(2,1)
112
          iat2=indzmat(2,2)
113
          Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,4))
114
         END IF
115
    END IF
116
    IF (NCart.LE.2) THEN
117
       if (natoms.ge.3) THEN
118
          iat1=indzmat(3,1)
119
          iat2=indzmat(3,2)
120
          iat3=indzmat(3,3)
121
          Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,7))
122
          CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,8))
123
       END IF
124
    END IF
125

    
126
    IStart=max(NCart+1,4)
127
    k=(IStart-1)*3+1
128
  DO I=IStart, Natoms
129
     iat1=indzmat(i,1)
130
     iat2=indzmat(i,2)
131
     iat3=indzmat(i,3)
132
     iat4=indzmat(i,4)
133
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,k))
134
     k=k+1
135
     CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,k))
136
     k=k+1
137
     CALL CONSTRAINTS_TORSION_DER2(Natoms,iat1,iat2,iat3,iat4, xyzatm, dzdc(1,k)) 
138
     k=k+1
139
  END DO
140
             
141

    
142

    
143

    
144

    
145
  if (debug) Call Header('CalcBMat_mixed over')
146

    
147
  ! ======================================================================
148

    
149
end subroutine CalcBMat_mixed