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

Go to the source code of this file.

Functions/Subroutines

subroutine init_surf_elm (numels, numels8, numels10, numelc, numeltg, numelt, numelp, numelr, npart, iparts, ipartc, iparttg, ipartt, ipartp, ipartr, surf_elm, mode)
subroutine deallocate_surf_elm (npart, surf_elm, mode)

Function/Subroutine Documentation

◆ deallocate_surf_elm()

subroutine deallocate_surf_elm ( integer, intent(in) npart,
type(part_type), dimension(npart), intent(inout) surf_elm,
integer, intent(in) mode )

Definition at line 199 of file init_surf_elm.F.

200
201 USE surf_mod
202
203! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
204! DEALLOCATE_SURF_ELM deallocates the structure SURF_ELM
205! MODE = 1 is for solid/shell and shell3n elements
206! MODE = 2 is for truss/beam and spring elements
207! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
208C-----------------------------------------------
209C I m p l i c i t T y p e s
210C-----------------------------------------------
211#include "implicit_f.inc"
212C-----------------------------------------------
213C D u m m y A r g u m e n t s
214C-----------------------------------------------
215 INTEGER, INTENT(IN) :: NPART,MODE
216 TYPE(PART_TYPE), DIMENSION(NPART), INTENT(INOUT) :: SURF_ELM
217! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
218! NPART : integer
219! number of /PART
220! SURF_ELM : PART_TYPE structure
221! %Nxxx : number of element per part
222! %xxx_PART : ID of the element
223! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
224C-----------------------------------------------
225C L o c a l V a r i a b l e s
226C-----------------------------------------------
227 INTEGER :: I
228C-----------------------------------------------
229 IF(mode==1) THEN
230 ! --------------------
231 DO i=1,npart
232 IF(surf_elm(i)%NSOL>0) DEALLOCATE( surf_elm(i)%SOL_PART )
233 IF(surf_elm(i)%NSOL10>0) DEALLOCATE( surf_elm(i)%SOL10_PART )
234 IF(surf_elm(i)%NSHELL>0) DEALLOCATE( surf_elm(i)%SHELL_PART )
235 IF(surf_elm(i)%NTRI>0) DEALLOCATE( surf_elm(i)%TRI_PART )
236 ENDDO
237 ! --------------------
238 ELSEIF(mode==2) THEN
239 ! --------------------
240 DO i=1,npart
241 IF(surf_elm(i)%NTRUSS>0) DEALLOCATE( surf_elm(i)%TRUSS_PART )
242 IF(surf_elm(i)%NBEAM>0) DEALLOCATE( surf_elm(i)%BEAM_PART )
243 IF(surf_elm(i)%NSPRING>0) DEALLOCATE( surf_elm(i)%SPRING_PART )
244 ENDDO
245 ! --------------------
246 ENDIF
247
248 RETURN

◆ init_surf_elm()

subroutine init_surf_elm ( integer, intent(in) numels,
integer, intent(in) numels8,
integer, intent(in) numels10,
integer, intent(in) numelc,
integer, intent(in) numeltg,
integer, intent(in) numelt,
integer, intent(in) numelp,
integer, intent(in) numelr,
integer, intent(in) npart,
integer, dimension(*), intent(in) iparts,
integer, dimension(*), intent(in) ipartc,
integer, dimension(*), intent(in) iparttg,
integer, dimension(*), intent(in) ipartt,
integer, dimension(*), intent(in) ipartp,
integer, dimension(*), intent(in) ipartr,
type(part_type), dimension(npart), intent(inout) surf_elm,
integer, intent(in) mode )

Definition at line 31 of file init_surf_elm.F.

35 USE surf_mod
36! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
37! INIT_SURF_ELM initializes the structure SURF_ELM
38! SURF_ELM gathers the element ID for each /PART
39! MODE = 1 is for solid/shell and shell3n elements
40! MODE = 2 is for truss/beam and spring elements
41! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
42C-----------------------------------------------
43C I m p l i c i t T y p e s
44C-----------------------------------------------
45#include "implicit_f.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER, INTENT(IN) :: NUMELS,NUMELS8,NUMELS10,NUMELC ,NUMELTG
50 INTEGER, INTENT(IN) :: NUMELT, NUMELP, NUMELR
51 INTEGER, INTENT(IN) :: NPART,MODE
52 INTEGER, DIMENSION(*), INTENT(IN) :: IPARTS ,IPARTC ,IPARTTG
53 INTEGER, DIMENSION(*), INTENT(IN) :: IPARTT ,IPARTP ,IPARTR
54 TYPE(PART_TYPE), DIMENSION(NPART), INTENT(INOUT) :: SURF_ELM
55! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
56! NPART : integer
57! number of /PART
58! NUMELxxx : integer
59! number of solid/solid8/10/shell/shell3n...
60! IPARTxxx : integer, dimension=number of element
61! ID of the /PART for the current I element
62! SURF_ELM : PART_TYPE structure
63! %Nxxx : number of element per part
64! %xxx_PART : ID of the element
65! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
66C-----------------------------------------------
67C L o c a l V a r i a b l e s
68C-----------------------------------------------
69 INTEGER :: ID_PART,I
70 INTEGER, DIMENSION(NPART) :: NBR_SOL_PART,NBR_SOL10_PART,NBR_SHELL_PART,NBR_TRI_PART
71 INTEGER, DIMENSION(NPART) :: NBR_TRUSS_PART,NBR_BEAM_PART,NBR_SPRING_PART
72! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
73! NBR_SOL(10)_PART : local number of element per part
74! *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
75C-----------------------------------------------
76 IF(mode==1) THEN
77 ! ---------------------------------
78 nbr_sol_part(1:npart) = 0
79 nbr_sol10_part(1:npart) = 0
80 nbr_shell_part(1:npart) = 0
81 nbr_tri_part(1:npart) = 0
82 ! --------------------
83 DO i=1,numels
84 id_part = iparts(i)
85 IF(i<=numels8) nbr_sol_part(id_part) = nbr_sol_part(id_part) + 1
86 IF(i>numels8) nbr_sol10_part(id_part) = nbr_sol10_part(id_part) + 1
87 ENDDO
88 DO i=1,numelc
89 id_part = ipartc(i)
90 nbr_shell_part(id_part) = nbr_shell_part(id_part) + 1
91 ENDDO
92 DO i=1,numeltg
93 id_part = iparttg(i)
94 nbr_tri_part(id_part) = nbr_tri_part(id_part) + 1
95 ENDDO
96 ! --------------------
97 DO id_part=1,npart
98 IF(nbr_sol_part(id_part)>0) ALLOCATE( surf_elm(id_part)%SOL_PART( nbr_sol_part(id_part) ) )
99 IF(nbr_sol10_part(id_part)>0) ALLOCATE( surf_elm(id_part)%SOL10_PART( nbr_sol10_part(id_part) ) )
100 IF(nbr_shell_part(id_part)>0) ALLOCATE( surf_elm(id_part)%SHELL_PART( nbr_shell_part(id_part) ) )
101 IF(nbr_tri_part(id_part)>0) ALLOCATE( surf_elm(id_part)%TRI_PART( nbr_tri_part(id_part) ) )
102 surf_elm(id_part)%NSOL = nbr_sol_part(id_part)
103 surf_elm(id_part)%NSOL10 = nbr_sol10_part(id_part)
104 surf_elm(id_part)%NSHELL = nbr_shell_part(id_part)
105 surf_elm(id_part)%NTRI = nbr_tri_part(id_part)
106 ENDDO
107 ! --------------------
108 nbr_sol_part(1:npart) = 0
109 nbr_sol10_part(1:npart) = 0
110 DO i=1,numels
111 id_part = iparts(i)
112 IF(i<=numels8) THEN
113 nbr_sol_part(id_part) = nbr_sol_part(id_part) + 1
114 surf_elm(id_part)%SOL_PART( nbr_sol_part(id_part) ) = i
115 ELSE
116 nbr_sol10_part(id_part) = nbr_sol10_part(id_part) + 1
117 surf_elm(id_part)%SOL10_PART( nbr_sol10_part(id_part) ) = i
118 ENDIF
119 ENDDO
120 nbr_shell_part(1:npart) = 0
121 DO i=1,numelc
122 id_part = ipartc(i)
123 nbr_shell_part(id_part) = nbr_shell_part(id_part) + 1
124 surf_elm(id_part)%SHELL_PART( nbr_shell_part(id_part) ) = i
125 ENDDO
126 nbr_tri_part(1:npart) = 0
127 DO i=1,numeltg
128 id_part = iparttg(i)
129 nbr_tri_part(id_part) = nbr_tri_part(id_part) + 1
130 surf_elm(id_part)%TRI_PART( nbr_tri_part(id_part) ) = i
131 ENDDO
132 ! --------------------
133 ! ---------------------------------
134 ELSEIF(mode==2) THEN
135 ! ---------------------------------
136 nbr_truss_part(1:npart) = 0
137 nbr_beam_part(1:npart) = 0
138 nbr_spring_part(1:npart) = 0
139 ! --------------------
140 DO i=1,numelt
141 id_part = ipartt(i)
142 nbr_truss_part(id_part) = nbr_truss_part(id_part) + 1
143
144 ENDDO
145 DO i=1,numelp
146 id_part = ipartp(i)
147 nbr_beam_part(id_part) = nbr_beam_part(id_part) + 1
148
149 ENDDO
150 DO i=1,numelr
151 id_part = ipartr(i)
152 nbr_spring_part(id_part) = nbr_spring_part(id_part) + 1
153
154 ENDDO
155 ! --------------------
156 DO id_part=1,npart
157 IF(nbr_truss_part(id_part)>0) ALLOCATE( surf_elm(id_part)%TRUSS_PART( nbr_truss_part(id_part) ) )
158 IF(nbr_beam_part(id_part)>0) ALLOCATE( surf_elm(id_part)%BEAM_PART( nbr_beam_part(id_part) ) )
159 IF(nbr_spring_part(id_part)>0) ALLOCATE( surf_elm(id_part)%SPRING_PART( nbr_spring_part(id_part) ) )
160 surf_elm(id_part)%NTRUSS = nbr_truss_part(id_part)
161 surf_elm(id_part)%NBEAM = nbr_beam_part(id_part)
162 surf_elm(id_part)%NSPRING = nbr_spring_part(id_part)
163 ENDDO
164 ! --------------------
165
166 nbr_truss_part(1:npart) = 0
167 DO i=1,numelt
168 id_part = ipartt(i)
169 nbr_truss_part(id_part) = nbr_truss_part(id_part) + 1
170 surf_elm(id_part)%TRUSS_PART( nbr_truss_part(id_part) ) = i
171 ENDDO
172 nbr_beam_part(1:npart) = 0
173 DO i=1,numelp
174 id_part = ipartp(i)
175 nbr_beam_part(id_part) = nbr_beam_part(id_part) + 1
176 surf_elm(id_part)%BEAM_PART( nbr_beam_part(id_part) ) = i
177 ENDDO
178 nbr_spring_part(1:npart) = 0
179 DO i=1,numelr
180 id_part = ipartr(i)
181 nbr_spring_part(id_part) = nbr_spring_part(id_part) + 1
182 surf_elm(id_part)%SPRING_PART( nbr_spring_part(id_part) ) = i
183 ENDDO
184 ! --------------------
185 ! ---------------------------------
186 ENDIF
187
188 RETURN