OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
elbuf_ini.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| elbuf_ini ../engine/source/elements/elbuf/elbuf_ini.F
25!||--- called by ------------------------------------------------------
26!|| rdresb ../engine/source/output/restart/rdresb.F
27!||--- calls -----------------------------------------------------
28!|| allocbuf_auto ../engine/source/elements/elbuf/allocbuf_auto.F
29!||--- uses -----------------------------------------------------
30!|| mat_elem_mod ../common_source/modules/mat_elem/mat_elem_mod.F90
31!||====================================================================
32 SUBROUTINE elbuf_ini(MAT_ELEM ,NGROUP ,IPARG)
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE mat_elem_mod
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "com_xfem1.inc"
45#include "param_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER ,INTENT(IN) :: NGROUP
50 INTEGER ,INTENT(INOUT) :: IPARG(NPARG,NGROUP)
51 TYPE(mat_elem_) ,INTENT(INOUT) :: MAT_ELEM
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 INTEGER ERR,NG,BUFLEN,ITY,NPT,IXFEM,IXEL,ISNOD,NEWLEN,INLOC,ISOLNOD
56 INTEGER IDAMP_FREQ_RANGE
57C=======================================================================
58c Element Buffer Routine (Solid)
59c------
60c 1) taille du tableau ELBUF pour restart
61c 2) allocation de la structure ELBUF_STR
62C=======================================================================
63 err = 0
64 ALLOCATE (mat_elem%ELBUF(ngroup), stat=err)
65 IF (err /= 0) THEN
66 ENDIF
67c-------------------------------------------------
68 DO ng = 1,ngroup
69 ity = iparg(5,ng)
70 npt = iparg(6,ng)
71 isolnod= iparg(28,ng)
72 buflen = iparg(66,ng)
73 ixfem = iparg(54,ng)
74 inloc = iparg(78,ng)
75 idamp_freq_range = iparg(93,ng)
76
77 newlen = buflen
78 IF(ity==1)THEN
79 isnod=iparg(28,ng)
80 ELSE
81 isnod=0
82 END IF
83c print*,' NG =',ng
84 IF (ity==1 .or. ity==2 .or. ity==51 .or. ity==3 .or.
85 . ity==7 .or. ity==101 .or. ity==4 .or. ity==5 .or.
86 . ity==6 .or. ity==100)THEN
87 CALL allocbuf_auto(mat_elem%ELBUF(ng),buflen,npt,ity,isnod,newlen,inloc,isolnod,
88 . idamp_freq_range)
89 iparg(66,ng)=newlen
90 END IF
91 ENDDO ! NG = 1,NGROUP
92C-----------
93 IF (icrack3d > 0) THEN
94 err = 0
95 ALLOCATE (mat_elem%XFEM_TAB(ngroup,nxel), stat=err)
96c IF (ERR /= 0) THEN
97c ENDIF
98 DO ixel=1,nxel
99 DO ng = 1,ngroup
100 ity = iparg(5,ng)
101 npt = iparg(6,ng)
102 isolnod= iparg(28,ng)
103 buflen = iparg(66,ng)
104 ixfem = iparg(54,ng)
105 inloc = iparg(78,ng)
106 idamp_freq_range = iparg(93,ng)
107 newlen = buflen
108c----
109c if xfem, count buffer's length only in the groups with xfem phantom elements
110c----
111 IF (ixfem > 0 .and. (ity==3 .or. ity==7)) THEN
112 CALL allocbuf_auto(mat_elem%XFEM_TAB(ng,ixel),buflen,npt,ity,isnod,newlen,inloc,
113 . isolnod,idamp_freq_range)
114 iparg(66,ng)=newlen
115 ENDIF
116 ENDDO
117 ENDDO
118 ELSE
119 ALLOCATE (mat_elem%XFEM_TAB(0,0), stat=err)
120 ENDIF
121C-----------
122 RETURN
123 END SUBROUTINE elbuf_ini
subroutine elbuf_ini(mat_elem, ngroup, iparg)
Definition elbuf_ini.F:33
subroutine allocbuf_auto(elbuf_tab, nlay, nptr, npts, nptt, nintlay, nel, npt, ng, ngroup, ity, igtyp, npropm, nummat, pm)