OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c_sectio.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/.
23C
24!||====================================================================
25!|| c_sectio ../starter/source/restart/ddsplit/c_sectio.f
26!||--- called by ------------------------------------------------------
27!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
28!||--- calls -----------------------------------------------------
29!|| nlocal ../starter/source/spmd/node/ddtools.f
30!||====================================================================
31 SUBROUTINE c_sectio(NSTRF ,CEP ,PROC,NSTRF_L,
32 . LSECBUF_L,NNODT_L,NNODL_L)
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36
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 "com01_c.inc"
45#include "com04_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER PROC, NSTRF_L, LSECBUF_L, NNODT_L, NNODL_L,
50 . nstrf(*), cep(*)
51C-----------------------------------------------
52C F u n c t i o n
53C-----------------------------------------------
54 INTEGER NLOCAL
55 EXTERNAL nlocal
56C-----------------------------------------------
57C L o c a l V a r i a b l e s
58C-----------------------------------------------
59 INTEGER NNOD_S, NSELS_S, NSELQ_S, NSELC_S, NSELT_S, NSELP_S,
60 . nselr_s, nseltg_s, nsint_s, nsels_s_l, nselq_s_l,
61 . nselc_s_l, nselt_s_l, nselp_s_l, nselr_s_l, nseltg_s_l,
62 . n, ip, p, j, k, off, nnod_s_l, typ_s
63C
64 nstrf_l = 30
65C LSECBUF_L = 0
66 lsecbuf_l = 10
67 nnodt_l = 0
68 nnodl_l = 0
69 ip = 30
70 DO n = 1, nsect
71 typ_s = nstrf(ip+1)
72 nnod_s = nstrf(ip+7)
73 nsels_s = nstrf(ip+8)
74 nselq_s = nstrf(ip+9)
75 nselc_s = nstrf(ip+10)
76 nselt_s = nstrf(ip+11)
77 nselp_s = nstrf(ip+12)
78 nselr_s = nstrf(ip+13)
79 nseltg_s= nstrf(ip+14)
80 nsint_s = nstrf(ip+15)
81 nsels_s_l = 0
82 nselq_s_l = 0
83 nselc_s_l = 0
84 nselt_s_l = 0
85 nselp_s_l = 0
86 nselr_s_l = 0
87 nseltg_s_l= 0
88c IP = IP + 30 + NSINT_S + NNOD_S
89c NSTRF_L = NSTRF_L + 30 + NSINT_S + NNOD_S
90 ip = ip + 30 + nsint_s
91 nstrf_l = nstrf_l + 30 + nsint_s
92C noeuds
93 nnod_s_l = 0
94 DO j = 1, nnod_s
95 k = nstrf(ip + j)
96 IF(nlocal(k,proc+1)==1)THEN
97 nnod_s_l = nnod_s_l + 1
98 END IF
99 END DO
100 IF(isecut==1) THEN
101C section cut
102 IF (typ_s>=1)THEN
103 nnodl_l = nnodl_l + nnod_s_l
104 ENDIF
105C section cut type 1 et superieur sur p0
106 IF(proc==0.AND.typ_s>=1) THEN
107 nnodt_l = nnodt_l + nnod_s_l
108 DO p = 2, nspmd
109 DO j = 1, nnod_s
110 k = nstrf(ip + j)
111 IF(nlocal(k,p)==1)THEN
112 nnodt_l = nnodt_l + 1
113 END IF
114 END DO
115 END DO
116 END IF
117 END IF
118C
119 ip = ip + nnod_s
120 nstrf_l = nstrf_l + nnod_s_l
121C
122 off = 0
123C solides
124 DO j = 1, nsels_s
125 k = nstrf(ip + j*2 - 1)
126 IF(cep(k+off)==proc) nsels_s_l = nsels_s_l + 1
127 END DO
128 nstrf_l = nstrf_l + 2*nsels_s_l
129 ip = ip + 2*nsels_s
130 off = off + numels
131C quad
132 DO j = 1, nselq_s
133 k = nstrf(ip + j*2 - 1)
134 IF(cep(k+off)==proc) nselq_s_l = nselq_s_l + 1
135 END DO
136 nstrf_l = nstrf_l + 2*nselq_s_l
137 ip = ip + 2*nselq_s
138 off = off + numelq
139C shell
140 DO j = 1, nselc_s
141 k = nstrf(ip + j*2 - 1)
142 IF(cep(k+off)==proc) nselc_s_l = nselc_s_l + 1
143 END DO
144 nstrf_l = nstrf_l + 2*nselc_s_l
145 ip = ip + 2*nselc_s
146 off = off + numelc
147C truss
148 DO j = 1, nselt_s
149 k = nstrf(ip + j*2 - 1)
150 IF(cep(k+off)==proc) nselt_s_l = nselt_s_l + 1
151 END DO
152 nstrf_l = nstrf_l + 2*nselt_s_l
153 ip = ip + 2*nselt_s
154 off = off + numelt
155C poutre
156 DO j = 1, nselp_s
157 k = nstrf(ip + j*2 - 1)
158 IF(cep(k+off)==proc) nselp_s_l = nselp_s_l + 1
159 END DO
160 nstrf_l = nstrf_l + 2*nselp_s_l
161 ip = ip + 2*nselp_s
162 off = off + numelp
163C ressort
164 DO j = 1, nselr_s
165 k = nstrf(ip + j*2 - 1)
166 IF(cep(k+off)==proc) nselr_s_l = nselr_s_l + 1
167 END DO
168 nstrf_l = nstrf_l + 2*nselr_s_l
169 ip = ip + 2*nselr_s
170 off = off + numelr
171C triangle
172 DO j = 1, nseltg_s
173 k = nstrf(ip + j*2 - 1)
174 IF(cep(k+off)==proc) nseltg_s_l = nseltg_s_l + 1
175 END DO
176 nstrf_l = nstrf_l + 2*nseltg_s_l
177 ip = ip + 2*nseltg_s
178 off = off + numeltg
179C cut
180 lsecbuf_l=lsecbuf_l+10
181 IF(typ_s>=100)lsecbuf_l=lsecbuf_l+12*nnod_s_l
182 IF(typ_s>=101)lsecbuf_l=lsecbuf_l+12*nnod_s_l
183 IF(typ_s>=102)lsecbuf_l=lsecbuf_l+6*nnod_s_l
184C.
185 ENDDO
186C
187 RETURN
188 END
subroutine c_sectio(nstrf, cep, proc, nstrf_l, lsecbuf_l, nnodt_l, nnodl_l)
Definition c_sectio.F:33
subroutine ddsplit(p, cep, cel, igeo, mat_elem, ipm, icode, iskew, iskn, insel, ibcslag, ipart, iparts, ipartq, ipartc, ipartt, ipartp, ipartr, iparttg, detonators, ipartx, npc, ixtg, group_param_tab, ixtg6, ixs, ixs10, ixs20, ixs16, ixq, ixc, ixt, ixp, ixr, itab, itabm1, gjbufi, nale, ale_connectivity, kxx, ixx, ibcl, ibfv, las, laccelm, nnlink, lllink, iparg, igrav, lgrav, ibvel, lbvel, iactiv, factiv, kinet, ipari, nprw, lprw, iexmad, npby, lpby, ixri, nstrf, ljoint, pornod, monvol, icontact, lagbuf, fr_iad, x, d, v, vr, dr, thke, dampr, damp, ms, in, tf, pm, skew, xframe, geo, eani, bufmat, bufgeo, bufsf, brmpc, gjbufr, w, veul, fill, dfill, wb, dsav, asav, msnf, spbuf, fac, vel, fsav, fzero, xlas, accelm, fbvel, gravfac, fr_wave, failwave, parts0, elbuf, rwl, rwsav, rby, rivet, secbuf, rvolu, rconx, nloc_dmg, fvmain, libagale, lenthg, lbufmat, lbufgeo, lbufsf, lenxlas, lnom_opt, lenlas, lenvolu, npts, cne, lcne, addcne, cni2, lcni2g, addcni2, cepi2, celi2, i2nsnt, probint, ddstat, pm1shf, dd_iad, kxsp, ixsp, nod2sp, cepsp, nthwa, nairwa, nmnt, l_mul_lag1, l_mul_lag, lwaspio, ipartsp, ispcond, pm1sph, wma, eigipm, eigibuf, eigrpm, iflow, rflow, memflow, iexlnk, fasolfr, iparth, fxbipm, fxbrpm, fxbnod, fxbmod, fxbglm, fxbcpm, fxbcps, fxblm, fxbfls, fxbdls, fxbdep, fxbvit, fxbacc, fxbelm, fxbsig, fxbgrvi, fxbgrvr, iadll, lll, ibmpc, lambda, lrbagale, iskwp, nskwp, isensp, nsensp, iaccp, naccp, ipart_state, mcp, temp, unitab, intstamp, iframe, clusters, partsav, ibft, fbft, ibcv, fconv, irbe3, lrbe3, frbe3, front_rm, rbym, irbym, lcrbym, inoise, fnoise, ms0, admsms, nom_sect, ispsym, sh4tree, sh3tree, ipadmesh, ibfflux, fbfflux, sh4trim, sh3trim, padmesh, msc, mstg, inc, intg, ptg, mcpc, mcptg, rcontact, acontact, pcontact, mscnd, incnd, mssa, mstr, msp, msrt, ibcr, fradia, dmelc, dmeltg, dmels, dmeltr, dmelp, dmelrt, res_sms, isphio, lprtsph, lonfsph, vsphio, sphveln, alph, ifill, ims, irbe2, lrbe2, ms_ply, zi_ply, inod_pxfem, iel_pxfem, icodply, iskwply, addcne_pxfem, cne_pxfem, cel_pxfem, ithvar, xdp, table, celsph, icfield, lcfield, cfield, msz2, itask, diag_sms, iloadp, lloadp, loadp, inod_crkxfem, iel_crkxfem, addcne_crkxfem, cne_crkxfem, cel_crkxfem, ibufssg_io, intercep, ibordnode, iedgesh, ibordedge, linale, nodedge, iedge, cep_crkxfem, iedge_tmp, crknodiad, elbuf_tab, nom_opt, lgauge, gauge, igaup, ngaup, nodlevxf, frontb_r2r, dflow, vflow, wflow, sph2sol, sol2sph, irst, elcutc, nodenr, kxfenod2elc, enrtag, intbuf_tab, i11flag, xfem_tab, lenthgr, rthbuf, ixig3d, kxig3d, knot, ipartig3d, wige, ncrkpart, indx_crk, crklvset, crkshell, crksky, crkavx, crkedge, sensors, stack, xfem_phantom, t8, tab_ump, poin_ump, sol2sph_typ, addcsrect, csrect, drape, loads, itagnd, icnds10, addcncnd, cepcnd, celcnd, cncnd, nativ_sms, i24maxnsne, multi_fvm, segquadfr, intbuf_fric_tab, subset, igrnod, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, igrpart, igrsurf, igrslin, poin_part_shell, poin_part_tri, poin_part_sol, mid_pid_shell, mid_pid_tri, mid_pid_sol, tag_nm, nindx_nm, indx_nm, tag_scratch, nindx_scrt, indx_scrt, flag_24_25, numnod_l, tag_skn, multiple_skew, igrsurf_proc, knotlocpc, knotlocel, ale_elm, size_ale_elm, pinch_data, tag_skins6, ibcscyc, lbcscyc, t_monvol, indx_s, indx_q, indx_tg, face_elm_s, face_elm_q, face_elm_tg, nbr_th_monvol, ebcs_tab, kloadpinter, loadpinter, dgaploadint, s_loadpinter, len_cep, dynain_data, drapeg, user_windows, output, interfaces, number_load_cyl, loads_per_proc, python, dpl0cld, vel0cld, names_and_titles, bcs_per_proc, constraint_struct, glob_therm, pblast)
Definition ddsplit.F:336
integer function nlocal(n, p)
Definition ddtools.F:349
program starter
Definition starter.F:39