Statistiques
| Révision :

root / src / CalcBMat_mixed.f90

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

1 2 pfleura2
subroutine CalcBMat_mixed (natoms, xyzatm, indzmat, dzdc)
2 1 pfleura2
3 12 pfleura2
!----------------------------------------------------------------------
4 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
5 12 pfleura2
!  Centre National de la Recherche Scientifique,
6 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
7 12 pfleura2
!
8 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
9 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
10 12 pfleura2
!
11 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
12 12 pfleura2
!  Contact: optnpath@gmail.com
13 12 pfleura2
!
14 12 pfleura2
! This file is part of "Opt'n Path".
15 12 pfleura2
!
16 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
17 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
18 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
19 12 pfleura2
!  or (at your option) any later version.
20 12 pfleura2
!
21 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
22 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
23 12 pfleura2
!
24 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
25 12 pfleura2
!  GNU Affero General Public License for more details.
26 12 pfleura2
!
27 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
28 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
29 12 pfleura2
!
30 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
31 12 pfleura2
! for commercial licensing opportunities.
32 12 pfleura2
!----------------------------------------------------------------------
33 12 pfleura2
34 1 pfleura2
  use Io_module
35 12 pfleura2
  use Path_module, only : NCart
36 1 pfleura2
37 1 pfleura2
  IMPLICIT NONE
38 1 pfleura2
39 1 pfleura2
40 2 pfleura2
  integer(KINT), INTENT(IN) :: natoms, indzmat(natoms,5)
41 2 pfleura2
  real(KREAL), INTENT(IN)   :: xyzatm(3,natoms)
42 2 pfleura2
  real(KREAL), INTENT(OUT)   :: dzdc(3*natoms,3*natoms)
43 1 pfleura2
44 1 pfleura2
45 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!
46 1 pfleura2
!
47 1 pfleura2
! This routine computes the derivatives of the internal coordinates
48 1 pfleura2
! with respect to the cartesian coordinates.
49 1 pfleura2
! This is what is called the B matrix in Baker coordinates :
50 1 pfleura2
! B(i,j)=dz_i/dx_j
51 1 pfleura2
!
52 1 pfleura2
! it uses the same routines as Calc_baker
53 1 pfleura2
!
54 1 pfleura2
! Here, it is used for mixed Cart+Z-mat system
55 1 pfleura2
!
56 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!
57 1 pfleura2
!
58 1 pfleura2
! Input:
59 1 pfleura2
! natoms: number of atoms
60 1 pfleura2
! xyzatm(3,natoms): cartesian geometry
61 1 pfleura2
! indzmat(natoms,5): index of the Z-matrix definition
62 1 pfleura2
! atmass(natoms): mass of the atoms
63 1 pfleura2
! atome(natoms): ??
64 1 pfleura2
!
65 1 pfleura2
! Output:
66 1 pfleura2
! dzdc(3*natoms,3*natoms): B matrix
67 1 pfleura2
!
68 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
69 1 pfleura2
70 1 pfleura2
71 1 pfleura2
  INTERFACE
72 1 pfleura2
     function valid(string) result (isValid)
73 1 pfleura2
       CHARACTER(*), intent(in) :: string
74 1 pfleura2
       logical                  :: isValid
75 1 pfleura2
     END function VALID
76 1 pfleura2
  END INTERFACE
77 1 pfleura2
78 1 pfleura2
  LOGICAL :: debug
79 1 pfleura2
  INTEGER(KINT) :: i,j,k,iat, istart
80 1 pfleura2
  INTEGER(KINT) :: iat1, iat2, iat3, iat4
81 1 pfleura2
82 1 pfleura2
83 1 pfleura2
84 1 pfleura2
  ! ======================================================================
85 1 pfleura2
86 1 pfleura2
  debug=valid('CalcBMat').OR.valid('CalcBMat_mixed')
87 1 pfleura2
88 1 pfleura2
  if (debug) Call Header('Entering CalcBMat_mixed')
89 1 pfleura2
  if (debug) THEN
90 1 pfleura2
     WRITE(*,*) 'DBG CalcBMat_mixed Xyzatm '
91 1 pfleura2
     DO iat=1,natoms
92 1 pfleura2
        write(*,'(1X,I5,3(1X,F15.6))') iat, xyzatm(1:3,iat)
93 1 pfleura2
     END DO
94 1 pfleura2
     WRITE(*,*) 'DBG CalcBMat_mixed IndZmat'
95 1 pfleura2
     DO iat=1,natoms
96 1 pfleura2
        write(*,'(6(1X,I5))') iat, indzmat(iat,1:4)
97 1 pfleura2
     END DO
98 1 pfleura2
  END IF
99 1 pfleura2
100 1 pfleura2
  dzdc=0.d0
101 1 pfleura2
  do i = 1, NCart
102 1 pfleura2
     iat=indzmat(i,1)
103 1 pfleura2
     do j=1,3
104 1 pfleura2
        k=(iat-1)*3+j
105 1 pfleura2
        dzdc(k,k)=1.d0
106 1 pfleura2
     END DO
107 1 pfleura2
  END DO
108 1 pfleura2
109 1 pfleura2
    IF (NCart.EQ.1) THEN
110 1 pfleura2
       if (natoms.ge.2) THEN
111 1 pfleura2
          iat1=indzmat(2,1)
112 1 pfleura2
          iat2=indzmat(2,2)
113 1 pfleura2
          Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,4))
114 1 pfleura2
         END IF
115 1 pfleura2
    END IF
116 1 pfleura2
    IF (NCart.LE.2) THEN
117 1 pfleura2
       if (natoms.ge.3) THEN
118 1 pfleura2
          iat1=indzmat(3,1)
119 1 pfleura2
          iat2=indzmat(3,2)
120 1 pfleura2
          iat3=indzmat(3,3)
121 1 pfleura2
          Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,7))
122 1 pfleura2
          CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,8))
123 1 pfleura2
       END IF
124 1 pfleura2
    END IF
125 1 pfleura2
126 1 pfleura2
    IStart=max(NCart+1,4)
127 1 pfleura2
    k=(IStart-1)*3+1
128 1 pfleura2
  DO I=IStart, Natoms
129 1 pfleura2
     iat1=indzmat(i,1)
130 1 pfleura2
     iat2=indzmat(i,2)
131 1 pfleura2
     iat3=indzmat(i,3)
132 1 pfleura2
     iat4=indzmat(i,4)
133 1 pfleura2
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,k))
134 1 pfleura2
     k=k+1
135 1 pfleura2
     CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,k))
136 1 pfleura2
     k=k+1
137 1 pfleura2
     CALL CONSTRAINTS_TORSION_DER2(Natoms,iat1,iat2,iat3,iat4, xyzatm, dzdc(1,k))
138 1 pfleura2
     k=k+1
139 1 pfleura2
  END DO
140 1 pfleura2
141 1 pfleura2
142 1 pfleura2
143 1 pfleura2
144 1 pfleura2
145 1 pfleura2
  if (debug) Call Header('CalcBMat_mixed over')
146 1 pfleura2
147 1 pfleura2
  ! ======================================================================
148 1 pfleura2
149 1 pfleura2
end subroutine CalcBMat_mixed