OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_rbody_lagmul.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!|| hm_read_rbody_lagmul ../starter/source/constraints/general/rbody/hm_read_rbody_lagmul.F
25!||--- called by ------------------------------------------------------
26!|| lectur ../starter/source/starter/lectur.F
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../starter/source/output/message/message.F
29!|| anodset ../starter/source/output/analyse/analyse_node.c
30!|| fretitl ../starter/source/starter/freform.F
31!|| hm_get_intv ../starter/source/devtools/hm_reader/hm_get_intv.F
32!|| hm_option_read_key ../starter/source/devtools/hm_reader/hm_option_read_key.F
33!|| hm_option_start ../starter/source/devtools/hm_reader/hm_option_start.F
34!|| hm_sz_r2r ../starter/source/coupling/rad2rad/routines_r2r.F
35!|| kinset ../starter/source/constraints/general/kinset.F
36!|| nodgrnr6 ../starter/source/starter/freform.F
37!|| usr2sys ../starter/source/system/sysfus.f
38!||--- uses -----------------------------------------------------
39!|| hm_option_read_mod ../starter/share/modules1/hm_option_read_mod.F
40!|| message_mod ../starter/share/message_module/message_mod.F
41!|| r2r_mod ../starter/share/modules1/r2r_mod.F
42!|| submodel_mod ../starter/share/modules1/submodel_mod.f
43!||====================================================================
44 SUBROUTINE hm_read_rbody_lagmul(RBYL ,NPBYL ,LPBYL ,IGRNOD ,LSUBMODEL ,
45 . ITAB ,ITABM1 ,IKINE ,IKINE1LAG,NOM_OPT)
46C-----------------------------------------------
47C M o d u l e s
48C-----------------------------------------------
49 USE groupdef_mod
50 USE message_mod
51 USE r2r_mod
52 USE submodel_mod
55C-----------------------------------------------
56C I m p l i c i t T y p e s
57C-----------------------------------------------
58#include "implicit_f.inc"
59C-----------------------------------------------
60C A n a l y s e M o d u l e
61C-----------------------------------------------
62#include "analyse_name.inc"
63C-----------------------------------------------
64C C o m m o n B l o c k s
65C-----------------------------------------------
66#include "units_c.inc"
67#include "param_c.inc"
68#include "lagmult.inc"
69#include "scr17_c.inc"
70#include "com04_c.inc"
71#include "r2r_c.inc"
72C-----------------------------------------------
73C D u m m y A r g u m e n t s
74C-----------------------------------------------
75 INTEGER NPBYL(NNPBY,*),LPBYL(*),
76 . itab(*), itabm1(*),ikine(*),ikine1lag(*)
77 my_real rbyl(nrby,*)
78 INTEGER NOM_OPT(LNOPT1,*)
79C-----------------------------------------------
80 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
81 TYPE(submodel_data),INTENT(IN)::LSUBMODEL(*)
82C-----------------------------------------------
83C L o c a l V a r i a b l e s
84C-----------------------------------------------
85 INTEGER J,K,L,N,NR,MM,ID,IGU,IGS,
86 . nskew,nsl,msl,sub_index,nrb,nrb_r2r
87 CHARACTER MESS*40
88 CHARACTER(LEN=NCHARTITLE) :: TITR
89 CHARACTER(LEN=NCHARKEY) :: KEY
90 LOGICAL IS_AVAILABLE
91 DATA mess/'RIGID BODY DEFINITIONS'/
92C-----------------------------------------------
93C E x t e r n a l F u n c t i o n s
94C-----------------------------------------------
95 INTEGER USR2SYS,NODGRNR6
96 EXTERNAL usr2sys,nodgrnr6
97C-----------------------------------
98C NPBYL(1,N) = MAIN NODE
99C NPBYL(2,N) = NUMBER OF SECONDARY NODES + MAIN
100C NPBYL(3,N) =
101C NPBYL(4,N) =
102C NPBYL(5,N) =
103C NPBYL(6,N) = IDENTIFICATEUR
104C NPBYL(7,N) =
105C NPBYL(8,N) =
106C======================================================================|
107 WRITE(iout,1000)
108C---
109 is_available = .false.
110 CALL hm_option_start('/RBODY')
111C---
112 k = 0
113 nrb = 0
114 nrb_r2r = 0
115C
116 DO nr=1,nrbody
117C
118C--------------------------------------------------
119C EXTRACT DATAS OF /RBODY/... LINE
120C--------------------------------------------------
121C
122 nrb_r2r = nrb_r2r + 1
123 IF (nsubdom > 0) THEN
124 IF(tagrby(nrb_r2r) == 0) CALL hm_sz_r2r(tagrby,nrb_r2r,lsubmodel)
125 ENDIF
126C
127 key=''
128 CALL hm_option_read_key(lsubmodel,
129 . option_id = id,
130 . option_titr = titr,
131 . keyword2 = key,
132 . submodel_index = sub_index)
133 IF(key(1:6)=='LAGMUL')THEN
134 nrb = nrb + 1
135 IF (nsubdom > 0) THEN ! TAGRBY is allocated only if NSUBDOM>0
136 IF(tagrby(nrb) == 0) CALL hm_sz_r2r(tagrby,nrb,lsubmodel)
137 ENDIF
138C---
139 nom_opt(1,nrb)=id
140 CALL fretitl(titr,nom_opt(lnopt1-ltitr+1,nrb),ltitr)
141C---
142 CALL hm_get_intv('node_ID',mm,is_available,lsubmodel)
143 mm = usr2sys(mm,itabm1,mess,id)
144C---
145 CALL hm_get_intv('grnd_ID',igu,is_available,lsubmodel)
146 nsl = nodgrnr6(mm,igu,igs,lpbyl(k+1),igrnod,itabm1,mess,id)
147 msl = nsl+1
148C---
149 lpbyl(k+msl) = mm
150C---
151 IF (nsl == 0) THEN
152 CALL ancmsg(msgid=352,
153 . msgtype=msgwarning,
154 . anmode=aninfo_blind_2,
155 . i1=id,
156 . c1=titr)
157 ENDIF
158 CALL anodset(mm, check_rb_m)
159 DO j=1, nsl
160 CALL anodset(lpbyl(j+k), check_rb_s)
161 ENDDO
162C---
163 DO j=1,msl
164 CALL kinset(512,itab(lpbyl(j+k)),ikine(lpbyl(j+k)),7,0,
165 . ikine1lag(lpbyl(j+k)))
166 ENDDO
167C---
168 npbyl(1,nrb) = mm
169 npbyl(2,nrb) = msl
170 npbyl(6,nrb) = id
171 lag_ncl = lag_ncl + nsl*6
172 lag_nkl = lag_nkl + nsl*21
173C---
174 WRITE(iout,1100)id,trim(titr),itab(mm),msl
175 WRITE(iout,1101)
176 WRITE(iout,1102) (itab(lpbyl(j+k)),j=1,nsl)
177 k = k + 3*msl
178 END IF ! IF(KEY(1:6)=='LAGMUL')THEN
179 ENDDO
180C---
181 RETURN
182C------------------------------
1831000 FORMAT(
184 . /' RIGID BODY DEFINITIONS (LAGRANGE MULTIPLIERS)'
185 . /' -------------------------------------------- '/)
1861100 FORMAT( /5x,'RIGID BODY ID ',i10,1x,a,
187 . /10x,'PRIMARY NODE ',i10
188 . /10x,'NUMBER OF NODES ',i10)
1891101 FORMAT( 10x,'SECONDARY NODES ')
1901102 FORMAT( 9x,10i10)
191 END
void anodset(int *id, int *type)
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
subroutine hm_read_rbody_lagmul(rbyl, npbyl, lpbyl, igrnod, lsubmodel, itab, itabm1, ikine, ikine1lag, nom_opt)
subroutine kinset(ik, node, ikine, idir, isk, ikine1)
Definition kinset.F:57
integer, parameter nchartitle
integer, parameter ncharkey
integer, dimension(:), allocatable tagrby
Definition r2r_mod.F:132
subroutine hm_sz_r2r(tag, val, lsubmodel)
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889
integer function nodgrnr6(m, igu, igs, ibuf, igrnod, itabm1, mess, id)
Definition freform.F:364
subroutine fretitl(titr, iasc, l)
Definition freform.F:620
integer function usr2sys(iu, itabm1, mess, id)
Definition sysfus.F:160
program starter
Definition starter.F:39