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

Go to the source code of this file.

Functions/Subroutines

subroutine nlocal_init_sta (elbuf_tab, nloc_dmg, iparg, ixc, ixs, ixtg, area, x, xrefs, xrefc, xreftg, ipm, bufmat)

Function/Subroutine Documentation

◆ nlocal_init_sta()

subroutine nlocal_init_sta ( type(elbuf_struct_), dimension(ngroup), target elbuf_tab,
type (nlocal_str_), target nloc_dmg,
integer, dimension(nparg,ngroup) iparg,
integer, dimension(nixc,*) ixc,
integer, dimension(nixs,*) ixs,
integer, dimension(nixtg,*) ixtg,
intent(in) area,
x,
xrefs,
xrefc,
xreftg,
integer, dimension(npropmi,*) ipm,
bufmat )

Definition at line 34 of file nlocal_init_sta.F.

38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
41 USE elbufdef_mod
42 USE message_mod
44 USE message_mod
45C-----------------------------------------------
46C I m p l i c i t T y p e s
47C-----------------------------------------------
48#include "implicit_f.inc"
49C-----------------------------------------------
50C C o m m o n B l o c k s
51C-----------------------------------------------
52#include "param_c.inc"
53#include "com01_c.inc"
54#include "com04_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58 TYPE(ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
59 TYPE (NLOCAL_STR_) , TARGET :: NLOC_DMG
60 INTEGER IPARG(NPARG,NGROUP),IXS(NIXS,*),IXC(NIXC,*),IXTG(NIXTG,*),
61 . IPM(NPROPMI,*)
62 my_real ,DIMENSION(NUMELC+NUMELTG),INTENT(IN) ::
63 . area
65 . x(3,*),xrefc(4,3,*),xreftg(3,3,*),xrefs(8,3,*),bufmat(*)
66C-----------------------------------------------
67C L o c a l V a r i a b l e s
68C-----------------------------------------------
69 LOGICAL :: CONVERGED,FAILURE
70 INTEGER :: L_NLOC,NG,ILOC,NEL,NFT,ITY,FORMU
72 . dt_nl,time,norm_1,norm,d
73 my_real,
74 . PARAMETER :: tol1 = 5.0d-4
75 my_real,
76 . PARAMETER :: tol2 = 1.0d-8
77 my_real,
78 . DIMENSION(:), POINTER :: fnl,unl,vnl,dnl,mnl
79
80 ! Initialization of the convergence flag
81 converged = .false.
82 ! Initialization of the failure flag
83 failure = .false.
84 ! Size of the non-local vectors
85 l_nloc = nloc_dmg%L_NLOC
86 ! Pointing the non-local forces vector
87 fnl => nloc_dmg%FNL(1:l_nloc,1)
88 vnl => nloc_dmg%VNL(1:l_nloc)
89 dnl => nloc_dmg%DNL(1:l_nloc)
90 unl => nloc_dmg%UNL(1:l_nloc)
91 mnl => nloc_dmg%MASS(1:l_nloc)
92 ! Initialization of the non-local time step
93 dt_nl = hundred
94 fnl = zero
95 vnl = zero
96 dnl = zero
97 unl = zero
98 time = zero
99 ! Loop of the initialization
100 DO WHILE (.NOT.converged)
101 ! Loop over the element groups
102 DO ng = 1,ngroup
103 ! Non-local flag
104 iloc = iparg(78,ng)
105 ! If the group is non-local
106 IF (iloc>0) THEN
107 ! Number of elements in the group
108 nel = iparg(2,ng)
109 ! NFT value
110 nft = iparg(3,ng)
111 ! Type of elements
112 ity = iparg(5,ng)
113 ! Formulation of the element
114 formu = iparg(23,ng)
115 ! If the elements are shells
116 IF (ity == 3) THEN
117 IF ((formu>10).AND.(formu<29)) THEN
118 CALL cbafint_reg_ini(elbuf_tab,nloc_dmg ,area ,ixc ,
119 . dt_nl ,x ,xrefc ,nft ,
120 . nel ,ng ,ipm ,bufmat ,
121 . time ,failure )
122 ELSE
123 CALL cfint_reg_ini(elbuf_tab,nloc_dmg ,area ,ixc ,
124 . dt_nl ,x ,xrefc ,nft ,
125 . nel ,ng ,ipm ,bufmat ,
126 . time ,failure )
127 ENDIF
128 ELSEIF (ity == 7) THEN
129 IF ((formu==1).OR.(formu==2)) THEN
130 CALL c3fint_reg_ini(elbuf_tab,nloc_dmg ,area ,ixtg ,
131 . dt_nl ,x ,xreftg ,nft ,
132 . nel ,ng ,ipm ,bufmat ,
133 . time ,failure )
134 ELSEIF ((formu==30).OR.(formu==31)) THEN
135 CALL cdkfint_reg_ini(elbuf_tab,nloc_dmg ,area ,ixtg ,
136 . dt_nl ,x ,xreftg ,nft ,
137 . nel ,ng ,ipm ,bufmat ,
138 . time ,failure )
139 ENDIF
140 ENDIF
141 ENDIF
142 ENDDO
143 ! Computation of the accelerations
144 fnl = fnl / mnl
145 ! Computation of the velocities
146 vnl = vnl + dt_nl*fnl
147 ! Resetting the forces
148 fnl = zero
149 ! Norm of the previous increment
150 norm_1 = sqrt(dot_product(dnl,dnl))
151 ! Computation of the increments
152 dnl = dt_nl*vnl
153 ! Norm of the current increment
154 norm = sqrt(dot_product(dnl,dnl))
155 ! Computation of the cumulated variable
156 unl = unl + dnl
157 ! Convergence criterion
158 converged = ((norm<tol1).AND.(abs(norm-norm_1)<tol2).AND.(time/=zero))
159 d = (sqrt(dot_product(dnl,dnl)))
160 IF (d .NE. d) THEN
161 CALL ancmsg(msgid=1765,msgtype=msgerror,
162 . anmode=aninfo_blind_1)
163 EXIT
164 ENDIF
165 ! Updating time
166 time = time + dt_nl
167 ENDDO
168 ! Resetting the non-local vectors
169 fnl = zero
170 vnl = zero
171 dnl = zero
172 ! Checking failure
173 IF (failure) THEN
174 CALL ancmsg(msgid=1767,msgtype=msgwarning,
175 . anmode=aninfo_blind_1)
176 ENDIF
177c-----------
subroutine c3fint_reg_ini(elbuf_tab, nloc_dmg, area, ixtg, dt_nl, x, xreftg, nft, nel, ng, ipm, bufmat, time, failure)
subroutine cbafint_reg_ini(elbuf_tab, nloc_dmg, area, ixc, dt_nl, x, xrefc, nft, nel, ng, ipm, bufmat, time, failure)
subroutine cdkfint_reg_ini(elbuf_tab, nloc_dmg, area, ixtg, dt_nl, x, xreftg, nft, nel, ng, ipm, bufmat, time, failure)
subroutine cfint_reg_ini(elbuf_tab, nloc_dmg, area, ixc, dt_nl, x, xrefc, nft, nel, ng, ipm, bufmat, time, failure)
#define my_real
Definition cppsort.cpp:32
norm(diag(diag(diag(inv(mat))) -id.SOL), 2) % destroy mumps instance id.JOB
subroutine area(d1, x, x2, y, y2, eint, stif0)
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