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

Go to the source code of this file.

Functions/Subroutines

subroutine tagnod_r2r_nl (ixc, ixtg, ixs, ixs10, ixs20, ixs16, tag_nlocal, mat_param)

Function/Subroutine Documentation

◆ tagnod_r2r_nl()

subroutine tagnod_r2r_nl ( integer, dimension(nixc,numelc), intent(in) ixc,
integer, dimension(nixtg,numeltg), intent(in) ixtg,
integer, dimension(nixs,numels), intent(in) ixs,
integer, dimension(6,numels10), intent(in) ixs10,
integer, dimension(12,numels20), intent(in) ixs20,
integer, dimension(8,numels16), intent(in) ixs16,
integer, dimension(numnod), intent(inout) tag_nlocal,
type (matparam_struct_), dimension(nummat), intent(in) mat_param )

Definition at line 30 of file tagnod_r2r_nl.F.

31C-----------------------------------------------
32C M o d u l e s
33C-----------------------------------------------
34 USE message_mod
35 USE matparam_def_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "com04_c.inc"
44#include "param_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER, INTENT(IN) :: IXC(NIXC,NUMELC),IXTG(NIXTG,NUMELTG),IXS(NIXS,NUMELS),IXS10(6,NUMELS10),
49 . IXS20(12,NUMELS20),IXS16(8,NUMELS16)
50 INTEGER, INTENT(INOUT) :: TAG_NLOCAL(NUMNOD)
51 TYPE (MATPARAM_STRUCT_) ,DIMENSION(NUMMAT) ,INTENT(IN) :: MAT_PARAM
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 INTEGER I,J,L,MID
56C=======================================================================
57C
58C-----------------------------------------------------------------------------------------------
59c-----Tag of nodes with non local dof-----------------------------------------------------------
60C-----------------------------------------------------------------------------------------------
61C
62C-----------------------------------------------------------------------------------------------
63 DO j=1,numelc
64 mid = ixc(1,j)
65 IF (mat_param(mid)%NLOC > 0)THEN
66 DO l=2,5
67 tag_nlocal(ixc(l,j))=1
68 ENDDO
69 ENDIF
70 ENDDO
71C-----------------------------------------------------------------------------------------------
72 DO j=1,numeltg
73 mid = ixtg(1,j)
74 IF (mat_param(mid)%NLOC > 0)THEN
75 DO l=2,4
76 tag_nlocal(ixtg(l,j))=1
77 ENDDO
78 ENDIF
79 ENDDO
80C-----------
81 DO j=1,numels8
82 mid = ixs(1,j)
83 IF (mat_param(mid)%NLOC > 0)THEN
84 DO l=2,9
85 tag_nlocal(ixs(l,j))=1
86 ENDDO
87 ENDIF
88 ENDDO
89C-----------
90 DO i=1,numels10
91 j = i + numels8
92 mid = ixs(1,j)
93 IF (mat_param(mid)%NLOC > 0)THEN
94 DO l=2,9
95 tag_nlocal(ixs(l,j))=1
96 ENDDO
97 DO l=1,6
98 IF (ixs10(l,i) /= 0) THEN
99 tag_nlocal(ixs10(l,i))=1
100 ENDIF
101 ENDDO
102 ENDIF
103 ENDDO
104C-----------
105 DO i=1,numels20
106 j = i + numels8 + numels10
107 mid = ixs(1,j)
108 IF (mat_param(mid)%NLOC > 0)THEN
109 DO l=2,9
110 tag_nlocal(ixs(l,j))=1
111 ENDDO
112 DO l=1,12
113 IF (ixs20(l,i) /= 0) THEN
114 tag_nlocal(ixs20(l,i))=1
115 ENDIF
116 ENDDO
117 ENDIF
118 ENDDO
119C-----------
120 DO i=1,numels16
121 j = i + numels8 + numels10 + numels20
122 mid = ixs(1,j)
123 IF (mat_param(mid)%NLOC > 0)THEN
124 DO l=2,9
125 tag_nlocal(ixs(l,j))=0
126 ENDDO
127 DO l=1,8
128 IF (ixs16(l,i) /= 0) THEN
129 tag_nlocal(ixs16(l,i))=0
130 ENDIF
131 ENDDO
132 ENDIF
133 ENDDO
134C
135 RETURN
136C