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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_preread_merge (smgrby, slpby, igrnod, lsubmodel)

Function/Subroutine Documentation

◆ hm_preread_merge()

subroutine hm_preread_merge ( integer smgrby,
integer slpby,
type (group_), dimension(ngrnod) igrnod,
type(submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 38 of file hm_preread_merge.F.

39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE groupdef_mod
43 USE message_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 SMGRBY, SLPBY
59C-----------------------------------------------
60 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
61 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(*)
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER I,J,ID,IGU,NN,UID,IMAIN,M_TYPE,ISECONDARY,S_TYPE,FLAGG_OPT,NOBJ
66 CHARACTER(LEN=NCHARKEY) :: KEY2
67 CHARACTER(LEN=NCHARTITLE) :: TITR
68 LOGICAL IS_AVAILABLE
69C-----------------------------------------------
70C E x t e r n a l F u n c t i o n s
71C-----------------------------------------------
72 INTEGER GRSIZEN
73C=======================================================================
74C Comptage du nombre de ligne dans les options /MERGE/RBODY
75C Augmente la taille de LPBY en fonction des merge de NODE et GRNOD
76C=======================================================================
77 smgrby = 0
78 nxtra_node = 0
79 nobj = 0
80C--------------------------------------------------
81C START BROWSING MODEL MERGE
82C--------------------------------------------------
83 is_available = .false.
84 CALL hm_option_start('/MERGE/RBODY')
85C--------------------------------------------------
86 DO i=1,nrbmerge
87C--------------------------------------------------
88C EXTRACT DATAS OF /RBODY/... LINE
89C--------------------------------------------------
90 CALL hm_option_read_key(lsubmodel,
91 . option_id = id,
92 . unit_id = uid,
93 . option_titr = titr,
94 . keyword2 = key2)
95
96C--------------------------------------------------
97C EXTRACT DATAS (INTEGER VALUES)
98C--------------------------------------------------
99 CALL hm_get_intv('NB_SUBOBJVE',nobj,is_available,lsubmodel)
100c
101 DO j=1,nobj
102 CALL hm_get_int_array_index('Main_ID',imain,j,is_available,lsubmodel)
103 CALL hm_get_int_array_index('M_type',m_type,j,is_available,lsubmodel)
104 CALL hm_get_int_array_index('Secon_ID',isecondary,j,is_available,lsubmodel)
105 CALL hm_get_int_array_index('S_type',s_type,j,is_available,lsubmodel)
106 CALL hm_get_int_array_index('Iflag',flagg_opt,j,is_available,lsubmodel)
107 IF (imain /= 0) THEN
108 smgrby = smgrby + 1
109 IF(s_type == 2) THEN
110 slpby = slpby + 1
111 nxtra_node = nxtra_node + 1
112 ELSEIF(s_type == 3) THEN
113 igu=isecondary
114 nn = grsizen(igu,igrnod,ngrnod)
115 slpby = slpby + nn
116 nxtra_node = nxtra_node + nn
117 ENDIF
118 ENDIF ! IMAIN /= 0
119 ENDDO
120
121 ENDDO
122C-----------
123 RETURN
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 function grsizen(igu, igrnod, grlen)
Definition nintrr.F:497