OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
init_i25_edge.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!|| init_i25_edge ../engine/source/interfaces/int25/init_i25_edge.F
25!||--- called by ------------------------------------------------------
26!|| resol ../engine/source/engine/resol.f
27!||--- uses -----------------------------------------------------
28!|| intbufdef_mod ../common_source/modules/interfaces/intbufdef_mod.F90
29!||====================================================================
30 SUBROUTINE init_i25_edge(NLEDGE,NINTER,NPARI,IPARI,INTBUF_TAB)
31!$COMMENT
32! INIT_I25_EDGE description :
33! for interface type 25, find the solid edge & non-main edge
34!
35! INIT_I25_EDGE organization :
36! loop over the interface
37! * if NiN is an interface type 25 with edge to edge --> find the solid edge
38!$ENDCOMMENT
39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE intbufdef_mod
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "i25edge_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER, INTENT(in) :: NLEDGE !< dim of ledge array
55 INTEGER, INTENT(in) :: NINTER !< number of interface
56 INTEGER, INTENT(in) :: NPARI !< dim of IPARI array
57 INTEGER, DIMENSION(NPARI,NINTER), INTENT(in) :: IPARI !< interface data
58 TYPE(intbuf_struct_), DIMENSION(NINTER), INTENT(inout) :: INTBUF_TAB !< interface data
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER :: I,J
63 INTEGER :: INTERFACE_TYPE
64 INTEGER :: SOL_EDGE,SH_EDGE,IEDGE,NEDGE
65 INTEGER, DIMENSION(:), ALLOCATABLE :: TMP_ARRAY
66C-----------------------------------------------
67
68 ! ------------------------
69 ! loop over the interface
70 DO i=1,ninter
71 intbuf_tab(i)%NUMBER_EDGE_TYPE1 = 0
72 intbuf_tab(i)%NUMBER_EDGE_TYPE1_0 = 0
73 interface_type = ipari(7,i)
74 iedge = ipari(58,i)
75 ! -----------------
76 ! check if the interface is a type 25 with edge to edge
77 IF(interface_type==25.AND.iedge/=0) THEN
78 nedge = ipari(68,i)
79 ALLOCATE (tmp_array(nedge) )
80 ! ----------
81 ! loop over the edge to find the edge solid
82 DO j=1,nedge
83 IF(intbuf_tab(i)%LEDGE((j-1)*nledge+ledge_type)==1) THEN
84 intbuf_tab(i)%NUMBER_EDGE_TYPE1 = intbuf_tab(i)%NUMBER_EDGE_TYPE1 + 1
85 tmp_array(intbuf_tab(i)%NUMBER_EDGE_TYPE1) = j
86 ENDIF
87 ENDDO
88 ALLOCATE( intbuf_tab(i)%EDGE_TYPE1(intbuf_tab(i)%NUMBER_EDGE_TYPE1) )
89 intbuf_tab(i)%EDGE_TYPE1(1:intbuf_tab(i)%NUMBER_EDGE_TYPE1) = tmp_array(1:intbuf_tab(i)%NUMBER_EDGE_TYPE1)
90 ! ----------
91
92 ! ----------
93 ! loop over the edge to find the edge solid & the edge S
94 sol_edge = iedge/10 ! solids
95 sh_edge = iedge-10*sol_edge ! shells
96 DO j=1,nedge
97 IF(intbuf_tab(i)%LEDGE((j-1)*nledge+ledge_type)>=0.AND.
98 . (intbuf_tab(i)%LEDGE((j-1)*nledge+ledge_type)==1.OR.sh_edge==0) ) THEN
99 intbuf_tab(i)%NUMBER_EDGE_TYPE1_0 = intbuf_tab(i)%NUMBER_EDGE_TYPE1_0 + 1
100 tmp_array(intbuf_tab(i)%NUMBER_EDGE_TYPE1_0) = j
101 ENDIF
102 ENDDO
103 ALLOCATE( intbuf_tab(i)%EDGE_TYPE1_0(intbuf_tab(i)%NUMBER_EDGE_TYPE1_0) )
104 intbuf_tab(i)%EDGE_TYPE1_0(1:intbuf_tab(i)%NUMBER_EDGE_TYPE1_0) = tmp_array(1:intbuf_tab(i)%NUMBER_EDGE_TYPE1_0)
105 ! ----------
106
107 DEALLOCATE( tmp_array )
108 ELSE
109 ALLOCATE( intbuf_tab(i)%EDGE_TYPE1(intbuf_tab(i)%NUMBER_EDGE_TYPE1) )
110 ALLOCATE( intbuf_tab(i)%EDGE_TYPE1_0(intbuf_tab(i)%NUMBER_EDGE_TYPE1_0) )
111 ENDIF
112 ! -----------------
113 ENDDO
114 ! ------------------------
115
116 RETURN
117 END SUBROUTINE init_i25_edge
118
subroutine init_i25_edge(nledge, ninter, npari, ipari, intbuf_tab)
subroutine resol(timers, element, nodes, coupling, af, iaf, iskwn, neth, ipart, nom_opt, kxx, ixx, ixtg, ixs, ixq, ixt, ixp, ixr, ifill, mat_elem, ims, npc, ibcl, ibfv, idum, las, laccelm, nnlink, lnlink, iparg, dd_iad, igrv, iexlnk, kinet, ipari, nprw, iconx, npby, lpby, lrivet, nstrf, ljoint, nodpor, monvol, ilink, llink, linale, neflsw, nnflsw, icut, cluster, itask, inoise, thke, damp, pm, skews, geo, eani, bufmat, bufgeo, bufsf, w, veul, fill, dfill, alph, wb, dsave, asave, msnf, tf, forc, vel, fsav, fzero, xlas, accelm, agrv, fr_wave, failwave, parts0, elbuf, rwbuf, sensors, rwsav, rby, rivet, secbuf, volmon, lambda, wa, fv, partsav, uwa, val2, phi, segvar, r, crflsw, flsw, fani, xcut, anin, tani, secfcum, bufnois, idata, rdata, iframe, kxsp, ixsp, nod2sp, ispsym, ispcond, xframe, spbuf, xspsym, vspsym, pv, fsavd, ibvel, lbvel, wasph, w16, isphio, lprtsph, lonfsph, vsphio, fbvel, lagbuf, ibcslag, iactiv, dampr, gjbufi, gjbufr, rbmpc, ibmpc, sphveln, nbrcvois, nbsdvois, lnrcvois, lnsdvois, nercvois, nesdvois, lercvois, lesdvois, npsegcom, lsegcom, nporgeo, ixtg1, npbyl, lpbyl, rbyl, igeo, ipm, madprt, madsh4, madsh3, madsol, madnod, madfail, iad_rby, fr_rby, fr_wall, iad_rby2, fr_rby2, iad_i2m, fr_i2m, addcni2, procni2, iadi2, fr_mv, iadmv2, fr_ll, fr_rl, iadcj, fr_cj, fr_sec, iad_sec, iad_cut, fr_cut, rg_cut, newfront, fr_mad, fxbipm, fxbrpm, fxbnod, fxbmod, fxbglm, fxbcpm, fxbcps, fxblm, fxbfls, fxbdls, fxbdep, fxbvit, fxbacc, fxbelm, fxbsig, fxbgrvi, fxbgrvr, eigipm, eigibuf, eigrpm, lnodpor, fr_i18, graphe, iflow, rflow, lgrav, dd_r2r, fasolfr, fr_lagf, llagf, lprw, icontact, rcontact, sh4tree, sh3tree, ipadmesh, padmesh, msc, mstg, inc, intg, ptg, iskwp, nskwp, isensp, nsensp, iaccp, naccp, ipart_state, acontact, pcontact, factiv, sh4trim, sh3trim, mscnd, incnd, ibfflux, fbfflux, rbym, irbym, lnrbym, icodrbym, ibcv, fconv, ibftemp, fbftemp, iad_rbym, fr_rbym, weight_rm, ms_ply, zi_ply, inod_pxfem, iel_pxfem, iadc_pxfem, adsky_pxfem, icode_ply, icodt_ply, iskew_ply, admsms, madclnod, nom_sect, mcpc, mcptg, dmelc, dmeltg, mssa, dmels, mstr, dmeltr, msp, dmelp, msrt, dmelrt, ibcr, fradia, res_sms, table, irbe2, lrbe2, iad_rbe2, fr_rbe2, phie, msf, procne_pxfem, iadsdp_pxfem, iadrcp_pxfem, icfield, lcfield, cfield, msz2, diag_sms, iloadp, lloadp, loadp, inod_crk, iel_crk, iadc_crk, adsky_crk, cne_crk, procne_crk, iadsdp_crk, iadrcp_crk, ibufssg_io, ibc_ply, dmint2, ibordnode, elbuf_tab, por, nodedge, iad_edge, fr_edge, fr_nbedge, crknodiad, lgauge, gauge, igaup, ngaup, nodlevxf, dd_r2r_elem, nodglobxfe, sph2sol, sol2sph, irst, dmsph, wagap, xfem_tab, elcutc, nodenr, kxfenod2elc, enrtag, rthbu f, kxig3d, ixig3d, knot, wige, wsmcomp, stack, cputime_mp_glob, cputime_mp, tab_ump, poin_ump, sol2sph_typ, irunn_bis, addcsrect, iad_frnor, fr_nor, procnor, iad_fredg, fr_edg, drape_sh4n, drape_sh3n, tab_mat, nativ0_sms, multi_fvm, segquadfr, ms_2d, h3d_data, subsets, igrnod, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, igrpart, igrsurf, forneqs, nloc_dmg, iskwp_l, knotlocpc, knotlocel, pinch_data, tag_skins6, ale_connectivity, xcell, xface, ne_nercvois, ne_nesdvois, ne_lercvois, ne_lesdvois, ibcscyc, lbcscyc, t_monvol, id_global_vois, face_vois, dynain_data, fcont_max, ebcs_tab, diffusion, kloadpinter, loadpinter, dgaploadint, drapeg, user_windows, output, interfaces, dt, loads, python, dpl0cld, vel0cld, ndamp_vrel, id_damp_vrel, fr_damp_vrel, ndamp_vrel_rbyg, names_and_titles, unitab, liflow, lrflow, glob_therm, pblast, rbe3)
Definition resol.F:633