Skip to content

Commit 49b341d

Browse files
committed
manual updates and hcp corrections
1 parent 7b5c015 commit 49b341d

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

42 files changed

+3282173
-41497
lines changed

.gitignore

+2-1
Original file line numberDiff line numberDiff line change
@@ -13,12 +13,13 @@ xs_convert/*
1313
flux_convert/*
1414
manual/*.ps
1515
manual/*.dvi
16-
manual/*converted-to.pdf
16+
manual/figures/*converted-to.pdf
1717
manual/test/*.indexes
1818
manual/test/*.out
1919
manual/test/spectra-pka*
2020
data/*
2121
manual/*synctex
22+
manual/*synctex.gz
2223
manual/test/plot_example/*.ps
2324
Makefile2
2425
spectra-pka.dSYM/*

bca.f90

+11-8
Original file line numberDiff line numberDiff line change
@@ -129,9 +129,9 @@ SUBROUTINE sdtrim_run(ke,direction_vec,ievent,pos_vec,pkaelement,itime,done_bca)
129129
CHARACTER (LEN=500) :: commandstring
130130
LOGICAL, intent(out) :: done_bca
131131

132-
! skip unless above min energy
132+
! skip unless above min energy=threshold energy
133133

134-
IF(ke.GE.min_pka_energy) THEN
134+
IF(ke.GE.assumed_ed) THEN
135135
CALL triinpwrite(ke,pkaelement)
136136

137137
write(commandstring,*) TRIM(ADJUSTL(sdtrim_path))//' >tri.cmd.out'
@@ -155,16 +155,18 @@ SUBROUTINE sdtrim_run(ke,direction_vec,ievent,pos_vec,pkaelement,itime,done_bca)
155155
CALL system(sdstr)
156156

157157

158-
done_bca=.true.
159-
ELSE
160-
done_bca=.false.
158+
159+
160+
161161

162-
END IF ! above threshold
162+
END IF
163163

164-
164+
done_bca=.true.
165165

166166
!STOP
167-
END IF
167+
ELSE
168+
done_bca=.false.
169+
END IF ! above threshold
168170

169171

170172
END SUBROUTINE sdtrim_run
@@ -224,6 +226,7 @@ SUBROUTINE read_bca(ievent,direction_vec,pos_vec,itime)
224226

225227
!17/9/2019 - as standard we will skip if below the displacement threshold
226228
! this time it will be the full displacement thresh (not the PKA min)
229+
![ update 3/1/2020 - now we don't intiate bca unless above threshold]
227230
! atom will not be displaced (and thus won't contribute to damage) if
228231
! below E_d
229232
IF(histene.LT.assumed_ed) cycle fileread

create_configs.f90

+1-10
Original file line numberDiff line numberDiff line change
@@ -258,7 +258,6 @@ SUBROUTINE create_configs
258258
IF(choice==pka_events_id(ievent)) foundi=ievent
259259
ievent=ievent+1
260260
END DO
261-
!PRINT *,'here',choice,ievent,pka_events_id(ievent),foundi,num_events
262261

263262
IF(foundi.LE.num_events) THEN
264263
IF((pka_events_mass(foundi)==config_parent_nums(ichannel)).AND. &
@@ -271,7 +270,6 @@ SUBROUTINE create_configs
271270
! (it has already been selected at random, so this is OK)
272271
! provided we have not reached the maximum for the parent atom type
273272
! first see if it (the parent) is one of the input types (must be)
274-
!PRINT *,'here',number_pka_files
275273
ifiles=1
276274
DO
277275
IF(ifiles.GT.number_pka_files) cycle choiceloop ! shouldn't happen
@@ -281,7 +279,6 @@ SUBROUTINE create_configs
281279
(TRIM(ADJUSTL(parent_ele(ifiles)))==TRIM(ADJUSTL(config_parent_eles(ichannel))))) EXIT
282280
ifiles=ifiles+1
283281
END DO
284-
!PRINT *,'here2',ifiles,initial_atom_types_count(ifiles),REAL(natoms,DBL)*pka_ratios(ifiles)
285282
IF(initial_atom_types_count(ifiles).GE.NINT(REAL(natoms,DBL)*pka_ratios(ifiles))) THEN
286283
! cannot have any more target atoms of this type
287284
! need to cycle and find one already defined
@@ -334,7 +331,6 @@ SUBROUTINE create_configs
334331
END IF
335332
ienergy=ienergy+1
336333
END DO
337-
!PRINT *,ienergy,ireal,SUM(config_pka_vectors(ichannel,1:ienergy)),total_channelpkas
338334

339335

340336
CALL random_number(ireal)
@@ -471,7 +467,6 @@ SUBROUTINE create_configs
471467
END IF
472468
ienergy=ienergy+1
473469
END DO
474-
!write(701,*) jevent,ievent,ienergy,jenergy,pka_min_sep(jevent,:),pka_min_sep(ievent,:)
475470
DO ii=1,MIN(ienergy,jenergy)
476471
! can contribute to all bins up to lowest PKA energy
477472
total_sep_dist(ii)=total_sep_dist(ii)+sqrt(current_sep)
@@ -487,7 +482,6 @@ SUBROUTINE create_configs
487482
pka_min_sep(jevent,2*ii)=REAL(pka_events_id(ievent),DBL)
488483
END IF
489484
END DO
490-
!write(701,*) jevent,ievent,ienergy,jenergy,pka_min_sep(jevent,:),pka_min_sep(ievent,:)
491485

492486

493487
END DO ! ievent
@@ -515,9 +509,7 @@ SUBROUTINE create_configs
515509
NINT(pka_min_sep(MINLOC(pka_min_sep(1:num_events,1)),2)), &
516510
TRIM(outstr)
517511

518-
!PRINT *,pka_min_sep(1:num_events,1)
519-
!PRINT *,pka_events_id(1:num_events)
520-
!write(700,*) num_events,event_dist
512+
521513
ELSE
522514
jenergy=1
523515
jevent=1
@@ -559,7 +551,6 @@ SUBROUTINE create_configs
559551
ireal=sqrt(DOT_PRODUCT(pka_events_vec(ievent,1:3),pka_events_vec(ievent,1:3)))* &
560552
sqrt(2._DBL*ke*1000._DBL/(pka_events_mass(ievent)*avogadro))
561553

562-
563554
write(pka_events,'(x,I19,3F20.5,3ES20.5,2x,A15,3x,I15,5x,I20,2ES20.9,I10,3ES20.5)') &
564555
pka_events_id(ievent),jrealvector,pka_events_vec(ievent,:)/ireal, &
565556
pka_events_ele(ievent),pka_events_mass(ievent), &

create_hcp.f90

+20-6
Original file line numberDiff line numberDiff line change
@@ -41,10 +41,17 @@ SUBROUTINE create_hcp()
4141
x(ijk,1)=latt*REAL(i,DBL)-latt*(REAL(j,DBL))*sin(pi/6._DBL)
4242
x(ijk,2)=latt*REAL(j,DBL)*cos(pi/6._DBL)
4343
x(ijk,3)=latt*sqrt(3.0_DBL)*REAL(k,DBL)
44+
45+
46+
!3/1/2020 - in a hcpb lattice, the x coordinates with the
47+
! above definition will be negative for large j (see bk 14)
48+
! since this is a perfect box, we should shift as required
49+
IF (x(ijk,1).LT.0._DBL) THEN
50+
x(ijk,1)=x(ijk,1)+lx(1)
51+
END IF
4452
! tests
4553
!CALL define_atom_position_hcp(ijk,ww)
46-
!write(111,*) ijk,i,j,k,x(ijk,:)
47-
54+
!write(111,*) ijk,i,j,k,x(ijk,:)
4855

4956
! in a hcp lattice there is only one more atom in each unit cell:
5057
! at (2/3,1/3,0.5)
@@ -54,8 +61,11 @@ SUBROUTINE create_hcp()
5461
latt*(REAL(j,DBL)+1._DBL/3._DBL)*sin(pi/6._DBL)
5562
x(ijk,2)=latt*(REAL(j,DBL)+1._DBL/3._DBL)*cos(pi/6._DBL)
5663
x(ijk,3)=latt*sqrt(3.0_DBL)*(REAL(k,DBL)+0.5_DBL)
57-
!CALL define_atom_position_hcp(ijk,ww)
58-
!write(111,*) ijk,i,j,k,x(ijk,:)
64+
65+
IF (x(ijk,1).LT.0._DBL) THEN
66+
x(ijk,1)=x(ijk,1)+lx(1)
67+
END IF
68+
5969
end do
6070
end do
6171
end do
@@ -102,8 +112,12 @@ SUBROUTINE define_atom_position_hcp(nn,xx)
102112

103113
xx(3)=latt*sqrt(3.0_DBL)*(REAL(k,DBL)+REAL(mod(nn-1,2),DBL)*0.5_DBL)
104114

105-
!write(111,*) nn,i,j,k,xx
106-
115+
!3/1/2020 - in a hcp lattice, the x coordinates with the
116+
! above definition will be negative for large j (see bk 14)
117+
! since this is a perfect box, we should shift as required
118+
IF (xx(1).LT.0._DBL) THEN
119+
xx(1)=xx(1)+lx(1)
120+
END IF
107121

108122
END SUBROUTINE define_atom_position_hcp
109123

manual/bca_test/ZR.in

+43
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
flux_filename="fluxes_specter.dat"
2+
results_stub="ZR"
3+
num_columns=6
4+
columns= pka_filename pka_ratios parent_ele parent_num ngamma_parent_mass ngamma_daughter_mass
5+
"example_data/Zr090s.asc" 0.51450000 Zr 90 89.904697659 90.905639587
6+
"example_data/Zr091s.asc" 0.11220000 Zr 91 90.905639587 91.905034675
7+
"example_data/Zr092s.asc" 0.17150000 Zr 92 91.905034675 92.906469947
8+
"example_data/Zr094s.asc" 0.17380000 Zr 94 93.906310828 94.908038530
9+
"example_data/Zr096s.asc" 0.02800000 Zr 96 95.908271433 96.910951206
10+
flux_norm_type=2
11+
pka_filetype=2
12+
do_mtd_sums=.true.
13+
do_ngamma_estimate=.t.
14+
do_global_sums=.t.
15+
do_exclude_light_from_total=.t.
16+
number_pka_files=5
17+
flux_rescale_value=3.25e14
18+
max_global_recoils=400
19+
energies_once_perfile=.t.
20+
do_tdam=.t.
21+
assumed_ed=40.0
22+
23+
do_user_output_energy_grid=.true.
24+
user_energybin_file="outenergies_1keV.dat"
25+
user_grid_option=3
26+
27+
28+
do_timed_configs=.t.
29+
config_max_pka_vectors=10
30+
config_do_exclude_light_pkas=.t.
31+
32+
33+
nsteps=100
34+
timestep=1
35+
box_nunits=500
36+
do_output_configs=.f.
37+
38+
overlap_stop=.false.
39+
do_store_bca_output=.f.
40+
latt=3.232
41+
box_type=3
42+
sdtrim_path="/work/SDTrimSP/src/SDTrimSP"
43+
do_bca=.t.

manual/bca_test/energy_analyse.dat

+129
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,129 @@
1+
SDTrimSP: VERSION 5.06 03.01.2020
2+
------------------------------------------------------
3+
4+
ENERGY ANALYSE PROJECTLE( 1):
5+
NUC.LOSS (<ED): 0.1157 keV
6+
NUC.LOSS (>ED): 0.3166 keV
7+
E(TRANSFER)-E_BULK: 0.3764 keV (Energie of recoils first generation)
8+
--------------------
9+
sum NUC.LOSS: 0.4323 keV
10+
11+
NUCL.LOSS : -0.4448 keV
12+
ELECT.LOSS : -0.0402 keV
13+
E_BACK : -0.0000 keV
14+
E_TRAN : -0.0000 keV
15+
E_STOP : -0.0176 keV
16+
E_SBE : -0.0000 keV
17+
--------------------
18+
sum ENERGY : -0.5027 keV
19+
20+
E_TOT : 0.5027 keV
21+
E_INPUT : 0.5027 keV from outside E0*NH (*NR)
22+
23+
ENERGY ANALYSE PARTICLE( 2):
24+
NUC.LOSS (<ED): 0.2388 keV
25+
NUC.LOSS (>ED): 0.0479 keV
26+
--------------------
27+
sum NUC.LOSS: 0.2867 keV
28+
29+
NUCL.LOSS : -0.2867 keV
30+
ELECT.LOSS : -0.0125 keV
31+
E_BACK : -0.0000 keV
32+
E_TRAN : -0.0000 keV
33+
E_STOP : -0.0629 keV
34+
E_SBE : -0.0000 keV
35+
--------------------
36+
sum ENERGY : -0.3621 keV
37+
38+
E_TOT : 0.3621 keV from projectiles and recoils
39+
E_INPUT : 0.1385 keV from projectiles
40+
41+
ENERGY ANALYSE PARTICLE( 3):
42+
NUC.LOSS (<ED): 0.0709 keV
43+
NUC.LOSS (>ED): 0.0525 keV
44+
--------------------
45+
sum NUC.LOSS: 0.1235 keV
46+
47+
NUCL.LOSS : -0.1235 keV
48+
ELECT.LOSS : -0.0060 keV
49+
E_BACK : -0.0000 keV
50+
E_TRAN : -0.0000 keV
51+
E_STOP : -0.0237 keV
52+
E_SBE : -0.0000 keV
53+
--------------------
54+
sum ENERGY : -0.1532 keV
55+
56+
E_TOT : 0.1532 keV from projectiles and recoils
57+
E_INPUT : 0.0000 keV from projectiles
58+
59+
ENERGY ANALYSE PARTICLE( 4):
60+
NUC.LOSS (<ED): 0.0859 keV
61+
NUC.LOSS (>ED): 0.1043 keV
62+
--------------------
63+
sum NUC.LOSS: 0.1902 keV
64+
65+
NUCL.LOSS : -0.1902 keV
66+
ELECT.LOSS : -0.0104 keV
67+
E_BACK : -0.0000 keV
68+
E_TRAN : -0.0000 keV
69+
E_STOP : -0.0373 keV
70+
E_SBE : -0.0000 keV
71+
--------------------
72+
sum ENERGY : -0.2379 keV
73+
74+
E_TOT : 0.2379 keV from projectiles and recoils
75+
E_INPUT : 0.2379 keV from projectiles
76+
77+
ENERGY ANALYSE PARTICLE( 5):
78+
NUC.LOSS (<ED): 0.0351 keV
79+
NUC.LOSS (>ED): 0.0415 keV
80+
--------------------
81+
sum NUC.LOSS: 0.0766 keV
82+
83+
NUCL.LOSS : -0.0766 keV
84+
ELECT.LOSS : -0.0018 keV
85+
E_BACK : -0.0000 keV
86+
E_TRAN : -0.0000 keV
87+
E_STOP : -0.0032 keV
88+
E_SBE : -0.0000 keV
89+
--------------------
90+
sum ENERGY : -0.0816 keV
91+
92+
E_TOT : 0.0816 keV from projectiles and recoils
93+
E_INPUT : 0.0000 keV from projectiles
94+
95+
ENERGY ANALYSE PARTICLE( 6):
96+
NUC.LOSS (<ED): 0.0000 keV
97+
NUC.LOSS (>ED): 0.0000 keV
98+
--------------------
99+
sum NUC.LOSS: 0.0000 keV
100+
101+
NUCL.LOSS : -0.0000 keV
102+
ELECT.LOSS : -0.0000 keV
103+
E_BACK : -0.0000 keV
104+
E_TRAN : -0.0000 keV
105+
E_STOP : -0.0000 keV
106+
E_SBE : -0.0000 keV
107+
--------------------
108+
sum ENERGY : -0.0000 keV
109+
110+
E_TOT : 0.0000 keV from projectiles and recoils
111+
E_INPUT : 0.0000 keV from projectiles
112+
113+
ENERGY ANALYSE PARTICLE(all):
114+
NUC.LOSS (<ED): 0.4308 keV
115+
NUC.LOSS (>ED): 0.2461 keV
116+
--------------------
117+
sum NUC.LOSS: 0.6769 keV
118+
119+
NUCL.LOSS : -0.6769 keV
120+
ELECT.LOSS : -0.0307 keV
121+
E_BACK : -0.0000 keV
122+
E_TRAN : -0.0000 keV
123+
E_STOP : -0.1271 keV
124+
E_SBE : -0.0000 keV
125+
--------------------
126+
sum ENERGY : -0.8347 keV
127+
128+
E_TOT : 0.8347 keV from projectiles and recoils
129+
E_INPUT : 0.3764 keV from projectiles

0 commit comments

Comments
 (0)