OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sgeodel3.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"
#include "comlock.inc"
#include "units_c.inc"
#include "param_c.inc"
#include "lockon.inc"
#include "lockoff.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine sgeodel3 (ngl, offg, volg, deltax, volg0, geo, l_max, dt, nel, idel7nok)

Function/Subroutine Documentation

◆ sgeodel3()

subroutine sgeodel3 ( integer, dimension(mvsiz), intent(in) ngl,
intent(inout) offg,
intent(in) volg,
intent(in) deltax,
intent(in) volg0,
intent(in) geo,
intent(in) l_max,
type(dt_), intent(inout) dt,
integer, intent(in) nel,
integer, intent(inout) idel7nok )

Definition at line 38 of file sgeodel3.F.

42C-----------------------------------------------
43C M o d u l e s
44C-----------------------------------------------
45 USE message_mod
46 USE dt_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51#include "mvsiz_p.inc"
52#include "comlock.inc"
53C-----------------------------------------------
54C C o m m o n B l o c k s
55C-----------------------------------------------
56#include "units_c.inc"
57#include "param_c.inc"
58C-----------------------------------------------
59C D u m m y A r g u m e n t s
60C-----------------------------------------------
61 INTEGER, INTENT(INOUT) :: IDEL7NOK
62 INTEGER ,INTENT(IN) :: NEL
63 INTEGER ,DIMENSION(MVSIZ) ,INTENT(IN) :: NGL
64 my_real, DIMENSION(NPROPG) , INTENT(IN) :: geo
65 my_real, DIMENSION(NEL) , INTENT(IN) :: volg0
66 my_real, DIMENSION(MVSIZ) , INTENT(IN) :: volg,deltax,l_max
67 my_real, DIMENSION(NEL) , INTENT(INOUT) :: offg
68 TYPE(DT_), INTENT(INOUT) :: DT
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72 INTEGER I,J,ICOUNT,LIST(MVSIZ),ITET
74 . tet_colla(mvsiz),def_v(mvsiz),aps_r(mvsiz),
75 . c_min,al,vdefmin,vdefmax,aspmax,colmin,c_max,gdel
76C---------------------------------------------
77 vdefmin = max(geo(190),dt%BRICK_DEL_DEFV_MIN)
78 vdefmax = geo(191)
79 aspmax = geo(192)
80 colmin = max(geo(193),dt%BRICK_DEL_COL_MIN)
81C-----
82 gdel=vdefmin+vdefmax+aspmax+colmin
83 IF(gdel==zero.AND.dt%IDEL_BRICK==0) RETURN
84C-----
85 IF(dt%BRICK_DEL_DEFV_MAX>zero .AND. (dt%BRICK_DEL_DEFV_MAX<vdefmax
86 . .OR.vdefmax==zero) ) vdefmax = dt%BRICK_DEL_DEFV_MAX
87 IF(dt%BRICK_DEL_ASP_MAX>zero .AND. ( dt%BRICK_DEL_ASP_MAX<aspmax
88 . .OR.aspmax==zero) ) aspmax = dt%BRICK_DEL_ASP_MAX
89 c_min = one
90 c_max = one
91 IF (l_max(1) >zero) THEN
92 itet = 0
93 ELSE
94 itet = 1
95 END IF
96C--- tet
97 IF (itet >0) THEN
98 c_max = 1.24*sqr3
99 c_min = one/c_max
100 END IF
101C
102 IF ((vdefmin+vdefmax) >zero) THEN
103 DO i=1,nel
104 IF (offg(i)==zero) cycle
105 def_v(i) = volg(i)/volg0(i)
106 END DO
107 END IF
108C
109 IF (vdefmin >zero) THEN
110 icount = 0
111 DO i=1,nel
112 IF (offg(i)==zero) cycle
113 IF (def_v(i) < vdefmin) THEN
114 offg(i) = zero
115 icount=icount+1
116 list(icount)=i
117 END IF
118 END DO
119 IF (icount > 0) THEN
120#include "lockon.inc"
121 WRITE(iout,1001)
122 WRITE(istdo,1001)
123 DO j=1,icount
124 i=list(j)
125 WRITE(iout,'(6X,I10,1PG20.13)')ngl(i),def_v(i)
126 WRITE(istdo,'(6X,I10,1PG20.13)')ngl(i),def_v(i)
127 ENDDO
128 WRITE(iout,*)
129 WRITE(istdo,*)
130#include "lockoff.inc"
131 idel7nok = 1
132 END IF !(ICOUNT > 0) THEN
133 END IF
134C
135 IF (vdefmax >zero) THEN
136 icount = 0
137 DO i=1,nel
138 IF (offg(i)==zero) cycle
139 IF (def_v(i) > vdefmax) THEN
140 offg(i) = zero
141 icount=icount+1
142 list(icount)=i
143 END IF
144 END DO
145 IF (icount > 0) THEN
146#include "lockon.inc"
147 WRITE(iout,1002)
148 WRITE(istdo,1002)
149 DO j=1,icount
150 i=list(j)
151 WRITE(iout,'(6X,I10,1PG20.13)')ngl(i),def_v(i)
152 WRITE(istdo,'(6X,I10,1PG20.13)')ngl(i),def_v(i)
153 ENDDO
154 WRITE(iout,*)
155 WRITE(istdo,*)
156#include "lockoff.inc"
157 idel7nok = 1
158 END IF !(ICOUNT > 0) THEN
159 END IF
160C--- Hexa : APS_r=lmax/lmin lmax~sqrt(Amax); lmin~lc & V~ lc*Amax ->
161C--- APS_r~sqrt(Amax/lc^2)=sqrt(V/lc^3) ; now we compute L_max for Hexa
162 IF ((aspmax+colmin) >zero) THEN
163 IF (itet ==0) THEN
164 DO i=1,nel
165 IF (offg(i)==zero) cycle
166 aps_r(i) = l_max(i)/deltax(i)
167 tet_colla(i) = deltax(i) / l_max(i)
168 END DO
169 ELSE
170 DO i=1,nel
171 IF (offg(i)==zero) cycle
172 al = sqrt(volg(i)/deltax(i)**3)
173 aps_r(i) = c_max*al
174 tet_colla(i) = c_min / al
175 END DO
176 END IF
177 END IF
178 IF (aspmax>zero) THEN
179 icount = 0
180 DO i=1,nel
181 IF (offg(i)==zero) cycle
182 IF (aps_r(i) > aspmax) THEN
183 offg(i) = zero
184 icount=icount+1
185 list(icount)=i
186 END IF
187 END DO
188 IF (icount > 0) THEN
189#include "lockon.inc"
190 WRITE(iout,1003)
191 WRITE(istdo,1003)
192 DO j=1,icount
193 i=list(j)
194 WRITE(iout,'(6X,I10,1PG20.13)')ngl(i),aps_r(i)
195 WRITE(istdo,'(6X,I10,1PG20.13)')ngl(i),aps_r(i)
196 ENDDO
197 WRITE(iout,*)
198 WRITE(istdo,*)
199#include "lockoff.inc"
200 idel7nok = 1
201 END IF !(ICOUNT > 0) THEN
202 END IF
203C
204C--- Tet4 : TET_c= h/sqrt(A)/1.24 h~lc; V~ lc*A*2/6 ->
205C--- TET_c~sqrt(h^2/A)/1.24=sqrt(h^3/V)/1.24/sqrt(3)
206C--- TET_c =1/ASP_r
207 IF (colmin>zero) THEN
208 icount = 0
209 DO i=1,nel
210 IF (offg(i)==zero) cycle
211 IF (tet_colla(i) < colmin) THEN
212 offg(i) = zero
213 icount=icount+1
214 list(icount)=i
215 END IF
216 END DO
217 IF (icount > 0) THEN
218#include "lockon.inc"
219 WRITE(iout,1004)
220 WRITE(istdo,1004)
221 DO j=1,icount
222 i=list(j)
223 WRITE(iout,'(6X,I10,1PG20.13)')ngl(i),tet_colla(i)
224 WRITE(istdo,'(6X,I10,1PG20.13)')ngl(i),tet_colla(i)
225 ENDDO
226 WRITE(iout,*)
227 WRITE(istdo,*)
228#include "lockoff.inc"
229 idel7nok = 1
230 END IF !(ICOUNT > 0) THEN
231 END IF
232C
233 RETURN
234 1001 FORMAT(/
235 . 'THE FOLLOWING SOLID ELEMENTS WILL BE DELETED BY MINIMUM VOLUME RATIO' /)
236 1002 FORMAT(/
237 . 'THE FOLLOWING SOLID ELEMENTS WILL BE DELETED BY MAXIMUM VOLUME RATIO' /)
238 1003 FORMAT(/
239 . 'THE FOLLOWING SOLID ELEMENTS WILL BE DELETED BY MAXIMUM ASPECT RATIO' /)
240 1004 FORMAT(/
241 . 'THE FOLLOWING SOLID ELEMENTS WILL BE DELETED BY MINIMUM COLLAPSE RATIO' /)
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21