OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sensor_energy_bilan.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"
#include "parit_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine sensor_energy_bilan (jft, jlt, ei, ek, off, ipart, itask, sensors)

Function/Subroutine Documentation

◆ sensor_energy_bilan()

subroutine sensor_energy_bilan ( integer, intent(in) jft,
integer, intent(in) jlt,
intent(in) ei,
intent(in) ek,
intent(in) off,
integer, dimension(*), intent(in) ipart,
integer, intent(in) itask,
type (sensors_), intent(inout) sensors )

Definition at line 50 of file sensor_energy_bilan.F.

51C-----------------------------------------------
52C M o d u l e s
53C-----------------------------------------------
54 USE sensor_mod
55C-----------------------------------------------
56C I m p l i c i t T y p e s
57C-----------------------------------------------
58#include "implicit_f.inc"
59C-----------------------------------------------
60C G l o b a l P a r a m e t e r s
61C-----------------------------------------------
62#include "mvsiz_p.inc"
63C-----------------------------------------------
64C C o m m o n B l o c k s
65C-----------------------------------------------
66#include "parit_c.inc"
67C-----------------------------------------------
68C D u m m y A r g u m e n t s
69C-----------------------------------------------
70 INTEGER, INTENT(in) :: JFT,JLT
71 INTEGER, INTENT(in) :: ITASK
72 INTEGER, DIMENSION(*), INTENT(in) :: IPART
73C REAL
74 my_real, DIMENSION(*), INTENT(in) :: ei,ek
75 my_real, DIMENSION(*), INTENT(in) :: off
76 type (sensors_),INTENT(INOUT) :: SENSORS
77C-----------------------------------------------
78C L o c a l V a r i a b l e s
79C-----------------------------------------------
80 INTEGER I,MX,II,J,IC,NEL,IJK
81 INTEGER :: K,IPART_SENS,LOCAL_INDEX
82 my_real, DIMENSION(MVSIZ,2) :: fstparit
83 INTEGER :: NGR_SENSOR
84C-----------------------------------------------
85 ngr_sensor=sensors%NGR_SENSOR(itask+1)
86 IF(iparit>0) THEN
87 IF(sensors%SENS_GROUP(ngr_sensor)%NUM_PART>0) THEN
88 IF(sensors%SENS_GROUP(ngr_sensor)%NUM_PART==1) THEN
89 DO i=jft,jlt
90 IF( off(i)/=zero ) THEN
91 fstparit(i,1) = ei(i)
92 fstparit(i,2) = ek(i)
93 ELSE
94 fstparit(i,1) = zero
95 fstparit(i,2) = zero
96 ENDIF
97 ENDDO
98 nel = jlt-jft+1
99 k = sensors%SENS_GROUP(ngr_sensor)%PART(1,3) ! id of the sensor
100 ijk = itask+1
101 CALL sum_6_float(1,nel,fstparit(1,1),sensors%SENSOR_STRUCT(k)%FBSAV6_SENS(1,1,ijk),2)
102 CALL sum_6_float(1,nel,fstparit(1,2),sensors%SENSOR_STRUCT(k)%FBSAV6_SENS(2,1,ijk),2)
103 ELSEIF(sensors%SENS_GROUP(ngr_sensor)%NUM_PART>1) THEN
104
105 DO j=1,sensors%SENS_GROUP(ngr_sensor)%NUM_PART
106 ipart_sens = sensors%SENS_GROUP(ngr_sensor)%PART(j,1) ! id of the part linked to the sensor
107 local_index = 0
108 DO i=jft,jlt
109 mx=ipart(i)
110 IF( (ipart_sens==mx).AND.(off(i)/=zero) ) THEN
112 fstparit(local_index,1) = ei(i)
113 fstparit(local_index,2) = ek(i)
114 ENDIF
115 ENDDO
116
117 k = sensors%SENS_GROUP(ngr_sensor)%PART(j,3) ! id of the sensor
118 ijk = itask+1
119 CALL sum_6_float(1,local_index,fstparit(1,1),sensors%SENSOR_STRUCT(k)%FBSAV6_SENS(1,1,ijk),2)
120 CALL sum_6_float(1,local_index,fstparit(1,2),sensors%SENSOR_STRUCT(k)%FBSAV6_SENS(2,1,ijk),2)
121 ENDDO
122 ENDIF
123 ENDIF
124 ENDIF
125C---
126 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine local_index(il, ig, nodes, n)
Definition local_index.F:37
subroutine sum_6_float(jft, jlt, f, f6, n)
Definition parit.F:64