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

Go to the source code of this file.

Functions/Subroutines

subroutine w_llink (nnlink, lllink, nodlocal, proc, nllink_l, len_ia)

Function/Subroutine Documentation

◆ w_llink()

subroutine w_llink ( integer, dimension(10,*) nnlink,
integer, dimension(*) lllink,
integer, dimension(*) nodlocal,
integer proc,
integer nllink_l,
integer len_ia )

Definition at line 31 of file w_llink.F.

33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "com04_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER PROC,NLLINK_L,LEN_IA,
49 . NNLINK(10,*), LLLINK(*), NODLOCAL(*)
50C-----------------------------------------------
51C F u n c t i o n
52C-----------------------------------------------
53 INTEGER NLOCAL
54 EXTERNAL nlocal
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER I, J, K, KL, NL, N, NLL
59 INTEGER, DIMENSION(:), ALLOCATABLE :: LLLTMP
60 INTEGER, DIMENSION(:,:), ALLOCATABLE :: NNLTMP
61C
62! ----------------------
63! allocate 1d array
64 ALLOCATE( llltmp(nllink_l) )
65! allocate 2d array
66 ALLOCATE( nnltmp(10,nlink) )
67! ----------------------
68 k = 0
69 kl = 0
70 DO i = 1, nlink
71 nl = nnlink(1,i)
72 DO j = 1, 10
73 nnltmp(j,i) = nnlink(j,i)
74 ENDDO
75 nll = 0
76 DO j = 1, nl
77 n = lllink(k+j)
78 IF (nlocal(n,proc+1)==1)THEN
79 nll = nll + 1
80 llltmp(kl+nll) = nodlocal(n)
81 ENDIF
82 ENDDO
83 kl = kl + nll
84 k = k + nl
85 nnltmp(1,i) = nll
86 ENDDO
87C
88 CALL write_i_c(nnltmp,10*nlink)
89 CALL write_i_c(llltmp,nllink_l)
90 len_ia = len_ia + nllink_l + 10*nlink
91C
92! ----------------------
93! deallocate 1d array
94 DEALLOCATE( llltmp )
95! deallocate 2d array
96 DEALLOCATE( nnltmp )
97! ----------------------
98 RETURN
integer function nlocal(n, p)
Definition ddtools.F:349
character *2 function nl()
Definition message.F:2354
void write_i_c(int *w, int *len)