OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
plot_curve.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!|| plot_curve ../common_source/sortie/plot_curve.F
25!||--- called by ------------------------------------------------------
26!|| add_mass_stat ../starter/source/tools/admas/add_mass_stat.F
27!|| outrin ../starter/source/materials/time_step/outri.F
28!||--- uses -----------------------------------------------------
29!|| message_mod ../engine/share/message_module/message_mod.F
30!|| names_and_titles_mod ../common_source/modules/names_and_titles_mod.F
31!||====================================================================
32 SUBROUTINE plot_curve(X, Y, NB_POINTS, INPUT_SIZE_X, INPUT_SIZE_Y,
33 . INPUT_X_MINVALUE, INPUT_Y_MINVALUE, INPUT_X_MAXVALUE,
34 . INPUT_Y_MAXVALUE, INPUT_SYMBOL, INPUT_CURVE_TYPE,
35 . INPUT_TXT_X, INPUT_TXT_Y)
36c
37C-----------------------------------------------
38 USE message_mod
40C-----------------------------------------------
41C I m p l i c i t T y p e s
42C-----------------------------------------------
43#include "implicit_f.inc"
44C-----------------------------------------------
45C A n a l y s e M o d u l e
46C-----------------------------------------------
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "com01_c.inc"
51#include "com04_c.inc"
52#include "scr17_c.inc"
53#include "scr03_c.inc"
54#include "units_c.inc"
55#include "warn_c.inc"
56#include "param_c.inc"
57#include "remesh_c.inc"
58#include "sphcom.inc"
59C-----------------------------------------------
60C D u m m y A r g u m e n t s
61C-----------------------------------------------
62 my_real x(nb_points),y(nb_points)
63 INTEGER NB_POINTS,INPUT_SIZE_X,INPUT_SIZE_Y, INPUT_CURVE_TYPE
64 my_real INPUT_X_MINVALUE, INPUT_X_MAXVALUE, INPUT_Y_MINVALUE, INPUT_Y_MAXVALUE
65 CHARACTER*1 INPUT_SYMBOL
66 CHARACTER(*) INPUT_TXT_X, INPUT_TXT_Y
67C-----------------------------------------------
68 OPTIONAL :: input_size_x, input_size_y, input_x_minvalue, input_y_minvalue,
69 . input_x_maxvalue, input_y_maxvalue, input_symbol,
70 . input_curve_type, input_txt_x, input_txt_y
71C-----------------------------------------------
72C L o c a l V a r i a b l e s
73C-----------------------------------------------
74 CHARACTER(len=60) :: FMTA
75 INTEGER I,J,II,CURVE(NB_POINTS),SIZE_X,SIZE_Y,CURVE_TYPE,COORDX,COORDY,LENA
76 my_real INCR_X,INCR_Y,X_MINVALUE, X_MAXVALUE, Y_MINVALUE, Y_MAXVALUE
77 CHARACTER(LEN=NCHARLINE) :: CHAR(100)
78 CHARACTER(LEN=NCHARLINE) :: CHAR1(100)
79 CHARACTER(LEN=NCHARLINE) :: CHAR2
80 CHARACTER(LEN=NCHARLINE) :: TXT_X
81 CHARACTER(LEN=NCHARLINE) :: TXT_Y
82 CHARACTER*1 SYMBOL
83 INTEGER, DIMENSION(:,:), ALLOCATABLE :: GRID
84C--------------------------------------------------------------
85C GENERIC ROUTINE TO PLOT CURVES OR HISTOGRAMS IN .out files
86C--------------------------------------------------------------
87C MANDATORY
88C NB_POINTS : NUMBER OF POINTS OF THE CURVE TO PLOT
89C X : X COORDS
90C Y : Y COORDS
91C OPTIONAL :
92C INPUT_SIZE_X : X SIZE (NUMBER OF CHAR) OF THE PLOT, DEFAULT = 100
93C INPUT_SIZE_Y : Y SIZE (NUMBER OF CHAR) OF THE PLOT, DEFAULT = 30
94C INPUT_X_MINVALUE : MIN VALUE OF THE ABSCISSA , DEFAULT : VALUE IS SET AUTOMATICALLY
95C INPUT_Y_MINVALUE : MIN VALUE OF THE ORDINATE , DEFAULT : VALUE IS SET AUTOMATICALLY
96C INPUT_X_MAXVALUE : MAX VALUE OF THE ABSCISSA , DEFAULT : VALUE IS SET AUTOMATICALLY
97C INPUT_Y_MAXVALUE : MAX VALUE OF THE ORDINATE , DEFAULT : VALUE IS SET AUTOMATICALLY
98C INPUT_SYMBOL : CHARACTER TO PLOT THE CURVE/HISTOGRAM, DEFAULT = '#'
99C INPUT_CURVE_TYPE , DEFAULT = 0'
100C 0 : PLOT CURVE
101C 1 : PLOT HISTOGRAM
102C INPUT_TXT_X : ABSCISSA LEGEND , DEFAULT : NONE
103C INPUT_TXT_Y : ORDINATE LEGEND , DEFAULT : NONE
104C=======================================================================
105 IF ( .NOT. PRESENT(input_size_x)) THEN
106 size_x = 100
107 ELSE
108 size_x = input_size_x
109 ENDIF
110c
111 IF ( .NOT. PRESENT(input_size_y)) THEN
112 size_y = 30
113 ELSE
114 size_y = input_size_y
115 ENDIF
116c
117 IF ( .NOT. PRESENT(input_x_minvalue)) THEN
118 x_minvalue = ep20
119 DO i=1,nb_points
120 x_minvalue = min(x(i),x_minvalue)
121 ENDDO
122 ELSE
123 x_minvalue = input_x_minvalue
124 ENDIF
125c
126 IF ( .NOT. PRESENT(input_y_minvalue)) THEN
127 y_minvalue = ep20
128 DO i=1,nb_points
129 y_minvalue = min(y(i),y_minvalue)
130 ENDDO
131 ELSE
132 y_minvalue = input_y_minvalue
133 ENDIF
134c
135 IF ( .NOT. PRESENT(input_x_maxvalue)) THEN
136 x_maxvalue = -ep20
137 DO i=1,nb_points
138 x_maxvalue = max(x(i),x_maxvalue)
139 ENDDO
140 ELSE
141 x_maxvalue = input_x_maxvalue
142 ENDIF
143c
144 IF ( .NOT. PRESENT(input_y_maxvalue)) THEN
145 y_maxvalue = -ep20
146 DO i=1,nb_points
147 y_maxvalue = max(y(i),y_maxvalue)
148 ENDDO
149 ELSE
150 y_maxvalue = input_y_maxvalue
151 ENDIF
152c
153 IF ( .NOT. PRESENT(input_symbol)) THEN
154 symbol(1:1) = '#'
155 ELSE
156 symbol(1:1) = input_symbol(1:1)
157 ENDIF
158c
159 IF ( .NOT. PRESENT(input_curve_type)) THEN
160 curve_type = 0
161 ELSE
162 curve_type = input_curve_type
163 ENDIF
164c
165 IF ( .NOT. PRESENT(input_txt_x)) THEN
166 txt_x = ''
167 ELSE
168 txt_x = ''
169 txt_x(1:len_trim(input_txt_x)) = input_txt_x(1:len_trim(input_txt_x))
170 ENDIF
171c
172 IF ( .NOT. PRESENT(input_txt_y)) THEN
173 txt_y = ''
174 ELSE
175 txt_y = ''
176 txt_y(1:len_trim(input_txt_y)) = input_txt_y(1:len_trim(input_txt_y))
177 ENDIF
178C=======================================================================
179 char=''
180 char1=''
181 char2=''
182 curve(1:nb_points) = 0
183 incr_x = (x_maxvalue-x_minvalue)/(size_x-1)
184 incr_y = (y_maxvalue-y_minvalue)/(size_y-1)
185c
186 ALLOCATE(grid(size_x,size_y))
187 DO j = 1, size_y
188 DO i = 1, size_x
189 grid(i,j) = 0
190 ENDDO
191 ENDDO
192c
193 IF(curve_type == 0)THEN
194 DO i=1,nb_points
195 coordx = min(size_x,max(1,int((x(i) - x_minvalue)/incr_x)))
196 coordy = min(size_y,max(1,int((y(i) - y_minvalue)/incr_y)))
197 grid(coordx,coordy) = 1
198 ENDDO
199 ELSEIF(curve_type == 1)THEN
200 DO i=1,nb_points
201 coordx = min(size_x,max(1,int((x(i) - x_minvalue)/incr_x)))
202 coordy = min(size_y,max(1,int((y(i) - y_minvalue)/incr_y)))
203 DO j=1,coordy
204 grid(coordx,j) = 1
205 ENDDO
206 ENDDO
207 ENDIF
208c
209 DO j = 1, size_y
210 char(j)= " "
211 ENDDO
212 DO j = 1, size_y
213 DO i = 1, size_x
214 IF( grid(i,size_y+1-j) == 1) char(j)(i:i)= symbol(1:1)
215 ENDDO
216 ENDDO
217
218 DEALLOCATE(grid)
219
220 IF(PRESENT(input_txt_y)) THEN
221 WRITE(iout,'(12X,A)') txt_y(1:len_trim(txt_y))
222 ENDIF
223C
224 WRITE(iout,'(19X,A)') '^'
225 WRITE(iout,'(19X,A,A)') '|',char(1)(1:size_x)
226 WRITE(iout,'(9X,F7.3,1X,A,A,A)') y_maxvalue,'--','|',char(2)(1:size_x)
227 DO i = 3,size_y-1
228 WRITE(iout,'(19X,A,A)') '|',char(i)(1:size_x)
229 ENDDO
230 WRITE(iout,'(9X,F7.3,1X,A,A,A)') y_minvalue,'--','|',char(size_y)(1:size_x)
231C
232 DO ii = 1,size_x+2
233 char2(ii:ii) = '-'
234 ENDDO
235 char2(size_x+2:size_x+3) = '>'
236 IF(PRESENT(input_txt_x) ) THEN
237 char2(size_x+4:size_x+3+len_trim(txt_x)) = txt_x(1:len_trim(txt_x))
238 ENDIF
239C
240 lena = len_trim(char2)
241 WRITE(iout,'(20X,A)') char2(1:lena)
242c
243 char2 = ' '
244 char2(1:1)= '|'
245 char2(size_x:size_x)= '|'
246 lena = len_trim(char2)
247 WRITE(iout,'(20X,A)') char2(1:lena)
248C
249 IF (size_x <= 10) THEN
250 fmta='(14X,1PG11.3,5X,1PG11.3)'
251 ELSEIF (size_x <= 20) THEN
252 fmta='(14X,1PG11.3,8X,1PG11.3)'
253 ELSEIF (size_x <= 30) THEN
254 fmta='(14X,1PG11.3,18X,1PG11.3)'
255 ELSEIF (size_x <= 40) THEN
256 fmta='(14X,1PG11.3,28X,1PG11.3)'
257 ELSEIF (size_x <= 50) THEN
258 fmta='(14X,1PG11.3,38X,1PG11.3)'
259 ELSEIF (size_x <= 60) THEN
260 fmta='(14X,1PG11.3,48X,1PG11.3)'
261 ELSEIF (size_x <= 70) THEN
262 fmta='(14X,1PG11.3,58X,1PG11.3)'
263 ELSEIF (size_x <= 80) THEN
264 fmta='(14X,1PG11.3,68X,1PG11.3)'
265 ELSEIF (size_x <= 90) THEN
266 fmta='(14X,1PG11.3,78X,1PG11.3)'
267 ELSE
268 fmta='(14 X,1PG11.3,85X,1PG11.3)'
269 ENDIF
270c
271 WRITE(iout,fmt=fmta) x_minvalue,x_maxvalue
272c
273 WRITE(iout,*) ' '
274 WRITE(iout,*) ' '
275C------------------------------
276 RETURN
277 END
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
integer, parameter ncharline
subroutine plot_curve(x, y, nb_points, input_size_x, input_size_y, input_x_minvalue, input_y_minvalue, input_x_maxvalue, input_y_maxvalue, input_symbol, input_curve_type, input_txt_x, input_txt_y)
Definition plot_curve.F:36