OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
int18_alloc.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "task_c.inc"
#include "parit_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine int18_alloc (number_inter18, inter18_list, multi_fvm, ipari, xcell_remote, nspmd)

Function/Subroutine Documentation

◆ int18_alloc()

subroutine int18_alloc ( integer, intent(inout) number_inter18,
integer, dimension(ninter), intent(inout) inter18_list,
type(multi_fvm_struct) multi_fvm,
integer, dimension(npari,ninter), intent(in) ipari,
type(array_type), dimension(ninter), intent(inout) xcell_remote,
integer, intent(in) nspmd )
Parameters
[in]nspmdnumber of spmd
[in,out]number_inter18number of interface 18
[in,out]inter18_listlist of interface 18
[in,out]xcell_remoteremote data structure for interface 18

Definition at line 33 of file int18_alloc.F.

34!$COMMENT
35! INT18_ALLOC description
36! allocation of array for interface 18 & interface 18 combined
37! with law151
38!
39! int18_alloc organization :
40! - check if /INT18 is used
41! - check if /INT18 + /LAW151 is used
42! - allocate the arrays
43!$ENDCOMMENT
44C-----------------------------------------------
45C M o d u l e s
46C-----------------------------------------------
47 USE multi_fvm_mod
48 USE groupdef_mod
49 USE tri7box
50 USE array_mod
51C-----------------------------------------------
52C I m p l i c i t T y p e s
53C-----------------------------------------------
54#include "implicit_f.inc"
55#include "comlock.inc"
56#include "com04_c.inc"
57#include "param_c.inc"
58#include "task_c.inc"
59#include "parit_c.inc"
60C-----------------------------------------------
61C D u m m y A r g u m e n t s
62C-----------------------------------------------
63 INTEGER, INTENT(in) :: NSPMD !< number of spmd
64 INTEGER, INTENT(inout) :: NUMBER_INTER18 !< number of interface 18
65 INTEGER, DIMENSION(NINTER), INTENT(inout) :: INTER18_LIST !< list of interface 18
66 INTEGER, DIMENSION(NPARI,NINTER), INTENT(in) :: IPARI
67 TYPE(MULTI_FVM_STRUCT) :: MULTI_FVM
68 TYPE(array_type), DIMENSION(NINTER), INTENT(inout) :: XCELL_REMOTE !< remote data structure for interface 18
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72 INTEGER :: N,NN,II,JJ,MY_SIZE,MY_SIZE_2,MY_SIZE_3
73 INTEGER :: ISU1,NBRIC,NSN,NTY,INACTI,NODE_ID,IBRIC,NODFI
74 INTEGER :: P
75C-----------------------------------------------
76 ! check if int18 + law151 is used in the model
77 ! and create a list of int18
78 multi_fvm%IS_INT18_LAW151 = .false.
79 my_size = 0
80 my_size_2 = 0
81 number_inter18 = 0
82
83 DO n=1,ninter
84 nty =ipari(7,n)
85 inacti = ipari(22,n)
86 xcell_remote(n)%SIZE_MY_REAL_ARRAY_1D = 0
87 ! int18 = int7 + inacti=7 (7+7=18)
88 IF( (nty==7).AND.(inacti ==7)) THEN
89 IF(multi_fvm%IS_USED) THEN
90 multi_fvm%IS_INT18_LAW151 = .true.
91 my_size = numnod + numels
92 my_size_2 = numels
93 ENDIF
94 number_inter18 = number_inter18 + 1
95 inter18_list(number_inter18) = n ! list of interface int18
96 ENDIF
97 ENDDO
98 ! number & list of interface 18 for MULTI_FVM solve
99 multi_fvm%NUMBER_INT18 = 0
100 IF(multi_fvm%IS_INT18_LAW151) multi_fvm%NUMBER_INT18 = number_inter18
101 ALLOCATE( multi_fvm%INT18_LIST(multi_fvm%NUMBER_INT18) )
102 ! allocation of X/V/MASS extended to NUMNOD+NUMELS
103 ! 1:NUMNOD --> classical x/v/mass
104 ! NUMNOD+1:NUMNOD+NUMELS --> x/v/mass of phantom nodes (located to the center of
105 ! the ALE elements)
106 ALLOCATE( multi_fvm%X_APPEND(3*my_size) )
107 ALLOCATE( multi_fvm%V_APPEND(3*my_size) )
108 ALLOCATE( multi_fvm%MASS_APPEND(my_size) )
109 ALLOCATE( multi_fvm%KINET_APPEND(my_size) )
110 ! allocation of force array : size = NUMELS
111 my_size_2 = my_size_2 * nthread
112
113 IF(iparit/=0) THEN
114 my_size_3 = 0
115 ELSE
116 my_size_3 = my_size_2
117 ENDIF
118
119 multi_fvm%SIZE_FORCE_INT_1 = 3
120 multi_fvm%SIZE_FORCE_INT_2 = my_size_3
121 ALLOCATE( multi_fvm%FORCE_INT(3,my_size_3) )
122 ! allocation of INT18_GLOBAL_LIST : marker for the interface /INT18+LAW151
123 ALLOCATE( multi_fvm%INT18_GLOBAL_LIST(ninter) )
124
125 ! --------------------------
126 ! allocation of remote array for parith/on
127 IF(multi_fvm%IS_USED) THEN
128 ALLOCATE( multi_fvm%R_AFI(ninter) )
129 DO ii=1,multi_fvm%NUMBER_INT18
130 n = inter18_list(ii) ! list of interface 18 + law151
131 IF( ALLOCATED( multi_fvm%R_AFI(n)%R_FORCE_INT ) ) DEALLOCATE( multi_fvm%R_AFI(n)%R_FORCE_INT )
132 nodfi = 0
133 DO p = 1,nspmd
134 nodfi = nodfi + nsnfi(n)%P(p)
135 ENDDO
136 multi_fvm%R_AFI(n)%NODFI = nodfi
137 ALLOCATE( multi_fvm%R_AFI(n)%R_FORCE_INT(3,6,nodfi*nthread) )
138 multi_fvm%R_AFI(n)%R_FORCE_INT(1:3,1:6,1:nodfi*nthread) = 0d+00
139 ENDDO
140 ELSE
141 ALLOCATE( multi_fvm%R_AFI(0) )
142 ENDIF
143 ! allocation of local array for parith/on
144 IF(iparit/=0) THEN
145 ALLOCATE( multi_fvm%FORCE_INT_PON(3,6,my_size_2) )
146 multi_fvm%SIZE_FORCE_INT_PON = my_size_2
147 ELSE
148 ALLOCATE( multi_fvm%FORCE_INT_PON(0,0,0) )
149 multi_fvm%SIZE_FORCE_INT_PON = 0
150 ENDIF
151 ! --------------------------
152
153 IF( multi_fvm%IS_INT18_LAW151 ) THEN
154 multi_fvm%INT18_LIST(1:multi_fvm%NUMBER_INT18) = inter18_list(1:multi_fvm%NUMBER_INT18)
155 ENDIF
156
157 RETURN
subroutine int18_alloc(number_inter18, inter18_list, multi_fvm, ipari, xcell_remote, nspmd)
Definition int18_alloc.F:34
type(int_pointer), dimension(:), allocatable nsnfi
Definition tri7box.F:440