Statistiques
| Révision :

root / src / AnalyzeGeom.f90

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

1 7 pfleura2
 SUBROUTINE AnalyzeGeom(GeomCart,Values)
2 7 pfleura2
! This routines read a list of geometrical variables to monitor
3 7 pfleura2
! This is inspired from Xyz2Path (that was inspired by Xyz2scan ...)
4 7 pfleura2
5 12 pfleura2
!----------------------------------------------------------------------
6 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
7 12 pfleura2
!  Centre National de la Recherche Scientifique,
8 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
9 12 pfleura2
!
10 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
11 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
12 12 pfleura2
!
13 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
14 12 pfleura2
!  Contact: optnpath@gmail.com
15 12 pfleura2
!
16 12 pfleura2
! This file is part of "Opt'n Path".
17 12 pfleura2
!
18 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
19 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
20 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
21 12 pfleura2
!  or (at your option) any later version.
22 12 pfleura2
!
23 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
24 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
25 12 pfleura2
!
26 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
27 12 pfleura2
!  GNU Affero General Public License for more details.
28 12 pfleura2
!
29 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
30 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
31 12 pfleura2
!
32 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
33 12 pfleura2
! for commercial licensing opportunities.
34 12 pfleura2
!----------------------------------------------------------------------
35 7 pfleura2
36 12 pfleura2
37 7 pfleura2
  use VarTypes
38 7 pfleura2
  use Path_module
39 7 pfleura2
  use Io_module
40 7 pfleura2
41 7 pfleura2
  IMPLICIT NONE
42 7 pfleura2
43 7 pfleura2
44 7 pfleura2
  INTERFACE
45 7 pfleura2
     function valid(string) result (isValid)
46 7 pfleura2
       CHARACTER(*), intent(in) :: string
47 7 pfleura2
       logical                  :: isValid
48 7 pfleura2
     END function VALID
49 7 pfleura2
50 7 pfleura2
     SUBROUTINE die(routine, msg, file, line, unit)
51 7 pfleura2
52 7 pfleura2
       Use VarTypes
53 7 pfleura2
       Use io_module
54 7 pfleura2
55 7 pfleura2
       implicit none
56 7 pfleura2
57 7 pfleura2
       character(len=*), intent(in)           :: routine, msg
58 7 pfleura2
       character(len=*), intent(in), optional :: file
59 7 pfleura2
       integer(KINT), intent(in), optional      :: line, unit
60 7 pfleura2
61 7 pfleura2
     END SUBROUTINE die
62 7 pfleura2
63 7 pfleura2
64 7 pfleura2
     SUBROUTINE Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive,XPrimRef)
65 7 pfleura2
66 7 pfleura2
       Use VarTypes
67 7 pfleura2
       Use Io_module
68 7 pfleura2
       Use Path_module, only : pi
69 7 pfleura2
70 7 pfleura2
       IMPLICIT NONE
71 7 pfleura2
72 7 pfleura2
       Type (ListCoord), POINTER :: Coordinate
73 7 pfleura2
       INTEGER(KINT), INTENT(IN) :: Nat,NPrim
74 7 pfleura2
       REAL(KREAL), INTENT(IN) :: x(Nat), y(Nat), z(Nat)
75 7 pfleura2
       REAL(KREAL), INTENT(IN), OPTIONAL :: XPrimRef(NPrim)
76 7 pfleura2
       REAL(KREAL), INTENT(OUT) :: XPrimitive(NPrim)
77 7 pfleura2
78 7 pfleura2
     END SUBROUTINE CALC_XPRIM
79 7 pfleura2
80 7 pfleura2
  END INTERFACE
81 7 pfleura2
82 7 pfleura2
! Input
83 7 pfleura2
  REAL(KREAL),INTENT(IN) :: GeomCart(Nat,3)
84 7 pfleura2
  REAL(KREAL), INTENT(OUT) :: Values(NbVar)
85 7 pfleura2
86 7 pfleura2
  LOGICAL :: Debug
87 7 pfleura2
  INTEGER(KINT) :: I,J,K,NatT
88 7 pfleura2
  REAL(KREAL), ALLOCATABLE :: GeoCartLoc(:,:) ! (Nat+NbCom,3)
89 7 pfleura2
  REAL(KREAL), ALLOCATABLE :: x(:),y(:),z(:) ! Nat+NbCom
90 7 pfleura2
  REAL(KREAL) :: COG(3),Weight
91 7 pfleura2
92 7 pfleura2
93 7 pfleura2
94 7 pfleura2
  Debug=Valid('AnaGeom')
95 7 pfleura2
96 7 pfleura2
  If (Debug) Call Header("Entering AnalyzeGeom")
97 7 pfleura2
98 7 pfleura2
  if (debug) THEN
99 7 pfleura2
     WRITE(*,*) "AnalyzeGeom  - GeomCart"
100 7 pfleura2
     DO K=1,Nat
101 7 pfleura2
        WRITE(*,'(1X,I5,3(1X,F15.8))') K,GeomCart(K,1:3)
102 7 pfleura2
     END DO
103 7 pfleura2
  END IF
104 7 pfleura2
105 7 pfleura2
  NAtt=Nat+NbCom
106 7 pfleura2
  ALLOCATE(GeoCartLoc(Natt,3),x(Natt),y(Natt),z(Natt))
107 7 pfleura2
  GeoCartLoc(1:Nat,:)=GeomCart(:,:)
108 7 pfleura2
  CurBary => Bary
109 7 pfleura2
110 7 pfleura2
  DO I=1, NbCom
111 7 pfleura2
     COG=0.
112 7 pfleura2
     Weight=0.
113 7 pfleura2
     DO j=1,CurBary%ListAtoms(0)
114 7 pfleura2
        DO k=1,3
115 7 pfleura2
           COG(k)=COG(k)+GeomCart(CurBary%ListAtoms(j),k)*CurBary%Weights(j)
116 7 pfleura2
        END DO
117 7 pfleura2
        Weight=Weight+CurBary%Weights(j)
118 7 pfleura2
     END DO
119 7 pfleura2
     COG=COG/Weight
120 7 pfleura2
     DO k=1,3
121 7 pfleura2
        GeoCartLoc(Nat+i,k)=COG(k)
122 7 pfleura2
     END DO
123 7 pfleura2
  END DO
124 7 pfleura2
125 7 pfleura2
  Values=0.
126 7 pfleura2
127 7 pfleura2
  if (debug) THEN
128 7 pfleura2
     WRITE(*,*) "AnalyzeGeom before Calc_Xprim - GeomCartLoc"
129 7 pfleura2
     DO K=1,Nat+NbCom
130 7 pfleura2
        WRITE(*,*) K,GeoCartLoc(K,1:3)
131 7 pfleura2
     END DO
132 7 pfleura2
  END IF
133 7 pfleura2
134 7 pfleura2
  x = GeoCartLoc(:,1)
135 7 pfleura2
  y = GeoCartLoc(:,2)
136 7 pfleura2
  z = GeoCartLoc(:,3)
137 7 pfleura2
138 7 pfleura2
   Call Calc_XPrim(Natt,x,y,z,GeomList,NbVar,Values)
139 7 pfleura2
140 7 pfleura2
   DeALLOCATE(GeoCartLoc,x,y,z)
141 7 pfleura2
142 7 pfleura2
   if (debug) THEN
143 7 pfleura2
      WRITE(*,*) 'AnalyzeGeom: NbVar,Values',NbVar,Values
144 7 pfleura2
   END IF
145 7 pfleura2
146 7 pfleura2
  If (Debug) Call Header("Exiting AnalizeGeom")
147 7 pfleura2
148 7 pfleura2
END SUBROUTINE AnalyzeGeom