OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
inigrav_part_list.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"
#include "scr17_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine inigrav_part_list (ipart, igrpart, ebcs_tab)

Function/Subroutine Documentation

◆ inigrav_part_list()

subroutine inigrav_part_list ( integer, dimension(lipart1,*), intent(in), target ipart,
type (group_), dimension(ngrpart) igrpart,
type(t_ebcs_tab), intent(inout) ebcs_tab )

Definition at line 31 of file inigrav_part_list.F.

32C-----------------------------------------------
33C Description
34C-----------------------------------------------
35C we need to enumerate all PARTS related to INIGRAV and record gravity vectors
36C this will be used to apply pressure gradient due to hydrostatic pressure with /EBCS/NRF
37C-----------------------------------------------
38C M o d u l e s
39C-----------------------------------------------
40 USE inigrav
41 USE message_mod
42 USE groupdef_mod
43 USE ebcs_mod
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C C o m m o n B l o c k s
50C-----------------------------------------------
51#include "com04_c.inc"
52#include "scr17_c.inc"
53C-----------------------------------------------
54C D u m m y A r g u m e n t s
55C-----------------------------------------------
56 INTEGER, INTENT(IN),TARGET :: IPART(LIPART1,*)
57 TYPE (GROUP_) , DIMENSION(NGRPART) :: IGRPART
58 TYPE(T_EBCS_TAB), INTENT(INOUT) :: EBCS_TAB
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 LOGICAL :: lFOUND_EBCS_NRF
63 INTEGER :: KK,JJ,ID_PART,TYP,NSEG,NP
64 INTEGER :: IGRP
65 my_real :: grav0,ngx,ngy,ngz
66C---------------------------------------------
67C S o u r c e L i n e s
68C-----------------------------------------------
69
70 !-- pre-condition to run this subroutine (this also avoid to access array with 0 as index)
71 IF(.NOT. ebcs_tab%is_created)RETURN
72 IF(npart == 0)RETURN
73
74 !-- checking if user defined /EBCS/NRF
75 lfound_ebcs_nrf = .false.
76 DO kk=1,ebcs_tab%nebcs
77 typ = ebcs_tab%tab(kk)%poly%type
78 nseg = ebcs_tab%tab(kk)%poly%nb_elem
79 IF(typ == 10 .AND. nseg > 0) THEN
80 lfound_ebcs_nrf = .true.
81 EXIT
82 ENDIF
83 ENDDO
84 IF(.NOT.lfound_ebcs_nrf)RETURN
85
86 !-- allocations
87 inigrav_parts%IS_ALLOCATED = .false.
88 ALLOCATE(inigrav_parts%TAGPART(npart))
89 ALLOCATE(inigrav_parts%GRAV0(npart))
90 ALLOCATE(inigrav_parts%NG(3,npart))
91 inigrav_parts%IS_ALLOCATED = .true.
92
93 !-- list of PARTs
94 inigrav_parts%TAGPART(1:npart) = 0
95 inigrav_parts%GRAV0(1:npart) = zero
96 DO kk=1,ninigrav
97 igrp = inigrv(1,kk)
98 grav0 = linigrav(07,kk)
99 ngx = linigrav(08,kk)
100 ngy = linigrav(09,kk)
101 ngz = linigrav(10,kk)
102 IF(igrp == 0)cycle
103 np = igrpart(igrp)%NENTITY
104 DO jj=1,np
105 id_part = igrpart(igrp)%ENTITY(jj) ! UID : IPART(4,IGRPART(IGRP)%ENTITY(JJ))
106 inigrav_parts%TAGPART(id_part) = 1
107 inigrav_parts%GRAV0(id_part) = grav0
108 inigrav_parts%NG(1,id_part) = ngx
109 inigrav_parts%NG(2,id_part) = ngy
110 inigrav_parts%NG(3,id_part) = ngz
111 ENDDO
112 ENDDO !next K
113
114 !DEALLOCATE INIGRAV_PARTS WHEN NO LONGER USED BY /EBCS/NRF (WHEN HYDROSTATIC PRESSURE WAS INITIALIZED)
115
116 RETURN
#define my_real
Definition cppsort.cpp:32
integer, dimension(:,:), allocatable inigrv
Definition inigrav_mod.F:38
type(t_inigrav_parts) inigrav_parts
Definition inigrav_mod.F:52