Statistiques
| Révision :

root / src / CalcBMat_mixed.f90 @ 2

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

1
subroutine CalcBMat_mixed (natoms, xyzatm, indzmat, dzdc, atmass,atome)
2

    
3
  use Io_module
4
  use Path_module, only : MW, NCart
5

    
6
  IMPLICIT NONE
7

    
8

    
9
  integer(KINT) :: natoms, indzmat(natoms,5),atome(natoms)
10
  real(KREAL)   :: xyzatm(3,natoms), dzdc(3*natoms,3*natoms),atmass(natoms)
11

    
12

    
13
!!!!!!!!!!!!!!!!!!!!!
14
!
15
! This routine computes the derivatives of the internal coordinates
16
! with respect to the cartesian coordinates.
17
! This is what is called the B matrix in Baker coordinates :
18
! B(i,j)=dz_i/dx_j
19
!
20
! it uses the same routines as Calc_baker
21
!
22
! Here, it is used for mixed Cart+Z-mat system
23
!
24
!!!!!!!!!!!!!!!!!!!!!!
25
!
26
! Input:
27
! natoms: number of atoms
28
! xyzatm(3,natoms): cartesian geometry
29
! indzmat(natoms,5): index of the Z-matrix definition
30
! atmass(natoms): mass of the atoms
31
! atome(natoms): ??
32
!
33
! Output:
34
! dzdc(3*natoms,3*natoms): B matrix
35
!
36
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
37

    
38

    
39
  INTERFACE
40
     function valid(string) result (isValid)
41
       CHARACTER(*), intent(in) :: string
42
       logical                  :: isValid
43
     END function VALID
44
  END INTERFACE
45

    
46
  LOGICAL :: debug
47
  INTEGER(KINT) :: i,j,k,iat, istart
48
  INTEGER(KINT) :: iat1, iat2, iat3, iat4
49

    
50

    
51

    
52
  ! ======================================================================
53

    
54
  debug=valid('CalcBMat').OR.valid('CalcBMat_mixed')
55

    
56
  if (debug) Call Header('Entering CalcBMat_mixed')
57
  if (debug) THEN
58
     WRITE(*,*) 'DBG CalcBMat_mixed Xyzatm '
59
     DO iat=1,natoms
60
        write(*,'(1X,I5,3(1X,F15.6))') iat, xyzatm(1:3,iat)
61
     END DO
62
     WRITE(*,*) 'DBG CalcBMat_mixed IndZmat'
63
     DO iat=1,natoms
64
        write(*,'(6(1X,I5))') iat, indzmat(iat,1:4)
65
     END DO
66
  END IF
67

    
68
  dzdc=0.d0
69
  do i = 1, NCart
70
     iat=indzmat(i,1)
71
     do j=1,3
72
        k=(iat-1)*3+j
73
        dzdc(k,k)=1.d0
74
     END DO
75
  END DO
76

    
77
    IF (NCart.EQ.1) THEN
78
       if (natoms.ge.2) THEN
79
          iat1=indzmat(2,1)
80
          iat2=indzmat(2,2)
81
          Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,4))
82
         END IF
83
    END IF
84
    IF (NCart.LE.2) THEN
85
       if (natoms.ge.3) THEN
86
          iat1=indzmat(3,1)
87
          iat2=indzmat(3,2)
88
          iat3=indzmat(3,3)
89
          Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,7))
90
          CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,8))
91
       END IF
92
    END IF
93

    
94
    IStart=max(NCart+1,4)
95
    k=(IStart-1)*3+1
96
  DO I=IStart, Natoms
97
     iat1=indzmat(i,1)
98
     iat2=indzmat(i,2)
99
     iat3=indzmat(i,3)
100
     iat4=indzmat(i,4)
101
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,k))
102
     k=k+1
103
     CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,k))
104
     k=k+1
105
     CALL CONSTRAINTS_TORSION_DER2(Natoms,iat1,iat2,iat3,iat4, xyzatm, dzdc(1,k)) 
106
     k=k+1
107
  END DO
108
             
109

    
110

    
111

    
112

    
113
  if (debug) Call Header('CalcBMat_mixed over')
114

    
115
  ! ======================================================================
116

    
117
end subroutine CalcBMat_mixed