OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_surfgr2.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_surfgr2 (ngrele, elchar, numel, id, igrelem, tagbuf, titr, titr1, indx, nindx, flag, nindx_sol, nindx_sol10, indx_sol, indx_sol10, flag_grbric, lsubmodel)

Function/Subroutine Documentation

◆ hm_surfgr2()

subroutine hm_surfgr2 ( integer ngrele,
character, dimension(*) elchar,
integer numel,
integer id,
type (group_), dimension(ngrele) igrelem,
integer, dimension(*) tagbuf,
character(len=nchartitle) titr,
character(len=nchartitle) titr1,
integer, dimension(*) indx,
integer nindx,
integer flag,
integer nindx_sol,
integer nindx_sol10,
integer, dimension(*) indx_sol,
integer, dimension(*) indx_sol10,
logical flag_grbric,
type(submodel_data), dimension(nsubmod) lsubmodel )

Definition at line 36 of file hm_surfgr2.F.

40C-----------------------------------------------
41C M o d u l e s
42C-----------------------------------------------
43 USE groupdef_mod
44 USE message_mod
46 USE submodel_mod
48C-----------------------------------------------
49C I m p l i c i t T y p e s
50C-----------------------------------------------
51#include "implicit_f.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "com04_c.inc"
56C-----------------------------------------------
57C D u m m y A r g u m e n t s
58C-----------------------------------------------
59 INTEGER NUMEL,NGRELE,INDX(*),NINDX,
60 . NEMAX,ID,TAGBUF(*),
61 . FLAG
62 CHARACTER ELCHAR*(*)
63 CHARACTER(LEN=NCHARTITLE) :: TITR,TITR1
64 LOGICAL :: FLAG_GRBRIC
65 INTEGER :: NINDX_SOL, NINDX_SOL10
66 INTEGER, DIMENSION(*) :: INDX_SOL, INDX_SOL10
67!
68 TYPE (GROUP_) , DIMENSION(NGRELE) :: IGRELEM
69 TYPE(SUBMODEL_DATA) LSUBMODEL(NSUBMOD)
70! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
71! FLAG_GRBRIC : flag to initialize the INDX_SOL(10) arrays
72! and optimize an old and expensive treatment in SSURFTAG
73! NINDX_SOL(10) : number of the tagged solid(10) element
74! --> need to split solid and solid10
75! for a treatment in the SSURFTAG routine
76! only useful for /SURF/GRBRIC
77! INDX_SOL(10) : ID of the tagged solid(10) element
78! --> need to split solid and solid10
79! for a treatment in the SSURFTAG routine
80! only useful for /SURF/GRBRIC
81! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
82C-----------------------------------------------
83C L o c a l V a r i a b l e s
84C-----------------------------------------------
85 INTEGER J,L,IE,IADV,K,ISU, NENTITY, KK ,JJ, NENTITY_POS,NENTITY_NEG
86 LOGICAL IS_AVAILABLE,IS_ENCRYPTED
87 INTEGER,DIMENSION(:),ALLOCATABLE :: TAG_ENTITY_POS, TAG_ENTITY_NEG,LIST_ENTITY
88! FLAG_GRBRIC : check if the option is /GCBRIC
89C-----------------------------------------------
90 INTERFACE
91 SUBROUTINE groups_get_elem_list(arg1,arg2,arg3)
92 USE submodel_mod
93 INTEGER,DIMENSION(:),ALLOCATABLE :: arg1
94 INTEGER,INTENT(INOUT) :: arg2
95 TYPE(SUBMODEL_DATA) :: arg3(NSUBMOD)
96 END SUBROUTINE
97 END INTERFACE
98C=======================================================================
99 IF(elchar(1:6)=='GRBRIC') flag_grbric = .true.
100
101 CALL groups_get_elem_list(list_entity, nentity, lsubmodel)
102 DO kk=1,nentity
103 jj=list_entity(kk)
104 IF(jj/=0)THEN
105 isu=0
106 DO k=1,ngrele
107 IF (jj == igrelem(k)%ID) isu=k
108 IF (jj ==-igrelem(k)%ID) isu=-k
109 ENDDO
110 IF (isu > 0)THEN
111 DO l=1,igrelem(isu)%NENTITY
112 ie=igrelem(isu)%ENTITY(l)
113 IF(tagbuf(ie)==0)THEN
114 tagbuf(ie)=1
115 nindx=nindx+1
116 indx(nindx)=ie
117 IF(flag_grbric) THEN
118 IF(ie<=numels8) THEN
119 nindx_sol=nindx_sol+1
120 indx_sol(nindx_sol)=ie
121 ELSE
122 nindx_sol10=nindx_sol10+1
123 indx_sol10(nindx_sol10)=ie
124 ENDIF
125 ENDIF
126 END IF
127 ENDDO
128 ELSEIF (isu < 0)THEN
129 DO l=1,igrelem(-isu)%NENTITY
130 ie=igrelem(-isu)%ENTITY(l)
131 IF(tagbuf(ie)==0)THEN
132 tagbuf(ie)=-1
133 nindx=nindx+1
134 indx(nindx)=ie
135 IF(flag_grbric) THEN
136 IF(ie<=numels8) THEN
137 nindx_sol=nindx_sol+1
138 indx_sol(nindx_sol)=ie
139 ELSE
140 nindx_sol10=nindx_sol10+1
141 indx_sol10(nindx_sol10)=ie
142 ENDIF
143 ENDIF
144 END IF
145 ENDDO
146 ELSEIF(flag==0)THEN
147 CALL ancmsg(msgid=192,msgtype=msgwarning,anmode=aninfo,c1=titr1,c2=titr1,c3=titr,c4=titr1,i1=id,c5=elchar,i2=jj)
148 ENDIF
149 ENDIF
150 ENDDO
151 IF(ALLOCATED(list_entity))DEALLOCATE (list_entity)
152C-----------
153 RETURN
subroutine groups_get_elem_list(list_entity, nentity, lsubmodel)
initmumps id
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