OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
ani_segquadfr.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!|| ani_segquadfr1 ../starter/source/output/anim/ani_segquadfr.F
25!||--- called by ------------------------------------------------------
26!|| lectur ../starter/source/starter/lectur.F
27!||====================================================================
28 SUBROUTINE ani_segquadfr1(IXQ ,SEGTAG ,KNOD2ELQ ,NOD2ELQ ,X ,NSEG)
29C-----------------------------------------------
30C I m p l i c i t T y p e s
31C-----------------------------------------------
32#include "implicit_f.inc"
33C-----------------------------------------------
34C C o m m o n B l o c k s
35C-----------------------------------------------
36#include "com01_c.inc"
37#include "com04_c.inc"
38C-----------------------------------------------
39C D u m m y A r g u m e n t s
40C-----------------------------------------------
41C REAL
42 INTEGER
43 . NSEG,
44 . IXQ(NIXQ,*),SEGTAG(4,*),KNOD2ELQ(*),NOD2ELQ(*)
46 . x(3,*)
47C-----------------------------------------------
48C L o c a l V a r i a b l e s
49C-----------------------------------------------
50 INTEGER JQ,JJ,K,NQQ,N1,N2,ISEG,KK,KQ,N,L1,L2,L, TRUEAXE, NQQ1,NQQ2
51 INTEGER NODTAG(4),LINES(2,4),NQ(4)
52 DATA lines/1,2,
53 . 2,3,
54 . 3,4,
55 . 4,1/
56C REAL
57C-----------------------------------------------
58C
59 DO jq=1,numelq
60 nodtag(1:4)=1
61 DO l=1,4
62 nq(l) = ixq(l+1,jq)
63 l1 = lines(1,l)
64 l2 = lines(2,l)
65 nqq1 = ixq(l1+1,jq)
66 nqq2 = ixq(l2+1,jq)
67 DO k=knod2elq(nqq1)+1,knod2elq(nqq1+1)
68 kq=nod2elq(k)
69 IF(kq==jq .OR. kq > numelq)cycle
70 DO kk=1,4
71 IF(ixq(lines(1,kk)+1,kq)==nqq1.AND.ixq(lines(2,kk)+1,kq)==nqq2) THEN
72 nodtag(l)=0
73 ELSEIF(ixq(lines(1,kk)+1,kq)==nqq2.AND.ixq(lines(2,kk)+1,kq)==nqq1) THEN
74 nodtag(l)=0
75 ENDIF
76 ENDDO
77 ENDDO
78 ENDDO
79C
80 DO l=1,4
81 l1 = lines(1,l)
82 l2 = lines(2,l)
83 trueaxe= 1
84 n1 = nq(l1)
85 n2 = nq(l2)
86 IF(n2d==1.AND.x(2,n1)<=em10.AND.x(2,n2)<=em10) THEN ! Case Axi omit nodes of revolution axe z ( y=0)
87 trueaxe= 0
88 ENDIF
89
90 IF(trueaxe==1)THEN
91 IF(nodtag(l)==1) THEN ! nodes of external lines
92 nseg=nseg+1
93 segtag(l,jq) = 1
94 ENDIF
95 ENDIF
96 ENDDO
97 ENDDO
98C
99 RETURN
100 END
101!||====================================================================
102!|| ani_segquadfr2 ../starter/source/output/anim/ani_segquadfr.F
103!||--- called by ------------------------------------------------------
104!|| lectur ../starter/source/starter/lectur.F
105!||====================================================================
106 SUBROUTINE ani_segquadfr2(SEGTAG ,SEGQUADFR )
107C-----------------------------------------------
108C I m p l i c i t T y p e s
109C-----------------------------------------------
110#include "implicit_f.inc"
111C-----------------------------------------------
112C C o m m o n B l o c k s
113C-----------------------------------------------
114#include "com01_c.inc"
115#include "com04_c.inc"
116C-----------------------------------------------
117C D u m m y A r g u m e n t s
118C-----------------------------------------------
119 INTEGER
120 . SEGTAG(4,*), SEGQUADFR(2,*)
121C-----------------------------------------------
122C L o c a l V a r i a b l e s
123C-----------------------------------------------
124 INTEGER N,JJ,LL
125C REAL
126C-----------------------------------------------
127C
128 nsegquadfr=0
129 DO n=1,numelq
130 DO jj=1,4
131 IF(segtag(jj,n)==1)THEN
132 nsegquadfr=nsegquadfr+1
133 segquadfr(1,nsegquadfr)=n
134 segquadfr(2,nsegquadfr)=jj
135 END IF
136 END DO
137 END DO
138 RETURN
139 END
subroutine ani_segquadfr1(ixq, segtag, knod2elq, nod2elq, x, nseg)
subroutine ani_segquadfr2(segtag, segquadfr)
#define my_real
Definition cppsort.cpp:32