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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_count_2d_element_seatbelt (nb_shells, lsubmodel)

Function/Subroutine Documentation

◆ hm_count_2d_element_seatbelt()

subroutine hm_count_2d_element_seatbelt ( integer, intent(inout) nb_shells,
type(submodel_data), dimension(nsubmod), intent(in) lsubmodel )

Definition at line 38 of file hm_count_2d_element_seatbelt.F.

39C-----------------------------------------------
40C ROUTINE DESCRIPTION :
41C ===================
42C ROUTINE TO COUNT NUMBER OF /SHELLs FOR 2D SEATBELTS
43C-----------------------------------------------
44C DUMMY ARGUMENTS DESCRIPTION:
45C ===================
46C
47C NAME DESCRIPTION
48C
49C NB_SHELLS NUMBER OF /SHELLs FOR 2D SEATBELTS
50C LSUBMODEL SUBMODEL STRUCTURE
51C============================================================================
52C M o d u l e s
53C-----------------------------------------------
54 USE message_mod
58C-----------------------------------------------
59C I m p l i c i t T y p e s
60C-----------------------------------------------
61#include "implicit_f.inc"
62C-----------------------------------------------
63C D u m m y A r g u m e n t s
64C-----------------------------------------------
65C INPUT ARGUMENTS
66 INTEGER,INTENT(INOUT) :: NB_SHELLS
67 TYPE(SUBMODEL_DATA),INTENT(IN) :: LSUBMODEL(NSUBMOD)
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER :: I,J,ID,SUBMODEL_INDEX,NB_PART,NB_MAT,NB_MAT_119,MAT_ID,NB_SHELLS_PART
72 INTEGER, DIMENSION(:), ALLOCATABLE :: PART_MAT119,MAT119_IDS
73 CHARACTER(LEN=NCHARLINE) :: KEY
74 LOGICAL :: IS_AVAILABLE
75C-----------------------------------------------
76 nb_mat_119 = 0
77C-----------------------------------------------
78C Check existence of Mat laws 119 in the model
79C-----------------------------------------------
80 CALL hm_option_count('/MAT',nb_mat)
81c
82 CALL hm_option_start('/MAT')
83 DO i=1,nb_mat
84 key = ''
85 CALL hm_option_read_key(lsubmodel,keyword2 = key)
86 IF(key(1:6) == 'LAW119' .OR. key(1:11) == 'SH_SEATBELT') THEN
87 nb_mat_119 = nb_mat_119 + 1
88 ENDIF
89 ENDDO
90C-----------------------------------------------
91C Search Parts with Mat 119
92C-----------------------------------------------
93 IF (nb_mat_119 /= 0) THEN
94 ALLOCATE(mat119_ids(nb_mat_119))
95 mat119_ids(1:nb_mat_119) = 0
96 j = 0
97 CALL hm_option_start('/MAT')
98 DO i=1,nb_mat
99 key = ''
100 CALL hm_option_read_key(lsubmodel, option_id=id, keyword2=key, submodel_index=submodel_index)
101 IF(key(1:6) == 'LAW119' .OR. key(1:11) == 'SH_SEATBELT') THEN
102 j = j + 1
103 mat119_ids(j) = id
104 ENDIF
105 ENDDO
106C-----------------------------------------------
107 CALL hm_option_count('/PART',nb_part)
108 ALLOCATE(part_mat119(nb_part))
109 part_mat119(1:nb_part) = 0
110c
111 CALL hm_option_start('/PART')
112 DO i=1,nb_part
113 CALL hm_option_read_key(lsubmodel, option_id=id, submodel_index=submodel_index)
114 CALL hm_get_intv('materialid',mat_id,is_available,lsubmodel)
115 DO j=1,nb_mat_119
116 IF(mat_id == mat119_ids(j)) part_mat119(i) = mat119_ids(j)
117 ENDDO
118 ENDDO
119C-----------------------------------------------
120C Count /SHELLs
121C-----------------------------------------------
122c
123 nb_shells = 0
124 nb_shells_part = 0
125 CALL hm_option_start('/PART')
126 DO i=1,nb_part
127 CALL hm_option_next()
128 IF(part_mat119(i) /= 0) THEN
129 CALL cpp_count_elements_in_part(nb_shells_part)
130 nb_shells = nb_shells + nb_shells_part
131 ENDIF
132 ENDDO
133c
134 IF (ALLOCATED(part_mat119)) DEALLOCATE(part_mat119)
135 IF (ALLOCATED(mat119_ids)) DEALLOCATE(mat119_ids)
136C--------------------------------------------------
137 ENDIF
138 RETURN
139C
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_count(entity_type, hm_option_number)
subroutine hm_option_next()
subroutine hm_option_start(entity_type)
initmumps id
integer, parameter ncharline
integer nsubmod