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

Go to the source code of this file.

Functions/Subroutines

subroutine fvinjt6 (njet, ibagjet, rbagjet, npc, tf, nsensor, sensor_tab, scalt, datainj, python)

Function/Subroutine Documentation

◆ fvinjt6()

subroutine fvinjt6 ( integer njet,
integer, dimension(nibjet,*) ibagjet,
rbagjet,
integer, dimension(*) npc,
tf,
integer, intent(in) nsensor,
type (sensor_str_), dimension(nsensor), intent(in) sensor_tab,
scalt,
datainj,
type(python_) python )

Definition at line 33 of file fvinjt6.F.

35C-----------------------------------------------
36C M o d u l e s
37C-----------------------------------------------
38 USE sensor_mod
39 USE python_funct_mod
40 USE finter_mixed_mod
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "com04_c.inc"
49#include "com08_c.inc"
50#include "param_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER ,INTENT(IN) :: NSENSOR
55 INTEGER NJET, IBAGJET(NIBJET,*), NPC(*)
56C REAL
58 . rbagjet(nrbjet,*), tf(*),scalt,datainj(6,njet)
59 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) ,INTENT(IN) :: SENSOR_TAB
60 type(python_) :: PYTHON
61C-----------------------------------------------
62C L o c a l V a r i a b l e s
63C-----------------------------------------------
64 INTEGER IINJ, IMASS, IFLU, ISENS, ITEMP
66 . tstart, fmass, gmass, gmass_old, gmtot, gmtot_old, dgmass,
67 . tsg, dydx, rmwg, ftemp, temp, efac ,
68 . cpa, cpb, cpc, cpg, cvg
69C-----------------------------------------------
70 DO iinj=1,njet
71 fmass=rbagjet(5,iinj)
72 gmass_old=rbagjet(7,iinj)
73 gmtot_old=rbagjet(8,iinj)
74 imass=ibagjet(1,iinj)
75 iflu =ibagjet(2,iinj)
76 isens=ibagjet(4,iinj)
77 IF(isens==0)THEN
78 tstart=zero
79 ELSE
80 tstart=sensor_tab(isens)%TSTART
81 ENDIF
82 IF (tt>=tstart.AND.dt1>zero)THEN
83 tsg=(tt-tstart)*scalt
84 IF (imass>0) THEN
85 gmass=fmass*finter_mixed(python,nfunct,imass,tsg,npc,tf)
86 IF(iflu==1)gmass = gmass*scalt*dt1 + gmass_old
87 ELSE
88 gmass=fmass
89 ENDIF
90 dgmass=max(zero,gmass-gmass_old)
91 ELSE
92 dgmass=zero
93 gmass=zero
94 ENDIF
95 gmtot=gmtot_old+dgmass
96 IF (dt1>zero) THEN
97 datainj(2,iinj)=dgmass/dt1
98 ELSE
99 datainj(2,iinj)=zero
100 ENDIF
101C------------
102C Temperature
103C------------
104 rmwg =rbagjet(1,iinj)
105 cpa =rbagjet(2,iinj)
106 cpb =rbagjet(3,iinj)
107 cpc =rbagjet(4,iinj)
108 ftemp=rbagjet(6,iinj)
109 itemp=ibagjet(3,iinj)
110 efac =zero
111 temp =zero
112 IF(tt>=tstart)THEN
113 tsg = (tt-tstart)*scalt
114 IF(itemp>0) THEN
115 temp=ftemp*finter_mixed(python,nfunct,itemp,tsg,npc,tf)
116 ELSE
117 temp=ftemp
118 ENDIF
119 efac= temp*(cpa+half*cpb*temp+third*cpc*temp*temp)
120 ENDIF
121C
122 IF (ibagjet(12,iinj)==2) efac=efac-rmwg*temp
123C
124 datainj(4,iinj)=efac
125 cpg=cpa+cpb*temp+cpc*temp*temp
126 cvg=cpg-rmwg
127 datainj(5,iinj)=cpg/cvg
128C
129 rbagjet(7,iinj)=gmass
130 rbagjet(8,iinj)=gmtot
131 ENDDO
132 RETURN
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21