root / src / Decomp_frag.f90
Historique | Voir | Annoter | Télécharger (5,07 ko)
1 |
!This subroutines decomposes a connectivity list into fragments. |
---|---|
2 |
SUBROUTINE Decomp_Frag(na,ListConnect,ListAt,nbfrag,Fragment,NbAtFrag,FragAt) |
3 |
|
4 |
!---------------------------------------------------------------------- |
5 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
6 |
! Centre National de la Recherche Scientifique, |
7 |
! Université Claude Bernard Lyon 1. All rights reserved. |
8 |
! |
9 |
! This work is registered with the Agency for the Protection of Programs |
10 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
11 |
! |
12 |
! Authors: P. Fleurat-Lessard, P. Dayal |
13 |
! Contact: optnpath@gmail.com |
14 |
! |
15 |
! This file is part of "Opt'n Path". |
16 |
! |
17 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
18 |
! it under the terms of the GNU Affero General Public License as |
19 |
! published by the Free Software Foundation, either version 3 of the License, |
20 |
! or (at your option) any later version. |
21 |
! |
22 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
23 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
24 |
! |
25 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
26 |
! GNU Affero General Public License for more details. |
27 |
! |
28 |
! You should have received a copy of the GNU Affero General Public License |
29 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
30 |
! |
31 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
32 |
! for commercial licensing opportunities. |
33 |
!---------------------------------------------------------------------- |
34 |
|
35 |
Use Path_module, only : NMaxL |
36 |
Use Io_module |
37 |
|
38 |
IMPLICIT NONE |
39 |
|
40 |
INTEGER(KINT), INTENT(IN) :: na |
41 |
INTEGER(KINT), INTENT(IN) :: ListConnect(na,0:NMaxL) |
42 |
LOGICAL, INTENT(IN) :: ListAt(na) |
43 |
INTEGER(KINT), INTENT(OUT) :: NbFrag,Fragment(na),NbAtFrag(na),FragAt(na,na) |
44 |
|
45 |
INTEGER(KINT) :: i, j, iat, jat |
46 |
INTEGER(KINT) :: IdxFrag, IdxtoDo, IFrag,IaFaire |
47 |
INTEGER(KINT), ALLOCATABLE :: ToDo(:) |
48 |
|
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 |
END INTERFACE |
57 |
|
58 |
|
59 |
debug=valid('decompfrag').OR.valid('Decomp_frag') |
60 |
if (debug) Call Header('Entering DecomFrag') |
61 |
! We analyse the connectivity in terms of fragments |
62 |
ALLOCATE(ToDo(na)) |
63 |
|
64 |
Fragment=0 |
65 |
ToDo=0 |
66 |
IdxFrag=0 |
67 |
NbFrag=0 |
68 |
NbAtFrag=0 |
69 |
Fragment=0 |
70 |
FragAt=0 |
71 |
|
72 |
DO I=1,na |
73 |
IdxToDo=1 |
74 |
ToDo(IdxToDo)=0 |
75 |
|
76 |
if (debug) WRITE(*,*) 'Treating atom I, fragment(I)',I,Fragment(I) |
77 |
IF (ListAt(I).OR.(ListConnect(I,0).NE.0)) THEN |
78 |
IF (Fragment(I).EQ.0) THEN |
79 |
IdxFrag=IdxFrag+1 |
80 |
NbFrag=NbFrag+1 |
81 |
IFrag=IdxFrag |
82 |
Fragment(I)=IFrag |
83 |
NbAtFrag(IFrag)=NbAtFrag(IFrag)+1 |
84 |
FragAt(IFrag,NbAtFrag(IFrag))=I |
85 |
ELSE |
86 |
IFrag=Fragment(I) |
87 |
END IF |
88 |
DO J=1,ListConnect(I,0) |
89 |
Iat=ListConnect(I,J) |
90 |
IF ((Fragment(Iat).NE.0).AND.(Fragment(Iat).NE.IFrag)) THEN |
91 |
WRITE(*,*) 'Error : Atoms ',I,' and ',Iat |
92 |
WRITE(*,*) 'are linked, but belongs to fragments ',IFrag,' and ',Fragment(Iat) |
93 |
STOP |
94 |
END IF |
95 |
IF (Fragment(Iat).EQ.0) THEN |
96 |
ToDo(IdxToDo)=Iat |
97 |
Fragment(Iat)=IFrag |
98 |
NbAtFrag(IFrag)=NbAtFrag(IFrag)+1 |
99 |
FragAt(IFrag,NbAtFrag(IFrag))=Iat |
100 |
IdxToDo=IdxToDo+1 |
101 |
END IF |
102 |
END DO |
103 |
ToDo(IdxToDo)=0 |
104 |
|
105 |
If (debug) WRITE(*,*) 'ToDo:',ToDo(1:IdxToDo) |
106 |
If (debug) WRITE(*,*) 'IFrag=',IFrag |
107 |
|
108 |
IAfaire=1 |
109 |
|
110 |
DO WHILE (ToDo(IAfaire).NE.0) |
111 |
Iat=ToDo(IaFaire) |
112 |
IF (ListAt(I).OR.(ListConnect(I,0).NE.0)) THEN |
113 |
if (debug) WRITE(*,*) 'ToDo treating ',Iat |
114 |
IF (Fragment(Iat).EQ.0) THEN |
115 |
WRITE(*,*) 'Error: Atom ',Iat,' does not belong to any fragment !' |
116 |
STOP |
117 |
END IF |
118 |
|
119 |
DO J=1,ListConnect(Iat,0) |
120 |
Jat=ListConnect(Iat,J) |
121 |
IF ((Fragment(ListConnect(Iat,J)).NE.0).AND.(Fragment(ListConnect(Iat,J)).NE.IFrag)) THEN |
122 |
WRITE(*,*) 'Error: Atoms ',Iat,' and ',ListConnect(Iat,J) |
123 |
WRITE(*,*) 'are linked, but belongs to fragments ',IFrag,' and ',Fragment(ListConnect(Iat,J)) |
124 |
STOP |
125 |
END IF |
126 |
IF (Fragment(Jat).EQ.0) THEN |
127 |
ToDo(IdxToDo)=ListConnect(Iat,J) |
128 |
Fragment(Jat)=IFrag |
129 |
NbAtFrag(IFrag)=NbAtFrag(IFrag)+1 |
130 |
FragAt(IFrag,NbAtFrag(IFrag))=Jat |
131 |
IdxToDo=IdxToDo+1 |
132 |
END IF |
133 |
END DO |
134 |
ToDo(IdxToDo)=0 |
135 |
If (debug) WRITE(*,*) 'IAfaire, IdxToDo,ToDo :',IAfaire,IdxToDo,' == ',ToDo(IaFaire+1:IdxToDo) |
136 |
IAFaire=IAFaire+1 |
137 |
END IF |
138 |
END DO |
139 |
END IF |
140 |
END DO |
141 |
|
142 |
IF (debug) THEN |
143 |
WRITE(*,*) 'DECOMP_FRAG: I found ',NbFrag, 'fragments' |
144 |
DO I=1,NbFrag |
145 |
WRITE(*,*) 'Fragment ', i,' with ',NbAtFrag(I),' atoms.' |
146 |
WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I)) |
147 |
END DO |
148 |
END IF |
149 |
|
150 |
if (debug) Call Header('DecomFrag over') |
151 |
|
152 |
END SUBROUTINE Decomp_Frag |
153 |
|