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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_elngrr (ixr, geo, ngrele, id, igrelem, tagbuf, titr, flag, lsubmodel)

Function/Subroutine Documentation

◆ hm_elngrr()

subroutine hm_elngrr ( integer, dimension(nixr,*) ixr,
geo,
integer ngrele,
integer id,
type (group_), dimension(ngrele) igrelem,
integer, dimension(*) tagbuf,
character(len=nchartitle) titr,
integer flag,
type(submodel_data), dimension(*) lsubmodel )

Definition at line 36 of file hm_elngrr.F.

39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE message_mod
43 USE groupdef_mod
44 USE submodel_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51C-----------------------------------------------
52C C o m m o n B l o c k s
53C-----------------------------------------------
54#include "param_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58 INTEGER IXR(NIXR,*),TAGBUF(*)
59 INTEGER NGRELE,ID,FLAG
61 . geo(npropg,*)
62 CHARACTER(LEN=NCHARTITLE) :: TITR
63 TYPE(SUBMODEL_DATA) LSUBMODEL(*)
64C-----------------------------------------------
65 TYPE (GROUP_) , DIMENSION(NGRELE) :: IGRELEM
66C-----------------------------------------------
67C L o c a l V a r i a b l e s
68C-----------------------------------------------
69 INTEGER J,L,IE,IADV,JREC,K,ISU,NIX2,IPIDT,KK,JJ,NEMAX
70 LOGICAL IS_AVAILABLE
71C=======================================================================
72 is_available = .false.
73 CALL hm_get_intv('idsmax' ,nemax,is_available,lsubmodel)
74 DO kk = 1,nemax
75 CALL hm_get_int_array_index ('ids',jj ,kk,is_available,lsubmodel)
76 IF (jj /= 0) THEN
77 isu=0
78 DO k=1,ngrele
79 IF (jj == igrelem(k)%ID) isu=k
80 ENDDO
81 IF (isu /= 0) THEN
82 DO l=1,igrelem(isu)%NENTITY
83 ie=igrelem(isu)%ENTITY(l)
84 ipidt=nint(geo(1,ixr(1,ie)))
85 IF(ipidt == 12)THEN
86 nix2=4
87 ELSE
88 nix2=3
89 ENDIF
90 DO k=2,nix2
91C tag les noeuds connectes a l'element
92 tagbuf(ixr(k,ie))=1
93 ENDDO
94 ENDDO
95 ELSEIF (flag == 0) THEN
96 CALL ancmsg(msgid=172,
97 . msgtype=msgwarning,
98 . anmode=aninfo,
99 . i1=id,c1=titr,
100 . c2='GRSPRI',
101 . i2=jj)
102 ENDIF
103 ENDIF
104 ENDDO
105C-----------
106 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_int_array_index(name, ival, index, is_available, lsubmodel)
subroutine hm_get_intv(name, ival, is_available, 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