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

Go to the source code of this file.

Functions/Subroutines

subroutine law112_upd (titr, uparam, npc, pld, numtabl, itable, table, mat_id)

Function/Subroutine Documentation

◆ law112_upd()

subroutine law112_upd ( character(len=nchartitle) titr,
uparam,
integer, dimension(*) npc,
pld,
integer numtabl,
integer, dimension(numtabl) itable,
type(ttable), dimension(ntable) table,
integer mat_id )

Definition at line 33 of file law112_upd.F.

35C-----------------------------------------------
36C M o d u l e s
37C-----------------------------------------------
38 USE message_mod
39 USE table_mod
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "com04_c.inc"
49C-----------------------------------------------
50C D u m m y A r g u m e n t s
51C-----------------------------------------------
52 CHARACTER(LEN=NCHARTITLE) :: TITR
53 INTEGER MAT_ID,NUMTABL,ITABLE(NUMTABL)
54 INTEGER NPC(*)
55 my_real uparam(*),pld(*)
56 TYPE(TTABLE), DIMENSION(NTABLE) :: TABLE
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I,K,ITAB
61 my_real slopemin,dx,dy
62C=======================================================================
63 ! Recovering tabulated flag
64 itab = nint(uparam(14))
65c
66 ! Checking yield stress functions slope
67 IF (itab > 0) THEN
68 DO i = 1,numtabl
69 slopemin = infinity
70 DO k = 2,SIZE(table(itable(i))%X(1)%VALUES)
71 dx = table(itable(i))%X(1)%VALUES(k) - table(itable(i))%X(1)%VALUES(k-1)
72 dy = table(itable(i))%Y%VALUES(k) - table(itable(i))%Y%VALUES(k-1)
73 slopemin = min(slopemin,dy/dx)
74 ENDDO
75 IF (slopemin < zero) THEN
76 CALL ancmsg(msgid=2059 ,
77 . msgtype=msgerror,
78 . anmode=aninfo_blind_2,
79 . i1=mat_id,
80 . i2=table(itable(i))%NOTABLE,
81 . c1=titr)
82 ENDIF
83 ENDDO
84 ENDIF
85c-----------
86 RETURN
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
integer, parameter nchartitle
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889