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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_preread_rbe3 (lnum, lreal, igrnod, grnod_uid, lsubmodel)

Function/Subroutine Documentation

◆ hm_preread_rbe3()

subroutine hm_preread_rbe3 ( integer lnum,
integer lreal,
type (group_), dimension(ngrnod) igrnod,
integer grnod_uid,
type(submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 39 of file hm_preread_rbe3.F.

40C-------------------------------------
41C LECTURE STRUCTURE RIGIDES
42C-----------------------------------------------
43C M o d u l e s
44C-----------------------------------------------
45 USE unitab_mod
46 USE r2r_mod
47 USE message_mod
48 USE groupdef_mod
49 USE submodel_mod
52C-----------------------------------------------
53C I m p l i c i t T y p e s
54C-----------------------------------------------
55#include "implicit_f.inc"
56C-----------------------------------------------
57C C o m m o n B l o c k s
58C-----------------------------------------------
59#include "com04_c.inc"
60#include "param_c.inc"
61#include "r2r_c.inc"
62C-----------------------------------------------
63C D u m m y A r g u m e n t s
64C-----------------------------------------------
65 INTEGER :: LNUM,LREAL
66 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
67 INTEGER :: GRNOD_UID
68 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(*)
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72 INTEGER :: I, NSLT,NM,INGU,IGS,J,NN,NRB,UID,ID
73 LOGICAL :: IS_AVAILABLE
74 CHARACTER(LEN=NCHARTITLE) :: TITR
75C=======================================================================
76 is_available = .false.
77 CALL hm_option_start('/RBE3')
78 lnum = 0
79 lreal = 0
80 nrb = 0
81 IF (nrbe3 == 0) RETURN
82 DO i=1,nrbe3
83 nrb=nrb+1
84C----------Multidomaines --> on ignore les rbe3 non tages---------
85 IF(nsubdom > 0)THEN
86 IF(tagrb3(nrb) == 0)CALL hm_sz_r2r(tagrb3,nrb,lsubmodel)
87 END IF
88C--------------------------------------------------
89C EXTRACT DATAS OF /RBE3/... LINE
90C--------------------------------------------------
91 CALL hm_option_read_key(lsubmodel,option_id = id,unit_id = uid,option_titr = titr)
92 CALL hm_get_intv('nset',nslt,is_available,lsubmodel)
93 nm = 0
94 DO j=1,nslt
95 CALL hm_get_int_array_index('independentnodesets',ingu,j,is_available,lsubmodel)
96 IF(ingu == 0) THEN
97 nn = 0
98 igs = 0
99 ELSE
100 CALL c_hash_find(grnod_uid,ingu,igs)
101 IF(igs == 0) THEN
102 nn = 0
103 ELSE
104 nn = igrnod(igs)%NENTITY
105 ENDIF
106 ENDIF
107 nm = nm + nn
108 ENDDO
109 lreal = lreal + nm
110 lnum = lnum +nrbe3l
111 ENDDO
112 RETURN
void c_hash_find(int *map, int *key, int *val)
subroutine hm_get_int_array_index(name, ival, index, is_available, lsubmodel)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
initmumps id
integer, parameter nchartitle
integer, parameter ncharkey
integer, dimension(:), allocatable tagrb3
Definition r2r_mod.F:138
subroutine hm_sz_r2r(tag, val, lsubmodel)