OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
st_qaprint_transformations.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!|| st_qaprint_transformations ../starter/source/output/qaprint/st_qaprint_transformations.F
25!||--- called by ------------------------------------------------------
26!|| st_qaprint_driver ../starter/source/output/qaprint/st_qaprint_driver.F
27!||--- calls -----------------------------------------------------
28!||--- uses -----------------------------------------------------
29!|| submodel_mod ../starter/share/modules1/submodel_mod.F
30!||====================================================================
31 SUBROUTINE st_qaprint_transformations(RTRANS,LSUBMODEL,IGRNOD)
32C============================================================================
33C M o d u l e s
34C-----------------------------------------------
35 USE qa_out_mod
36 USE submodel_mod
37 USE groupdef_mod
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "com04_c.inc"
47#include "param_c.inc"
48#include "tabsiz_c.inc"
49#include "units_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 my_real, INTENT(IN) :: rtrans(ntransf,nrtrans)
54 TYPE(submodel_data), INTENT(IN) :: LSUBMODEL(*)
55 TYPE (GROUP_) ,TARGET, INTENT(IN), DIMENSION(NGRNOD) :: IGRNOD
56C--------------------------------------------------
57C L o c a l V a r i a b l e s
58C-----------------------------------------------
59 INTEGER I, MY_ID, MY_TRANS, TEMP_INT, ITRANSSUB, IGS, IS_INTEGER_RTRANS(NRTRANS)
60 CHARACTER(LEN=NCHARTITLE) :: TITR
61 CHARACTER (LEN=255) :: VARNAME
62 DOUBLE PRECISION TEMP_DOUBLE
63C-----------------------------------------------
64C /TRANSFORM
65C-----------------------------------------------
66 is_integer_rtrans(1:nrtrans)=0
67C
68 IF (myqakey('/TRANSFORM')) THEN
69 DO my_trans=1,ntransf
70C
71 titr(1:nchartitle)=''
72 my_id = nint(rtrans(my_trans,19))
73 IF(len_trim(titr)/=0)THEN
74 CALL qaprint(titr(1:len_trim(titr)),my_id,0.0_8)
75 ELSE
76 CALL qaprint('A_TRANSFORMATION_FAKE_NAME', my_id,0.0_8)
77 END IF
78 is_integer_rtrans(19)=1
79C
80 WRITE(varname,'(A)') 'Transformation_Type'
81 temp_int = nint(rtrans(my_trans,2))
82 CALL qaprint(varname(1:len_trim(varname)),temp_int,0.0_8)
83 is_integer_rtrans(2)=1
84C
85 itranssub=nint(rtrans(my_trans,1))
86 IF(itranssub/=0)THEN
87 itranssub=lsubmodel(itranssub)%NOSUBMOD
88 WRITE(varname,'(A)') 'Submodel_ID'
89 CALL qaprint(varname(1:len_trim(varname)),itranssub,0.0_8)
90 END IF
91 is_integer_rtrans(1)=1
92C
93 igs= nint(rtrans(my_trans,18))
94 IF(igs/=0)THEN
95 igs=igrnod(igs)%ID
96 WRITE(varname,'(A)') 'Grnod_ID'
97 CALL qaprint(varname(1:len_trim(varname)),igs,0.0_8)
98 END IF
99 is_integer_rtrans(18)=1
100C
101 DO i=1,nrtrans
102C
103 IF(is_integer_rtrans(i)/=0) cycle
104C
105 IF(rtrans(my_trans,i)/=zero)THEN
106C
107C VARNAME: variable name in ref.extract (without blanks)
108 WRITE(varname,'(A,I0)') 'RTRANS_',i
109 temp_double = rtrans(my_trans,i)
110 CALL qaprint(varname(1:len_trim(varname)),0,temp_double)
111 END IF
112 END DO
113C
114 END DO ! MY_TRANS=1,NTRANSF
115 END IF
116C-----------------------------------------------
117 RETURN
118 END
#define my_real
Definition cppsort.cpp:32
integer, parameter nchartitle
logical function myqakey(value)
@purpose Check if a given value is part of the values set by env variable Useful to make a condition ...
Definition qa_out_mod.F:694
subroutine qaprint(name, idin, value)
@purpose print one entry to QA extract file example of call for real print CALL QAPRINT('MY_LABEL',...
Definition qa_out_mod.F:390
subroutine st_qaprint_transformations(rtrans, lsubmodel, igrnod)