OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cjoint.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!|| cjoint ../engine/source/constraints/general/cyl_joint/cjoint.F
25!||--- called by ------------------------------------------------------
26!|| resol ../engine/source/engine/resol.F
27!||--- calls -----------------------------------------------------
28!|| telesc ../engine/source/constraints/general/cyl_joint/telesc.F
29!||--- uses -----------------------------------------------------
30!|| joint_mod ../engine/share/modules/joint_mod.F
31!||====================================================================
32 SUBROUTINE cjoint(A ,AR ,V ,VR,X ,
33 2 FSAV ,LJOINT,MS,IN,IADCJ,
34 3 FR_CJ,TAG_LNK_SMS,ITASK)
35 USE joint_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C D u m m y A r g u m e n t s
42C-----------------------------------------------
43 INTEGER LJOINT(*), FR_CJ(*), IADCJ(NSPMD+1,*), TAG_LNK_SMS(*),
44 . ITASK
46 . a(3,numnod), ar(3,numnod), v(3,numnod), vr(3,numnod), x(3,numnod), fsav(nthvki,*),
47 . ms(*), in(*)
48C-----------------------------------------------
49C C o m m o n B l o c k s
50C-----------------------------------------------
51#include "com01_c.inc"
52#include "com04_c.inc"
53#include "param_c.inc"
54#include "sms_c.inc"
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER K, N, NN, KIND(NJOINT), ICSIZE
59 LOGICAL :: CONDITION
60C-----------------------------------------------
61C
62 k=1
63 DO n=1,njoint
64 kind(n) = k
65 IF(idtmins==0.AND.idtmins_int==0)THEN
66 k = k +1
67 ELSE
68 k=k+ljoint(k)+1
69 ENDIF
70 END DO
71
72 IF(idtmins==0.AND.idtmins_int==0)THEN
73 DO n=1,njoint
74 nn=ninter+nrwall+nrbody+nsect+n
75 k = kind(n)
76 condition = ( (cyl_join(n)%NUMBER_NODE>0).OR.(cyl_join(n)%NUMBER_MAIN_NODE>0) )
77 IF(condition) CALL telesc(n,a,ar,v,vr,x,fsav(1,nn),ms,in,itask)
78 END DO
79 ELSE
80 DO n=1,njoint
81 IF(tag_lnk_sms(n)/=0)cycle
82 nn=ninter+nrwall+nrbody+nsect+n
83 k = kind(n)
84 condition = ( (cyl_join(n)%NUMBER_NODE>0).OR.(cyl_join(n)%NUMBER_MAIN_NODE>0) )
85 IF(condition) CALL telesc(n,a,ar,v,vr,x,fsav(1,nn),ms,in,itask)
86 END DO
87 END IF
88
89 RETURN
90 END SUBROUTINE cjoint
subroutine cjoint(a, ar, v, vr, x, fsav, ljoint, ms, in, iadcj, fr_cj, tag_lnk_sms, itask)
Definition cjoint.F:35
#define my_real
Definition cppsort.cpp:32
type(joint_type), dimension(:), allocatable cyl_join
Definition joint_mod.F:61
subroutine telesc(n_joint, a, ar, v, vr, x, fs, ms, in, itask)
Definition telesc.F:35