Statistiques
| Révision :

root / src / AnalyzeGeom.f90

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

1
 SUBROUTINE AnalyzeGeom(GeomCart,Values)
2
! This routines read a list of geometrical variables to monitor
3
! This is inspired from Xyz2Path (that was inspired by Xyz2scan ...)
4

    
5
!----------------------------------------------------------------------
6
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
7
!  Centre National de la Recherche Scientifique,
8
!  Université Claude Bernard Lyon 1. All rights reserved.
9
!
10
!  This work is registered with the Agency for the Protection of Programs 
11
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
12
!
13
!  Authors: P. Fleurat-Lessard, P. Dayal
14
!  Contact: optnpath@gmail.com
15
!
16
! This file is part of "Opt'n Path".
17
!
18
!  "Opt'n Path" is free software: you can redistribute it and/or modify
19
!  it under the terms of the GNU Affero General Public License as
20
!  published by the Free Software Foundation, either version 3 of the License,
21
!  or (at your option) any later version.
22
!
23
!  "Opt'n Path" is distributed in the hope that it will be useful,
24
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
25
!
26
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
27
!  GNU Affero General Public License for more details.
28
!
29
!  You should have received a copy of the GNU Affero General Public License
30
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
31
!
32
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
33
! for commercial licensing opportunities.
34
!----------------------------------------------------------------------
35

    
36

    
37
  use VarTypes
38
  use Path_module
39
  use Io_module
40

    
41
  IMPLICIT NONE
42

    
43

    
44
  INTERFACE
45
     function valid(string) result (isValid)
46
       CHARACTER(*), intent(in) :: string
47
       logical                  :: isValid
48
     END function VALID
49

    
50
     SUBROUTINE die(routine, msg, file, line, unit)
51

    
52
       Use VarTypes
53
       Use io_module
54

    
55
       implicit none
56

    
57
       character(len=*), intent(in)           :: routine, msg
58
       character(len=*), intent(in), optional :: file
59
       integer(KINT), intent(in), optional      :: line, unit
60

    
61
     END SUBROUTINE die
62

    
63

    
64
     SUBROUTINE Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive,XPrimRef)
65

    
66
       Use VarTypes
67
       Use Io_module
68
       Use Path_module, only : pi
69

    
70
       IMPLICIT NONE
71

    
72
       Type (ListCoord), POINTER :: Coordinate
73
       INTEGER(KINT), INTENT(IN) :: Nat,NPrim
74
       REAL(KREAL), INTENT(IN) :: x(Nat), y(Nat), z(Nat)
75
       REAL(KREAL), INTENT(IN), OPTIONAL :: XPrimRef(NPrim) 
76
       REAL(KREAL), INTENT(OUT) :: XPrimitive(NPrim)
77

    
78
     END SUBROUTINE CALC_XPRIM
79

    
80
  END INTERFACE
81

    
82
! Input
83
  REAL(KREAL),INTENT(IN) :: GeomCart(Nat,3)
84
  REAL(KREAL), INTENT(OUT) :: Values(NbVar)
85

    
86
  LOGICAL :: Debug
87
  INTEGER(KINT) :: I,J,K,NatT
88
  REAL(KREAL), ALLOCATABLE :: GeoCartLoc(:,:) ! (Nat+NbCom,3)
89
  REAL(KREAL), ALLOCATABLE :: x(:),y(:),z(:) ! Nat+NbCom
90
  REAL(KREAL) :: COG(3),Weight
91

    
92

    
93

    
94
  Debug=Valid('AnaGeom')
95

    
96
  If (Debug) Call Header("Entering AnalyzeGeom")
97

    
98
  if (debug) THEN
99
     WRITE(*,*) "AnalyzeGeom  - GeomCart"
100
     DO K=1,Nat
101
        WRITE(*,'(1X,I5,3(1X,F15.8))') K,GeomCart(K,1:3)
102
     END DO
103
  END IF
104

    
105
  NAtt=Nat+NbCom
106
  ALLOCATE(GeoCartLoc(Natt,3),x(Natt),y(Natt),z(Natt))
107
  GeoCartLoc(1:Nat,:)=GeomCart(:,:)
108
  CurBary => Bary
109

    
110
  DO I=1, NbCom
111
     COG=0.
112
     Weight=0.
113
     DO j=1,CurBary%ListAtoms(0)
114
        DO k=1,3
115
           COG(k)=COG(k)+GeomCart(CurBary%ListAtoms(j),k)*CurBary%Weights(j)
116
        END DO
117
        Weight=Weight+CurBary%Weights(j)
118
     END DO
119
     COG=COG/Weight
120
     DO k=1,3
121
        GeoCartLoc(Nat+i,k)=COG(k)
122
     END DO
123
  END DO
124
     
125
  Values=0.
126

    
127
  if (debug) THEN
128
     WRITE(*,*) "AnalyzeGeom before Calc_Xprim - GeomCartLoc"
129
     DO K=1,Nat+NbCom
130
        WRITE(*,*) K,GeoCartLoc(K,1:3)
131
     END DO
132
  END IF
133

    
134
  x = GeoCartLoc(:,1)
135
  y = GeoCartLoc(:,2)
136
  z = GeoCartLoc(:,3)
137

    
138
   Call Calc_XPrim(Natt,x,y,z,GeomList,NbVar,Values)
139

    
140
   DeALLOCATE(GeoCartLoc,x,y,z)
141

    
142
   if (debug) THEN
143
      WRITE(*,*) 'AnalyzeGeom: NbVar,Values',NbVar,Values
144
   END IF
145

    
146
  If (Debug) Call Header("Exiting AnalizeGeom")
147

    
148
END SUBROUTINE AnalyzeGeom