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

Go to the source code of this file.

Functions/Subroutines

subroutine deallocate_igrsurf_split (t_monvol, igrsurf_proc)
 This routine deallocates the local IGSURF_PROC arrays.

Function/Subroutine Documentation

◆ deallocate_igrsurf_split()

subroutine deallocate_igrsurf_split ( type(monvol_struct_), dimension(nvolu), intent(inout) t_monvol,
type(surf_), dimension(nsurf,nspmd), intent(inout) igrsurf_proc )

This routine deallocates the local IGSURF_PROC arrays.

loop over the NVOLU airbaig and NSURF surfaces to deallote the structure

Definition at line 34 of file deallocate_igrsurf_split.F.

35!$COMMENT
36! DEALLOCATE_IGRSURF_SPLIT description
37! DEALLOCATE_IGRSURF_SPLIT deallocates the local IGSURF_PROC arrays
38!
39! DEALLOCATE_IGRSURF_SPLIT organization :
40! -loop over NVOLU in order to deallocate the array
41!$ENDCOMMENT
42
43 USE groupdef_mod
45C-----------------------------------------------
46C I m p l i c i t T y p e s
47C-----------------------------------------------
48#include "implicit_f.inc"
49C-----------------------------------------------
50C C o m m o n B l o c k s
51C-----------------------------------------------
52#include "param_c.inc"
53#include "com01_c.inc"
54#include "com04_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58 TYPE(SURF_), DIMENSION(NSURF,NSPMD), INTENT(INOUT) :: IGRSURF_PROC
59 TYPE(MONVOL_STRUCT_), DIMENSION(NVOLU), INTENT(INOUT) :: T_MONVOL
60
61! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
62! IGRSURF_PROC : SURF_ ; dimension=NSURF*NSPMD
63! local surface property array (=IGRSURF for each proc)
64! %ELTYP --> type of element (shell, triangle...)
65! %ELEM --> element id
66! %NSEG --> total element number
67! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER :: NV,IS
72 INTEGER :: PROC,K1
73C-----------------------------------------------------
74C S o u r c e L i n e s
75C-----------------------------------------------------
76 ! --------------------------------------
77 ! Airbag
78 k1 = 1
79 DO nv=1,nvolu ! NVOLU = number of volume
80 is = t_monvol(nv)%EXT_SURFID
81 DO proc=1,nspmd
82 ! several MONVOL can refer to the same surface ID
83 IF(igrsurf_proc(is,proc)%NSEG>0.AND.ALLOCATED(igrsurf_proc(is,proc)%ELTYP) ) THEN
84 DEALLOCATE( igrsurf_proc(is,proc)%ELTYP )
85 DEALLOCATE( igrsurf_proc(is,proc)%ELEM )
86 ENDIF
87 ENDDO
88 k1 = k1 + nimv
89 ! --------------------
90 ! deallocation of NUMBER_TRI_PER_PROC :
91 DEALLOCATE( t_monvol(nv)%NUMBER_TRI_PER_PROC )
92 ! --------------------
93 ENDDO
94 ! --------------------------------------
95
96
97 ! --------------------------------------
98 ! Surface
99 DO is=1,nsurf
100 DO proc=1,nspmd
101 IF(ALLOCATED( igrsurf_proc(is,proc)%LOCAL_SEG )) DEALLOCATE( igrsurf_proc(is,proc)%LOCAL_SEG )
102 IF(ALLOCATED( igrsurf_proc(is,proc)%ELTYP ))DEALLOCATE( igrsurf_proc(is,proc)%ELTYP )
103 IF(ALLOCATED( igrsurf_proc(is,proc)%ELEM ))DEALLOCATE( igrsurf_proc(is,proc)%ELEM )
104 ENDDO
105 ENDDO
106 ! --------------------------------------
107 RETURN