Statistiques
| Révision :

root / src / CalcBMat_int.f90 @ 4

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

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

    
3
  use Io_module
4
  use Path_module, only : MW,Pi
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
!!!!!!!!!!!!!!!!!!!!!!
23
!
24
! Input:
25
! natoms: number of atoms
26
! xyzatm(3,natoms): cartesian geometry
27
! indzmat(natoms,5): index of the Z-matrix definition
28
! atmass(natoms): mass of the atoms
29
! atome(natoms): ??
30
!
31
! Output:
32
! dzdc(3*natoms,3*natoms): B matrix
33
!
34
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
35

    
36

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

    
44
  LOGICAL :: debug
45
  INTEGER(KINT) :: i,j,k,iat
46
  INTEGER(KINT) :: iat1, iat2, iat3, iat4
47

    
48

    
49
  ! ======================================================================
50

    
51

    
52
  debug=valid('CalcBmat_int').OR.valid('CalcBMat')
53
  if (debug) Call Header('Entering CalcBmat_int')
54

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

    
66
  dzdc=0.d0
67
  if (natoms.ge.2) THEN
68
     iat1=indzmat(2,1)
69
     iat2=indzmat(2,2)
70
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,4))
71
   END IF
72
  if (natoms.ge.3) THEN
73
     iat1=indzmat(3,1)
74
     iat2=indzmat(3,2)
75
     iat3=indzmat(3,3)
76
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,7))
77
     CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,8))
78
  END IF
79
  k=10
80
  DO I=4, Natoms
81
     iat1=indzmat(i,1)
82
     iat2=indzmat(i,2)
83
     iat3=indzmat(i,3)
84
     iat4=indzmat(i,4)
85
     Call CONSTRAINTS_BONDLENGTH_DER(Natoms,iat1,iAT2, xyzatm, dzdc(1,k))
86
     k=k+1
87
     CALL CONSTRAINTS_BONDANGLE_DER(Natoms,iAt1,iAT2,iAt3, xyzatm, dzdc(1,k))
88
     k=k+1
89
     CALL CONSTRAINTS_TORSION_DER2(Natoms,iat1,iat2,iat3,iat4, xyzatm, dzdc(1,k)) 
90
     k=k+1
91
  END DO
92

    
93

    
94
  if (debug) THEN
95
     WRITE(*,*) 'DBG CALCBMAT_INT dzdc '
96
     k=min(3*natoms,12)
97
     DO iat=1,natoms
98
        DO j=1,3
99
           write(*,'(1X,I5,12(1X,F12.6))') 3*iat-3+j, dzdc(1:k,3*iat-3+j)
100
        END DO
101
     END DO
102
  END IF             
103

    
104
  if (debug) Call Header('CalcBmat_int Over')
105
  ! ======================================================================
106

    
107
end subroutine CalcBmat_int