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

Go to the source code of this file.

Functions/Subroutines

subroutine w_failwave (failwave, nodglob, numnod, numnod_l, len_am, itab)

Function/Subroutine Documentation

◆ w_failwave()

subroutine w_failwave ( type (failwave_str_) failwave,
integer, dimension(numnod_l), intent(in) nodglob,
integer, intent(in) numnod,
integer, intent(in) numnod_l,
integer, intent(inout) len_am,
integer, dimension(*) itab )

Definition at line 30 of file w_failwave.F.

31C-----------------------------------------------
32C M o d u l e s
33C-----------------------------------------------
34 USE failwave_mod
35 USE my_alloc_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C D u m m y A r g u m e n t s
42C-----------------------------------------------
43 INTEGER , INTENT(IN) :: NUMNOD,NUMNOD_L
44 INTEGER , INTENT(INOUT) :: LEN_AM
45 INTEGER , DIMENSION(NUMNOD_L) , INTENT(IN) :: NODGLOB
46 TYPE (FAILWAVE_STR_) :: FAILWAVE
47 INTEGER ITAB(*)
48C-----------------------------------------------
49C L o c a l V a r i a b l e s
50C-----------------------------------------------
51 INTEGER I,IWAVE,NNOD,NDDL,SIZE,LEN,NNOD_L,IAD,NG,NL,NN
52 INTEGER, DIMENSION(:), ALLOCATABLE :: INDX_LOC,IDXI_LOC
53 INTEGER, DIMENSION(4) :: HEAD
54 INTEGER, DIMENSION(:), ALLOCATABLE :: RBUF
55C=======================================================================
56 CALL my_alloc(indx_loc,numnod_l)
57 CALL my_alloc(idxi_loc,numnod_l)
58 iwave = failwave%WAVE_MOD
59 nnod = failwave%NNOD
60 nddl = failwave%NDDL
61 SIZE = failwave%SIZE
62c
63 IF (iwave == 0) THEN
64 head(1:4) = 0
65 CALL write_i_c(head,4)
66 len_am = len_am + 4
67c
68 ELSE
69c
70 nnod_l = 0
71 idxi_loc(:) = 0
72 DO i = 1,numnod_l
73 ng = nodglob(i)
74 nn = failwave%IDXI(ng)
75 IF (nn > 0) THEN
76 nnod_l = nnod_l + 1
77 indx_loc(nnod_l) = i
78 idxi_loc(i) = nnod_l
79 ENDIF
80 ENDDO
81c
82 head(1) = iwave
83 head(2) = nddl
84 head(3) = SIZE
85 head(4) = nnod_l
86c
87 CALL write_i_c(head,4)
88 len_am = len_am + 4
89c
90 CALL write_i_c(indx_loc,nnod_l)
91 len_am = len_am + nnod_l
92c
93 CALL write_i_c(idxi_loc,numnod_l)
94 len_am = len_am + numnod_l
95c
96 len = nnod_l*nddl*SIZE + nnod_l
97 ALLOCATE( rbuf(len) )
98 rbuf(:) = 0
99 CALL write_i_c(rbuf,len)
100 len_am = len_am + len
101c---
102 DEALLOCATE( rbuf )
103 ENDIF
104c--------------------------------
105 DEALLOCATE(indx_loc)
106 DEALLOCATE(idxi_loc)
107 RETURN
void write_i_c(int *w, int *len)