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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_prelecjoi (num, igrnod, lsubmodel)

Function/Subroutine Documentation

◆ hm_prelecjoi()

subroutine hm_prelecjoi ( integer num,
type (group_), dimension(ngrnod) igrnod,
type(submodel_data), dimension(*) lsubmodel )

Definition at line 38 of file hm_prelecjoi.F.

39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE r2r_mod
43 USE groupdef_mod
44 USE submodel_mod
46C-----------------------------------------------
47C I m p l i c i t T y p e s
48C-----------------------------------------------
49#include "implicit_f.inc"
50C-----------------------------------------------
51C C o m m o n B l o c k s
52C-----------------------------------------------
53#include "com04_c.inc"
54#include "r2r_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58 INTEGER NUM
59C-----------------------------------------------
60 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
61 TYPE(SUBMODEL_DATA) LSUBMODEL(*)
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER I, NS, IGU, NY
66 LOGICAL :: IS_AVAILABLE
67C-----------------------------------------------
68C E x t e r n a l F u n c t i o n s
69C-----------------------------------------------
70 INTEGER GRSIZEN
71C=======================================================================
72C
73 is_available = .false.
74C
75 num = 0
76 ny = 0
77C
78 CALL hm_option_start('/CYL_JOINT')
79C
80 DO i=1,njoint
81 ny=ny+1
82 IF(nsubdom>0)THEN
83 IF(tagcyl(ny)==0)CALL hm_sz_r2r(tagcyl,ny,lsubmodel)
84 END IF
85C----------------------------------------------------------------------
86 CALL hm_option_read_key(lsubmodel)
87C
88 CALL hm_get_intv('dependentnodeset',igu,is_available,lsubmodel)
89C
90 ns = grsizen(igu,igrnod,ngrnod) + 3
91 num = num + ns
92 ENDDO
93C-----------
94 RETURN
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
integer, dimension(:), allocatable tagcyl
Definition r2r_mod.F:137
integer function grsizen(igu, igrnod, grlen)
Definition nintrr.F:497
subroutine hm_sz_r2r(tag, val, lsubmodel)