OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
int18_law151_init.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "com01_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine int18_law151_init (multi_fvm, igrbric, ipari, ixs, igroups, iparg, elbuf_tab, force_int, x, v, ms, kinet, x_append, v_append, mass_append, kinet_append, force_int_pon)

Function/Subroutine Documentation

◆ int18_law151_init()

subroutine int18_law151_init ( type(multi_fvm_struct) multi_fvm,
type (group_), dimension(ngrbric), intent(in) igrbric,
integer, dimension(npari,*), intent(in) ipari,
integer, dimension(nixs, *), intent(in) ixs,
integer, dimension(numels), intent(in) igroups,
integer, dimension(nparg,*), intent(in) iparg,
type (elbuf_struct_), dimension(ngroup), intent(in) elbuf_tab,
intent(inout) force_int,
intent(in) x,
intent(in) v,
intent(in) ms,
integer, dimension(*), intent(in) kinet,
intent(inout) x_append,
intent(inout) v_append,
intent(inout) mass_append,
integer, dimension(*), intent(inout) kinet_append,
real(kind=8), dimension(3,6,*), intent(inout) force_int_pon )

Definition at line 33 of file int18_law151_init.F.

38
39!$COMMENT
40! INT18_LAW151_INIT description
41! initialization of array for /INT18 + LAW 151
42!
43! INT18_LAW151_INIT organization :
44! - x/V/MASS_append :
45! * (1:NUMNOD) : classical x/v/mass
46! * (NUMNOD+1:NUMNOD+NUMELS) : phantom node x/v/mass
47! - kinet_append :
48! * (1:NUMNOD) : classical kinet
49! * (NUMNOD+1:NUMNOD+NUMELS) : =0 (no kinet for phantom node)
50! - force_int array :
51! * for parith/off :
52! dimension = 3,NUMELS*NTHREADS
53! each itask thread works in (1+itask*numels:(1+itask)*numels)
54!$ENDCOMMENT
55C-----------------------------------------------
56C M o d u l e s
57C-----------------------------------------------
58 USE multi_fvm_mod
59 USE groupdef_mod
60 USE elbufdef_mod
61 USE message_mod
62C-----------------------------------------------
63C I m p l i c i t T y p e s
64C-----------------------------------------------
65#include "implicit_f.inc"
66#include "comlock.inc"
67#include "com04_c.inc"
68#include "param_c.inc"
69#include "com01_c.inc"
70C-----------------------------------------------
71C D u m m y A r g u m e n t s
72C-----------------------------------------------
73 INTEGER, DIMENSION(NPARI,*), INTENT(in) :: IPARI
74 TYPE (ELBUF_STRUCT_), DIMENSION(NGROUP), INTENT(in) :: ELBUF_TAB
75 INTEGER, DIMENSION(NUMELS), INTENT(in) ::IGROUPS
76 INTEGER, DIMENSION(NPARG,*), INTENT(in) ::IPARG
77 my_real, DIMENSION(3,*), INTENT(in) :: x,v
78 my_real, DIMENSION(3,*), INTENT(inout) :: x_append,v_append
79 my_real, DIMENSION(*), INTENT(in) :: ms
80 INTEGER, DIMENSION(*), INTENT(in) :: KINET
81 my_real, DIMENSION(*), INTENT(inout) :: mass_append
82 INTEGER, DIMENSION(*), INTENT(inout) :: KINET_APPEND
83 my_real, DIMENSION(3,*), INTENT(inout) :: force_int
84 REAL(kind=8), dimension(3,6,*), INTENT(inout) :: force_int_pon
85 INTEGER, DIMENSION(NIXS, *), INTENT(in) :: IXS
86 TYPE(MULTI_FVM_STRUCT) :: MULTI_FVM
87 TYPE (GROUP_) , DIMENSION(NGRBRIC), INTENT(in) :: IGRBRIC
88C-----------------------------------------------
89C L o c a l V a r i a b l e s
90C-----------------------------------------------
91 INTEGER :: N,NN,II,JJ,MY_SIZE
92 INTEGER :: NFT,GROUP_ID,ILOC
93 INTEGER :: ISU1,NSN,NTY,INACTI,NODE_ID,IBRIC
94 LOGICAL, DIMENSION(:), ALLOCATABLE :: TAG
95C-----------------------------------------------
96 ! X/V/MASS extended
97 ! 1:NUMNOD --> classical x/v/mass
98 ! NUMNOD+1:NUMNOD+NUMELS --> x/v/mass of phantom nodes (located to the center of
99 ! the ALE elements)
100 ! INT18_GLOBAL_LIST --> true if /INT18 + LAW151 for the NIN interface
101 multi_fvm%INT18_GLOBAL_LIST(1:ninter) = .false.
102 ALLOCATE(tag(numels))
103 tag(1:numels)=.false.
104 IF( multi_fvm%IS_INT18_LAW151 ) THEN
105 DO n=1,multi_fvm%NUMBER_INT18
106 nn = multi_fvm%INT18_LIST(n)
107 multi_fvm%INT18_GLOBAL_LIST(nn) = .true.
108 ENDDO
109! ! 1:NUMNOD --> classical x/v/mass
110 x_append(1:3,1:numnod) = x(1:3,1:numnod)
111 v_append(1:3,1:numnod) = v(1:3,1:numnod)
112 mass_append(1:numnod) = ms(1:numnod)
113 kinet_append(1:numnod) = kinet(1:numnod)
114! ! initialization of phantom nodes
115 x_append( 1:3,numnod+1:numnod+numels ) = zero
116 v_append( 1:3,numnod+1:numnod+numels ) = zero
117 ! KINET : not used for phantom nodes, always equal to 0
118 mass_append(numnod+1:numnod+numels) = zero
119 kinet_append(numnod+1:numnod+numels) = 0
120 force_int(1:multi_fvm%SIZE_FORCE_INT_1,1:multi_fvm%SIZE_FORCE_INT_2) = zero
121
122 my_size = multi_fvm%SIZE_FORCE_INT_PON
123 force_int_pon(1:3,1:6,1:my_size) = zero
124
125 DO nn=1,multi_fvm%NUMBER_INT18
126 n = multi_fvm%INT18_LIST(nn)
127 isu1 = ipari(45,n)
128 nsn = ipari(5,n) ! number of secondary nodes
129 DO ii = 1,nsn
130 ibric = igrbric(isu1)%ENTITY(ii) ! id of the phantom element
131 IF(.NOT. tag(ibric)) THEN ! otherwise already done with a previous interface
132 group_id = igroups(ibric) ! id of the element group
133 nft = iparg(3,group_id)
134 iloc = ibric - nft
135 ! mass
136 mass_append(numnod + ibric) = elbuf_tab(group_id)%GBUF%RHO(iloc) * elbuf_tab(group_id)%GBUF%VOL(iloc)
137 ! position
138 DO jj = 2, 9
139 node_id = ixs(jj, ibric) ! id of node of the phantom element
140 x_append(1, numnod + ibric) = x_append(1, numnod + ibric) + one_over_8 * x(1, node_id)
141 x_append(2, numnod + ibric) = x_append(2, numnod + ibric) + one_over_8 * x(2, node_id)
142 x_append(3, numnod + ibric) = x_append(3, numnod + ibric) + one_over_8 * x(3, node_id)
143 ENDDO
144 ! velocity
145 v_append(1, numnod + ibric) = multi_fvm%VEL(1, ibric)
146 v_append(2, numnod + ibric) = multi_fvm%VEL(2, ibric)
147 v_append(3, numnod + ibric) = multi_fvm%VEL(3, ibric)
148 tag(ibric)=.true.
149 ENDIF
150 ENDDO
151 ENDDO
152 ENDIF
153 IF(ALLOCATED(tag))DEALLOCATE(tag)
154
155 RETURN
#define my_real
Definition cppsort.cpp:32