Statistiques
| Révision :

root / src / Mixed2cart.f90

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

1 1 pfleura2
SUBROUTINE Mixed2Cart(Nat,IndZmat,IntCoord,XyzCoord)
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 Path_module, ONLY : Pi,NCart,NCoord
35 1 pfleura2
36 1 pfleura2
  IMPLICIT NONE
37 1 pfleura2
38 1 pfleura2
  INTEGER, PARAMETER :: Kint=Kind(1)
39 1 pfleura2
  INTEGER, PARAMETER :: KREAL=Kind(1.0D0)
40 1 pfleura2
41 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: Nat
42 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: IndZmat(Nat,5)
43 1 pfleura2
  REAL(KREAL), INTENT(IN) :: IntCoord(*)
44 1 pfleura2
  REAL(KREAL), INTENT(OUT) :: XyzCoord(Nat,3)
45 1 pfleura2
46 2 pfleura2
  INTEGER(KINT) :: I, J, Idx, IBeg, Iat
47 1 pfleura2
  REAl(KREAL), ALLOCATABLE :: ValZmat(:,:),XyzTmp(:,:)
48 1 pfleura2
  REAL(KREAL) :: d, a_val
49 1 pfleura2
50 1 pfleura2
  LOGICAL :: Debug
51 1 pfleura2
52 1 pfleura2
  INTERFACE
53 1 pfleura2
     function valid(string) result (isValid)
54 1 pfleura2
       CHARACTER(*), intent(in) :: string
55 1 pfleura2
       logical                  :: isValid
56 1 pfleura2
     END function VALID
57 1 pfleura2
  END INTERFACE
58 1 pfleura2
59 1 pfleura2
  debug=valid('mixed2cart')
60 1 pfleura2
61 1 pfleura2
  if (debug) WRITE(*,*) "================ Entering Mixed2Cart =================="
62 1 pfleura2
63 1 pfleura2
64 1 pfleura2
  ALLOCATE(ValZmat(Nat,3),XyzTmp(Nat,3))
65 1 pfleura2
66 1 pfleura2
  if (debug) WRITE(*,*) "DBG Mixed2Cart, IntCoord:",IntCoord(1:NCoord)
67 1 pfleura2
  Idx=1
68 1 pfleura2
  valzmat=0.
69 1 pfleura2
  XyzTmp=0.
70 1 pfleura2
  DO I=1,NCart
71 1 pfleura2
     XYZTmp(I,1:3)=IntCoord(Idx:Idx+2)
72 1 pfleura2
     valzmat(I,1:3)=IntCoord(Idx:Idx+2)
73 1 pfleura2
     Idx=Idx+3
74 1 pfleura2
  END DO
75 1 pfleura2
76 1 pfleura2
  IBeg=NCart+1
77 1 pfleura2
  SELECT CASE (NCart)
78 1 pfleura2
  CaSE (1)
79 1 pfleura2
     Idx=4
80 1 pfleura2
     XyzTmp(2,1)=IntCoord(Idx)
81 1 pfleura2
     XyzTmp(2,1:3)= XyzTmp(2,1:3)+ XyzTmp(1,1:3)
82 1 pfleura2
     if (Nat.GE.3) THEN
83 1 pfleura2
        Idx=Idx+1
84 1 pfleura2
        d=IntCoord(Idx)
85 1 pfleura2
        Idx=Idx+1
86 1 pfleura2
        a_val=IntCoord(Idx)
87 1 pfleura2
        Idx=Idx+1
88 1 pfleura2
        call ConvertZmat_cart_3(3,IndZmat,d,a_val,       &
89 1 pfleura2
             XyzTmp(1,1), XyzTmp(1,2),XyzTmp(1,3))
90 1 pfleura2
     ENDIF
91 1 pfleura2
     IBeg=4
92 1 pfleura2
  CASE (2)
93 1 pfleura2
     Idx=7
94 1 pfleura2
     if (Nat.GE.3) THEN
95 1 pfleura2
        d=IntCoord(Idx)
96 1 pfleura2
        idx=idx+1
97 1 pfleura2
        a_val=IntCoord(Idx)
98 1 pfleura2
        Idx=Idx+1
99 1 pfleura2
        call ConvertZmat_cart_3(3,IndZmat,d,a_val,       &
100 1 pfleura2
             XyzTmp(1,1), XyzTmp(1,2),XyzTmp(1,3))
101 1 pfleura2
     ENDIF
102 1 pfleura2
     IBeg=4
103 1 pfleura2
  CASE DEFAULT
104 1 pfleura2
     Ibeg=NCart+1
105 1 pfleura2
  END SELECT
106 1 pfleura2
107 1 pfleura2
  DO iat=IBeg,Nat
108 1 pfleura2
     ValZmat(iat,1)=IntCoord(idx)
109 1 pfleura2
     Idx=Idx+1
110 1 pfleura2
     do j=2,3
111 1 pfleura2
        ValZmat(iat,J)=IntCoord(idx)*180./Pi
112 1 pfleura2
        Idx=Idx+1
113 1 pfleura2
     END DO
114 1 pfleura2
  END DO
115 1 pfleura2
116 1 pfleura2
  DO iat=iBeg,Nat
117 1 pfleura2
     call ConvertZmat_cart(iat,IndZmat,ValZmat,       &
118 1 pfleura2
          XyzTmp(1,1), XyzTmp(1,2),XyzTmp(1,3))
119 1 pfleura2
  END DO
120 1 pfleura2
121 1 pfleura2
  if (debug) THEN
122 1 pfleura2
     WRITE(*,*) 'DBG Mixed2Cart XyzTmp'
123 1 pfleura2
     DO I=1,Nat
124 1 pfleura2
        WRITe(*,'(1X,I3,3(1X,F10.4))') I, XyzTmp(I,1:3)
125 1 pfleura2
     END DO
126 1 pfleura2
  END IF
127 1 pfleura2
128 1 pfleura2
!  XyzCoord=Reshape(XyzTmp,(/3,Nat/),ORDER=(/2,1/))
129 1 pfleura2
  XyzCoord=XyzTmp
130 1 pfleura2
131 1 pfleura2
  DEALLOCATE(valzmat,xyztmp)
132 1 pfleura2
  if (debug) WRITE(*,*) "================ Mixed2Cart Over =================="
133 1 pfleura2
134 1 pfleura2
END SUBROUTINE Mixed2Cart