OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
write_sensors.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| write_sensors ../starter/source/tools/sensor/write_sensors.F
25!||--- called by ------------------------------------------------------
26!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
27!||--- calls -----------------------------------------------------
28!|| fretitl ../starter/source/starter/freform.F
29!||--- uses -----------------------------------------------------
30!||====================================================================
31 SUBROUTINE write_sensors(SENSORS,NUMNOD,NODLOCAL)
32C-----------------------------------------------
33C M o d u l e s
34C-----------------------------------------------
35 USE sensor_mod , ONLY : sensors_, sensor_str_,
36 . isenbuf, lsenbuf, nsenparr, nsenpari
37 USE write_mod, ONLY : write_integer
39 USE python_funct_mod
40C-----------------------------------------------
41C I m p l i c i t T y p e s
42C-----------------------------------------------
43#include "implicit_f.inc"
44#include "scr17_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER ,INTENT(IN) :: NUMNOD
49 INTEGER ,DIMENSION(NUMNOD) ,INTENT(IN) :: NODLOCAL
50 TYPE (SENSORS_) ,TARGET ,INTENT(IN) :: SENSORS
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54 INTEGER I,ISEN,LEN,IAD,NFIX,NPARI,NPARR,NVAR,N1,N2,TYP
55 INTEGER, DIMENSION(LTITR) :: ITITLE
56 INTEGER, DIMENSION(:), ALLOCATABLE :: LTEMP
57 my_real, DIMENSION(:), ALLOCATABLE :: rbuf
58 CHARACTER(LEN = nchartitle) :: TITLE
59 TYPE (SENSOR_STR_) ,POINTER :: SENSOR
60C=======================================================================
61 IF (sensors%NSENSOR > 0) THEN
62 nfix = 11
63c
64 DO isen=1,sensors%NSENSOR
65 sensor => sensors%SENSOR_TAB(isen)
66 typ = sensor%TYPE
67 npari = sensor%NPARI
68 nparr = sensor%NPARR
69 nvar = sensor%NVAR
70 title = sensor%TITLE
71 ALLOCATE (ltemp(npari))
72 ltemp(1:npari) = sensor%IPARAM(1:npari)
73c update node system number after renumbering for sensors using nodes
74 IF (typ == 2) THEN ! /sens/disp
75 n1 = nodlocal(sensor%IPARAM(1))
76 n2 = nodlocal(sensor%IPARAM(2))
77 ltemp(1) = n1
78 ltemp(2) = n2
79 ELSE IF (typ == 9) THEN ! /sens/vel
80 n1 = nodlocal(sensor%IPARAM(1))
81 ltemp(1) = n1
82 ELSE IF (typ == 13) THEN ! /sens/work
83 n2 = sensor%IPARAM(2)
84 n1 = nodlocal(sensor%IPARAM(1))
85 IF (n2 > 0) THEN
86 n2 = nodlocal(sensor%IPARAM(2))
87 END IF
88 ltemp(1) = n1
89 ltemp(2) = n2
90 ELSE IF (typ == 15) THEN ! /sens/dist_surf
91 ltemp(1) = nodlocal(sensor%IPARAM(1))
92 IF (sensor%IPARAM(2) == 0) THEN
93 ltemp(3) = nodlocal(sensor%IPARAM(3))
94 ltemp(4) = nodlocal(sensor%IPARAM(4))
95 ltemp(5) = nodlocal(sensor%IPARAM(5))
96 END IF
97 END IF
98c
99 len = nfix + npari + nparr + nvar
100 ALLOCATE (rbuf(len) )
101c
102 iad = 0
103 rbuf(iad+1) = sensor%TYPE
104 rbuf(iad+2) = sensor%SENS_ID
105 rbuf(iad+3) = sensor%STATUS
106 rbuf(iad+4) = sensor%TCRIT
107 rbuf(iad+5) = sensor%TMIN
108 rbuf(iad+6) = sensor%TDELAY
109 rbuf(iad+7) = sensor%TSTART
110 rbuf(iad+8) = sensor%VALUE
111 rbuf(iad+9) = sensor%NPARI
112 rbuf(iad+10)= sensor%NPARR
113 rbuf(iad+11)= sensor%NVAR
114 iad = iad + nfix
115c
116 IF (npari > 0) THEN
117 DO i = 1,npari
118 rbuf(iad+i) = ltemp(i)
119 END DO
120 iad = iad + npari
121 END IF
122 IF (nparr > 0) THEN
123 DO i = 1,nparr
124 rbuf(iad+i) = sensor%RPARAM(i)
125 END DO
126 iad = iad + nparr
127 END IF
128 IF (nvar > 0) THEN
129 DO i = 1,nvar
130 rbuf(iad+i) = sensor%VAR(i)
131 END DO
132 iad = iad + nvar
133 END IF
134c
135 CALL write_db(rbuf,len)
136 DEALLOCATE(rbuf)
137 DEALLOCATE(ltemp)
138c
139c write sensor title
140 CALL fretitl(title,ititle,ltitr)
141 CALL write_i_c(ititle,ltitr)
142c
143 IF (typ==29.OR.typ==30.OR.typ==31)THEN
144 CALL write_i_c(sensor%INTEGER_USERPARAM,nsenpari)
145 CALL write_i_c(sensor%INTEGER_USERBUF,isenbuf)
146
147 CALL write_db(sensor%FLOAT_USERPARAM,nsenparr)
148 CALL write_db(sensor%FLOAT_USERBUF,lsenbuf)
149 ENDIF
150 IF(typ == 40) THEN
151 CALL write_integer(sensor%PYTHON_FUNCTION_ID)
152 ENDIF
153c
154 END DO
155c---------------------------------------
156c Write Logical sensor index array
157c---------------------------------------
158
159 CALL write_integer(sensors%LOGICAL_SENSOR_COUNT)
160 CALL write_i_c(sensors%LOGICAL_SENSORS_LIST,sensors%LOGICAL_SENSOR_COUNT)
161
162c---------------------------------------
163c Write spmd/PON exchange arrays
164c---------------------------------------
165
166 CALL write_dpdb(sensors%FSAV,12*6*sensors%SFSAV)
167 CALL write_i_c(sensors%TABSENSOR,sensors%STABSEN)
168 END IF
169c-----------
170 RETURN
171 END
#define my_real
Definition cppsort.cpp:32
integer, parameter nchartitle
subroutine write_integer(a)
Definition write_mod.F:40
subroutine fretitl(titr, iasc, l)
Definition freform.F:620
subroutine write_sensors(sensors, numnod, nodlocal)
subroutine write_db(a, n)
Definition write_db.F:140
subroutine write_dpdb(a, n)
Definition write_db.F:302
void write_i_c(int *w, int *len)