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

Go to the source code of this file.

Functions/Subroutines

subroutine cnloc_matini (elbuf_str, nel, ipm, bufmat, time, varnl, failure)

Function/Subroutine Documentation

◆ cnloc_matini()

subroutine cnloc_matini ( type(elbuf_struct_), target elbuf_str,
integer nel,
integer, dimension(npropmi,*) ipm,
target bufmat,
time,
varnl,
logical failure )

Definition at line 35 of file cnloc_matini.F.

38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
41 USE elbufdef_mod
42 USE message_mod
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "param_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER NEL
55 TYPE(ELBUF_STRUCT_), TARGET :: ELBUF_STR
57 . varnl(nel,*),bufmat(*),time
58 TARGET :: bufmat
59 INTEGER IPM(NPROPMI,*)
60 LOGICAL :: FAILURE
61C-----------------------------------------------
62C L o c a l V a r i a b l e s
63C-----------------------------------------------
64 INTEGER I,K,IR,IS,IT,IADBUF,NPTT,NPTR,NPTS,
65 . IJ(5),IJ1,IJ2,IJ3,IJ4,IJ5,IPG,
66 . ILAW,IMAT,NUVAR,NUPARAM
67 TYPE(BUF_LAY_), POINTER :: BUFLY
68 TYPE(L_BUFEL_), POINTER :: LBUF
69 TYPE(BUF_MAT_), POINTER :: MBUF
70 TYPE(G_BUFEL_), POINTER :: GBUF
71 my_real,
72 . DIMENSION(:), POINTER :: uparam,uvar,thkn
73C=======================================================================
74 ! Buffer of the first layer
75 bufly => elbuf_str%BUFLY(1)
76 ! General buffer of the elements of the group
77 gbuf => elbuf_str%GBUF
78 ! Global thickness of the shell
79 thkn => gbuf%THK(1:nel)
80C
81 ! Number of integration points in the thickness
82 nptr = elbuf_str%NPTR
83 npts = elbuf_str%NPTS
84 nptt = bufly%NPTT
85 ilaw = bufly%ILAW
86 imat = bufly%IMAT
87 nuvar = bufly%NVAR_MAT
88C
89 ! Material properties and parameters
90 iadbuf = max(1,ipm(7,imat))
91 nuparam = ipm(9,imat)
92 uparam => bufmat(iadbuf:iadbuf+nuparam)
93C
94 DO k=1,5
95 ij(k) = nel*(k-1)
96 ENDDO
97 ij1 = ij(1) + 1
98 ij2 = ij(2) + 1
99 ij3 = ij(3) + 1
100 ij4 = ij(4) + 1
101 ij5 = ij(5) + 1
102C
103 ! Loop over integration points in the plane
104 DO ir = 1,nptr
105 DO is = 1,npts
106 ! Current Gauss point
107 ipg = (is-1)*elbuf_str%NPTR + ir
108 ! Loop over thickness integration points
109 DO it = 1,nptt
110 ! Integration point buffer
111 lbuf => bufly%LBUF(ir,is,it)
112 ! Interval variable buffer
113 uvar => bufly%MAT(ir,is,it)%VAR
114 ! Non-local plastic strain update
115 IF (gbuf%G_PLANL > 0) THEN
116 DO i = 1,nel
117 varnl(i,it) = max(varnl(i,it),zero)
118 lbuf%PLANL(i) = lbuf%PLANL(i) + varnl(i,it)
119 ENDDO
120 ENDIF
121 ! Select the material initialization routine
122 SELECT CASE (ilaw)
123 CASE(104)
124 CALL cnloc_mat104_ini(nel ,ipg ,it ,nuparam ,nuvar ,uparam ,
125 . uvar ,lbuf%PLA ,lbuf%OFF ,lbuf%THK ,gbuf%OFF ,lbuf%SIG(ij1),
126 . lbuf%SIG(ij2),lbuf%SIG(ij3) ,lbuf%SIG(ij4) ,lbuf%SIG(ij5),
127 . thkn ,lbuf%DMG ,nptr ,npts ,nptt ,bufly ,
128 . time ,varnl(1,it),failure)
129 END SELECT
130 ! Plastic strain to regularize
131 IF (gbuf%G_PLANL > 0) THEN
132 DO i = 1,nel
133 varnl(i,it) = lbuf%PLA(i)
134 ENDDO
135 ENDIF
136 ENDDO
137 ENDDO
138 ENDDO
139C-----------
subroutine cnloc_mat104_ini(nel, ipg, ipt, nuparam, nuvar, uparam, uvar, pla, off, thkly, offg, sigoxx, sigoyy, sigoxy, sigoyz, sigozx, thk, dmg, nptr, npts, nptt, bufly, time, varnl, failure)
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21