OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
impbufdef_mod.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!|| impbufdef_mod ../engine/share/modules/impbufdef_mod.F
25!||--- called by ------------------------------------------------------
26!|| dealloc_impbuf ../engine/source/implicit/imp_solv.F
27!|| imp_buck ../engine/source/implicit/imp_buck.F
28!|| imp_chkm ../engine/source/implicit/imp_solv.F
29!|| imp_fout ../engine/source/implicit/imp_solv.F
30!|| imp_restarcp ../engine/source/implicit/imp_sol_init.F
31!|| imp_sol_init ../engine/source/implicit/imp_sol_init.F
32!|| imp_solv ../engine/source/implicit/imp_solv.F
33!|| resol ../engine/source/engine/resol.F
34!|| wrrestp ../engine/source/output/restart/wrrestp.F
35!||====================================================================
37C-----------------------------------------------------------------------
38#include "my_real.inc"
39C=======================================================================
40c DEFINE SIZES (integers arrays)
41C=======================================================================
42 integer :: s_iadk
43 integer :: s_jdik
44 integer :: s_isij
45 integer :: s_imij
46 integer :: s_nss
47 integer :: s_iss
48 integer :: s_isij2
49 integer :: s_nss2
50 integer :: s_iss2
51 integer :: s_nsc2
52 integer :: s_nrowk
53 integer :: s_icok
54 integer :: s_icokm
55 integer :: s_nmij2
56 integer :: s_nss3
57 integer :: s_isb2
58 integer :: s_nsrb2
59 integer :: s_ikc
60 integer :: s_ikud
61 integer :: s_w_ddl
62 integer :: s_iadm
63 integer :: s_jdim
64 integer :: s_ndofi
65 integer :: s_iddli
66 integer :: s_ikinw
67 integer :: s_inbuf_c
68C-
69 integer :: s_i_stok ! replace NUM_IMP
70 integer :: s_cand_n ! replace NS_IMP
71 integer :: s_cand_e ! replace NE_IMP
72 integer :: s_indsubt ! replace IND_IMP
73C=======================================================================
74c DEFINE SIZES (float arrays)
75C=======================================================================
76 integer :: s_diag_k
77 integer :: s_lt_k
78 integer :: s_diag_m
79 integer :: s_lt_m
80 integer :: s_lb
81 integer :: s_lb0
82 integer :: s_bkud
83 integer :: s_d_imp
84 integer :: s_dr_imp
85 integer :: s_elbuf_c
86 integer :: s_bufmat_c
87 integer :: s_x_c
88 integer :: s_dd
89 integer :: s_ddr
90 integer :: s_x_a
91 integer :: s_fext
92 integer :: s_dg
93 integer :: s_dgr
94 integer :: s_dg0
95 integer :: s_dgr0
96 integer :: s_bufin_c
97 integer :: s_ac
98 integer :: s_acr
99c=======================================================================
100c define type IMPBUF_STRUCT_ for implicit structure array
101c=======================================================================
102C=======================================================================
104C=======================================================================
105c integers & small integer arrays
106C=======================================================================
107 integer :: nddl
108 integer :: nnzk
109C----NS_IMP... will be changed to POINTER and pt to %I_STOK... in resol
110 integer :: nrbyac
111 integer :: nint2
112 integer :: NMC
113 integer :: nmc2
114 integer :: nmonv
115 integer, DIMENSION(20) :: lsize
116 integer, DIMENSION(20) :: i_imp
117C=======================================================================
118c DEFINE ARRAYS (integers arrays)
119C=======================================================================
120 integer, DIMENSION(:) , ALLOCATABLE :: irbyac
121 integer, DIMENSION(:) , ALLOCATABLE :: nsc
122 integer, DIMENSION(:) , ALLOCATABLE :: iint2
123 integer, DIMENSION(:) , ALLOCATABLE :: nkud
124 integer, DIMENSION(:) , ALLOCATABLE :: imonv
125 integer, DIMENSION(:) , ALLOCATABLE :: iddl
126 integer, DIMENSION(:) , ALLOCATABLE :: ndof
127 integer, DIMENSION(:) , ALLOCATABLE :: inloc
128 integer, DIMENSION(:) , ALLOCATABLE :: iadk
129 integer, DIMENSION(:) , ALLOCATABLE :: jdik
130 integer, DIMENSION(:) , ALLOCATABLE :: isij
131 integer, DIMENSION(:) , ALLOCATABLE :: imij
132 integer, DIMENSION(:) , ALLOCATABLE :: nss
133 integer, DIMENSION(:) , ALLOCATABLE :: iss
134 integer, DIMENSION(:) , ALLOCATABLE :: isij2
135 integer, DIMENSION(:) , ALLOCATABLE :: nss2
136 integer, DIMENSION(:) , ALLOCATABLE :: iss2
137 integer, DIMENSION(:) , ALLOCATABLE :: nsc2
138 integer, DIMENSION(:) , ALLOCATABLE :: nrowk
139 integer, DIMENSION(:) , ALLOCATABLE :: icok
140 integer, DIMENSION(:) , ALLOCATABLE :: icokm
141 integer, DIMENSION(:) , ALLOCATABLE :: nmij2
142 integer, DIMENSION(:) , ALLOCATABLE :: nss3
143 integer, DIMENSION(:) , ALLOCATABLE :: isb2
144 integer, DIMENSION(:) , ALLOCATABLE :: nsrb2
145 integer, DIMENSION(:) , ALLOCATABLE :: ikc
146 integer, DIMENSION(:) , ALLOCATABLE :: ikud
147 integer, DIMENSION(:) , ALLOCATABLE :: w_ddl
148 integer, DIMENSION(:) , ALLOCATABLE :: iadm
149 integer, DIMENSION(:) , ALLOCATABLE :: jdim
150 integer, DIMENSION(:) , ALLOCATABLE :: ndofi
151 integer, DIMENSION(:) , ALLOCATABLE :: iddli
152 integer, DIMENSION(:) , ALLOCATABLE :: ikinw
153 integer, DIMENSION(:) , ALLOCATABLE :: inbuf_c
154C---for contact
155 integer, DIMENSION(:) , ALLOCATABLE :: i_stok
156 integer, DIMENSION(:) , ALLOCATABLE :: cand_n
157 integer, DIMENSION(:) , ALLOCATABLE :: cand_e
158 integer, DIMENSION(:) , ALLOCATABLE :: indsubt
159C=======================================================================
160c DEFINE ARRAYS (float arrays)
161C=======================================================================
162 my_real, DIMENSION(25) :: r_imp
163 my_real, DIMENSION(:) , ALLOCATABLE :: diag_k
164 my_real, DIMENSION(:) , ALLOCATABLE :: lt_k
165 my_real, DIMENSION(:) , ALLOCATABLE :: diag_m
166 my_real, DIMENSION(:) , ALLOCATABLE :: lt_m
167 my_real, DIMENSION(:) , ALLOCATABLE :: lb
168 my_real, DIMENSION(:) , ALLOCATABLE :: lb0
169 my_real, DIMENSION(:) , ALLOCATABLE :: bkud
170 my_real, DIMENSION(:) , ALLOCATABLE :: d_imp
171 my_real, DIMENSION(:) , ALLOCATABLE :: dr_imp
172 my_real, DIMENSION(:) , ALLOCATABLE :: elbuf_c
173 my_real, DIMENSION(:) , ALLOCATABLE :: bufmat_c
174 my_real, DIMENSION(:) , ALLOCATABLE :: x_c
175 my_real, DIMENSION(:) , ALLOCATABLE :: dd
176 my_real, DIMENSION(:) , ALLOCATABLE :: ddr
177 my_real, DIMENSION(:) , ALLOCATABLE :: x_a
178 my_real, DIMENSION(:) , ALLOCATABLE :: fext
179 my_real, DIMENSION(:) , ALLOCATABLE :: dg
180 my_real, DIMENSION(:) , ALLOCATABLE :: dgr
181 my_real, DIMENSION(:) , ALLOCATABLE :: dg0
182 my_real, DIMENSION(:) , ALLOCATABLE :: dgr0
183 my_real, DIMENSION(:) , ALLOCATABLE :: bufin_c
184 my_real, DIMENSION(:) , ALLOCATABLE :: ac
185 my_real, DIMENSION(:) , ALLOCATABLE :: acr
186C=======================================================================
187 END TYPE impbuf_struct_
188C=======================================================================
189c---------------
190 END MODULE impbufdef_mod
191!||====================================================================
192!|| imp_ktan_def ../engine/share/modules/impbufdef_mod.F
193!||--- called by ------------------------------------------------------
194!|| cmatch3 ../engine/source/elements/shell/coqueba/cmatc3.F
195!|| cmatip3 ../engine/source/elements/shell/coqueba/cmatc3.F
196!|| etfac_ini ../engine/source/implicit/imp_init.F
197!|| get_etfac_s ../engine/source/elements/solid/solide8z/get_etfac_s.F
198!|| gethkt3 ../engine/source/elements/solid/solide8z/gethkt3.F
199!|| iktmat_ini ../engine/source/implicit/imp_init.F
200!|| imp_ktan ../engine/share/modules/impbufdef_mod.F
201!|| ktbuf_ini ../engine/source/implicit/imp_init.F
202!|| mmats ../engine/source/elements/solid/solide8z/mmats.F
203!|| put_etfac ../engine/source/elements/solid/solide8z/put_etfac.F
204!|| putsignor3 ../engine/source/elements/solid/solide8z/putsignor3.F
205!|| putsignorc3 ../engine/source/elements/shell/coqueba/cmatc3.F
206!|| sktcons2 ../engine/source/elements/solid/solide8z/sktcons2.F
207!||====================================================================
209#include "my_real.inc"
210C------
211 TYPE mlaw_tag_ ! element buffer variables depending on material law
212 INTEGER :: l_etfac ! = 1
213 INTEGER :: l_sige ! = 6 ; = 5 for shell
214 INTEGER :: l_a_kt
215 INTEGER :: l_s ubkt ! =6
216 END TYPE mlaw_tag_
217
218C TYPE L_KTBUFG_ ! general law (hyper-elastic, elasto-plastic)
219C my_real, DIMENSION(:) , POINTER :: ETFAC ! relative tangent modulus ratio per ele
220C END TYPE L_KTBUFG_
221
222 TYPE l_ktbufep_ ! elastoplastic material per integration point
223 my_real, DIMENSION(:) , POINTER :: a_kt ! alpha dgama for shell
224 my_real, DIMENSION(:) , POINTER :: sige ! trail stress
225 END TYPE l_ktbufep_
226
227 TYPE l_ktbufgm_ ! modulus KT general matrix per integration point
228C----------------|DD(L_SUBKT) | DG(L_SUBKT) |
229C----------------| sym | GG(L_SUBKT) |
230 my_real, DIMENSION(:) , POINTER :: kt_dd
231 my_real, DIMENSION(:) , POINTER :: kt_dg
232 my_real, DIMENSION(:) , POINTER :: kt_gg
233 END TYPE l_ktbufgm_
234
236C------the following integer arguments are not necessary for the moment
237c integer :: MLAW ! 1
238c integer :: NEL ! 2
239c integer :: NPTR ! 3
240c integer :: NPTS ! 4
241c integer :: NPTT ! 5
242C ------------add MLAW_TAG here to avoid pass everywhere the arguments
243 my_real , DIMENSION(:) , ALLOCATABLE :: etfac ! relative tangent modulus ratio - per element(global)
244 TYPE(mlaw_tag_) , DIMENSION(:) , ALLOCATABLE :: mlaw_tag ! variable dimensions - per element(global)
245 TYPE (l_ktbufep_) , DIMENSION(:,:,:) , ALLOCATABLE :: ktbufep ! EP mat - per integration point
246 TYPE (l_ktbufgm_) , DIMENSION(:,:,:) , ALLOCATABLE :: ktbufmg ! ET mat - per integration point
247 END TYPE ktbuf_struct_
248C
249 END MODULE imp_ktan_def
250!||====================================================================
251!|| imp_bfgs ../engine/share/modules/impbufdef_mod.F
252!||--- called by ------------------------------------------------------
253!|| bfgs_0 ../engine/source/implicit/imp_bfgs.F
254!|| bfgs_1 ../engine/source/implicit/imp_bfgs.F
255!|| bfgs_1p ../engine/source/implicit/imp_bfgs.F
256!|| bfgs_2 ../engine/source/implicit/imp_bfgs.F
257!|| bfgs_2p ../engine/source/implicit/imp_bfgs.F
258!|| bfgs_h1 ../engine/source/implicit/imp_bfgs.F
259!|| bfgs_h1p ../engine/source/implicit/imp_bfgs.F
260!|| bfgs_h2 ../engine/source/implicit/imp_bfgs.F
261!|| bfgs_h2p ../engine/source/implicit/imp_bfgs.F
262!|| bfgs_ini ../engine/source/implicit/imp_bfgs.F
263!|| bfgs_ls ../engine/source/implicit/imp_bfgs.F
264!|| deallocm_imp ../engine/source/implicit/imp_solv.F
265!|| get_slin ../engine/source/implicit/imp_bfgs.F
266!|| nsloan_0 ../engine/source/implicit/imp_bfgs.F
267!|| nsloan_5 ../engine/source/implicit/imp_bfgs.F
268!||====================================================================
269 MODULE imp_bfgs
270C
271#include "my_real.inc"
272 INTEGER n_bfgs,iactb
273 my_real s_lin
274C
275C tableau de int de : V,W pour BFGS algorithm----
276 my_real, DIMENSION(:,:), ALLOCATABLE :: bfgs_v,bfgs_w
277C
278 END MODULE imp_bfgs
279!||====================================================================
280!|| imp_dyna ../engine/share/modules/impbufdef_mod.F
281!||--- called by ------------------------------------------------------
282!|| deallocm_imp ../engine/source/implicit/imp_solv.F
283!|| du_ini ../engine/source/implicit/imp_solv.F
284!|| du_ini_hp ../engine/source/implicit/imp_solv.F
285!|| dyna_cpk0 ../engine/source/implicit/imp_dyna.F
286!|| dyna_cpr0 ../engine/source/implicit/imp_dyna.F
287!|| dyna_in0 ../engine/source/implicit/imp_dyna.F
288!|| dyna_ina ../engine/source/implicit/imp_dyna.F
289!|| dyna_ini ../engine/source/implicit/imp_dyna.F
290!|| dyna_iniv ../engine/source/implicit/imp_dyna.F
291!|| dyna_ivfac ../engine/source/implicit/imp_dyna.F
292!|| dyna_wex ../engine/source/implicit/imp_dyna.F
293!|| ecrit ../engine/source/output/ecrit.F
294!|| freimpl ../engine/source/input/freimpl.F
295!|| fv_fint0 ../engine/source/constraints/general/impvel/fv_imp0.F
296!|| getdyna_a ../engine/source/implicit/imp_dyna.F
297!|| imp_dycrb ../engine/source/implicit/imp_dyna.F
298!|| imp_dykv ../engine/source/implicit/imp_dyna.F
299!|| imp_dykv0 ../engine/source/implicit/imp_dyna.F
300!|| imp_dynam ../engine/source/implicit/imp_dyna.F
301!|| imp_dynar ../engine/source/implicit/imp_dyna.F
302!|| imp_fhht ../engine/source/implicit/imp_dyna.F
303!|| imp_fhht1 ../engine/source/implicit/imp_dyna.F
304!|| imprrest ../engine/source/output/restart/rdresb.F
305!|| impwrest ../engine/source/output/restart/wrrest.F
306!|| inte_dyna ../engine/source/implicit/imp_dyna.F
307!|| rbe2cor ../engine/source/constraints/general/rbody/rgbcor.F
308!|| rbe2cor0 ../engine/source/constraints/general/rbody/rgbcor.F
309!|| rbycor ../engine/source/constraints/general/rbody/rbycor.F
310!|| rgbcor ../engine/source/constraints/general/rbody/rgbcor.F
311!|| stop_sensor ../engine/source/tools/sensor/stop_sensor.F
312!|| wfv_imp ../engine/source/constraints/general/impvel/fv_imp0.F
313!||====================================================================
314 MODULE imp_dyna
315C
316#include "my_real.inc"
317C
318C tableau de travail : implicit dynamic ----
319 my_real dy_g,dy_b,dy_edamp
320 my_real, DIMENSION(:,:), ALLOCATABLE :: dy_d,dy_dr,dy_v
321 my_real, DIMENSION(:,:), ALLOCATABLE :: dy_vr,dy_a,dy_ar
322 my_real, DIMENSION(:,:), ALLOCATABLE :: dy_in
323 my_real, DIMENSION(:,:), ALLOCATABLE :: dy_dam,dy_damr
324 my_real, DIMENSION(:), ALLOCATABLE :: dy_diak0,dy_ltk0
325 my_real, DIMENSION(:), ALLOCATABLE :: dy_r0,dy_r1
326 my_real, DIMENSION(:,:), ALLOCATABLE :: dy_dam0,dy_damr0
327 INTEGER, DIMENSION(:), ALLOCATABLE :: dy_iadk0,dy_jdik0
328C
329 END MODULE imp_dyna
330!||====================================================================
331!|| imp_monv ../engine/share/modules/impbufdef_mod.F
332!||--- called by ------------------------------------------------------
333!|| id_mvini ../engine/source/airbag/monv_imp0.F
334!|| monv_diag ../engine/source/airbag/monv_imp0.F
335!|| monv_fvl ../engine/source/airbag/monv_imp0.F
336!|| monv_m3 ../engine/source/airbag/monv_imp0.F
337!|| monv_prem ../engine/source/airbag/monv_imp0.F
338!|| mv_matv ../engine/source/airbag/monv_imp0.F
339!|| recu_kdis ../engine/source/airbag/monv_imp0.F
340!||====================================================================
341 MODULE imp_monv
342#include "my_real.inc"
345C int de taille NUMN_MV :noeuds locales de mv
346 INTEGER, DIMENSION(:), ALLOCATABLE :: in_mv
347C int IDDL de taille 3*NUMN_MV,6*(NRB_FR ,4*NI2_FR)
348 INTEGER, DIMENSION(:,:), ALLOCATABLE :: id_mv,id_mvm,id_mvm4
349 INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: id_mvm2,id_mvm3
350C int de taille NI2_MV,NRB_MV :------
351 INTEGER, DIMENSION(:,:), ALLOCATABLE :: ii2_mv,irb_mv,irbe2_mv
352 INTEGER, DIMENSION(:), ALLOCATABLE :: irbe3_mv
353C K_DIAG reels de taille (3,NUMN_MV)
354 my_real, DIMENSION(:,:),ALLOCATABLE :: diag_mv
355C K_DIAG reels de taille (6,NRB_MV)
356 my_real, DIMENSION(:,:),ALLOCATABLE :: diag_mvm,diag_mvm4
357C K_DIAG reels de taille (6,4,NI2_MV)
358 my_real, DIMENSION(:,:,:),ALLOCATABLE :: diag_mvm2
359 my_real, DIMENSION(:,:,:),ALLOCATABLE :: diag_mvm3
360C int (3,NBC_MV),(2,NFX_MV),(NRW_MV)
361 INTEGER, DIMENSION(:,:), ALLOCATABLE :: ibc_mv,ifx_mv
362 INTEGER, DIMENSION(:), ALLOCATABLE :: irw_mv,ispc_mv
363 my_real, DIMENSION(:), ALLOCATABLE :: fcdi_mv,mcdi_mv
364C
365 END MODULE imp_monv
366!||====================================================================
367!|| imp_rwl ../engine/share/modules/impbufdef_mod.F
368!||--- called by ------------------------------------------------------
369!|| diag_int ../engine/source/mpi/implicit/imp_fri.F
370!|| dim_kinkn ../engine/source/implicit/imp_int_k.F
371!|| fr_u2dd ../engine/source/mpi/implicit/imp_fri.F
372!|| fv_rwl ../engine/source/constraints/general/rwall/srw_imp.F
373!|| fv_rwl0 ../engine/source/constraints/general/rwall/srw_imp.F
374!|| fv_rwlr0 ../engine/source/constraints/general/rwall/srw_imp.F
375!|| imp3_a2b ../engine/source/airbag/monv_imp0.F
376!|| imp3_u2x ../engine/source/airbag/monv_imp0.F
377!|| ind_kinefr ../engine/source/mpi/implicit/imp_fri.F
378!|| ind_kinfrk ../engine/source/mpi/implicit/imp_fri.F
379!|| ini_kinkn ../engine/source/implicit/imp_int_k.F
380!|| monv_fvl ../engine/source/airbag/monv_imp0.F
381!|| rwl_impd ../engine/source/constraints/general/rwall/srw_imp.F
382!|| upd_fr ../engine/source/mpi/implicit/imp_fri.F
383!|| upd_kml ../engine/source/mpi/implicit/imp_fri.F
384!|| upd_ksl ../engine/source/mpi/implicit/imp_fri.F
385!|| updk_mv ../engine/source/airbag/monv_imp0.F
386!||====================================================================
387 MODULE imp_rwl
388#include "my_real.inc"
389 INTEGER n_rwl
390C tableau de int de taille N_RWL :noeuds secnds de sliding RW
391 INTEGER, DIMENSION(:), ALLOCATABLE :: in_rwl
392C tableau de Direction normale reels de taille (3,N_RWL)
393 my_real, DIMENSION(:,:),ALLOCATABLE :: nor_rwl
394C
395 END MODULE imp_rwl
396!||====================================================================
397!|| imp_lintf ../engine/share/modules/impbufdef_mod.F
398!||--- called by ------------------------------------------------------
399!|| diag_kif ../engine/source/implicit/imp_solv.F
400!|| imp_solv ../engine/source/implicit/imp_solv.F
401!|| ini_kif ../engine/source/implicit/imp_solv.F
402!|| matv_kif ../engine/source/implicit/imp_solv.F
403!|| save_kif ../engine/source/implicit/imp_solv.F
404!||====================================================================
406#include "my_real.inc"
407 INTEGER nddlif,nzif
408C tableau de int de la [k] interface
409 INTEGER, DIMENSION(:), ALLOCATABLE :: iadif,jdiif,iftok
410C tableau de reels de la [k] interface
411 my_real, DIMENSION(:),ALLOCATABLE :: diag_if,lt_if
412C
413 END MODULE imp_lintf
414!||====================================================================
415!|| imp_rest ../engine/share/modules/impbufdef_mod.F
416!||--- called by ------------------------------------------------------
417!|| imp_trans ../engine/source/output/restart/wrrest.F
418!|| imp_trans0 ../engine/source/output/restart/wrrest.F
419!|| imprrest ../engine/source/output/restart/rdresb.F
420!|| impwrest ../engine/source/output/restart/wrrest.F
421!||====================================================================
422 MODULE imp_rest
423#include "my_real.inc"
424C tableau de reels de R-file
425 my_real, DIMENSION(:),ALLOCATABLE :: imp_rr
426C
427 END MODULE imp_rest
428C
429!||====================================================================
430!|| imp_ppat ../engine/share/modules/impbufdef_mod.F
431!||--- called by ------------------------------------------------------
432!|| dim_span ../engine/source/implicit/ind_glob_k.F
433!|| fil_span0 ../engine/source/implicit/ind_glob_k.F
434!|| fil_span1 ../engine/source/implicit/ind_glob_k.F
435!|| ind_span ../engine/source/implicit/ind_glob_k.F
436!||====================================================================
437 MODULE imp_ppat
438C tableau de int de pre-filtrage
439 INTEGER, DIMENSION(:),ALLOCATABLE :: pre_fpat
440C
441 END MODULE imp_ppat
442!||====================================================================
443!|| imp_qstat ../engine/share/modules/impbufdef_mod.F
444!||--- called by ------------------------------------------------------
445!|| deallocm_imp ../engine/source/implicit/imp_solv.F
446!|| dis_cp ../engine/source/implicit/imp_solv.F
447!|| qstat_end ../engine/source/implicit/imp_dyna.F
448!|| qstat_ini ../engine/source/implicit/imp_dyna.F
449!|| qstat_it ../engine/source/implicit/imp_dyna.F
450!||====================================================================
452C
453#include "my_real.inc"
454C
455C tableau de travail : linear quasi-static (iterative)----
456 my_real, DIMENSION(:), ALLOCATABLE :: qs_u,qs_d
457C tableau de travail : D_n-1 used for Gravity case
458 my_real, DIMENSION(:), ALLOCATABLE :: d_n_1,dr_n_1
459C
460 END MODULE imp_qstat
461!||====================================================================
462!|| imp_kbcs ../engine/share/modules/impbufdef_mod.F
463!||--- called by ------------------------------------------------------
464!|| deallocm_imp ../engine/source/implicit/imp_solv.F
465!|| freimpl ../engine/source/input/freimpl.F
466!|| imp_init ../engine/source/implicit/imp_init.F
467!|| imp_mumps1 ../engine/source/implicit/imp_mumps.F
468!|| lecimpl ../engine/source/input/lectur.F
469!|| prout_buck ../engine/source/input/lectur.F
470!||====================================================================
471 MODULE imp_kbcs
472C tableau de travail de BCS-EXT
473 INTEGER mem_bcs
474 my_real, DIMENSION(:),ALLOCATABLE :: hold
476 my_real emin_b,emax_b,shift_b
477C
478 END MODULE imp_kbcs
479!||====================================================================
480!|| imp_knon ../engine/share/modules/impbufdef_mod.F
481!||--- called by ------------------------------------------------------
482!|| deallocm ../engine/source/implicit/imp_solv.F
483!|| int_matv ../engine/source/implicit/imp_int_k.F
484!|| int_matvp ../engine/source/implicit/imp_int_k.F
485!|| kin_knl ../engine/source/implicit/imp_int_k.F
486!|| recu_kdis0 ../engine/source/implicit/lin_solv.F
487!||====================================================================
488 MODULE imp_knon
489#include "my_real.inc"
492 INTEGER, DIMENSION(:), ALLOCATABLE :: in_kn
493 INTEGER, DIMENSION(:,:), ALLOCATABLE :: id_kn,id_knm,id_knm4
494 INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: id_knm2,id_knm3
495 INTEGER, DIMENSION(:,:), ALLOCATABLE :: ii2_kn,irb_kn,irbe2_kn
496 INTEGER, DIMENSION(:,:), ALLOCATABLE :: ibc_kn,ifx_kn
497 INTEGER, DIMENSION(:), ALLOCATABLE :: irw_kn,irbe3_kn,ispc_kn
498 my_real, DIMENSION(:), ALLOCATABLE :: fcdi_kn,mcdi_kn
499C
500 END MODULE imp_knon
501!||====================================================================
502!|| imp_aspc ../engine/share/modules/impbufdef_mod.F
503!||--- called by ------------------------------------------------------
504!|| bc_imp2 ../engine/source/constraints/general/bcs/bc_imp0.F
505!|| bc_impa ../engine/source/constraints/general/bcs/bc_imp0.F
506!|| bc_impr1 ../engine/source/constraints/general/bcs/bc_imp0.F
507!|| diag_int ../engine/source/mpi/implicit/imp_fri.F
508!|| dim_kinkn ../engine/source/implicit/imp_int_k.F
509!|| fr_u2dd ../engine/source/mpi/implicit/imp_fri.F
510!|| get_nspc ../engine/source/constraints/general/bcs/bc_imp0.F
511!|| imp3_a2b ../engine/source/airbag/monv_imp0.F
512!|| imp3_u2x ../engine/source/airbag/monv_imp0.F
513!|| imp_init ../engine/source/implicit/imp_init.F
514!|| ind_kinefr ../engine/source/mpi/implicit/imp_fri.F
515!|| ind_kinfrk ../engine/source/mpi/implicit/imp_fri.F
516!|| ini_kinkn ../engine/source/implicit/imp_int_k.F
517!|| kin_knl ../engine/source/implicit/imp_int_k.F
518!|| monv_fvl ../engine/source/airbag/monv_imp0.F
519!|| put_nspc ../engine/source/constraints/general/bcs/bc_imp0.F
520!|| upd_aspc0 ../engine/source/constraints/general/bcs/bc_imp0.F
521!|| upd_fr ../engine/source/mpi/implicit/imp_fri.F
522!|| upd_kml ../engine/source/mpi/implicit/imp_fri.F
523!|| upd_ksl ../engine/source/mpi/implicit/imp_fri.F
524!|| updk_mv ../engine/source/airbag/monv_imp0.F
525!||====================================================================
526 MODULE imp_aspc
527 INTEGER nspcl,nspcnt
528#include "my_real.inc"
529 INTEGER, DIMENSION(:),ALLOCATABLE :: in_spc,ic_spc
530 my_real, DIMENSION(:), ALLOCATABLE :: skew_spc
531C
532 END MODULE imp_aspc
533C
534!||====================================================================
535!|| imp_worki ../engine/share/modules/impbufdef_mod.F
536!||--- called by ------------------------------------------------------
537!|| imp_chkm ../engine/source/implicit/imp_solv.F
538!|| imp_solv ../engine/source/implicit/imp_solv.F
539!||====================================================================
541#include "my_real.inc"
542 INTEGER, DIMENSION(:),ALLOCATABLE :: iadi,jdii,itok
544 my_real,
545 . DIMENSION(:),ALLOCATABLE :: diag_i,lt_i,xi_c
546
547 END MODULE imp_worki
548C
549!||====================================================================
550!|| imp_workh ../engine/share/modules/impbufdef_mod.F
551!||--- called by ------------------------------------------------------
552!|| deallocm_imp ../engine/source/implicit/imp_solv.F
553!|| imp_pcgh ../engine/source/implicit/imp_pcg.F
554!|| imp_ppcgh ../engine/source/implicit/imp_pcg.F
555!|| ini_k0h ../engine/source/implicit/imp_solv.F
556!|| ini_kisc ../engine/source/implicit/lin_solv.F
557!|| lin_solv ../engine/source/implicit/lin_solv.F
558!|| lin_solvh0 ../engine/source/implicit/lin_solv.F
559!|| lin_solvh1 ../engine/source/implicit/lin_solv.F
560!|| lin_solvhm ../engine/source/implicit/lin_solv.F
561!|| lin_solvih2 ../engine/source/implicit/lin_solv.F
562!|| mav_liuh ../engine/source/implicit/produt_v.F
563!|| mav_lu_h ../engine/source/implicit/produt_v.F
564!|| mav_lui_h ../engine/source/implicit/produt_v.F
565!|| mmav_lth ../engine/source/implicit/produt_v.F
566!|| prec5hc_solv ../engine/source/implicit/prec_solv.F
567!|| produt_uh ../engine/source/implicit/produt_v.F
568!|| produt_uh2 ../engine/source/implicit/produt_v.F
569!|| produt_vmh ../engine/source/implicit/produt_v.F
570!||====================================================================
572#include "my_real.inc"
574 my_real k_lamda0,k_lamda1
575 my_real,
576 . DIMENSION(:),ALLOCATABLE :: diag_t,l_u,l_f0
577 my_real,
578 . DIMENSION(:),ALLOCATABLE :: pcg_w1,pcg_w2,pcg_w3
579 my_real,
580 . DIMENSION(:),ALLOCATABLE :: tmp_w1,tmp_w2
581#if defined knf
582!dec$ attributes offload:mic :: IADK0,JDIK0,IADM0,JDIM0
583#endif
584 INTEGER, DIMENSION(:),ALLOCATABLE :: iadk0,jdik0,iadm0,jdim0
585#if defined knf
586!dec$ attributes offload:mic :: IADI0,JDII0
587#endif
588 INTEGER, DIMENSION(:),ALLOCATABLE :: iadi0,jdii0
589#if defined knf
590!dec$ attributes offload:mic :: LT_K0,LT_M0,LT_I0
591#endif
592 my_real,
593 . DIMENSION(:),ALLOCATABLE :: lt_k0,lt_m0,lt_i0
594
595 END MODULE imp_workh
596C
597!||====================================================================
598!|| imp_workg ../engine/share/modules/impbufdef_mod.F
599!||--- called by ------------------------------------------------------
600!|| imp_buck ../engine/source/implicit/imp_buck.F
601!||====================================================================
603#include "my_real.inc"
604 INTEGER iprmes_el(30)
605 my_real,
606 . DIMENSION(:),ALLOCATABLE :: diag_kg,lt_kg
607
608 END MODULE imp_workg
609C
610!||====================================================================
611!|| imp_fvbcl ../engine/share/modules/impbufdef_mod.F
612!||--- called by ------------------------------------------------------
613!|| bc_impr1 ../engine/source/constraints/general/bcs/bc_imp0.F
614!|| fv_imp1 ../engine/source/constraints/general/impvel/fv_imp0.F
615!|| fvbc_allo ../engine/source/constraints/general/impvel/fv_imp0.F
616!|| fvbc_deallo ../engine/source/constraints/general/impvel/fv_imp0.F
617!|| recu_ul ../engine/source/constraints/general/impvel/fv_imp0.F
618!|| recukin ../engine/source/implicit/recudis.F
619!|| upd_glob_k ../engine/source/implicit/upd_glob_k.F
620!||====================================================================
622#include "my_real.inc"
624 INTEGER, DIMENSION(:),ALLOCATABLE :: ict_1,icr_1,ikud_1
625 my_real,
626 . DIMENSION(:),ALLOCATABLE :: bkud_1,fvbcudl
627
628 END MODULE imp_fvbcl
629C
630!||====================================================================
631!|| imp_pcg_proj ../engine/share/modules/impbufdef_mod.F
632!||--- called by ------------------------------------------------------
633!|| deallocm_imp ../engine/source/implicit/imp_solv.F
634!|| freimpl ../engine/source/input/freimpl.F
635!|| imp_inisi ../engine/source/implicit/imp_pcg.F
636!|| imp_inist ../engine/source/implicit/imp_pcg.F
637!|| imp_inix ../engine/source/implicit/imp_pcg.F
638!|| imp_ppcgh ../engine/source/implicit/imp_pcg.F
639!|| imp_pro_p ../engine/source/implicit/imp_pcg.F
640!|| imp_solv ../engine/source/implicit/imp_solv.F
641!|| imp_updst ../engine/source/implicit/imp_pcg.F
642!|| imp_updv2 ../engine/source/implicit/imp_pcg.F
643!|| ini_k0h ../engine/source/implicit/imp_solv.F
644!|| lecimpl ../engine/source/input/lectur.F
645!||====================================================================
647#include "my_real.inc"
648 INTEGER m_vs,ncg_run
649 my_real
650 . k_tmp(2,2),m_tmp(2,2)
651 my_real,
652 . DIMENSION(:,:),ALLOCATABLE :: proj_s,proj_t,proj_k
653 my_real,
654 . DIMENSION(:),ALLOCATABLE :: proj_la_1,proj_v,proj_w
655
656 END MODULE imp_pcg_proj
657C
658!||====================================================================
659!|| imp_ktan ../engine/share/modules/impbufdef_mod.F
660!||--- called by ------------------------------------------------------
661!|| cmatch3 ../engine/source/elements/shell/coqueba/cmatc3.F
662!|| cmatip3 ../engine/source/elements/shell/coqueba/cmatc3.F
663!|| etfac_ini ../engine/source/implicit/imp_init.F
664!|| get_etfac_s ../engine/source/elements/solid/solide8z/get_etfac_s.F
665!|| gethkt3 ../engine/source/elements/solid/solide8z/gethkt3.F
666!|| iktmat_ini ../engine/source/implicit/imp_init.F
667!|| ktbuf_ini ../engine/source/implicit/imp_init.F
668!|| mmats ../engine/source/elements/solid/solide8z/mmats.F
669!|| put_etfac ../engine/source/elements/solid/solide8z/put_etfac.F
670!|| putsignor3 ../engine/source/elements/solid/solide8z/putsignor3.F
671!|| putsignorc3 ../engine/source/elements/shell/coqueba/cmatc3.F
672!|| sktcons2 ../engine/source/elements/solid/solide8z/sktcons2.F
673!||--- uses -----------------------------------------------------
674!|| imp_ktan_def ../engine/share/modules/impbufdef_mod.F
675!||====================================================================
676 MODULE imp_ktan
677
678 USE imp_ktan_def
679
680 TYPE(ktbuf_struct_),TARGET,DIMENSION(:),ALLOCATABLE :: ktbuf_str
681 END MODULE imp_ktan
682!||====================================================================
683!|| imp_spbrm ../engine/share/modules/impbufdef_mod.F
684!||--- called by ------------------------------------------------------
685!|| deallocm_imp ../engine/source/implicit/imp_solv.F
686!|| freimpl ../engine/source/input/freimpl.F
687!|| lecimpl ../engine/source/input/lectur.F
688!|| spb_ieref3 ../engine/source/implicit/imp_solv.F
689!|| spb_ieref_bc ../engine/source/implicit/imp_solv.F
690!|| spb_ref_nds ../engine/source/implicit/imp_solv.F
691!|| spb_rm_rig ../engine/source/implicit/imp_solv.F
692!|| spbrm_pre ../engine/source/implicit/imp_solv.F
693!|| spmd_e_ref ../engine/source/mpi/implicit/imp_spmd.F
694!|| spmd_n_ref ../engine/source/mpi/implicit/imp_spmd.F
695!||====================================================================
697
699 INTEGER, DIMENSION(:),ALLOCATABLE :: ibc_b
700 INTEGER, DIMENSION(:),ALLOCATABLE :: ie_bc4,ie_bc3
701C------introduced due to SPMD-----
702 my_real
703 . x_ref(3,4),d_ref(3,4),rlskew(9)
704C-----E_REF(4)4N of elem_ref, NBC_B ,IBC_B(NBC_B): node_id w/ BC;
705C------IE_BC(NE_BC) Elem_id which has the BC nodes
706C-------N_SEG=3 3N seg, 0 : no ref; ----
707
708 END MODULE imp_spbrm
709C
710!||====================================================================
711!|| imp_frk ../engine/share/modules/impbufdef_mod.F
712!||--- called by ------------------------------------------------------
713!|| dim_fr_k ../engine/source/mpi/implicit/imp_fri.F
714!|| dim_nrmax ../engine/source/mpi/implicit/imp_fri.F
715!|| fr_dlft ../engine/source/mpi/implicit/imp_fri.F
716!|| get_ikin2g ../engine/source/mpi/implicit/imp_fri.F
717!|| getnddli_g ../engine/source/mpi/implicit/imp_fri.F
718!|| imp_pcgh ../engine/source/implicit/imp_pcg.F
719!|| ind_fr_k ../engine/source/mpi/implicit/imp_fri.F
720!|| ind_fr_k0 ../engine/source/mpi/implicit/imp_fri.F
721!|| ind_kine_kp ../engine/source/mpi/implicit/imp_fri.F
722!|| ind_nrfr ../engine/source/mpi/implicit/imp_fri.F
723!|| ini_fr_k ../engine/source/mpi/implicit/imp_fri.F
724!|| kin_nrmax ../engine/source/mpi/implicit/imp_fri.F
725!|| kin_nrmax0 ../engine/source/mpi/implicit/imp_fri.F
726!|| nddli_frb ../engine/source/mpi/implicit/imp_fri.F
727!|| pr_deb ../engine/source/implicit/imp_solv.F
728!|| pr_matrix ../engine/source/implicit/imp_solv.F
729!|| pr_solnfo ../engine/source/implicit/imp_solv.F
730!|| set_ikin2g ../engine/source/mpi/implicit/imp_fri.F
731!|| spc_fr_k ../engine/source/mpi/implicit/imp_fri.F
732!|| spmd_inf_g ../engine/source/mpi/implicit/imp_spmd.F
733!|| spmd_max_iv ../engine/source/mpi/implicit/imp_spmd.F
734!|| spmd_sumf_k ../engine/source/mpi/implicit/imp_spmd.F
735!|| spmd_sumf_v ../engine/source/mpi/implicit/imp_spmd.F
736!|| spmd_sumfc_v ../engine/source/mpi/implicit/imp_spmd.F
737!|| upd_fr_k ../engine/source/mpi/implicit/imp_fri.F
738!|| zero_ikin2g ../engine/source/mpi/implicit/imp_fri.F
739!||====================================================================
740 MODULE imp_frk
741C
743C NDDLFRB :nb de noeuds fr. partages par au moins 3 proc,----
744C 50d1m DDLP0 :dernier ddl de noeuds fr.avec procs precedents ----
745C 50d1m DDLP1 :premier ddl de noeuds fr.avec procs suivants ----
747C
748C tableau de int de : connectivite des noeuds FR. locaux----
749 INTEGER, DIMENSION(:), ALLOCATABLE :: ifrloc
750 INTEGER, DIMENSION(:), ALLOCATABLE :: iad_rl,fr_icol
751C tableau de int de taille NKINE indice loc->global: ----
752 INTEGER, DIMENSION(:), ALLOCATABLE :: ikin2g
753C tableau de int de : matrice locale des noeuds FR. locaux par proc----
754 INTEGER, DIMENSION(:), ALLOCATABLE :: nd_fr,iadfr,jdifr,iddlfr
755#if defined knf
756!dec$ attributes offload:mic :: IFR2K
757#endif
758 INTEGER, DIMENSION(:), ALLOCATABLE :: ifr2k,jfr2k
759C
760 END MODULE imp_frk
761C
#define my_real
Definition cppsort.cpp:32
if(complex_arithmetic) id
integer, dimension(:), allocatable in_spc
integer, dimension(:), allocatable ic_spc
integer nspcl
integer nspcnt
integer iactb
integer n_bfgs
integer, dimension(:), allocatable dy_iadk0
integer, dimension(:), allocatable dy_jdik0
integer ndfrmax
integer nrmax
integer, dimension(:), allocatable fr_icol
integer nddlfrb1
integer, dimension(:), allocatable ifrloc
integer, dimension(:), allocatable ifr2k
integer, dimension(:), allocatable ikin2g
integer len_v
integer n_frnn
integer, dimension(:), allocatable iadfr
integer, dimension(:), allocatable iddlfr
integer, dimension(:), allocatable jfr2k
integer, dimension(:), allocatable jdifr
integer ddlp0
integer len_k
integer, dimension(:), allocatable iad_rl
integer, dimension(:), allocatable nd_fr
integer nzkfr
integer nddlfr
integer ddlp1
integer nddlfrb
integer nfvbcl
integer, dimension(:), allocatable icr_1
integer nkud_l
integer, dimension(:), allocatable ikud_1
integer, dimension(:), allocatable ict_1
integer nkud_1
integer maxset_b
integer lmemn
integer b_mcore
integer msg_lvl
integer mem_bcs
integer b_order
integer msgl_b
integer nbc_kn
integer rkn_max
integer numn_kn
integer nrbe3_kn
integer, dimension(:,:), allocatable id_knm4
integer, dimension(:,:), allocatable irb_kn
integer, dimension(:,:,:), allocatable id_knm2
integer, dimension(:), allocatable ispc_kn
integer, dimension(:), allocatable irw_kn
integer, dimension(:,:), allocatable id_kn
integer, dimension(:), allocatable in_kn
integer, dimension(:,:), allocatable ibc_kn
integer, dimension(:,:), allocatable irbe2_kn
integer, dimension(:,:), allocatable ii2_kn
integer, dimension(:,:), allocatable id_knm
integer nspc_kn
integer ni2_kn
integer nrw_kn
integer, dimension(:,:,:), allocatable id_knm3
integer nfx_kn
integer nrbe2_kn
integer, dimension(:,:), allocatable ifx_kn
integer, dimension(:), allocatable irbe3_kn
integer nrb_kn
type(ktbuf_struct_), dimension(:), allocatable, target ktbuf_str
integer, dimension(:), allocatable jdiif
integer nddlif
integer, dimension(:), allocatable iadif
integer nzif
integer, dimension(:), allocatable iftok
integer ni2_mv
integer, dimension(:), allocatable irw_mv
integer numn_mv
integer nspc_mv
integer r3m_max
integer, dimension(:), allocatable irbe3_mv
integer, dimension(:,:), allocatable id_mvm4
integer, dimension(:,:), allocatable irbe2_mv
integer nrw_mv
integer nnmax_mv
integer nfx_mv
integer, dimension(:,:), allocatable ii2_mv
integer, dimension(:), allocatable in_mv
integer, dimension(:,:), allocatable ifx_mv
integer nbc_mv
integer nrb_mv
integer, dimension(:,:,:), allocatable id_mvm2
integer nrbe2_mv
integer, dimension(:,:,:), allocatable id_mvm3
integer, dimension(:), allocatable ispc_mv
integer, dimension(:,:), allocatable id_mv
integer nrbe3_mv
integer, dimension(:,:), allocatable irb_mv
integer, dimension(:,:), allocatable ibc_mv
integer, dimension(:,:), allocatable id_mvm
integer, dimension(:), allocatable pre_fpat
integer, dimension(:), allocatable in_rwl
integer n_rwl
integer ilskew
integer ne_bc3
integer lskew_g
integer ne_bc4
integer, dimension(6) ikce
integer, dimension(:), allocatable ie_bc4
integer, dimension(:), allocatable ibc_b
integer nbc_b
integer n_seg
integer, dimension(4) e_ref
integer, dimension(:), allocatable ie_bc3
integer, dimension(30) iprmes_el
integer, dimension(:), allocatable jdik0
integer, dimension(:), allocatable iadi0
integer, dimension(:), allocatable jdim0
integer, dimension(:), allocatable jdii0
integer, dimension(:), allocatable iadk0
integer, dimension(:), allocatable iadm0
integer w_maxl
integer istop_h
integer nddli
integer, dimension(:), allocatable iadi
integer, dimension(:), allocatable itok
integer nsl
integer nnzi
integer nsrem
integer, dimension(:), allocatable jdii
integer iconta
integer s_elbuf_c
integer s_bufmat_c
integer s_inbuf_c
integer s_bufin_c
integer s_indsubt