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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_preread_grav (num, igrnod, lsubmodel)

Function/Subroutine Documentation

◆ hm_preread_grav()

subroutine hm_preread_grav ( integer num,
type (group_), dimension(ngrnod) igrnod,
type(submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 36 of file hm_preread_grav.F.

37C-----------------------------------------------
38C M o d u l e s
39C-----------------------------------------------
40 USE groupdef_mod
41 USE submodel_mod
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C C o m m o n B l o c k s
50C-----------------------------------------------
51#include "com04_c.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER NUM
56C-----------------------------------------------
57 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
58 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(*)
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER I,ID,IGU,IGS,NN,UID,FLAG_FMT,FLAG_FMT_TMP,IFIX_TMP
63 CHARACTER(LEN=NCHARTITLE) :: TITR
64 LOGICAL IS_AVAILABLE
65C-----------------------------------------------
66C E x t e r n a l F u n c t i o n s
67C-----------------------------------------------
68 INTEGER NGR2USRN
69C=======================================================================
70 is_available = .false.
71 num = 0
72C--------------------------------------------------
73C START BROWSING MODEL GRAV
74C--------------------------------------------------
75 CALL hm_option_start('/GRAV')
76C--------------------------------------------------
77C BROWSING MODEL PARTS 1->NGRAV
78C--------------------------------------------------
79 DO i=1,ngrav
80 titr = ''
81C--------------------------------------------------
82C EXTRACT DATAS OF /PART/... LINE
83C--------------------------------------------------
84 CALL hm_option_read_key(lsubmodel,
85 . option_id = id,
86 . option_titr = titr)
87C--------------------------------------------------
88C EXTRACT DATAS (INTEGER VALUES)
89C--------------------------------------------------
90 CALL hm_get_intv ('entityid',igu,is_available,lsubmodel)
91C--------------------------------------------------
92 IF (igu /= 0) THEN
93 igs = ngr2usrn(igu,igrnod,ngrnod,nn)
94 ELSE
95 nn = numnod
96 ENDIF
97 num = num + nn
98C--------------------------------------------------
99 ENDDO
100C-----------
101 RETURN
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