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

Go to the source code of this file.

Functions/Subroutines

subroutine ebcs_main (igrsurf, segvar, volmon, a, v, w, x, fsav, fv, ms, stifn, iparg, elbuf_tab, ebcs_tab, multi_fvm, ixq, ixs, ixtg, fsky, fsavsurf, time, dt1, nsensor, sensor_tab, python, npc, tf, snpc, stf)

Function/Subroutine Documentation

◆ ebcs_main()

subroutine ebcs_main ( type (surf_), dimension(nsurf) igrsurf,
type(t_segvar) segvar,
volmon,
a,
v,
w,
x,
fsav,
fv,
dimension(numnod), intent(inout) ms,
stifn,
integer, dimension(nparg,ngroup) iparg,
type(elbuf_struct_), dimension(ngroup) elbuf_tab,
type(t_ebcs_tab), intent(inout), target ebcs_tab,
type(multi_fvm_struct), intent(in) multi_fvm,
integer, dimension(nixq,numelq), intent(in) ixq,
integer, dimension(nixs,numels), intent(in) ixs,
integer, dimension(nixtg,numeltg), intent(in) ixtg,
intent(inout) fsky,
dimension(th_surf_num_channel,nsurf), intent(inout) fsavsurf,
intent(in) time,
intent(in) dt1,
integer, intent(in) nsensor,
type (sensor_str_), dimension(nsensor), intent(in) sensor_tab,
type (python_), intent(in) python,
integer, dimension(snpc), intent(in) npc,
tf,
integer, intent(in) snpc,
integer, intent(in) stf )

Definition at line 47 of file ebcs_main.F.

52C-----------------------------------------------
53C M o d u l e s
54C-----------------------------------------------
55 USE segvar_mod, ONLY : t_segvar
56 USE elbufdef_mod
57 USE groupdef_mod
58 USE ebcs_mod
59 USE multi_fvm_mod
61 USE sensor_mod, ONLY : sensor_str_
62 USE python_funct_mod
63C-----------------------------------------------
64C I m p l i c i t T y p e s
65C-----------------------------------------------
66#include "implicit_f.inc"
67C-----------------------------------------------
68C C o m m o n B l o c k s
69C-----------------------------------------------
70#include "param_c.inc"
71#include "com01_c.inc"
72#include "com04_c.inc"
73#include "parit_c.inc"
74C-----------------------------------------------
75C D u m m y A r g u m e n t s
76C-----------------------------------------------
77 my_real,INTENT(IN) :: dt1 !time step
78 my_real,INTENT(IN) :: time !simulation time
79 my_real,INTENT(INOUT) :: fsavsurf(th_surf_num_channel,nsurf)
80 INTEGER IPARG(NPARG,NGROUP)
81 INTEGER,INTENT(IN) :: IXQ(NIXQ,NUMELQ),IXS(NIXS,NUMELS),IXTG(NIXTG,NUMELTG)
82 my_real volmon(*),v(3,numnod),w(3,numnod),a(3,numnod),x(3,numnod),fsav(nthvki,*),
83 . fv(*),stifn(numnod)
84 my_real,intent(inout) :: ms(numnod)
85 TYPE(ELBUF_STRUCT_), DIMENSION(NGROUP) :: ELBUF_TAB
86 TYPE (SURF_) , DIMENSION(NSURF) :: IGRSURF
87 TYPE(t_ebcs_tab), TARGET, INTENT(INOUT) :: EBCS_TAB
88 TYPE(MULTI_FVM_STRUCT),INTENT(IN) :: MULTI_FVM
89 my_real, DIMENSION(8,LSKY), INTENT(INOUT) :: fsky ! acceleration array for parith/on option
90 INTEGER,INTENT(IN) :: NSENSOR
91 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) ,INTENT(IN) :: SENSOR_TAB
92 TYPE (PYTHON_), INTENT(IN) :: PYTHON
93 INTEGER,INTENT(IN) :: SNPC, STF
94 INTEGER,INTENT(IN) :: NPC(SNPC)
95 my_real :: tf(stf)
96 TYPE(t_segvar) :: SEGVAR
97C-----------------------------------------------
98C L o c a l V a r i a b l e s
99C-----------------------------------------------
100 INTEGER I,TYP,ISU,NSEG,VOLU,NOD
101 CLASS(t_ebcs), POINTER :: EBCS
102 LOGICAL HAS_TH
103C-----------------------------------------------
104C S o u r c e L i n e s
105C-----------------------------------------------
106
107 !/TH/SURF (RESET)
108 DO i = 1, nebcs
109 IF(.NOT.ebcs_tab%need_to_compute(i)) cycle !EBCS may be on domain 0 only depending on ebcs type
110 ebcs => ebcs_tab%tab(i)%poly
111 has_th = ebcs%has_th
112 IF(has_th)THEN
113 isu = ebcs%surf_id
114 fsavsurf(1:5,isu) = zero
115 ! FSAVSURF(6,ISU) is cumulative value : not reset
116 ENDIF
117 ENDDO
118
119 DO i = 1, nebcs
120 IF(.NOT.ebcs_tab%need_to_compute(i)) cycle
121 ebcs => ebcs_tab%tab(i)%poly
122 IF(ebcs%is_multifluid)return
123 typ = ebcs%type
124 isu = ebcs%surf_id
125 nseg = ebcs%nb_elem
126 nod = ebcs%nb_node
127 IF (typ == 0) THEN
128 select type (twf => ebcs_tab%tab(i)%poly)
129 type is (t_ebcs_gradp0)
130 CALL ebcs0(nseg, ebcs%iseg, segvar,
131 . a, v, x,
132 . ebcs%node_list, nod, ebcs%elem_list,ebcs%ielem,
133 . ebcs%vold, ebcs%pold, ebcs%p0,
134 . ebcs%la, fv, ms, stifn, iparg, elbuf_tab, twf)
135 end select
136 ELSE IF (typ <= 3)THEN
137 CALL ebcs1(nseg,ebcs%iseg,segvar,
138 . a,v,x,
139 . ebcs%node_list,nod,ebcs%elem_list,
140 . ebcs%vold,ebcs%pold,ebcs%la,
141 . fv,ms,stifn,ebcs_tab, i)
142 ELSE IF (typ == 4) THEN
143 select type (twf => ebcs_tab%tab(i)%poly)
144 type is (t_ebcs_vel)
145 CALL ebcs4(nseg,ebcs%iseg,segvar,
146 . a,v,x,
147 . ebcs%node_list,nod,ebcs%elem_list,
148 . ebcs%la,fv,ms,stifn,twf)
149 end select
150 ELSE IF (typ == 5) THEN
151 select type (twf => ebcs_tab%tab(i)%poly)
152 type is (t_ebcs_normv)
153 CALL ebcs5(nseg,ebcs%iseg,segvar,
154 . a,v,x,
155 . ebcs%node_list,nod,ebcs%elem_list,
156 . ebcs%la,fv,ms,stifn,twf)
157 end select
158 ELSE IF (typ == 6) THEN
159 select type (twf => ebcs_tab%tab(i)%poly)
160 type is (t_ebcs_inip)
161 CALL ebcs6(nseg,ebcs%iseg,segvar,
162 . a,v,x,
163 . ebcs%node_list,nod,ebcs%elem_list,
164 . ebcs%ro0,ebcs%en0,ebcs%p0,
165 . ebcs%vold,ebcs%pold,ebcs%la,
166 . ms,stifn,twf)
167 end select
168 ELSE IF (typ == 7) THEN
169 select type (twf => ebcs_tab%tab(i)%poly)
170 type is (t_ebcs_iniv)
171 CALL ebcs7(nseg,ebcs%iseg,segvar,
172 . a,v,x,
173 . ebcs%node_list,nod,ebcs%elem_list,
174 . ebcs%ro0,ebcs%en0,ebcs%v0,
175 . ebcs%la,ms,stifn,twf)
176 end select
177 ELSE IF (typ == 10) THEN
178 select type (twf => ebcs)
179 type is (t_ebcs_nrf)
180 CALL ebcs10(nseg,twf%iseg,segvar,
181 . a,v,w,x,
182 . twf%node_list,nod,twf%elem_list,twf%ielem,twf%iface,
183 . twf%la,twf,iparg,elbuf_tab,multi_fvm,ixq,ixs,ixtg,
184 . ebcs_parithon(i)%ELEM_ADRESS,fsky,fsavsurf)
185 end select
186 ELSE IF (typ == 11) THEN
187 select type (twf => ebcs)
188 type is (t_ebcs_propellant)
189 call ebcs11(nseg,twf%iseg,segvar,
190 . v,w,x,
191 . twf%node_list,nod,twf%elem_list,twf%ielem,twf%iface,
192 . twf%la,ms,stifn,twf,iparg,elbuf_tab,ixq,ixs,ixtg,
193 . fsavsurf,time,iparit,dt1,
194 . numels, numelq, numeltg,numnod, nparg, ngroup, nixs, nixq, nixtg, nsurf, iale, n2d,
195 . nfunct, npc, tf ,snpc, stf, python,
196 . nsensor, sensor_tab)
197 end select
198 ELSE IF (typ == 100) THEN
199 SELECT TYPE(ebcs)
200 TYPE IS (t_ebcs_monvol)
201 volu = ebcs%monvol_id
202 CALL ebcs_vol2seg(nseg,igrsurf(isu)%NODES,ebcs%iseg,segvar,a,v,x,volmon(nrvolu*(volu-1)+1),fsav(1,volu))
203 END SELECT
204 ENDIF
205 ENDDO
206
207c-----------
208 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine ebcs0(nseg, iseg, segvar, a, v, x, liste, nod, irect, ielem, vo, po, p0, la, fv, ms, stifn, iparg, elbuf_tab, ebcs)
Definition ebcs0.F:37
subroutine ebcs10(nseg, iseg, segvar, a, v, w, x, liste, nod, irect, ielem, iface, la, ebcs, iparg, elbuf_tab, multi_fvm, ixq, ixs, ixtg, elem_adress, fsky, fsavsurf)
Definition ebcs10.F:41
subroutine ebcs1(nseg, iseg, segvar, a, v, x, liste, nod, irect, vo, po, la, fv, ms, stifn, ebcs_tab, iebcs)
Definition ebcs1.F:36
subroutine ebcs4(nseg, iseg, segvar, a, v, x, liste, nod, irect, la, fv, ms, stifn, ebcs)
Definition ebcs4.F:32
subroutine ebcs5(nseg, iseg, segvar, a, v, x, liste, nod, irect, la, fv, ms, stifn, ebcs)
Definition ebcs5.F:35
subroutine ebcs6(nseg, iseg, segvar, a, v, x, liste, nod, irect, ro0, en0, p0, vo, po, la, ms, stifn, ebcs)
Definition ebcs6.F:37
subroutine ebcs7(nseg, iseg, segvar, a, v, x, liste, nod, irect, ro0, en0, v0, la, ms, stifn, ebcs)
Definition ebcs7.F:36
subroutine ebcs_vol2seg(nseg, surf_nodes, iseg, segvar, a, v, x, volmon, fsav)
OPTION /TH/SURF outputs of Pressure and Area needed Tabs.
Definition th_surf_mod.F:60
integer, parameter th_surf_num_channel
number of /TH/SURF channels : AREA, VELOCITY, MASSFLOW, P A, MASS
Definition th_surf_mod.F:99