Statistiques
| Révision :

root / src / Int2cart.f90

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

1
SUBROUTINE Int2Cart(Nat,IndZmat,IntCoord,XyzCoord)
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 Path_module, ONLY : Pi
35

    
36
  IMPLICIT NONE
37
  
38
  INTEGER, PARAMETER :: Kint=Kind(1)
39
  INTEGER, PARAMETER :: KREAL=Kind(1.0D0)
40

    
41
  INTEGER(KINT), INTENT(IN) :: Nat
42
  INTEGER(KINT), INTENT(IN) :: IndZmat(Nat,5)
43
  REAL(KREAL), INTENT(IN) :: IntCoord(3*Nat-6)
44
  REAL(KREAL), INTENT(OUT) :: XyzCoord(Nat,3)
45

    
46
  INTEGER(KINT) :: I
47
  REAl(KREAL), ALLOCATABLE :: ValZmat(:,:),XyzTmp(:,:)
48
  REAL(KREAL) :: d, a_val
49
  LOGICAL :: debug
50

    
51
  INTERFACE
52
     function valid(string) result (isValid)
53
       CHARACTER(*), intent(in) :: string
54
       logical                  :: isValid
55
     END function VALID
56

    
57
  END INTERFACE
58

    
59
  debug=valid('int2cart')
60

    
61
   if (debug) WRITE(*,*) '================ Entering Int2Cart ==================='
62

    
63
  ALLOCATE(ValZmat(Nat,3),XyzTmp(Nat,3))
64

    
65
  ValZmat=0.d0
66
  ValZmat(2,1)=IntCoord(1)
67
  ValZmat(3,1)=IntCoord(2)
68
  ValZmat(3,2)=IntCoord(3)*180./Pi
69
  DO I=4,Nat
70
     ValZmat(I,1)=IntCoord(3*I-8)
71
     ValZmat(I,2)=IntCoord(3*I-7)*180./Pi
72
     ValZmat(I,3)=IntCoord(3*I-6)*180./Pi
73
  END DO
74

    
75
  IF (debug) THEN
76
     WRITE(*,*) 'DBG Int2Cart'
77
     DO I=1,Nat
78
        WRITe(*,'(1X,I3,3(1X,I3,1X,F10.4))') IndZmat(I,1), IndZmat(I,2), ValZmat(I,1), IndZmat(I,3),&
79
             ValZmat(I,2), IndZmat(I,4), Valzmat(I,3)
80
     END DO
81
  END IF
82

    
83
  Xyztmp=0.d0
84
  Xyztmp(2,1)=valzmat(2,1)
85
  d=valzmat(3,1)
86
  a_val=valzmat(3,2)/180.*Pi
87
!              write(*,*) "aval,pi",a_val,valzmat(3,2),pi
88
  if (Nat.GE.3) THEN
89
     if (IndZmat(3,2).EQ.1)  THEN
90
        Xyztmp(3,1)=Xyztmp(1,1)+d*cos(a_val)
91
     ELSE
92
        Xyztmp(3,1)=Xyztmp(2,1)-d*cos(a_val)
93
     ENDIF
94
     Xyztmp(3,2)=d*sin(a_val)
95
  ENDIF
96
  !              i=1
97
  !                WRITE(*,*) 'TOTOCart:',i, (Xyztmp(I,J),J=1,3)
98
  !                WRITE(*,*) 'TOTOZma:',i, (valzmat(I,J),J=1,3)
99
  !              i=2
100
  !                WRITE(*,*) 'TOTOCart:',i, (Xyztmp(I,J),J=1,3)
101
  !                WRITE(*,*) 'TOTOZma:',i, (valzmat(I,J),J=1,3)
102
  !              i=3
103
  !                WRITE(*,*) 'TOTOCart:',i, (Xyztmp(I,J),J=1,3)
104
  !                WRITE(*,*) 'TOTOZma:',i, (valzmat(I,J),J=1,3)
105

    
106
  DO i=4,Nat
107
     call ConvertZmat_cart(i,IndZmat,valzmat,                &
108
          Xyztmp(1,1), Xyztmp(1,2),Xyztmp(1,3))
109
     !                  WRITE(*,*) 'TOTOZma:',i,IndZmat(I,1),            &
110
     !                        (IndZmat(I,J+1),valzmat(I,J),J=1,3)
111
     !                   WRITE(*,*) 'TOTOCart:',i, (Xyztmp(I,J),J=1,3)
112
  END DO
113

    
114
  IF (debug) THEN
115
     WRITE(*,*) 'DBG Int2Cart XyzTmp'
116
     DO I=1,Nat
117
        WRITe(*,'(1X,I3,3(1X,F10.4))') I, XyzTmp(I,1:3)
118
     END DO
119
  END IF
120

    
121

    
122
!  XyzCoord=Reshape(XyzTmp,(/3,Nat/),ORDER=(/2,1/))
123
  XyzCoord=XyzTmp
124

    
125
  DEALLOCATE(valzmat,xyztmp)
126
  if (debug) WRITE(*,*) '================ Exiting Int2cart ==================='
127

    
128
END SUBROUTINE Int2Cart