42 1 IPART ,RNOISE ,IPARTC ,IPARTG ,IGRPART ,
43 2 IPM ,PERTURB ,LSUBMODEL,UNITAB ,IDPERTURB,
44 3 INDEX ,INDEX_ITYP,NPART_SHELL,OFFS,QP_IPERTURB,
55 USE format_mod ,
ONLY : lfield
59#include "implicit_f.inc"
71 TYPE (UNIT_TYPE_),
INTENT(IN) ::UNITAB
73 . RNOISE(NPERTURB,NUMELC+NUMELTG+NUMELS+NUMSPH),
74 . QP_RPERTURB(NPERTURB,4)
75 INTEGER IPART(LIPART1,*),IPARTC(*),
76 . ipartg(*),ipm(npropmi,*),
77 . perturb(nperturb),offs,
78 . idperturb(nperturb),index(numelc+numeltg+numels+numsph),
79 . index_ityp(numelc+numeltg+numels+numsph),npart_shell,
80 . qp_iperturb(nperturb,6)
83 TYPE (GROUP_) ,
DIMENSION(NGRPART) :: IGRPART
87 INTEGER I,J,K,NUMA,I_METHOD,MAX_PART,
88 . CPT_PART,NB_RANDOM,I_SEED,DISTRIB(50),
89 . II,NB_INTERV,IGRPRT,N,IOK,SEED,SEED_RANDOM,
90 . ITYP,L,I_PERTURB_VAR,SIZEY,EMPTY
91 CHARACTER(LEN=NCHARTITLE) :: TITR
92 CHARACTER(LEN=NCHARKEY) :: KEY
94 INTEGER,
DIMENSION(:,:),
ALLOCATABLE :: TAB_PART
95 INTEGER,
DIMENSION(:),
ALLOCATABLE :: A_SEED
96 INTEGER,
DIMENSION(1:8) :: DT_SEED
98 . mean,sd,mean_input,sd_input,max_distrib,temp,min_value,
99 . max_value,interv,
VALUE,max_value1,minval,maxval,bid
100 my_real,
DIMENSION(:),
ALLOCATABLE :: array
101 CHARACTER*100 CHAR(100)
102 CHARACTER*100 CHAR1(100)
105 CHARACTER(LEN=NCHARFIELD)::CHVAR
110 DATA mess/
'PERTURBATION DEFINITION '/
119 is_available = .false.
124 DO i=1+offs,npart_shell+offs
129 . option_id = idperturb(i),
130 . option_titr = titr)
142 CALL hm_get_intv(
'grpart_ID' ,igrprt ,is_available,lsubmodel)
144 IF (chvar(1:5) ==
'thick' .OR. chvar(1:5) ==
'THICK') i_perturb_var = 1
148 IF(chvar(k:k) /=
' ') empty = 0
152 IF (i_perturb_var /= 1 .AND. empty == 0)
CALL ancmsg(msgid=1194,
160 IF (igrprt /= 0)
THEN
162 IF (igrpart(n)%ID == igrprt)
THEN
182 . c2=
'GROUP OF PART')
184 cpt_part = igrpart(igrprt)%NENTITY
186 max_part =
max(max_part,cpt_part)
189 ALLOCATE(tab_part(nperturb,max_part))
195 DO i = 1+offs,npart_shell+offs
198 index(1:(numelc+numeltg+numels+numsph)) = 0
199 index_ityp(1:numelc+numeltg+numels+numsph) = 0
204 . option_id = idperturb(i),
205 . option_titr = titr)
211 CALL hm_get_floatv(
'F_Mean' ,mean ,is_available, lsubmodel, unitab)
212 CALL hm_get_floatv(
'Deviation' ,sd ,is_available, lsubmodel, unitab)
213 CALL hm_get_floatv(
'Min_cut' ,minval ,is_available, lsubmodel, unitab)
214 CALL hm_get_floatv(
'Max_cut' ,maxval ,is_available, lsubmodel, unitab)
215 CALL hm_get_intv(
'Seed' ,seed ,is_available, lsubmodel)
216 CALL hm_get_intv(
'Idistri' ,i_method,is_available, lsubmodel)
219 IF(i_method == 0) i_method = 2
220 IF(minval == zero .AND. maxval == zero)
THEN
221 IF(i_method == 1)
THEN
222 ELSEIF(i_method == 2)
THEN
231 qp_iperturb(i,1) = idperturb(i)
232 qp_iperturb(i,2) = ityp
233 qp_iperturb(i,3) = seed
234 qp_iperturb(i,4) = i_method
235 qp_rperturb(i,1) = mean
236 qp_rperturb(i,2) = sd
237 qp_rperturb(i,3) = minval
238 qp_rperturb(i,4) = maxval
246 CALL hm_get_intv(
'grpart_ID',igrprt,is_available,lsubmodel)
247 qp_iperturb(i,5) = igrprt
249 IF (chvar(1:5) ==
'thick' .OR. chvar(1:5) ==
'THICK') qp_iperturb(i,6) = 1
251 ! checking shell part group
252 IF (igrprt /= 0)
THEN
254 IF (igrpart(n)%ID == igrprt)
THEN
266 DO j=1,igrpart(igrprt)%NENTITY
267 cpt_part = cpt_part + 1
268 numa = igrpart(igrprt)%ENTITY(j)
269 tab_part(i,cpt_part) = numa
274 IF(i_method == 2)
THEN
276 . idperturb(i),
'GAUSSIAN',mean_input,sd_input,seed
277 WRITE (iout,
'(10I10)') ipart(4,tab_part(i,1:cpt_part))
280 ELSEIF(i_method == 1)
THEN
282 . idperturb(i),
'RANDOM',seed
283 WRITE (iout,
'(10I10)') ipart(4,tab_part(i,1:cpt_part))
292 IF (ipartc(ii) == tab_part(i,k))
THEN
293 nb_random = nb_random + 1
294 index(nb_random) = ii
295 index_ityp(nb_random) = 3
301 IF(ipartg(ii) == tab_part(i,k))
THEN
302 nb_random = nb_random + 1
303 index(nb_random) = ii
304 index_ityp(nb_random) = 7
311 CALL random_seed(size=i_seed)
312 ALLOCATE(a_seed(1:i_seed))
313 CALL random_seed(get=a_seed)
314 CALL date_and_time(values=dt_seed)
315 a_seed=dt_seed(8)*dt_seed(7)*dt_seed(6)
316 seed=dt_seed(8)*dt_seed(7)*dt_seed(6)
317 CALL random_seed(put=a_seed)
321 CALL random_seed(size=i_seed)
322 ALLOCATE(a_seed(1:i_seed))
324 CALL random_seed(put=a_seed)
334 ALLOCATE(array(nb_random+2))
335 CALL random_number(array)
340 IF ( i_method == 2)
THEN
341 DO ii = 1, nb_random+1, 2
342 temp = sd * sqrt(-2.0*log(array(ii))) * cos(2*pi*array(ii+1)) +
345 . sd * sqrt(-2.0*log(array(ii))) * sin(2*pi*array(ii+1)) + mean
349 array(ii) =
max(
min(maxval,array(ii)),minval)
350 max_value =
max(array(ii),max_value)
351 min_value =
min(array(ii),min_value)
353 ELSEIF(i_method == 1)
THEN
355 array(ii) = array(ii)*(maxval-minval)+minval
356 max_value =
max(array(ii),max_value)
357 min_value =
min(array(ii),min_value)
363 IF (index_ityp(ii) == 3)
THEN
364 rnoise(i,index(ii)) = array(ii)
365 ELSEIF (index_ityp(ii) == 7)
THEN
366 rnoise(i,index(ii)+numelc) = array(ii)
371 mean = sum(array)/nb_random
372 sd = sqrt(sum((array - mean)**2)/nb_random)
375 IF(i_method == 2)
THEN
376 max_distrib = one /(sd*sqrt(two * pi))
377 ELSEIF(i_method == 1)
THEN
378 max_distrib = one /(max_value-min_value)
384 IF (minval /= -ep30 .AND. maxval /= ep30)
THEN
388 CALL plot_distrib( array,nb_random, nb_interv,sizey,min_value,
389 . max_value,max_distrib,
'#')
390 IF(i_method == 2)
THEN
391 WRITE (iout,2000) mean,sd
392 ELSEIF(i_method == 1)
THEN
393 WRITE (iout,2050) mean
395 IF(seed_random == 1)
WRITE (iout,2100) seed
398 IF (
ALLOCATED(array))
DEALLOCATE(array)
402 1000
FORMAT(/
' PERTURBATION ID',i10/
403 +
' ---------------'/
404 +
' TYPE . . . . . . . . . . . . . . .',a/
405 +
' INPUT MEAN VALUE . . . . . . . . .',1pg20.13/
406 +
' INPUT STANDARD DEVIATION . . . . .',1pg20.13/
407 +
' INPUT SEED VALUE . . . . . . . . .',i10/
408 +
' SHELL THICKNESSES, PARTS:')
409 1100
FORMAT(/
' PERTURBATION ID',i10/
410 +
' ---------------'/
411 +
' TYPE . . . . . . . . . . . . . . .',a/
412 +
' INPUT SEED VALUE . . . . . . . . .',i10/
413 +
' SHELL THICKNESSES, PARTS:')
416 +
' GENERATED MEAN VALUE . . . . . . .',1pg20.13/
417 +
' GENERATED STANDARD DEVIATION . . .',1pg20.13)
419 +
' GENERATED MEAN VALUE . . . . . . .',1pg20.13)
421 +
' GENERATED SEED VALUE . . . . . . .',i10/)
424 +
' DISTRIBUTION OF SCALE FACTORS APPLIED TO THICKNESSES OF SHELLS')
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)