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

Go to the source code of this file.

Functions/Subroutines

subroutine desacti (ixs, ixq, ixc, ixp, ixt, ixr, ixtg, iparg, iactiv, nsensor, sensor_tab, fsky, x, elbuf_tab, ibcv, fconv, ibcr, fradia, igroups, factiv, temp, mcp, pm, mcp_off, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, glob_therm)

Function/Subroutine Documentation

◆ desacti()

subroutine desacti ( integer, dimension(nixs,*) ixs,
integer, dimension(nixq,*) ixq,
integer, dimension(nixc,*) ixc,
integer, dimension(nixp,*) ixp,
integer, dimension(nixt,*) ixt,
integer, dimension(nixr,*) ixr,
integer, dimension(nixtg,*) ixtg,
integer, dimension(nparg,*) iparg,
integer, dimension(lactiv,*) iactiv,
integer, intent(in) nsensor,
type (sensor_str_), dimension(nsensor), intent(in) sensor_tab,
fsky,
x,
type(elbuf_struct_), dimension(ngroup), target elbuf_tab,
integer, dimension(*) ibcv,
fconv,
integer, dimension(*) ibcr,
fradia,
integer, dimension(*) igroups,
factiv,
temp,
mcp,
pm,
mcp_off,
type (group_), dimension(ngrbric) igrbric,
type (group_), dimension(ngrquad) igrquad,
type (group_), dimension(ngrshel) igrsh4n,
type (group_), dimension(ngrsh3n) igrsh3n,
type (group_), dimension(ngrtrus) igrtruss,
type (group_), dimension(ngrbeam) igrbeam,
type (group_), dimension(ngrspri) igrspring,
type (glob_therm_), intent(inout) glob_therm )

Definition at line 37 of file desacti.F.

44C-----------------------------------------------
45C M o d u l e s
46C-----------------------------------------------
47 USE elbufdef_mod
48 USE groupdef_mod
49 USE sensor_mod
50 use glob_therm_mod
51C-----------------------------------------------
52C I m p l i c i t T y p e s
53C-----------------------------------------------
54#include "implicit_f.inc"
55C-----------------------------------------------
56C C o m m o n B l o c k s
57C-----------------------------------------------
58#include "param_c.inc"
59#include "com01_c.inc"
60#include "com04_c.inc"
61#include "com08_c.inc"
62#include "parit_c.inc"
63C-----------------------------------------------
64C D u m m y A r g u m e n t s
65C-----------------------------------------------
66 INTEGER ,INTENT(IN) :: NSENSOR
67 INTEGER IACTIV(LACTIV,*),IPARG(NPARG,*),
68 . IXS(NIXS,*), IXQ(NIXQ,*), IXC(NIXC,*),
69 . IXT(NIXT,*),IXP(NIXP,*), IXR(NIXR,*), IXTG(NIXTG,*)
70 INTEGER IBCV(*), IBCR(*), IGROUPS(*)
71 my_real fsky(*), fconv(*), fradia(*)
72 my_real x(3,*), factiv(lractiv,*), temp(*), mcp(*), pm(npropm,*)
73 my_real mcp_off(*)
74 TYPE(ELBUF_STRUCT_), DIMENSION(NGROUP), TARGET :: ELBUF_TAB
75 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) ,INTENT(IN) :: SENSOR_TAB
76 type (glob_therm_) ,intent(inout) :: glob_therm
77C-----------------------------------------------
78 TYPE (GROUP_) , DIMENSION(NGRBRIC) :: IGRBRIC
79 TYPE (GROUP_) , DIMENSION(NGRQUAD) :: IGRQUAD
80 TYPE (GROUP_) , DIMENSION(NGRSHEL) :: IGRSH4N
81 TYPE (GROUP_) , DIMENSION(NGRSH3N) :: IGRSH3N
82 TYPE (GROUP_) , DIMENSION(NGRTRUS) :: IGRTRUSS
83 TYPE (GROUP_) , DIMENSION(NGRBEAM) :: IGRBEAM
84 TYPE (GROUP_) , DIMENSION(NGRSPRI) :: IGRSPRING
85C-----------------------------------------------
86C L o c a l V a r i a b l e s
87C-----------------------------------------------
88 INTEGER I,N,IFLAG,ISENS,IGSH,IGSH3,IGBR,IGQU,IGBM,IGTR,IGSP,OFFCHANGE
89 INTEGER ITHERM_FE
90 my_real startt, stopt
91C======================================================================|
92 offchange = 0
93 itherm_fe = glob_therm%ITHERM_FE
94!
95 DO n = 1,nactiv
96 isens = iactiv(2,n)
97 iflag = iactiv(1,n)
98 IF (iactiv(10,n) == 1) THEN
99 IF (isens > 0) THEN
100C----------------------------------------------------------------------
101C DESACTIVATION DES ELEMENTS
102C----------------------------------------------------------------------
103 IF (iflag == 1 .AND. tt > sensor_tab(isens)%TSTART) THEN
104 CALL eloff(ixs ,ixq ,ixc ,ixp ,ixt ,
105 . ixr ,ixtg ,iparg ,
106 . iactiv ,tt ,iflag ,n ,elbuf_tab,
107 . x ,temp ,mcp ,pm ,igroups ,
108 . mcp_off ,igrbric ,igrquad ,igrsh4n ,igrsh3n ,
109 . igrtruss,igrbeam ,igrspring,itherm_fe)
110
111 iactiv(1,n) = 0
112 offchange=1
113 IF (iparit /= 0) THEN
114 DO i=1,8*lsky
115 fsky(i)=zero
116 ENDDO
117 ENDIF
118C----------------------------------------------------------------------
119C ACTIVATION DES ELEMENTS
120C----------------------------------------------------------------------
121 ELSEIF (iflag == 0 .AND. tt <= sensor_tab(isens)%TSTART) THEN
122 CALL eloff(ixs ,ixq ,ixc ,ixp ,ixt ,
123 . ixr ,ixtg ,iparg ,
124 . iactiv ,tt ,iflag ,n ,elbuf_tab,
125 . x ,temp ,mcp ,pm ,igroups ,
126 . mcp_off ,igrbric ,igrquad ,igrsh4n ,igrsh3n ,
127 . igrtruss,igrbeam ,igrspring,itherm_fe)
128
129 iactiv(1,n) = 1
130 offchange=1
131 ENDIF
132 ENDIF
133
134 ELSEIF(iactiv(10,n) == 2) THEN
135C----------------------------------------------------------------------
136C DESACTIVATION DES ELEMENTS AT TIME ZERO
137C----------------------------------------------------------------------
138 IF(tt == zero) THEN
139 CALL eloff(ixs ,ixq ,ixc ,ixp ,ixt ,
140 . ixr ,ixtg ,iparg ,
141 . iactiv ,tt ,1 ,n ,elbuf_tab,
142 . x ,temp ,mcp ,pm ,igroups ,
143 . mcp_off ,igrbric ,igrquad ,igrsh4n ,igrsh3n ,
144 . igrtruss,igrbeam ,igrspring,itherm_fe)
145
146 iactiv(1,n) = 0
147 offchange=1
148 ENDIF
149C----------------------------------------------------------------------
150C ACTIVATION DES ELEMENTS
151C----------------------------------------------------------------------
152 startt = factiv(1,n)
153 stopt = factiv(2,n)
154 iflag = iactiv(1,n)
155 IF(itherm_fe > 0) THEN
156 startt = startt / glob_therm%THEACCFACT
157 stopt = stopt / glob_therm%THEACCFACT
158 ENDIF
159 IF(iflag == 0 .AND. tt >= startt .AND. tt < stopt) THEN
160 CALL eloff(ixs ,ixq ,ixc ,ixp ,ixt ,
161 . ixr ,ixtg ,iparg ,
162 . iactiv ,tt ,iflag ,n ,elbuf_tab,
163 . x ,temp ,mcp ,pm ,igroups ,
164 . mcp_off ,igrbric ,igrquad ,igrsh4n ,igrsh3n ,
165 . igrtruss,igrbeam ,igrspring,itherm_fe)
166 iactiv(1,n) = 1
167 offchange=1
168 ENDIF
169C----------------------------------------------------------------------
170C DESACTIVATION DES ELEMENTS
171C----------------------------------------------------------------------
172 IF(iflag == 1 .AND. tt > stopt) THEN
173 CALL eloff(ixs ,ixq ,ixc ,ixp ,ixt ,
174 . ixr ,ixtg ,iparg ,
175 . iactiv ,tt ,1 ,n ,elbuf_tab,
176 . x ,temp ,mcp ,pm ,igroups ,
177 . mcp_off ,igrbric ,igrquad ,igrsh4n ,igrsh3n ,
178 . igrtruss,igrbeam ,igrspring,itherm_fe)
179 iactiv(1,n) = 0
180 offchange=1
181 ENDIF
182 ENDIF
183 ENDDO ! N=1,NACTIV
184C
185 IF(itherm_fe > 0 .AND. offchange == 1) THEN
186 IF(glob_therm%NUMCONV > 0) CALL convecoff(ibcv, fconv, iparg, igroups, elbuf_tab,glob_therm)
187 IF(glob_therm%NUMRADIA > 0) CALL radiatoff(ibcr, fradia,iparg, igroups, ixs, elbuf_tab,glob_therm)
188 ENDIF
189
190 IF(itherm_fe > 0 .AND. tt == zero) THEN
191C Final call to set MCP_OFF(i) = 0 if all nodes
192 iflag=-1
193 CALL eloff(ixs ,ixq ,ixc ,ixp ,ixt ,
194 . ixr ,ixtg ,iparg ,
195 . iactiv ,tt ,iflag ,n ,elbuf_tab,
196 . x ,temp ,mcp ,pm ,igroups ,
197 . mcp_off ,igrbric ,igrquad ,igrsh4n ,igrsh3n ,
198 . igrtruss,igrbeam ,igrspring,itherm_fe)
199 ENDIF
200
201
202C
203 RETURN
subroutine convecoff(ibcv, fconv, iparg, igroups, elbuf_tab, glob_therm)
Definition convecoff.F:32
#define my_real
Definition cppsort.cpp:32
subroutine eloff(ixs, ixq, ixc, ixp, ixt, ixr, ixtg, iparg, iactiv, time, iflag, nn, elbuf_tab, x, temp, mcp, pm, igroups, mcp_off, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, itherm_fe)
Definition eloff.F:42
subroutine radiatoff(ibcr, fradia, iparg, igroups, ixs, elbuf_tab, glob_therm)
Definition radiatoff.F:32