OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
int18_law151_alloc.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_alloc ../starter/source/interfaces/int18/int18_law151_alloc.F
25!||--- called by ------------------------------------------------------
26!|| lectur ../starter/source/starter/lectur.F
27!||--- uses -----------------------------------------------------
28!||====================================================================
29 SUBROUTINE int18_law151_alloc(NPARI,NINTER,NUMNOD,NUMELS,MULTI_FVM,IPARI)
30!$COMMENT
31! INT18_LAW151_ALLOC description
32! allocation of array for interface 18 combined
33! with law151
34!
35! INT18_LAW151_ALLOC organization :
36! - check if /INT18 + /LAW151 is used
37! - allocate the arrays
38!$ENDCOMMENT
39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE multi_fvm_mod
43 USE groupdef_mod
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C D u m m y A r g u m e n t s
50C-----------------------------------------------
51 INTEGER, INTENT(in) :: NPARI !< first dim of ipari array
52 INTEGER, INTENT(in) :: NINTER !< number of interface
53 INTEGER, INTENT(in) :: NUMNOD !< number of node
54 INTEGER, INTENT(in) :: NUMELS !< number of solid
55 INTEGER, DIMENSION(NPARI,NINTER), INTENT(in) :: IPARI !< data of intarface
56 TYPE(MULTI_FVM_STRUCT) :: MULTI_FVM !< structure for multifluid solver
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER :: N,II,MY_SIZE
61 INTEGER :: NTY,INACTI
62 INTEGER, DIMENSION(NINTER) :: INT18_LIST
63 INTEGER, DIMENSION(NINTER) :: IS_INTER_USED_WITH_LAW151
64C-----------------------------------------------
65 ! check if int18 + law151 is used in the model
66 ! and create a list of int18 + law151
67 multi_fvm%IS_INT18_LAW151 = .false.
68 my_size = 0
69 ii = 0
70 ! -------------------------------
71 IF(multi_fvm%IS_USED) THEN
72 DO n=1,ninter
73 is_inter_used_with_law151(n) = 0
74 nty =ipari(7,n)
75 inacti = ipari(22,n)
76 ! int18 = int7 + inacti=7 (7+7=18)
77 IF( (nty==7).AND.(inacti ==7)) THEN
78 multi_fvm%IS_INT18_LAW151 = .true.
79 my_size = numnod + numels
80 ii = ii + 1
81 int18_list(ii) = n ! list of interface int18
82 is_inter_used_with_law151(n) = 1
83 ENDIF
84 ENDDO
85 ENDIF
86 ! -------------------------------
87 multi_fvm%S_APPEND_ARRAY = my_size
88 ! number & list of interface 18
89 multi_fvm%NUMBER_INT18 = ii
90 ALLOCATE( multi_fvm%INT18_LIST(multi_fvm%NUMBER_INT18) ) ; multi_fvm%INT18_LIST(:) = 0
91 ALLOCATE( multi_fvm%IS_INTER_USED_WITH_LAW151(ninter) ) ; multi_fvm%IS_INTER_USED_WITH_LAW151(:) = 0
92 ! allocation of X/V/MASS extended to NUMNOD+NUMELS
93 ! 1:NUMNOD --> classical x/v/mass
94 ! NUMNOD+1:NUMNOD+NUMELS --> x/v/mass of phantom nodes (located to the center of
95 ! the ALE elements)
96 ALLOCATE( multi_fvm%X_APPEND(3*my_size) )
97 ALLOCATE( multi_fvm%V_APPEND(3*my_size) )
98 ALLOCATE( multi_fvm%MASS_APPEND(my_size) )
99 ALLOCATE( multi_fvm%KINET_APPEND(my_size) )
100
101 ! allocation of INT18_GLOBAL_LIST : marker for the interface /INT18+LAW151
102 ALLOCATE( multi_fvm%INT18_GLOBAL_LIST(ninter) )
103
104 IF( multi_fvm%IS_INT18_LAW151 ) THEN
105 multi_fvm%INT18_LIST(1:multi_fvm%NUMBER_INT18) = int18_list(1:multi_fvm%NUMBER_INT18)
106 multi_fvm%IS_INTER_USED_WITH_LAW151(1:ninter) = is_inter_used_with_law151(1:ninter)
107 ENDIF
108
109 RETURN
110 END SUBROUTINE int18_law151_alloc
111C===============================================================================
subroutine int18_law151_alloc(npari, ninter, numnod, numels, multi_fvm, ipari)