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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_preread_impdisp (nimpdisp, igrnod, ipart, ipartr, unitab, lsubmodel)

Function/Subroutine Documentation

◆ hm_preread_impdisp()

subroutine hm_preread_impdisp ( integer, intent(out) nimpdisp,
type (group_), dimension(ngrnod), intent(in) igrnod,
integer, dimension(lipart1,*) ipart,
integer, dimension(*) ipartr,
type(unit_type_), intent(in) unitab,
type(submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 39 of file hm_preread_impdisp.F.

41C============================================================================
42C M o d u l e s
43C-----------------------------------------------
44 USE message_mod
45 USE groupdef_mod
46 USE submodel_mod
48 USE unitab_mod
50C-----------------------------------------------
51C I m p l i c i t T y p e s
52C-----------------------------------------------
53#include "implicit_f.inc"
54C-----------------------------------------------
55C C o m m o n B l o c k s
56C-----------------------------------------------
57#include "com04_c.inc"
58#include "scr17_c.inc"
59C-----------------------------------------------
60C D u m m y A r g u m e n t s
61C-----------------------------------------------
62 INTEGER ,INTENT(OUT) :: NIMPDISP
63 INTEGER IPART(LIPART1,*), IPARTR(*)
64 TYPE(UNIT_TYPE_) ,INTENT(IN) :: UNITAB
65 TYPE (GROUP_) , DIMENSION(NGRNOD) ,INTENT(IN) :: IGRNOD
66 TYPE(SUBMODEL_DATA), DIMENSION(*) ,INTENT(IN) :: LSUBMODEL
67C-----------------------------------------------
68C L o c a l V a r i a b l e s
69C-----------------------------------------------
70 INTEGER :: I,N,OPTID,NFDISP,NFGEO,IGS,GRNOD_ID,PART_ID,NNOD,JPART
71 CHARACTER(LEN=NCHARKEY) :: KEY
72 CHARACTER(LEN=NCHARTITLE) :: TITR
73 LOGICAL :: IS_AVAILABLE
74C-----------------------------------------------
75C E x t e r n a l F u n c t i o n s
76C-----------------------------------------------
77 INTEGER NGR2USRN
78 EXTERNAL ngr2usrn
79c--------------------------------------------------
80c Count number of nodes with imposed displacement => NIMPDISP
81C======================================================================|
82 is_available = .false.
83c
84 nimpdisp = 0
85c--------------------------------------------------
86c /IMPDISP
87c--------------------------------------------------
88 CALL hm_option_count('/IMPDISP',nfdisp)
89c
90 CALL hm_option_start('/IMPDISP')
91c
92 DO i=1,nfdisp
93c
94 CALL hm_option_read_key(lsubmodel,
95 . option_id = optid,
96 . option_titr = titr,
97 . keyword2 = key)
98c
99 IF (key(1:4) /= 'FGEO') THEN
100 CALL hm_get_intv('entityid' ,grnod_id ,is_available,lsubmodel)
101 igs = ngr2usrn(grnod_id,igrnod,ngrnod,nnod)
102 IF (igs > 0) nimpdisp = nimpdisp + nnod
103 ENDIF
104c
105 ENDDO ! DO I=1,NFDISP
106c--------------------------
107c /IMPDISP/FGEO
108c--------------------------
109 CALL hm_option_count('/IMPDISP/FGEO',nfgeo)
110c
111 CALL hm_option_start('/IMPDISP/FGEO')
112c
113 DO i=1,nfgeo
114c
115 CALL hm_option_read_key(lsubmodel,
116 . option_id = optid,
117 . option_titr = titr,
118 . keyword2 = key)
119 IF (key(1:4) == 'FGEO') THEN
120 CALL hm_get_intv('rad_spring_part' ,part_id ,is_available,lsubmodel)
121 IF (part_id > 0) THEN
122 jpart = 0
123 DO n=1,npart
124 IF (ipart(4,n) == part_id) jpart = n
125 ENDDO
126 IF (jpart == 0) THEN
127 CALL ancmsg(msgid=1077, msgtype=msgerror,
128 . anmode=aninfo,
129 . i1=optid,
130 . c1=titr,
131 . i2=part_id)
132 ENDIF
133 DO n=1,numelr
134 IF (ipartr(n) == jpart) nimpdisp = nimpdisp + 1
135 ENDDO
136 ENDIF
137c
138 CALL hm_get_intv('distribution_table_count' ,nnod ,is_available,lsubmodel)
139c
140 nimpdisp = nimpdisp + nnod
141 ENDIF
142 ENDDO ! DO I=1,NFGEO
143c-----------
144 RETURN
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_count(entity_type, hm_option_number)
subroutine hm_option_start(entity_type)
integer, parameter nchartitle
integer, parameter ncharkey
integer function ngr2usrn(iu, igrnod, ngrnod, num)
Definition nintrr.F:407
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