42
43
44
51 USE matparam_def_mod
53
54
55
56#include "implicit_f.inc"
57
58
59
60#include "scr17_c.inc"
61#include "com04_c.inc"
62#include "param_c.inc"
63#include "units_c.inc"
64
65
66
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
73
74
75
76 INTEGER :: INL,FLAGMAT,FLAGUNIT,IUNIT,UID,MAT_ID,IMAT,ILAW,NNLOC
78 CHARACTER(LEN=NCHARTITLE)::TITR
79 LOGICAL IS_AVAILABLE
80
81 is_available = .false.
82
83
84
85
87
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
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
101
102
103
104
105
107
108
109 DO inl = 1,nnloc
110
112 . option_id = mat_id ,
113 . unit_id = uid )
114
115
116
117 flagmat = 0
118
119 DO imat=1,nummat-1
120
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
132
133
134
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
150
151
152
153 CALL hm_get_floatv(
'LENGTH' ,rlen ,is_available, lsubmodel, unitab)
154 CALL hm_get_floatv(
'LE_MAX' ,le_max ,is_available, lsubmodel, unitab)
155
156
157
158 IF (le_max > zero) THEN
159
160 nloc_dmg%LE_MAX(imat) = le_max
161
162 CALL get_length(nloc_dmg%LEN(imat),nloc_dmg%LE_MAX(imat))
163 ELSE
164
165 nloc_dmg%LEN(imat) =
max(zero,rlen)
166
167 CALL get_lemax(nloc_dmg%LE_MAX(imat),nloc_dmg%LEN(imat))
168 ENDIF
169
170 mat_param(imat)%NLOC = 1
171
172 ilaw = ipm(2,imat)
173
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
178
179
180
181 WRITE(iout,2000) mat_id,ilaw,nloc_dmg%LEN(imat),nloc_dmg%LE_MAX(imat)
182
183 ENDDO
184
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/)
192
193 RETURN
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)
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)