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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_preread_load_centri (numcentri, igrnod, igrsurf, lsubmodel)

Function/Subroutine Documentation

◆ hm_preread_load_centri()

subroutine hm_preread_load_centri ( integer, intent(inout) numcentri,
type (group_), dimension(ngrnod) igrnod,
type (surf_), dimension(nsurf), target igrsurf,
type(submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 38 of file hm_preread_load_centri.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 "com04_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58 INTEGER,INTENT(INOUT) :: NUMCENTRI
59C-----------------------------------------------
60 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
61 TYPE (SURF_) ,TARGET, DIMENSION(NSURF) :: IGRSURF
62 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(*)
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 INTEGER :: I, ID, IGU, IGS, NN, UID, FLAG_FMT
67 INTEGER :: FLAG_FMT_TMP, IFIX_TMP, ISU, IS, J
68 CHARACTER(LEN=NCHARTITLE) :: TITR
69 LOGICAL IS_AVAILABLE
70 INTEGER, DIMENSION(:), POINTER :: INGR2USR
71C-----------------------------------------------
72C E x t e r n a l F u n c t i o n s
73C-----------------------------------------------
74 INTEGER NGR2USRN, NGR2USR
75C-----------------------------------------------
76C S o u r c e L i n e s
77C-----------------------------------------------
78 is_available = .false.
79C--------------------------------------------------
80C START BROWSING MODEL CLOAD
81C--------------------------------------------------
82 CALL hm_option_start('/LOAD/CENTRI')
83C-----------------------------------------------
84 numcentri = 0
85 DO i=1,nloadc
86
87 titr = ''
88C--------------------------------------------------
89C EXTRACT DATAS OF /LOAD/CENTRI... LINE
90C--------------------------------------------------
91 CALL hm_option_read_key(lsubmodel,
92 . option_id = id,
93 . option_titr = titr)
94C--------------------------------------------------
95C EXTRACT DATAS (INTEGER VALUES)
96C--------------------------------------------------
97 CALL hm_get_intv ('entityid',igu,is_available,lsubmodel)
98C-------
99 igs = ngr2usrn(igu,igrnod,ngrnod,nn)
100 numcentri = numcentri + nn
101 ENDDO
102C-----------
103 RETURN
104
105C-----------------------------------------------
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
initmumps id
integer, parameter nchartitle
integer function ngr2usrn(iu, igrnod, ngrnod, num)
Definition nintrr.F:407