OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_admlistcnt.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| hm_admlcnt ../starter/source/groups/hm_admlistcnt.f
25!||--- called by ------------------------------------------------------
26!|| hm_lecgre ../starter/source/groups/hm_lecgre.F
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../starter/source/output/message/message.F
29!|| groups_get_elem_list ../starter/source/groups/groups_get_elem_list.F
30!||--- uses -----------------------------------------------------
31!|| hm_option_read_mod ../starter/share/modules1/hm_option_read_mod.F
32!|| message_mod ../starter/share/message_module/message_mod.f
33!|| submodel_mod ../starter/share/modules1/submodel_mod.f
34!||====================================================================
35 SUBROUTINE hm_admlcnt(NIX ,IX ,NUMEL ,IPARTEL ,IPART ,
36 . KELTREE ,ELTREE ,KSONTREE,NSONTREE,KLEVTREE,
37 . NLIST ,MESS ,IX1 ,IX2 ,INDEX ,
38 . LL ,NEL ,ELKEY ,ID ,TITR, LSUBMODEL)
39 USE message_mod
41 USE submodel_mod
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47C-----------------------------------------------
48C G l o b a l P a r a m e t e r s
49C-----------------------------------------------
50#include "scr17_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER NIX, IX(NIX,*), NUMEL, IPARTEL(*), IPART(LIPART1,*),
55 . KELTREE, ELTREE(KELTREE,*), KSONTREE, NSONTREE, KLEVTREE,
56 . NLIST,IX1(*), IX2(*), INDEX(*), LL, NEL, LEVEL
57 CHARACTER MESS*40
58 INTEGER ID
59 CHARACTER(LEN=NCHARTITLE)::TITR
60 CHARACTER :: ELKEY*4
61 TYPE(submodel_data) LSUBMODEL(NSUBMOD)
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER LIST(NLIST), IL, JJ
66 INTEGER I, J, NOLD, K, IWORK(70000),II
67 INTEGER LELT, NE, IP, NLEV
68 LOGICAL IS_AVAILABLE, IS_ENCRYPTED
69 INTEGER,DIMENSION(:),ALLOCATABLE :: LIST_ENTITY
70 INTEGER :: NENTITY
71C-----------------------------------------------
72 INTERFACE
73 SUBROUTINE groups_get_elem_list(arg1,arg2,arg3)
74 USE submodel_mod
75 INTEGER,DIMENSION(:),ALLOCATABLE :: arg1
76 INTEGER,INTENT(INOUT) :: arg2
77 TYPE(submodel_data) :: arg3(NSUBMOD)
78 END SUBROUTINE
79 END INTERFACE
80C-----------------------------------------------
81C CONSTITUTION DE LIST
82C-----------------------------------------------
83 il = 0
84 CALL groups_get_elem_list(list_entity, nentity, lsubmodel)
85 DO ii=1,nentity
86 jj=list_entity(ii)
87 IF(jj /= 0)THEN
88 il = il + 1
89 list(il)=jj
90 ENDIF
91 enddo! NEXT II
92 IF(ALLOCATED(list_entity))DEALLOCATE (list_entity)
93
94C-----------------------
95C TRI DE LIST EN ORDRE CROISSANT
96C AVEC SUPPRESSION DES No DOUBLES
97C-----------------------
98 CALL my_orders(0,iwork,list,index,nlist,1)
99 DO i=1,nlist
100 index(nlist+i) = list(index(i))
101 ENDDO
102 k=1
103 nold = index(nlist+1)
104 DO i=1,nlist
105 IF(nold/=index(nlist+i))k=k+1
106 list(k) = index(nlist+i)
107 nold = index(nlist+i)
108 ENDDO
109 nel=k
110C-----------------------
111C TRI DE IX EN ORDRE CROISSANT si LL = 0
112C-----------------------
113 IF(ll==0)THEN
114 DO i=1,numel
115 ix2(i) = ix(nix,i)
116 ENDDO
117 CALL my_orders(0,iwork,ix2,index,numel,1)
118 DO i=1,numel
119 ix1(i) = ix2(index(i))
120 ENDDO
121 DO i=1,numel
122 ix2(i) = index(i)
123 ENDDO
124 ENDIF
125C-----------------------
126C RECHERCHE DES ELEMENTS DE LIST() DANS IX()
127C ALGO < NLIST+NUMEL
128C-----------------------
129 i=1
130 j=1
131 DO i=1,nel
132 DO WHILE(list(i)>ix1(j).AND.j<numel)
133 j=j+1
134 ENDDO
135 IF(list(i)==ix1(j))THEN
136 list(i)=ix2(j)
137 ELSE
138 CALL ancmsg(msgid=70,
139 . msgtype=msgerror,
140 . anmode=aninfo,
141 . c1=elkey,
142 . i1=id,
143 . c2=trim(titr),
144 . i2=list(i))
145 RETURN
146 ENDIF
147 ENDDO
148C-----------------------
149C
150C-----------------------
151 lelt = 0
152C
153 DO i=1,nel
154
155 ne=list(i)
156
157 ip=ipartel(ne)
158 nlev =ipart(10,ip)
159
160 level =eltree(klevtree,ne)
161 IF(level < 0) level=-(level+1)
162
163 lelt=lelt+nsontree**(nlev-level)
164
165 END DO
166C
167 nel=lelt
168C-----------------------
169 RETURN
170 END
subroutine groups_get_elem_list(list_entity, nentity, lsubmodel)
subroutine hm_admlcnt(nix, ix, numel, ipartel, ipart, keltree, eltree, ksontree, nsontree, klevtree, nlist, mess, ix1, ix2, index, ll, nel, elkey, id, titr, lsubmodel)
void my_orders(int *mode, int *iwork, int *data, int *index, int *n, int *irecl)
Definition my_orders.c:82
integer, parameter nchartitle
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889
program starter
Definition starter.F:39