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

Go to the source code of this file.

Functions/Subroutines

subroutine xyznod_crk0 (ilev)
subroutine xyznod_crk (icrk, nfnod_crkxfemg, nodglobxfe)

Function/Subroutine Documentation

◆ xyznod_crk()

subroutine xyznod_crk ( integer icrk,
integer nfnod_crkxfemg,
integer, dimension(*) nodglobxfe )

Definition at line 68 of file xyznod_crk.F.

69C-----------------------------------------------
70 USE crackxfem_mod
71C-----------------------------------------------
72C I m p l i c i t T y p e s
73C-----------------------------------------------
74#include "implicit_f.inc"
75C-----------------------------------------------
76C C o m m o n B l o c k s
77C-----------------------------------------------
78#include "com01_c.inc"
79#include "task_c.inc"
80C-----------------------------------------------
81C D u m m y A r g u m e n t s
82C-----------------------------------------------
83 INTEGER ICRK,NFNOD_CRKXFEMG,NODGLOBXFE(*)
84C-----------------------------------------------
85C L O C A L V A R I A B L E S
86C-----------------------------------------------
87 INTEGER ND,NNODE
88 REAL, DIMENSION(:,:), ALLOCATABLE :: XNODARRAY
89C=======================================================================
90c Write phantom node coordinates to ANIM file
91C-----------------------------------------------
92 IF (nspmd == 1) THEN
93 nnode = crknod(icrk)%CRKNUMNODS
94 ALLOCATE (xnodarray(3,nnode))
95 DO nd=1,nnode
96 xnodarray(1,nd) = crkavx(icrk)%XX(1,nd)
97 xnodarray(2,nd) = crkavx(icrk)%XX(2,nd)
98 xnodarray(3,nd) = crkavx(icrk)%XX(3,nd)
99 END DO
100 CALL write_r_c(xnodarray,3*nnode)
101 DEALLOCATE(xnodarray)
102 ELSE
103 IF (ispmd == 0) THEN
104 CALL spmd_wrt_crk_xyznod(icrk,nfnod_crkxfemg,nodglobxfe)
105 ELSE
106 CALL spmd_wrt_crk_xyznod(icrk,1,nodglobxfe)
107 ENDIF
108 ENDIF
109C-----------
110 RETURN
type(xfem_nodes_), dimension(:), allocatable crknod
type(xfem_avx_), dimension(:), allocatable crkavx
subroutine spmd_wrt_crk_xyznod(icrk, num, nodglobxfe)
void write_r_c(float *w, int *len)

◆ xyznod_crk0()

subroutine xyznod_crk0 ( integer ilev)

Definition at line 30 of file xyznod_crk.F.

31C-----------------------------------------------
32 USE crackxfem_mod
33C-----------------------------------------------
34C I m p l i c i t T y p e s
35C-----------------------------------------------
36#include "implicit_f.inc"
37C-----------------------------------------------
38C D u m m y A r g u m e n t s
39C-----------------------------------------------
40 INTEGER ILEV
41C-----------------------------------------------
42C L O C A L V A R I A B L E S
43C-----------------------------------------------
44 INTEGER ND,IAD
45C=======================================================================
46c Copy phantom node coordinates to work table for crack intersections
47C-----------------------------------------------
48 DO nd=1,crknod(ilev)%CRKNUMNODS
49 iad = crknod(ilev)%NOD2IAD(nd)
50 crkavx(ilev)%XX(1,nd) = crkavx(ilev)%X(1,iad)
51 crkavx(ilev)%XX(2,nd) = crkavx(ilev)%X(2,iad)
52 crkavx(ilev)%XX(3,nd) = crkavx(ilev)%X(3,iad)
53 END DO
54C-----------
55 RETURN