OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
r2r_input.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!|| r2r_input ../starter/source/coupling/rad2rad/r2r_input.F
25!||--- called by ------------------------------------------------------
26!|| r2r_group ../starter/source/coupling/rad2rad/r2r_group.f
27!||--- uses -----------------------------------------------------
28!|| r2r_mod ../starter/share/modules1/r2r_mod.F
29!|| reader_old_mod ../starter/share/modules1/reader_old_mod.f90
30!|| restmod ../starter/share/modules1/restart_mod.F
31!||====================================================================
32 SUBROUTINE r2r_input(IEXTER)
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE restmod
37 USE r2r_mod
39 USE reader_old_mod , ONLY : nslash
40 USE reader_old_mod , ONLY : kr2r
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "com01_c.inc"
49#include "com04_c.inc"
50#include "scr17_c.inc"
51#include "param_c.inc"
52#include "r2r_c.inc"
53C-----------------------------------------------
54C D u m m y A r g u m e n t s
55C-----------------------------------------------
56 INTEGER IEXTER(NR2R,*)
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER REF,I,J,S,START,ADDRESS(NSUBDOM+1),NB(NSUBDOM+1)
61 INTEGER COMPT,TAB_TMP((NSUBDOM+1)*NR2RLNK),IDOM,TLK
62 CHARACTER NAME_FULL*150,NAM*150,NAM_TMP*150,LINKZ*80,CHRUN*4
63 INTEGER :: LEN_TMP_NAME
64 CHARACTER(len=4096) :: TMP_NAME
65C-----------------------------------------------
66
67 ref = 1981
68 tab_tmp(:)=0
69
70C-----Creation of arrays for Links---
71
72 compt = 1
73 start = nslash(kr2r)+1
74
75 DO i=0,nsubdom
76 address(i+1)=compt
77 DO j=start,nr2rlnk
78 IF ((iexter(3,j)==i).OR.(iexter(4,j)==i)) THEN
79 tab_tmp(compt)=iexter(2,j)
80 compt = compt+1
81 ENDIF
82 END DO
83 nb(i+1)=compt-address(i+1)
84 END DO
85
86C-------------------------------------
87
88 WRITE(chrun,'(I4.4)')irun
89 ! *r2r is an input file for the engine
90 nam = rootnam0(1:len_trim(rootnam0))//'_'//chrun//'.r2r'
91 tmp_name=infile_name(1:infile_name_len)//nam(1:len_trim(nam))
92 len_tmp_name = infile_name_len+len_trim(nam)
93
94 OPEN(unit=ref,file=tmp_name(1:len_tmp_name),
95 . access='SEQUENTIAL',form='FORMATTED',status='UNKNOWN')
96
97 WRITE(ref,1000)'--------------------------------------------'
98 WRITE(ref,1000)' RAD2RAD INPUT FILE - GENERATED BY STARTER '
99 WRITE(ref,1000)'--------------------------------------------'
100 WRITE(ref,1400)'$ '
101
102C-----Generation of domains input cards--------
103
104 WRITE(ref,1000)'--------------------------------------------'
105 WRITE(ref,1000)' 1. DOMAINS '
106 WRITE(ref,1000)'--------------------------------------------'
107 name_full=rootnam0(1:len_trim(rootnam0))
108 WRITE(ref,1100) name_full
109
110 DO i=1,nsubdom+1
111 IF ((i-1)/=0) THEN
112 nam=dom_name(isubdom(8,i-1):isubdom(8,i-1)+isubdom(7,i-1)-1)
113 WRITE(ref,1100) nam
114 ENDIF
115 WRITE(ref,1500) (tab_tmp(j+address(i)-1),j=1,nb(i))
116 END DO
117
118C-----Generation of interfaces input cards -----
119
120 WRITE(ref,1000)'--------------------------------------------'
121 WRITE(ref,1000)' 2. INTERFACES '
122 WRITE(ref,1000)'--------------------------------------------'
123
124 DO i=start,nr2rlnk
125 IF (iexter(5,i)==40) THEN
126C---> type = 40 -> interface for main nodes of RBODY -----
127 WRITE(ref,1310) iexter(5,i)/10
128 ELSEIF (iexter(5,i)==50) THEN
129C---> type = 50 -> interface type KINE----------------- -----
130 WRITE(ref,1330) iexter(5,i)/10
131 ELSEIF (iexter(5,i)==60) THEN
132C---> type = 60 -> interface type FSI------------------ -----
133 tlk = 4
134 IF (flg_tied(5)==1) THEN
135 WRITE(ref,1350) tlk
136 ELSE
137 WRITE(ref,1340) tlk
138 ENDIF
139 WRITE(ref,*) ' 0.1'
140 ELSEIF (iexter(5,i)==70) THEN
141C---> type = 70 -> interface type NLOCAL--------------- -----
142 tlk = 4
143 WRITE(ref,1360) tlk
144 ELSEIF (flg_tied(iexter(5,i))==1) THEN
145 WRITE(ref,1320) iexter(5,i)
146 ELSE
147 WRITE(ref,1300) iexter(5,i)
148 ENDIF
149 WRITE(linkz,1800) iexter(2,i)
150C--------
151 DO j=1,2
152 IF (iexter(2+j,i)==0) THEN
153 nam_tmp = name_full
154 ELSE
155 idom = iexter(2+j,i)
156 s = isubdom(8,idom)
157 nam_tmp = dom_name(s:s+isubdom(7,idom)-1)
158 ENDIF
159 nam=trim(nam_tmp)//' '//trim(linkz)
160 WRITE(ref,1900) nam
161 END DO
162C--------
163 END DO
164
165C-----Generation of options input cards--------
166
167 WRITE(ref,1000)'--------------------------------------------'
168 WRITE(ref,1000)' 3. OPTIONS '
169 WRITE(ref,1000)'--------------------------------------------'
170
171 WRITE(ref,1400)'/SIFF '
172 WRITE(ref,1400)'/MLTPS/ON '
173 WRITE(ref,1400)'$ '
174 WRITE(ref,1400)'/END '
175 CLOSE(ref)
176
177C--------------------------------------------------------------C
178 RETURN
179
180 1000 FORMAT('$',a44)
181 1100 FORMAT('/DOMAIN/',a100)
182 1300 FORMAT('/LINK/TYPE',i1)
183 1310 FORMAT('/LINK/TYPE',i1,'/RBODY')
184 1320 FORMAT('/LINK/TYPE',i1,'/TIED')
185 1330 FORMAT('/LINK/TYPE',i1,'/KINE')
186 1340 FORMAT('/LINK/TYPE',i1,'/FSI')
187 1350 FORMAT('/LINK/TYPE',i1,'/TIED/FSI')
188 1360 FORMAT('/LINK/TYPE',i1,'/NLOCAL')
189 1400 FORMAT('',a10)
190 1500 FORMAT( 3x,10i5)
191 1600 FORMAT(' ',a10,i10)
192 1700 FORMAT(' SUBDOMAIN',i1,i10)
193 1800 FORMAT(i10)
194 1900 FORMAT(' ',a100)
195C-----------
196
197 RETURN
198 END SUBROUTINE r2r_input
integer infile_name_len
character(len=infile_char_len) infile_name
integer, dimension(:,:), allocatable isubdom
Definition r2r_mod.F:144
subroutine r2r_group(ngrou, innod, flag, iparts, ipartq, ipartc, ipartt, ipartp, ipartr, ipartg, ipartsp, ixs10, ixs20, ixs16, kk, buf_nod, ixr_kj, inom_opt, ipart_l, iad, nale_r2r, flg_r2r_err, pm_stack, iworksh, igrbric2, igrquad2, igrsh4n2, igrsh3n2, igrtruss2, igrbeam2, igrspring2, igrnod2, igrsurf2, igrslin2, lsubmodel, ale_euler, igeo_, nloc_dmg, detonators, nsensor, seatbelt_shell_to_spring, nb_seatbelt_shells, mat_param)
Definition r2r_group.F:59
subroutine r2r_input(iexter)
Definition r2r_input.F:33
program starter
Definition starter.F:39