40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
65
66
67
68#include "implicit_f.inc"
69
70
71
72
73 INTEGER,INTENT(IN)::IDMAX_PART,IDMAX_PROP,IDMAX_MAT,IDMAX_ELEM,IDMAX_TH,
74 . NB_SEATBELT_SHELLS
75 INTEGER,INTENT(INOUT)::SEATBELT_CONVERTED_ELEMENTS(3,NB_SEATBELT_SHELLS)
76 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(NSUBMOD)
77
78
79
80 INTEGER :: I,J,ID,SUBMODEL_INDEX,OFFSET,NB_PART,NB_MAT,NB_MAT_119,MAT_ID,ELEM_INDEX,NB_THSHELL,PART_ID
81 INTEGER, DIMENSION(:), ALLOCATABLE :: PART_SUB,PART_MAT119,MAT119_IDS
82 CHARACTER(LEN=NCHARLINE) :: KEY
83 LOGICAL :: IS_AVAILABLE
84
85 nb_mat_119 = 0
86
87
88
90
92 DO i=1,nb_mat
93 key = ''
95 . keyword2 = key)
96 IF(key(1:6) == 'LAW119' .OR. key(1:11) == 'SH_SEATBELT') THEN
97 nb_mat_119 = nb_mat_119 + 1
98 ENDIF
99 ENDDO
100
101
102
103 IF (nb_mat_119 /= 0) THEN
104 ALLOCATE(mat119_ids(nb_mat_119))
105 mat119_ids(1:nb_mat_119) = 0
106 j = 0
108 DO i=1,nb_mat
109 key = ''
112 . keyword2 = key,
113 . submodel_index = submodel_index)
114 IF(key(1:6) == 'LAW119' .OR. key(1:11) == 'SH_SEATBELT') THEN
115 j = j + 1
117 ENDIF
118 ENDDO
119
121 ALLOCATE(part_sub(nb_part))
122 ALLOCATE(part_mat119(nb_part))
123 part_mat119(1:nb_part) = 0
124
126 DO i=1,nb_part
129 . submodel_index = submodel_index)
130 CALL hm_get_intv(
'materialid',mat_id,is_available,lsubmodel)
131 DO j=1,nb_mat_119
132 IF(mat_id == mat119_ids(j)) part_mat119(i) =
id
133 ENDDO
134 ENDDO
135
136
137
138
139 elem_index = 0
140 DO i=1,nb_part
141 IF(part_mat119(i) /= 0) THEN
142 offset = 0
143 part_id = part_mat119(i)
144 CALL cpp_convert_2d_elements_seatbelt(part_id,idmax_part,idmax_prop,idmax_mat,
145 . idmax_elem,offset,seatbelt_converted_elements,elem_index)
146 ENDIF
147 ENDDO
148
149 IF (ALLOCATED(part_sub)) DEALLOCATE(part_sub)
150 IF (ALLOCATED(part_mat119)) DEALLOCATE(part_mat119)
151 IF (ALLOCATED(mat119_ids)) DEALLOCATE(mat119_ids)
152
153
154
155
158 DO i=1,nb_thshell
160 CALL cpp_get_submodel_index(submodel_index)
161 offset = 0
162 CALL cpp_convert_th_2d_element_seatbelt(idmax_th,offset,seatbelt_converted_elements,nb_seatbelt_shells)
163 ENDDO
164
165
166 ENDIF
167 RETURN
168
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)
integer, parameter ncharline