OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
int18_law151_init.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!|| int18_law151_init ../starter/source/interfaces/int18/int18_law151_init.F
25!||--- called by ------------------------------------------------------
26!|| lectur ../starter/source/starter/lectur.F
27!||--- uses -----------------------------------------------------
28!||====================================================================
29 SUBROUTINE int18_law151_init(S_APPEND_ARRAY,NINTER,NPARI,
30 1 NUMNOD,NUMELS,NGRBRIC,
31 2 MULTI_FVM,IGRBRIC,IPARI,IXS,
32 4 X ,V ,MS ,KINET ,
33 5 X_APPEND,V_APPEND,MASS_APPEND,KINET_APPEND)
34
35!$COMMENT
36! INT18_LAW151_INIT description
37! initialization of array for /INT18 + LAW 151
38!
39! INT18_LAW151_INIT organization :
40! - x/V/MASS_append :
41! * (1:NUMNOD) : classical x/v/mass
42! * (NUMNOD+1:NUMNOD+NUMELS) : phantom node x/v/mass
43! - kinet_append :
44! * (1:NUMNOD) : classical kinet
45! * (NUMNOD+1:NUMNOD+NUMELS) : =0 (no kinet for phantom node)
46!$ENDCOMMENT
47C-----------------------------------------------
48C M o d u l e s
49C-----------------------------------------------
50 USE multi_fvm_mod
51 USE groupdef_mod
52C-----------------------------------------------
53C I m p l i c i t T y p e s
54C-----------------------------------------------
55#include "implicit_f.inc"
56C-----------------------------------------------
57C D u m m y A r g u m e n t s
58C-----------------------------------------------
59 INTEGER, INTENT(in) :: S_APPEND_ARRAY !< size of append arrays
60 INTEGER, INTENT(in) :: NINTER !< number of interface
61 INTEGER, INTENT(in) :: NPARI !< size of IPARI
62 INTEGER, INTENT(in) :: NUMNOD !< number of node
63 INTEGER, INTENT(in) :: NUMELS !< number of solid
64 INTEGER, INTENT(in) :: NGRBRIC !< size of IGRBRIC structure
65 INTEGER, DIMENSION(NPARI,NINTER), INTENT(in) :: IPARI
66 my_real, DIMENSION(3,NUMNOD), INTENT(in) :: x,v
67 my_real, DIMENSION(3,S_APPEND_ARRAY), INTENT(inout) :: x_append,v_append
68 my_real, DIMENSION(NUMNOD), INTENT(in) :: ms
69 INTEGER, DIMENSION(NUMNOD), INTENT(in) :: KINET
70 my_real, DIMENSION(S_APPEND_ARRAY), INTENT(inout) :: mass_append
71 INTEGER, DIMENSION(S_APPEND_ARRAY), INTENT(inout) :: KINET_APPEND
72 INTEGER, DIMENSION(NIXS,NUMELS), INTENT(in) :: IXS
73 TYPE(multi_fvm_struct) :: MULTI_FVM
74 TYPE (group_) , DIMENSION(NGRBRIC), INTENT(in) :: igrbric
75C-----------------------------------------------
76C L o c a l V a r i a b l e s
77C-----------------------------------------------
78 INTEGER :: N,NN,II,JJ
79 INTEGER :: ISU1,NSN,NODE_ID,IBRIC
80 LOGICAL, DIMENSION(:), ALLOCATABLE :: TAG
81C-----------------------------------------------
82 ! X/V/MASS extended
83 ! 1:NUMNOD --> classical x/v/mass
84 ! numnod+1:numnod+numels --> x/v/mass of phantom nodes(located to the center of
85 ! the ALE elements)
86 ! INT18_GLOBAL_LIST --> true if /INT18 + LAW151 for the NIN interface
87 multi_fvm%INT18_GLOBAL_LIST(1:ninter) = .false.
88 ALLOCATE(tag(numels))
89 tag(1:numels)=.false.
90 IF( multi_fvm%IS_INT18_LAW151 ) THEN
91 DO n=1,multi_fvm%NUMBER_INT18
92 nn = multi_fvm%INT18_LIST(n)
93 multi_fvm%INT18_GLOBAL_LIST(nn) = .true.
94 ENDDO
95! ! 1:NUMNOD --> classical x/v/mass
96 x_append(1:3,1:numnod) = x(1:3,1:numnod)
97 v_append(1:3,1:numnod) = v(1:3,1:numnod)
98 mass_append(1:numnod) = ms(1:numnod)
99 kinet_append(1:numnod) = kinet(1:numnod)
100! ! initialization of phantom nodes
101 x_append( 1:3,numnod+1:numnod+numels ) = zero
102 v_append( 1:3,numnod+1:numnod+numels ) = zero
103 ! KINET : not used for phantom nodes, always equal to 0
104 mass_append(numnod+1:numnod+numels) = zero
105 kinet_append(numnod+1:numnod+numels) = 0
106
107 DO nn=1,multi_fvm%NUMBER_INT18
108 n = multi_fvm%INT18_LIST(nn)
109 isu1 = ipari(45,n)
110 nsn = ipari(5,n) ! number of secondary nodes
111 DO ii = 1,nsn
112 ibric = igrbric(isu1)%ENTITY(ii) ! id of the phantom element
113 IF(.NOT. tag(ibric)) THEN ! otherwise already done with a previous interface
114 ! mass
115 mass_append(numnod + ibric) = zero
116 ! position
117 DO jj = 2, 9
118 node_id = ixs(jj, ibric) ! id of node of the phantom element
119 x_append(1, numnod + ibric) = x_append(1, numnod + ibric) + one_over_8 * x(1, node_id)
120 x_append(2, numnod + ibric) = x_append(2, numnod + ibric) + one_over_8 * x(2, node_id)
121 x_append(3, numnod + ibric) = x_append(3, numnod + ibric) + one_over_8 * x(3, node_id)
122 ENDDO
123 ! velocity
124 v_append(1, numnod + ibric) = multi_fvm%VEL(1, ibric)
125 v_append(2, numnod + ibric) = multi_fvm%VEL(2, ibric)
126 v_append(3, numnod + ibric) = multi_fvm%VEL(3, ibric)
127 tag(ibric)=.true.
128 ENDIF
129 ENDDO
130 ENDDO
131 ENDIF
132 IF(ALLOCATED(tag))DEALLOCATE(tag)
133
134 RETURN
135 END SUBROUTINE int18_law151_init
136C===============================================================================
#define my_real
Definition cppsort.cpp:32
end diagonal values have been computed in the(sparse) matrix id.SOL
subroutine int18_law151_init(s_append_array, ninter, npari, numnod, numels, ngrbric, multi_fvm, igrbric, ipari, ixs, x, v, ms, kinet, x_append, v_append, mass_append, kinet_append)