OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
read5p.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!|| read5p ../engine/source/input/read5p.F
25!||--- called by ------------------------------------------------------
26!|| rdele ../engine/source/input/rdele.F
27!||--- calls -----------------------------------------------------
28!|| wciusc2 ../engine/source/input/wciusc2.F
29!||====================================================================
30 SUBROUTINE read5p(IREC,NBC,KEY0,IV2,JJ)
31C-----------------------------------------------
32C I m p l i c i t T y p e s
33C-----------------------------------------------
34#include "implicit_f.inc"
35C-----------------------------------------------
36C D u m m y A r g u m e n t s
37C-----------------------------------------------
38 INTEGER IV2(*), IREC, NBC, JJ
39 CHARACTER KEY0*(*)
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "units_c.inc"
44C-----------------------------------------------
45C L o c a l V a r i a b l e s
46C-----------------------------------------------
47 INTEGER K, I, N, J, NC1, NC2, NTOT
48 INTEGER, DIMENSION(:), ALLOCATABLE :: IV0,IV1
49C-----------------------------------------------
50C
51C First pass - count total number of elements
52c
53 ntot=0
54 k=0
55 DO i=1,nbc
56 CALL wciusc2(irec+k,1,n,key0)
57 k=k+1
58 ntot = ntot + n
59 ENDDO ! I
60
61 IF(ntot==0)RETURN ! no elements to read
62
63C Second pass - read all lines of elements as a single big line
64 ALLOCATE(iv0(ntot))
65 ALLOCATE(iv1(2*ntot))
66 iv0(1:ntot) = 0
67 iv1(1:2*ntot) = 0
68C
69 ntot = 0
70 k=0
71 DO i=1,nbc
72 CALL wciusc2(irec+k,1,n,key0)
73 READ(iusc2,*)(iv0(j),j=1,n)
74 DO j=1,n
75 iv1(2*(ntot+j) - 1) = iv0(j)
76 iv1(2*(ntot+j)) = iv0(j)
77 ENDDO
78 ntot = ntot + n
79 k=k+1
80 ENDDO
81C
82C Write the elements in groups of 10 - last line completed with last element
83 n=2*ntot
84 nc1=1
85 nc2 = 0
86 DO WHILE(nc2 < n)
87 jj = 0
88 nc2=min(nc1+9-jj,n)
89 DO j=nc1,nc2
90 jj=jj+1
91 iv2(jj)=iv1(j)
92 ENDDO
93 DO k=jj+1,10,2
94 iv2(k)=iv2(jj-1)
95 iv2(k+1)=iv2(jj)
96 ENDDO
97 WRITE(iin,'(10I10)')(iv2(j),j=1,10)
98 nc1=nc2+1
99 ENDDO
100 jj = 0
101
102 DEALLOCATE(iv0)
103 DEALLOCATE(iv1)
104
105 RETURN
106 END
#define min(a, b)
Definition macros.h:20
subroutine read5p(irec, nbc, key0, iv2, jj)
Definition read5p.F:31
subroutine wciusc2(irec, nbc, n, key0)
Definition wciusc2.F:38