OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
utable.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!|| utable_dum ../engine/source/user_interface/utable.F
25!||--- called by ------------------------------------------------------
26!|| radioss2 ../engine/source/engine/radioss2.F
27!||====================================================================
28 SUBROUTINE utable_dum(IERR)
29C-----------------------------------------------
30C I m p l i c i t T y p e s
31C-----------------------------------------------
32#include "implicit_f.inc"
33C-----------------------------------------------
34 INTEGER IERR
35 ierr=0
36 END
37!||====================================================================
38!|| get_u_numtable ../engine/source/user_interface/utable.F
39!||--- uses -----------------------------------------------------
40!|| table_glob_mod ../engine/share/modules/table_glob_mod.F
41!|| table_mod ../engine/share/modules/table_mod.F
42!||====================================================================
43 INTEGER FUNCTION get_u_numtable(TID)
44C-----------------------------------------------
45C M o d u l e s
46C-----------------------------------------------
48 USE table_mod
49C-----------------------------------------------
50C I m p l i c i t T y p e s
51C-----------------------------------------------
52#include "implicit_f.inc"
53C-----------------------------------------------
54#include "com04_c.inc"
55C-----------------------------------------------
56 INTEGER i,tid
57C need NTABLE
58c
60 DO i=1,ntable
61 IF(table(i)%NOTABLE==tid)THEN
63 RETURN
64 ENDIF
65 ENDDO
66 RETURN
67 END
68!||====================================================================
69!|| get_u_table ../engine/source/user_interface/utable.F
70!||--- calls -----------------------------------------------------
71!|| table_interp ../engine/source/tools/curve/table_tools.F
72!||--- uses -----------------------------------------------------
73!|| interface_table_mod ../engine/share/modules/table_mod.F
74!|| table_glob_mod ../engine/share/modules/table_glob_mod.F
75!||====================================================================
76 SUBROUTINE get_u_table(ITABLE,XX,YY)
77C-----------------------------------------------
78C M o d u l e s
79C-----------------------------------------------
82C-----------------------------------------------
83C I m p l i c i t T y p e s
84C-----------------------------------------------
85#include "implicit_f.inc"
86C-----------------------------------------------
87C C o m m o n B l o c k s
88C-----------------------------------------------
89 INTEGER ITABLE
90 my_real,
91 . DIMENSION(:) :: xx
93 . yy
94C
95 CALL table_interp(table(itable),xx,yy)
96 RETURN
97 END
98!||====================================================================
99!|| get_table_value ../engine/source/user_interface/utable.F
100!||--- calls -----------------------------------------------------
101!|| table_interp ../engine/source/tools/curve/table_tools.F
102!||--- uses -----------------------------------------------------
103!|| interface_table_mod ../engine/share/modules/table_mod.F
104!|| table_glob_mod ../engine/share/modules/table_glob_mod.F
105!||====================================================================
106 SUBROUTINE get_table_value(ITABLE,XX,XXDIM,YY)
109C-----------------------------------------------
110C I m p l i c i t T y p e s
111C-----------------------------------------------
112#include "implicit_f.inc"
113C-----------------------------------------------
114C C o m m o n B l o c k s
115C-----------------------------------------------
116 INTEGER ITABLE,XXDIM
117 my_real xx(xxdim)
118
119 my_real
120 . yy
121 my_real, DIMENSION(:),ALLOCATABLE :: xx2
122
123 ALLOCATE (xx2(xxdim))
124 xx2(1:xxdim)=xx(1:xxdim)
125C
126 CALL table_interp(table(itable),xx2,yy)
127
128 DEALLOCATE(xx2)
129 RETURN
130 END
131!||====================================================================
132!|| get_table_value_dydx ../engine/source/user_interface/utable.F
133!||--- calls -----------------------------------------------------
134!|| my_flush ../engine/source/system/machine.F
135!|| table_interp_dydx ../engine/source/tools/curve/table_tools.F
136!||--- uses -----------------------------------------------------
137!|| interface_table_mod ../engine/share/modules/table_mod.F
138!|| table_glob_mod ../engine/share/modules/table_glob_mod.F
139!||====================================================================
140 SUBROUTINE get_table_value_dydx(ITABLE,XX,XXDIM,YY,DYDX)
143C-----------------------------------------------
144C I m p l i c i t T y p e s
145C-----------------------------------------------
146#include "implicit_f.inc"
147C-----------------------------------------------
148C C o m m o n B l o c k s
149C-----------------------------------------------
150 INTEGER ITABLE,XXDIM
151 my_real xx(xxdim)
152
153 my_real
154 . yy,dydx
155 my_real, DIMENSION(:),ALLOCATABLE :: xx2
156
157 ALLOCATE (xx2(xxdim))
158 xx2(1:xxdim)=xx(1:xxdim)
159C
160 call my_flush(6)
161 CALL table_interp_dydx(table(itable),xx2,xxdim,yy,dydx)
162
163 DEALLOCATE(xx2)
164 RETURN
165 END
166!||====================================================================
167!|| get_u_vtable ../engine/source/user_interface/utable.F
168!||--- calls -----------------------------------------------------
169!|| table_vinterp ../engine/source/tools/curve/table_tools.f
170!||--- uses -----------------------------------------------------
171!|| interface_table_mod ../engine/share/modules/table_mod.F
172!|| table_glob_mod ../engine/share/modules/table_glob_mod.F
173!||====================================================================
174 SUBROUTINE get_u_vtable(ITABLE,NEL0,IPOS,XX,YY,DYDX1)
177C-----------------------------------------------
178C I m p l i c i t T y p e s
179C-----------------------------------------------
180#include "implicit_f.inc"
181C-----------------------------------------------
182C D u m m y A r g u m e n t s
183C-----------------------------------------------
184 INTEGER ITABLE,NEL0
185 INTEGER, DIMENSION(:,:) :: IPOS
186 my_real,
187 . DIMENSION(:,:) :: xx
188 my_real
189 . yy(*), dydx1(*)
190C-----------------------------------------------
191C L o c a l V a r i a b l e s
192C-----------------------------------------------
193C
194 CALL table_vinterp(table(itable),nel0,nel0,ipos,xx,yy,dydx1)
195 RETURN
196 END
197
198!||====================================================================
199!|| get_vtable_value ../engine/source/user_interface/utable.F
200!||--- calls -----------------------------------------------------
201!|| table_vinterp ../engine/source/tools/curve/table_tools.F
202!||--- uses -----------------------------------------------------
203!|| interface_table_mod ../engine/share/modules/table_mod.F
204!|| table_glob_mod ../engine/share/modules/table_glob_mod.F
205!||====================================================================
206 SUBROUTINE get_vtable_value(ITABLE,NEL0,IPOS,XX,XXDIM,YY,DYDX1)
209C-----------------------------------------------
210C I m p l i c i t T y p e s
211C-----------------------------------------------
212#include "implicit_f.inc"
213C-----------------------------------------------
214C D u m m y A r g u m e n t s
215C-----------------------------------------------
216 INTEGER ITABLE,NEL0,XXDIM
217 INTEGER IPOS(NEL0,XXDIM)
218 my_real xx(nel0,xxdim)
219 my_real yy(*), dydx1(*)
220
221 my_real, DIMENSION(:,:), ALLOCATABLE :: xx2
222 INTEGER, DIMENSION(:,:), ALLOCATABLE :: IPOS2
223
224C-----------------------------------------------
225C L o c a l V a r i a b l e s
226C-----------------------------------------------
227C
228 ALLOCATE (xx2(nel0,xxdim))
229 ALLOCATE (ipos2(nel0,xxdim))
230
231 ipos2(1:nel0,1:xxdim) = ipos(1:nel0,1:xxdim)
232 xx2(1:nel0,1:xxdim) = xx(1:nel0,1:xxdim)
233
234 CALL table_vinterp(table(itable),nel0,nel0,ipos2,xx2,yy,dydx1)
235
236 DEALLOCATE(xx2)
237 DEALLOCATE(ipos2)
238
239 RETURN
240 END
#define my_real
Definition cppsort.cpp:32
subroutine table_interp_dydx(table, xx, xxdim, yy, dydx)
subroutine get_vtable_value(itable, nel0, ipos, xx, xxdim, yy, dydx1)
Definition utable.F:207
subroutine get_table_value_dydx(itable, xx, xxdim, yy, dydx)
Definition utable.F:141
subroutine get_u_table(itable, xx, yy)
Definition utable.F:77
subroutine utable_dum(ierr)
Definition utable.F:29
subroutine get_table_value(itable, xx, xxdim, yy)
Definition utable.F:107
subroutine get_u_vtable(itable, nel0, ipos, xx, yy, dydx1)
Definition utable.F:175
integer function get_u_numtable(tid)
Definition utable.F:44
type(ttable), dimension(:), allocatable table
subroutine my_flush(iunit)
Definition machine.F:147
subroutine table_vinterp(table, dimx, nel, ipos, xx, yy, dydx1)