OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
w_tabmat_prop.F File Reference
#include "implicit_f.inc"
#include "param_c.inc"
#include "com01_c.inc"
#include "com04_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine w_tabmat_prop (iparg, ixc, ixtg, ixs, proc, ngroup_l, poin_part_shell, poin_part_tri, poin_part_sol, mid_pid_shell, mid_pid_tri, mid_pid_sol, ipartc, ipartg, iparts)

Function/Subroutine Documentation

◆ w_tabmat_prop()

subroutine w_tabmat_prop ( integer, dimension(nparg,*) iparg,
integer, dimension(nixc,numelc) ixc,
integer, dimension(nixtg,numeltg) ixtg,
integer, dimension(nixs,numels) ixs,
integer proc,
integer ngroup_l,
integer, dimension(2,npart), intent(in) poin_part_shell,
integer, dimension(2,npart), intent(in) poin_part_tri,
integer, dimension(2,npart,7), intent(in) poin_part_sol,
type(mid_pid_type), dimension(nummat), intent(in) mid_pid_shell,
type(mid_pid_type), dimension(nummat), intent(in) mid_pid_tri,
type(mid_pid_type), dimension(nummat,7), intent(in) mid_pid_sol,
integer, dimension(*), intent(in) ipartc,
integer, dimension(*), intent(in) ipartg,
integer, dimension(*), intent(in) iparts )

Definition at line 32 of file w_tabmat_prop.F.

36 USE mid_pid_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 "param_c.inc"
45#include "com01_c.inc"
46#include "com04_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 INTEGER, DIMENSION(*), INTENT(IN) :: IPARTC,IPARTG,IPARTS
51 INTEGER, DIMENSION(2,NPART), INTENT(IN) :: POIN_PART_SHELL,POIN_PART_TRI
52 INTEGER, DIMENSION(2,NPART,7), INTENT(IN) :: POIN_PART_SOL
53 TYPE(MID_PID_TYPE), DIMENSION(NUMMAT), INTENT(IN) :: MID_PID_SHELL,MID_PID_TRI
54 TYPE(MID_PID_TYPE), DIMENSION(NUMMAT,7), INTENT(IN) :: MID_PID_SOL
55 INTEGER IPARG(NPARG,*)
56 INTEGER IXC(NIXC,NUMELC),IXTG(NIXTG,NUMELTG),IXS(NIXS,NUMELS)
57 INTEGER NGROUP_L,PROC
58C-----------------------------------------------
59C L o c a l V a r i a b l e s
60C-----------------------------------------------
61 my_real tab_mat(ngroup_l)
62 INTEGER NG_L,NG,P,MID,PID,NFT,ISOL,INDI,ITY,ILAW
63 INTEGER :: POIN_ELM_TYP,POIN_MID,POIN_PID,POIN_PART
64C-----------------------------------------------
65! write the element cost
66! for LAW = 0, write ZERO (because the array MID_PID_[X] does not exist)
67 ng_l=0
68 tab_mat(1:ngroup_l)=zero
69 DO ng=1,ngroup
70 p = iparg(32,ng)
71
72 IF(p==proc)THEN
73 ng_l = ng_l+1
74 nft = iparg(3,ng)+1
75 ity = iparg(5,ng)
76 ilaw = iparg(1,ng)
77
78 IF(ity==1) THEN
79 mid = ixs(1,nft)
80 pid = ixs(10,nft)
81 isol = iparg(28,ng)
82
83 IF(isol==4) THEN
84 indi = 6
85 poin_elm_typ = 6
86 ELSEIF(isol==6) THEN
87 indi = 5
88 poin_elm_typ = 5
89 ELSEIF(isol==8) THEN
90 indi = 1
91 poin_elm_typ = 7
92 ELSEIF(isol==10) THEN
93 indi = 2
94 poin_elm_typ = 2
95 ELSEIF(isol==16) THEN
96 indi = 3
97 poin_elm_typ = 3
98 ELSEIF(isol==20) THEN
99 indi = 4
100 poin_elm_typ = 4
101 ELSE
102 indi = 7
103 poin_elm_typ = 1
104 ENDIF
105
106 indi = indi+2
107 poin_part = iparts(nft)
108 poin_mid = poin_part_sol(1,poin_part,poin_elm_typ)
109 poin_pid = poin_part_sol(2,poin_part,poin_elm_typ)
110 IF(ilaw/=0) THEN
111 tab_mat(ng_l) = mid_pid_sol(poin_mid,poin_elm_typ)%COST1D(poin_pid)
112 ELSE
113 tab_mat(ng_l) = zero
114 ENDIF
115
116 ELSEIF(ity==3) THEN
117 mid = ixc(1,nft)
118 pid = ixc(6,nft)
119 poin_part = ipartc(nft)
120 poin_mid = poin_part_shell(1,poin_part)
121 poin_pid = poin_part_shell(2,poin_part)
122 IF(ilaw/=0) THEN
123 tab_mat(ng_l)= mid_pid_shell(poin_mid)%COST1D(poin_pid)
124 ELSE
125 tab_mat(ng_l) = zero
126 ENDIF
127
128 ELSEIF(ity==7) THEN
129 mid = ixtg(1,nft)
130 pid = ixtg(5,nft)
131 poin_part = ipartg(nft)
132 poin_mid = poin_part_tri(1,poin_part)
133 poin_pid = poin_part_tri(2,poin_part)
134 IF(ilaw/=0) THEN
135 tab_mat(ng_l)= mid_pid_tri(poin_mid)%COST1D(poin_pid)
136 ELSE
137 tab_mat(ng_l) = zero
138 ENDIF
139 ENDIF
140 ENDIF
141 ENDDO
142
143 CALL write_db(tab_mat,ngroup_l)
144C-----------------------------------------------
#define my_real
Definition cppsort.cpp:32
subroutine write_db(a, n)
Definition write_db.F:140