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

Go to the source code of this file.

Functions/Subroutines

subroutine iniparsen (sensors, nsect, ninter, nintsub, nrwall, nrbody)

Function/Subroutine Documentation

◆ iniparsen()

subroutine iniparsen ( type (sensors_), intent(inout) sensors,
integer, intent(in) nsect,
integer, intent(in) ninter,
integer, intent(in) nintsub,
integer, intent(in) nrwall,
integer, intent(in) nrbody )

Definition at line 30 of file iniparsen.F.

31C-----------------------------------------------
32C M o d u l e s
33C-----------------------------------------------
34 USE message_mod
35 USE sensor_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43c#include "com04_c.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 INTEGER, INTENT(IN) :: NSECT,NINTER,NINTSUB,NRWALL,NRBODY
48 TYPE (SENSORS_) ,INTENT(INOUT) :: SENSORS
49C-----------------------------------------------
50C L o c a l V a r i a b l e s
51C-----------------------------------------------
52 INTEGER I,NOSYS,ISECT,IINT,IRWAL,IRBOD,COMPTEUR,SENS_TYPE,SECT_ID,INT_ID,SUB_ID,RWAL_ID,RBOD_ID
53 INTEGER, DIMENSION(0:NSECT+NINTER+NINTSUB+NRWALL+NRBODY) :: TABLOCAL
54C-----------------------------------------------
55C Special treatment of sensors with Parith/on (type 6,11,12,13)
56C Tabsensor(i) pointe vers les interfaces/sections/rwalls/rbodies concernees
57C par les sensors type force
58c=======================================================================
59 tablocal(:) = 0
60c
61 DO i=1,sensors%NSENSOR
62 sens_type = sensors%SENSOR_TAB(i)%TYPE
63 IF (sens_type == 12 ) THEN ! sensort type section
64 isect = sensors%SENSOR_TAB(i)%IPARAM(1)
65 tablocal(isect) = i
66 ELSEIF (sens_type == 6) THEN ! sensort type interface
67 int_id = sensors%SENSOR_TAB(i)%IPARAM(1)
68 iint = int_id + nsect
69 tablocal(iint) = i
70 ELSEIF (sens_type == 7) THEN ! sensort type rwall
71 rwal_id = sensors%SENSOR_TAB(i)%IPARAM(1)
72 irwal = rwal_id + nsect + ninter+ nintsub
73 tablocal(irwal) = i
74 ELSEIF (sens_type == 11) THEN ! sensort type rbody
75 rbod_id = sensors%SENSOR_TAB(i)%IPARAM(1)
76 irbod = rbod_id + nsect + ninter+ nintsub + nrwall
77 tablocal(irbod) = i
78 ELSEIF (sens_type == 13) THEN ! sensort type work
79 sect_id = sensors%SENSOR_TAB(i)%IPARAM(3)
80 int_id = sensors%SENSOR_TAB(i)%IPARAM(4)
81 sub_id = sensors%SENSOR_TAB(i)%IPARAM(5)
82 rwal_id = sensors%SENSOR_TAB(i)%IPARAM(6)
83 rbod_id = sensors%SENSOR_TAB(i)%IPARAM(7)
84
85 isect = sect_id
86 IF (isect > 0) tablocal(isect) = i
87c
88 iint = int_id + nsect
89 IF (int_id > 0) tablocal(iint)=i ! interface
90 iint = sub_id + nsect
91 IF (sub_id > 0) tablocal(iint)=i ! sub-interface
92c
93 irwal = rwal_id + nsect + ninter+ nintsub
94 IF (rwal_id > 0) tablocal(irwal)=i
95c
96 irbod = rbod_id + nsect + ninter+ nintsub + nrwall
97 IF (rbod_id > 0) tablocal(irbod)=i
98 ENDIF
99 ENDDO
100c------------
101 nosys=1 ! No systeme section,interface,rwall, rbody
102 DO WHILE (tablocal(nosys) == 0)
103 nosys=nosys+1
104 ENDDO
105C
106 DO i=1,nosys
107 sensors%TABSENSOR(i) = tablocal(nosys)
108 ENDDO
109C
110 compteur=1
111 DO i = nosys, nsect+ninter+nintsub+nrwall+nrbody
112 IF (tablocal(i)==0) THEN
113 sensors%TABSENSOR(i+1) = sensors%TABSENSOR(i)
114 ELSE
115 sensors%TABSENSOR(i+1) = sensors%TABSENSOR(i) + compteur
116 compteur=compteur+1
117 ENDIF
118 ENDDO
119C------------
120 RETURN