Statistiques
| Révision :

root / src / Mixed2cart.f90

Historique | Voir | Annoter | Télécharger (3,68 ko)

1
SUBROUTINE Mixed2Cart(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,NCart,NCoord
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(*)
44
  REAL(KREAL), INTENT(OUT) :: XyzCoord(Nat,3)
45

    
46
  INTEGER(KINT) :: I, J, Idx, IBeg, Iat
47
  REAl(KREAL), ALLOCATABLE :: ValZmat(:,:),XyzTmp(:,:)
48
  REAL(KREAL) :: d, a_val
49

    
50
  LOGICAL :: Debug
51

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

    
59
  debug=valid('mixed2cart')
60

    
61
  if (debug) WRITE(*,*) "================ Entering Mixed2Cart =================="
62

    
63

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

    
66
  if (debug) WRITE(*,*) "DBG Mixed2Cart, IntCoord:",IntCoord(1:NCoord)
67
  Idx=1
68
  valzmat=0.
69
  XyzTmp=0.
70
  DO I=1,NCart
71
     XYZTmp(I,1:3)=IntCoord(Idx:Idx+2)
72
     valzmat(I,1:3)=IntCoord(Idx:Idx+2)
73
     Idx=Idx+3
74
  END DO
75

    
76
  IBeg=NCart+1
77
  SELECT CASE (NCart)
78
  CaSE (1)
79
     Idx=4
80
     XyzTmp(2,1)=IntCoord(Idx)
81
     XyzTmp(2,1:3)= XyzTmp(2,1:3)+ XyzTmp(1,1:3) 
82
     if (Nat.GE.3) THEN
83
        Idx=Idx+1
84
        d=IntCoord(Idx)
85
        Idx=Idx+1
86
        a_val=IntCoord(Idx)
87
        Idx=Idx+1
88
        call ConvertZmat_cart_3(3,IndZmat,d,a_val,       &
89
             XyzTmp(1,1), XyzTmp(1,2),XyzTmp(1,3))
90
     ENDIF
91
     IBeg=4
92
  CASE (2)
93
     Idx=7
94
     if (Nat.GE.3) THEN
95
        d=IntCoord(Idx)
96
        idx=idx+1
97
        a_val=IntCoord(Idx)
98
        Idx=Idx+1
99
        call ConvertZmat_cart_3(3,IndZmat,d,a_val,       &
100
             XyzTmp(1,1), XyzTmp(1,2),XyzTmp(1,3))
101
     ENDIF
102
     IBeg=4
103
  CASE DEFAULT
104
     Ibeg=NCart+1
105
  END SELECT
106

    
107
  DO iat=IBeg,Nat
108
     ValZmat(iat,1)=IntCoord(idx)
109
     Idx=Idx+1
110
     do j=2,3
111
        ValZmat(iat,J)=IntCoord(idx)*180./Pi
112
        Idx=Idx+1
113
     END DO
114
  END DO
115

    
116
  DO iat=iBeg,Nat
117
     call ConvertZmat_cart(iat,IndZmat,ValZmat,       &
118
          XyzTmp(1,1), XyzTmp(1,2),XyzTmp(1,3))
119
  END DO
120

    
121
  if (debug) THEN 
122
     WRITE(*,*) 'DBG Mixed2Cart XyzTmp'
123
     DO I=1,Nat
124
        WRITe(*,'(1X,I3,3(1X,F10.4))') I, XyzTmp(I,1:3)
125
     END DO
126
  END IF
127

    
128
!  XyzCoord=Reshape(XyzTmp,(/3,Nat/),ORDER=(/2,1/))
129
  XyzCoord=XyzTmp
130

    
131
  DEALLOCATE(valzmat,xyztmp)
132
  if (debug) WRITE(*,*) "================ Mixed2Cart Over =================="
133

    
134
END SUBROUTINE Mixed2Cart