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

Go to the source code of this file.

Functions/Subroutines

subroutine utable_dum (ierr)
integer function get_u_numtable (tid)
subroutine get_u_table (itable, xx, yy)
subroutine get_table_value (itable, xx, xxdim, yy)
subroutine get_table_value_dydx (itable, xx, xxdim, yy, dydx)
subroutine get_u_vtable (itable, nel0, ipos, xx, yy, dydx1)
subroutine get_vtable_value (itable, nel0, ipos, xx, xxdim, yy, dydx1)

Function/Subroutine Documentation

◆ get_table_value()

subroutine get_table_value ( integer itable,
xx,
integer xxdim,
yy )

Definition at line 106 of file utable.F.

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
#define my_real
Definition cppsort.cpp:32
type(ttable), dimension(:), allocatable table

◆ get_table_value_dydx()

subroutine get_table_value_dydx ( integer itable,
xx,
integer xxdim,
yy,
dydx )

Definition at line 140 of file utable.F.

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
subroutine table_interp_dydx(table, xx, xxdim, yy, dydx)
subroutine my_flush(iunit)
Definition machine.F:147

◆ get_u_numtable()

integer function get_u_numtable ( integer tid)

Definition at line 43 of file utable.F.

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
integer function get_u_numtable(tid)
Definition utable.F:44

◆ get_u_table()

subroutine get_u_table ( integer itable,
dimension(:) xx,
yy )

Definition at line 76 of file utable.F.

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

◆ get_u_vtable()

subroutine get_u_vtable ( integer itable,
integer nel0,
integer, dimension(:,:) ipos,
dimension(:,:) xx,
yy,
dydx1 )

Definition at line 174 of file utable.F.

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

◆ get_vtable_value()

subroutine get_vtable_value ( integer itable,
integer nel0,
integer, dimension(nel0,xxdim) ipos,
xx,
integer xxdim,
yy,
dydx1 )

Definition at line 206 of file utable.F.

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

◆ utable_dum()

subroutine utable_dum ( integer ierr)

Definition at line 28 of file utable.F.

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