OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_nonlocal.F File Reference
#include "implicit_f.inc"
#include "scr17_c.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "units_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_read_nonlocal (mat_param, nloc_dmg, mlaw_tag, ipm, unitab, lsubmodel)

Function/Subroutine Documentation

◆ hm_read_nonlocal()

subroutine hm_read_nonlocal ( type (matparam_struct_), dimension(nummat), intent(inout) mat_param,
type(nlocal_str_) nloc_dmg,
type(mlaw_tag_), dimension(nummat), intent(inout) mlaw_tag,
integer, dimension(npropmi,nummat), intent(inout) ipm,
type (unit_type_), intent(in) unitab,
type (submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 40 of file hm_read_nonlocal.F.

42C-----------------------------------------------
43C M o d u l e s
44C-----------------------------------------------
45 USE unitab_mod
46 USE message_mod
47 USE submodel_mod
50 USE elbuftag_mod
51 USE matparam_def_mod
53C============================================================================
54C I m p l i c i t T y p e s
55C-----------------------------------------------
56#include "implicit_f.inc"
57C-----------------------------------------------
58C C o m m o n B l o c k s
59C-----------------------------------------------
60#include "scr17_c.inc"
61#include "com04_c.inc"
62#include "param_c.inc"
63#include "units_c.inc"
64C-----------------------------------------------
65C D u m m y A r g u m e n t s
66C-----------------------------------------------
67 TYPE(NLOCAL_STR_) :: NLOC_DMG
68 TYPE(MLAW_TAG_), DIMENSION(NUMMAT), INTENT(INOUT) :: MLAW_TAG
69 INTEGER ,DIMENSION(NPROPMI,NUMMAT), INTENT(INOUT) :: IPM
70 TYPE (UNIT_TYPE_) ,INTENT(IN) :: UNITAB
71 TYPE (SUBMODEL_DATA) ,DIMENSION(*) ,INTENT(IN) :: LSUBMODEL
72 TYPE (MATPARAM_STRUCT_) ,DIMENSION(NUMMAT) ,INTENT(INOUT) :: MAT_PARAM
73C-----------------------------------------------
74C L o c a l V a r i a b l e s
75C-----------------------------------------------
76 INTEGER :: INL,FLAGMAT,FLAGUNIT,IUNIT,UID,MAT_ID,IMAT,ILAW,NNLOC
77 my_real :: rlen,le_max
78 CHARACTER(LEN=NCHARTITLE)::TITR
79 LOGICAL IS_AVAILABLE
80C=======================================================================
81 is_available = .false.
82c--------------------------------------------------
83c COUNT NONLOCAL MODELS USING CFG FILES
84c--------------------------------------------------
85c
86 CALL hm_option_count('/NONLOCAL',nnloc)
87 ! Allocation for non-local computation
88 IF ((nnloc > 0).OR.(nloc_dmg%IMOD>0)) THEN
89 nloc_dmg%IMOD = 1
90 IF (.NOT.ALLOCATED(nloc_dmg%LEN)) ALLOCATE(nloc_dmg%LEN(nummat))
91 IF (.NOT.ALLOCATED(nloc_dmg%LE_MAX)) ALLOCATE(nloc_dmg%LE_MAX(nummat))
92 IF (.NOT.ALLOCATED(nloc_dmg%DENS)) ALLOCATE(nloc_dmg%DENS(nummat))
93 IF (.NOT.ALLOCATED(nloc_dmg%DAMP)) ALLOCATE(nloc_dmg%DAMP(nummat))
94 IF (.NOT.ALLOCATED(nloc_dmg%SSPNL)) ALLOCATE(nloc_dmg%SSPNL(nummat))
95 nloc_dmg%LEN(1:nummat) = zero
96 nloc_dmg%LE_MAX(1:nummat) = zero
97 nloc_dmg%DENS(1:nummat) = zero
98 nloc_dmg%DAMP(1:nummat) = zero
99 nloc_dmg%SSPNL(1:nummat) = zero
100 ENDIF
101c
102c--------------------------------------------------
103c START BROWSING NONLOCAL MODELS
104c--------------------------------------------------
105c
106 CALL hm_option_start('/NONLOCAL')
107c
108c--------------------------------------------------
109 DO inl = 1,nnloc
110c
111 CALL hm_option_read_key(lsubmodel,
112 . option_id = mat_id ,
113 . unit_id = uid )
114c--------------------------------------------------
115c Check MAT_ID
116c--------------------------------------------------
117 flagmat = 0
118 ! Loop over materials
119 DO imat=1,nummat-1
120 ! If found
121 IF (mat_id == ipm(1,imat)) THEN
122 flagmat = 1
123 CALL fretitl2(titr,ipm(npropmi-ltitr+1,imat),ltitr)
124 EXIT
125 ENDIF
126 ENDDO
127 IF (mat_id > 0 .AND. flagmat == 0) THEN
128 CALL ancmsg(msgid=1663,anmode=aninfo,msgtype=msgerror,
129 . i1= mat_id, c1='NONLOCAL', c2='NONLOCAL', c3='')
130 cycle
131 ENDIF
132c--------------------------------------------------
133c Check UNIT_ID
134c--------------------------------------------------
135 flagunit = 0
136 DO iunit=1,unitab%NUNITS
137 IF (unitab%UNIT_ID(iunit) == uid) THEN
138 flagunit = 1
139 EXIT
140 ENDIF
141 ENDDO
142 IF (uid > 0 .AND. flagunit == 0) THEN
143 CALL ancmsg(msgid=659, anmode=aninfo, msgtype=msgerror,
144 . i1= mat_id,
145 . i2= uid,
146 . c1='NONLOCAL',
147 . c2='NONLOCAL',
148 . c3= '')
149 ENDIF
150c--------------------------------------------------
151c Read card
152c--------------------------------------------------
153 CALL hm_get_floatv('LENGTH' ,rlen ,is_available, lsubmodel, unitab)
154 CALL hm_get_floatv('LE_MAX' ,le_max ,is_available, lsubmodel, unitab)
155c--------------------------------------------------
156c Check value
157c--------------------------------------------------
158 IF (le_max > zero) THEN
159 ! Save maximal target element length
160 nloc_dmg%LE_MAX(imat) = le_max
161 ! Compute the equivalent non-local internal length
162 CALL get_length(nloc_dmg%LEN(imat),nloc_dmg%LE_MAX(imat))
163 ELSE
164 ! Save the non-local internal length
165 nloc_dmg%LEN(imat) = max(zero,rlen)
166 ! Compute the corresponding maximal target element length
167 CALL get_lemax(nloc_dmg%LE_MAX(imat),nloc_dmg%LEN(imat))
168 ENDIF
169 ! Flag for non-local material
170 mat_param(imat)%NLOC = 1
171 ! Number of the material law
172 ilaw = ipm(2,imat)
173 ! Flag of saving non-local plastic strain and strain rate in buffer
174 mlaw_tag(imat)%G_PLANL = 1
175 mlaw_tag(imat)%L_PLANL = 1
176 mlaw_tag(imat)%G_EPSDNL = 1
177 mlaw_tag(imat)%L_EPSDNL = 1
178c--------------------------------------------------
179c Printout values
180c--------------------------------------------------
181 WRITE(iout,2000) mat_id,ilaw,nloc_dmg%LEN(imat),nloc_dmg%LE_MAX(imat)
182c
183 ENDDO
184c-----------------------------------------
185 2000 FORMAT(/
186 & 5x,' NON-LOCAL REGULARIZATION ',/,
187 & 5x,' ------------------------ ',/,
188 & 5x,'MATERIAL NUMBER . . . . . . . . . . . . . . . =',i10/,
189 & 5x,'MATERIAL LAW . . . . . . . . . . . . . . . . =',i10/,
190 & 5x,'NON-LOCAL INTERNAL LENGTH . . . . . . . . . . =',1pg20.13/,
191 & 5x,'MAXIMAL ELEMENT LENGTH TARGET . . . . . . . . =',1pg20.13/)
192c-----------------------------------------
193 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_option_count(entity_type, hm_option_number)
subroutine hm_option_start(entity_type)
#define max(a, b)
Definition macros.h:21
integer, parameter nchartitle
subroutine get_lemax(le_max, nloc_length)
subroutine get_length(nloc_length, le_max)
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
subroutine fretitl2(titr, iasc, l)
Definition freform.F:804