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

Go to the source code of this file.

Functions/Subroutines

subroutine law70_table (table, nfunc, length, lmax, rate, xi, yi)

Function/Subroutine Documentation

◆ law70_table()

subroutine law70_table ( type(table_4d_), intent(inout) table,
integer, intent(in) nfunc,
integer, dimension(nfunc) length,
integer, intent(inout) lmax,
intent(in) rate,
intent(in) xi,
intent(in) yi )

Definition at line 34 of file law70_table.F.

35C-----------------------------------------------
36C D e s c r i p t i o n
37C-----------------------------------------------
38c create X,Y vectors for all curves before unifying all abscissas
39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE table4d_mod, ONLY : table_4d_
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 INTEGER ,INTENT(IN) :: NFUNC
51 INTEGER ,INTENT(INOUT) :: LMAX
52 INTEGER ,DIMENSION(NFUNC) :: LENGTH
53 my_real ,DIMENSION(NFUNC) ,INTENT(IN) :: rate
54 my_real ,DIMENSION(LMAX,NFUNC) ,INTENT(IN) :: xi
55 my_real ,DIMENSION(LMAX,NFUNC) ,INTENT(IN) :: yi
56 TYPE(TABLE_4D_) ,INTENT(INOUT) :: TABLE
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER :: I,J,IPT,NPTX,NPTM,IPOS,NDIM,FUNC_ID,IERROR,STAT
61 INTEGER ,DIMENSION(NFUNC) :: PERM
62 INTEGER ,PARAMETER :: NPTMAX = 100 ! max number of function points
63 my_real :: x1,x2,y1,y2,deri
64 my_real ,DIMENSION(:) ,ALLOCATABLE :: xf,xs,ys
65 my_real ,DIMENSION(:,:) ,ALLOCATABLE :: yf
66C-----------------------------------------------
67C S o u r c e L i n e s
68C-----------------------------------------------
69 nptx = 0
70 DO i = 1,nfunc
71 nptx = nptx + length(i)
72 END DO
73 ALLOCATE (xf(nptx))
74c
75 IF (nfunc == 1) THEN
76 ALLOCATE (yf(nptx,nfunc))
77 xf(1:nptx) = xi(1:nptx,1)
78 yf(1:nptx,1) = yi(1:nptx,1)
79c
80 ELSE
81c--------------------------------------------------------
82c unify abscissas
83c--------------------------------------------------------
84c
85 CALL unify_abscissa_2d(nfunc,length,lmax,nptx ,xi ,xf )
86c
87 ALLOCATE (yf(nptx,nfunc))
88 DO i = 1,nfunc
89 CALL table_values_2d(length(i) ,nptx ,xi(1,i) ,yi(1,i) ,xf ,yf(1,i) )
90 END DO
91c
92c--------------------------------------------------------
93c check and correct intersections
94c--------------------------------------------------------
95c
96 CALL func2d_deintersect(nptx, nfunc ,yf )
97c
98 END IF
99c--------------------------------------------------------
100c d) check and correct monotonicity
101c--------------------------------------------------------
102 DO i = 1,nfunc
103 DO ipt = 2,nptx
104 IF (yf(ipt,i) < yf(ipt-1,i)) THEN
105 yf(ipt,i) = yf(ipt-1,i)
106 END IF
107 END DO
108 END DO
109c--------------------------------------------------------
110c second reduction of number of points of the 1st curve
111c and reinterpolate all table functions based on its abscissa distribution
112c--------------------------------------------------------
113 IF (nptx > nptmax) THEN
114 nptm = nptx
115 ALLOCATE (xs(nptm))
116 ALLOCATE (ys(nptm))
117 xs(1:nptm) = xf(1:nptm)
118 CALL vw_smooth(nptx,nptmax,xf,yf(1:nptx,1))
119c
120 DO i = 2,nfunc
121 ys(1:nptm) = yf(1:nptm,i)
122 CALL table_values_2d(nptm ,nptx ,xs ,ys ,xf ,yf(1,i) )
123 END DO
124 DEALLOCATE(ys)
125 DEALLOCATE(xs)
126 END IF
127c--------------------------------------------------------------------------
128c e) create 2D function table
129c--------------------------------------------------------
130 ndim = min(2,nfunc)
131 table%NDIM = ndim
132 ALLOCATE (table%X(ndim) ,stat=stat)
133 ALLOCATE (table%X(1)%VALUES(nptx) ,stat=stat)
134 IF (nfunc == 1) THEN
135 ALLOCATE (table%Y1D(nptx) ,stat=stat)
136 table%X(1)%VALUES(1:nptx) = xf(1:nptx)
137 table%Y1D(1:nptx) = yf(1:nptx,1)
138 ELSE
139 ALLOCATE (table%X(2)%VALUES(nfunc) ,stat=stat)
140 ALLOCATE (table%Y2D(nptx,nfunc) ,stat=stat)
141 table%X(1)%VALUES(1:nptx) = xf(1:nptx)
142 table%X(2)%VALUES(1:nfunc) = rate(1:nfunc)
143 DO i = 1,nfunc
144 table%Y2D(1:nptx,i) = yf(1:nptx,i)
145 END DO
146 END IF
147c
148 length(1:nfunc) = nptx
149c--------------------
150 DEALLOCATE (xf)
151 DEALLOCATE (yf)
152c--------------------
153 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine func2d_deintersect(npt, nfunc, yy)
#define min(a, b)
Definition macros.h:20
subroutine table_values_2d(len, nptf, xi, yi, xf, yf)
subroutine unify_abscissa_2d(nfunc, len, lmax, npt, xi, xf)
subroutine vw_smooth(npt, ntarget, x, y)
Definition vw_smooth.F:30