OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
mating.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!|| mating ../starter/source/materials/mat_share/mating.F
25!||--- called by ------------------------------------------------------
26!|| matini ../starter/source/materials/mat_share/matini.F
27!||====================================================================
28 SUBROUTINE mating(PM ,VOL ,OFF ,EINT ,RHO ,
29 . SIG ,IX ,NIX ,SIGI ,EPSP,
30 . NSIG ,MAT ,NUMS ,PT ,NEL ,
31 . FILL ,TEMP,TEMPEL )
32C-----------------------------------------------
33C I m p l i c i t T y p e s
34C-----------------------------------------------
35#include "implicit_f.inc"
36C-----------------------------------------------
37C C o m m o n B l o c k s
38C-----------------------------------------------
39#include "vect01_c.inc"
40#include "com01_c.inc"
41#include "com04_c.inc"
42#include "param_c.inc"
43#include "scry_c.inc"
44#include "sphcom.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER NIX, NSIG, NUMS, NEL
49 INTEGER IX(NIX,*),PT(*),MAT(*)
50 my_real :: PM(NPROPM,*), SIG(NEL,6), SIGI(NSIG,*)
51 my_real, DIMENSION(NEL) :: vol,off,eint,rho,epsp,fill
52 my_real, DIMENSION(NEL) :: temp,tempel
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56 INTEGER I,J,II,JJ,N,MA,IFLAGINI
57C=======================================================================
58 DO I=lft,llt
59 iflagini = 0
60 ma=mat(i)
61 off(i) =one
62 IF(ma == 0)cycle
63 eint(i)=pm(23,ma)
64 rho(i) =pm(89,ma)
65 IF (tempel(i) > zero) THEN
66 temp(i) = tempel(i)
67 ELSE
68 temp(i) = pm(79,ma)
69 END IF
70C-----------------------------
71 IF (isigi == 0) THEN
72C-----------------------------
73 sig(i,1)=-pm(104,ma)
74 sig(i,2)=-pm(104,ma)
75 sig(i,3)=-pm(104,ma)
76C
77 IF (jlag/=0 .AND. jsph == 0) THEN
78 vol(i) = vol(i) * ( rho(i) / pm(1,ma) )
79 ENDIF
80 IF (jeul+jale /= 0 .AND. pm(1,ma)/=zero) THEN
81 eint(i) = eint(i) * rho(i) / pm(1,ma)
82 ENDIF
83C
84 fill(i)=one
85C-----------------------------
86 ELSE ! CONTRAINTES INITIALES
87C-----------------------------
88 IF (abs(isigi)/=3.AND.abs(isigi)/=4.AND.abs(isigi)/=5) THEN
89 ii = i+nft
90 n = nint(sigi(7,ii))
91 IF(n == ix(nix,ii))THEN
92 jj = ii
93 iflagini = 1
94 ELSE
95 IF(jsph == 0)THEN
96 DO j = 1,max(numsol+numquad,numels+numelq)
97 jj= j
98 n = nint(sigi(7,j))
99 IF(n==0)GOTO 200
100 IF(n==ix(nix,ii))THEN
101 iflagini = 1
102 GOTO 60
103 ENDIF
104 ENDDO
105 ELSE
106 DO j = 1,numsph
107 jj= j
108 n = nint(sigi(7,j))
109 IF(n==0)GOTO 200
110 IF(n==ix(nix,ii))THEN
111 iflagini = 1
112 GOTO 60
113 ENDIF
114 ENDDO
115 ENDIF
116 GOTO 200
117 60 CONTINUE
118 ENDIF
119 ELSE
120 ii=nft+i
121 n =ix(nix,ii)
122 jj=pt(ii)
123 IF (jj == 0)GOTO 200
124 iflagini = 1
125 END IF
126C-----------
127 IF (iflagini == 1)THEN
128 sig(i,1)=sigi(1,jj)
129 sig(i,2)=sigi(2,jj)
130 sig(i,3)=sigi(3,jj)
131 sig(i,4)=sigi(4,jj)
132 sig(i,5)=sigi(5,jj)
133 sig(i,6)=sigi(6,jj)
134 IF (isigi == 3.OR.isigi == 4.OR.isigi == 5) THEN
135 IF(sigi(8,jj)/=zero) THEN
136 IF(jlag/=0.AND.jsph == 0)THEN
137 vol(i) = sigi(8,jj)*vol(i) / pm(1,ma)
138 rho(i) = sigi(8,jj)
139 ELSE
140 rho(i) = sigi(8,jj)
141 ENDIF
142 ELSEIF (jlag/=0.AND.jsph == 0) THEN
143 vol(i) = vol(i) * rho(i) / pm(1,ma)
144 ENDIF
145C EPSP NON UTILISE DANS MAT TYPE 1 ET ECRASE PAR EINT
146 IF (sigi(10,jj)/=zero) epsp(i) = sigi(10,jj)
147 IF (sigi( 9,jj)/=zero) eint(i) = sigi(9,jj)
148C TAUX DE REMPLISSAGE
149 IF(sigi(11,jj)/=zero) fill(i)=sigi(11,jj)
150 ENDIF
151 ENDIF
152 200 CONTINUE
153 ENDIF
154 ENDDO
155C-----------
156 RETURN
157 END
#define max(a, b)
Definition macros.h:21
subroutine mating(pm, vol, off, eint, rho, sig, ix, nix, sigi, epsp, nsig, mat, nums, pt, nel, fill, temp, tempel)
Definition mating.F:32