ESPUTR
calculation of sputtering yields
esputr2001_test.f90
Go to the documentation of this file.
1 
5 
6 ! Copyright (c) 2016 Forschungszentrum Juelich GmbH
7 ! Markus Brenneis, Vladislav Kotov
8 !
9 ! This file is part of ESPUTR.
10 !
11 ! ESPUTR is free software: you can redistribute it and/or modify
12 ! it under the terms of the GNU General Public License as published by
13 ! the Free Software Foundation, either version 3 of the License, or
14 ! (at your option) any later version.
15 !
16 ! ESPUTR is distributed in the hope that it will be useful,
17 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
18 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19 ! GNU General Public License for more details.
20 !
21 ! You should have received a copy of the GNU General Public License
22 ! along with ESPUTR. If not, see <http://www.gnu.org/licenses/>.
23 !
24 
26  use esputr
27  use esputr_test
28  use esputr2001
29  implicit none
30  public esputr2001_test_n
39  public esputr2001_test_eth
43 
44  private
45 
46  integer :: i_
48  character(*), parameter :: sputer2001_n_fitvalues_file = "../data/ECKSTEIN2007N"
49  character(*), parameter :: sputer2001_th_fitvalues_file = "../data/ECKSTEIN2007TH"
51  integer, parameter :: n_e0 = 38
53  integer, parameter :: n_combinations = 8
55  real(kind=ESPUTR_DP), dimension(N_E0), parameter :: e0 = (/ (i_, i_=0,200,10),(i_, i_=300,900,100),(i_, i_=1000,10000,1000) /)
57  character(10), dimension(3, N_COMBINATIONS), parameter :: combinations = reshape (&
58  (/ &
59  "D ", "Be ", "Beryllium ", &
60  "T ", "Be ", "Beryllium ", &
61  "D ", "Fe ", "Iron ", &
62  "T ", "Fe ", "Iron ", &
63  "D ", "Mo ", "Molybdenum", &
64  "T ", "Mo ", "Molybdenum", &
65  "D ", "W ", "Tungsten ", &
66  "T ", "W ", "Tungsten " &
67  /), (/ 3, n_combinations/) )
68 
70  real(kind=ESPUTR_DP), dimension(N_E0, N_COMBINATIONS), parameter :: expected2001 = reshape (&
71  (/ &
72  ! D->Be
73  0.000000000e+00, 3.517315511e-06, 2.784769387e-03, 1.167176911e-02, 2.174908020e-02, &
74  2.902745247e-02, 3.348122594e-02, 3.609674400e-02, 3.762438536e-02, 3.850689496e-02, &
75  3.899485826e-02, 3.923256282e-02, 3.930602035e-02, 3.926849578e-02, 3.915420134e-02, &
76  3.898585217e-02, 3.877897881e-02, 3.854447478e-02, 3.829015189e-02, 3.802171932e-02, &
77  3.774341740e-02, 3.485880922e-02, 3.224377567e-02, 2.999997837e-02, 2.807864040e-02, &
78  2.642054938e-02, 2.497583199e-02, 2.370519061e-02, 2.257802451e-02, 1.569601667e-02, &
79  1.231223625e-02, 1.024762756e-02, 8.837389011e-03, 7.804281917e-03, 7.010352244e-03, &
80  6.378575769e-03, 5.862291863e-03, 5.431454448e-03, &
81  ! T->Be
82  0.000000000e+00, 1.580435292e-05, 2.852500540e-03, 1.011495035e-02, 1.933632321e-02, &
83  2.787885884e-02, 3.462810870e-02, 3.957349789e-02, 4.308016264e-02, 4.553196702e-02, &
84  4.723158029e-02, 4.839660982e-02, 4.917888101e-02, 4.968387131e-02, 4.998539201e-02, &
85  5.013573645e-02, 5.017248698e-02, 5.012305314e-02, 5.000771257e-02, 4.984166982e-02, &
86  4.963646831e-02, 4.669012511e-02, 4.355490822e-02, 4.073809575e-02, 3.827303946e-02, &
87  3.611787579e-02, 3.422330378e-02, 3.254600972e-02, 3.105042704e-02, 2.179001573e-02, &
88  1.716786416e-02, 1.432772094e-02, 1.237930677e-02, 1.094761704e-02, 9.844882790e-03, &
89  8.965805968e-03, 8.246386677e-03, 7.645305840e-03, &
90  ! D->Fe
91  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
92  5.100112103e-04, 1.580374898e-03, 3.048681993e-03, 4.802776536e-03, 6.730775099e-03, &
93  8.732937593e-03, 1.072966503e-02, 1.266357317e-02, 1.449747440e-02, 1.621044766e-02, &
94  1.779355957e-02, 1.924607465e-02, 2.057246175e-02, 2.178020349e-02, 2.287828420e-02, &
95  2.387619842e-02, 3.010666093e-02, 3.285989703e-02, 3.423599482e-02, 3.495546787e-02, &
96  3.531556539e-02, 3.545963241e-02, 3.546527637e-02, 3.537826289e-02, 3.285087530e-02, &
97  3.004954688e-02, 2.764256700e-02, 2.561826456e-02, 2.390488458e-02, 2.243808759e-02, &
98  2.116778111e-02, 2.005591807e-02, 1.907351427e-02, &
99  ! T->Fe
100  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 4.030583889e-05, 1.206100604e-03, &
101  3.339086754e-03, 6.201780630e-03, 9.545002187e-03, 1.312860844e-02, 1.675507742e-02, &
102  2.028213798e-02, 2.361965885e-02, 2.671911408e-02, 2.956161820e-02, 3.214754907e-02, &
103  3.448870262e-02, 3.660286430e-02, 3.851029752e-02, 4.023160837e-02, 4.178653569e-02, &
104  4.319333400e-02, 5.196015755e-02, 5.591999659e-02, 5.795086136e-02, 5.903358165e-02, &
105  5.958253822e-02, 5.980301530e-02, 5.980890673e-02, 5.966880322e-02, 5.556524319e-02, &
106  5.095034766e-02, 4.695330807e-02, 4.357481794e-02, 4.070511218e-02, 3.824184196e-02, &
107  3.610405635e-02, 3.422970473e-02, 3.257122255e-02, &
108  ! D->Mo
109  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
110  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
111  3.764200472e-06, 5.671733972e-05, 1.535095689e-04, 2.899499471e-04, 4.639264579e-04, &
112  6.731062010e-04, 9.145875173e-04, 1.184908048e-03, 1.480169221e-03, 1.796202192e-03, &
113  2.128740151e-03, 5.586945212e-03, 8.143701414e-03, 9.724548975e-03, 1.070060098e-02, &
114  1.132629886e-02, 1.174256898e-02, 1.202710596e-02, 1.222455063e-02, 1.250755077e-02, &
115  1.203880448e-02, 1.147754165e-02, 1.093174817e-02, 1.042626758e-02, 9.964900289e-03, &
116  9.545251066e-03, 9.163228355e-03, 8.814552903e-03, &
117  ! T->Mo
118  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
119  0.000000000e+00, 0.000000000e+00, 7.457209864e-06, 9.347281503e-05, 2.603873988e-04, &
120  5.080951344e-04, 8.368249243e-04, 1.244684607e-03, 1.727395430e-03, 2.278518905e-03, &
121  2.889891433e-03, 3.552152515e-03, 4.255292454e-03, 4.989164748e-03, 5.743925250e-03, &
122  6.510376587e-03, 1.350334871e-02, 1.805931524e-02, 2.075911820e-02, 2.241112917e-02, &
123  2.347277421e-02, 2.418274363e-02, 2.467008950e-02, 2.500873141e-02, 2.542150891e-02, &
124  2.446126804e-02, 2.332673035e-02, 2.222459659e-02, 2.120341922e-02, 2.027073793e-02, &
125  1.942183560e-02, 1.864858809e-02, 1.794246619e-02, &
126  ! D->W
127  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
128  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
129  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
130  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
131  0.000000000e+00, 1.674048481e-04, 7.083969098e-04, 1.466363038e-03, 2.287401706e-03, &
132  3.062518277e-03, 3.740490999e-03, 4.309932970e-03, 4.779033480e-03, 6.655863423e-03, &
133  6.984090248e-03, 6.997561625e-03, 6.908640396e-03, 6.779674552e-03, 6.634937646e-03, &
134  6.485423360e-03, 6.336530438e-03, 6.191000809e-03, &
135  ! T->W
136  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
137  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
138  0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, 0.000000000e+00, &
139  0.000000000e+00, 8.705827047e-06, 4.259283291e-05, 9.613860211e-05, 1.681050765e-04, &
140  2.580041112e-04, 2.020298542e-03, 4.658360328e-03, 7.210635189e-03, 9.268944194e-03, &
141  1.082291151e-02, 1.198094226e-02, 1.285167311e-02, 1.351735066e-02, 1.592019769e-02, &
142  1.626619939e-02, 1.616626938e-02, 1.590805439e-02, 1.558613799e-02, 1.524037746e-02, &
143  1.488972934e-02, 1.454375049e-02, 1.420732585e-02 /), (/ n_e0, n_combinations /) )
145  integer, parameter :: n_combinations_theta=13
147  character(10), dimension(2, N_COMBINATIONS_THETA), parameter :: combinations_th = reshape (&
148  (/ &
149  "D ", "Be ", &
150  "T ", "Be ", &
151  "H ", "Fe ", &
152  "H ", "Fe ", &
153  "H ", "Fe ", &
154  "D ", "Mo ", &
155  "D ", "Mo ", &
156  "D ", "W ", &
157  "T ", "W ", &
158  "H ", "W ", &
159  "He ", "Nb ", &
160  "D ", "Ni ", &
161  "H ", "Ni " /), (/ 2, n_combinations_theta/) )
163  real(kind=ESPUTR_DP),dimension(N_COMBINATIONS_THETA) :: etheta=(/ &
164  11, &
165  1000, &
166  4000, &
167  8000, &
168  6000, &
169  115, &
170  75000, &
171  270, &
172  700, &
173  750, &
174  36500, &
175  4000, &
176  1000 /)
178  real(kind=ESPUTR_DP),dimension(N_COMBINATIONS_THETA) :: thetamax=(/ &
179  4.842048462e-01, &
180  1.400587692e+00, &
181  1.455016598e+00, &
182  1.474063830e+00, &
183  1.463894081e+00, &
184  8.144044996e-01, &
185  1.533924027e+00, &
186  9.465855469e-01, &
187  1.370370612e+00, &
188  1.129766008e+00, &
189  1.510606768e+00, &
190  1.448614114e+00, &
191  1.392779079e+00 /)
193  real(kind=ESPUTR_DP),dimension(N_COMBINATIONS_THETA) :: ythetamax=(/ &
194  1.278631895e+00, &
195  1.734397274e+01, &
196  1.648554854e+01, &
197  2.194311127e+01, &
198  1.899924523e+01, &
199  1.198215164e+00, &
200  5.648503105e+01, &
201  1.324261665e+00, &
202  2.470894247e+00, &
203  1.546335313e+00, &
204  1.760099941e+01, &
205  1.139561282e+01, &
206  7.206948643e+00 /)
207 
208  contains
209 
211  logical function esputr2001_test_wrong_file()
212  integer, dimension(4) :: err
213  call esputr2001_init("/__FOO_test_wrong_file_2001", "../data/ECKSTEIN2007TH", err(1))
214  call esputr2001_deallocate(err(2))
215  call esputr2001_init("ECKSTEIN2007N", "/__FOO_test_wrong_file_2001~2", err(3))
216  call esputr2001_deallocate(err(4))
217 ! call esputr2001_init("../data/ECKSTEIN2007TH", "../data/ECKSTEIN2007TH", err(7))
218  print *, "test_wrong_file:", err
219  esputr2001_test_wrong_file = all(err(:) == (/300, 0, 300, 0/))
220  end function esputr2001_test_wrong_file
221 
223  logical function esputr2001_test_wrong_ids()
224  integer, dimension(8) :: err
225  real(kind=ESPUTR_DP) :: crap
227  crap = esputr2001_yn(0.d0, -42, err(2))
228  crap = esputr2001_yn(0.d0, 1337, err(3))
229  crap = esputr2001_yth(1000.d0, 0.d0, -42, 1, err(4))
230  crap = esputr2001_yth(1000.d0, 0.d0, 1337, 1, err(5))
231  crap = esputr2001_yth(1000.d0, 0.d0, 1, -42, err(6))
232  crap = esputr2001_yth(1000.d0, 0.d0, 1, 1337, err(7))
233  call esputr2001_deallocate(err(8))
234  print *, "test_wrong_ids:", err
235  esputr2001_test_wrong_ids = all(err == (/0, 100, 100, 153, 155, 155, 154, 0/))
236  end function esputr2001_test_wrong_ids
237 
239  logical function esputr2001_test_double_init()
240  integer, dimension(7) :: err
244  call esputr2001_deallocate(err(4))
247  call esputr2001_deallocate(err(7))
248  print *, "test_double_init:", err
249  esputr2001_test_double_init = all(err == (/0, 100, 100, 0, 0, 100, 0/))
250  end function esputr2001_test_double_init
251 
253  logical function esputr2001_test_call_uninitialized()
254  integer, dimension(4) :: err
255  integer :: icrap,icrap2
256  real(kind=ESPUTR_DP) :: rcrap
257  icrap = esputr2001_getprojectiletargetidn("D", "Be", err(1))
258  call esputr2001_getprojectiletargetidsth("D", "Be", icrap, icrap2, err(2))
259  rcrap = esputr2001_yn(0.d0, 1, err(3))
260  rcrap = esputr2001_yth(1000.d0, 1.d0, 1, 1, err(4))
261  print *, "test_call_uninitialized:", err
262  esputr2001_test_call_uninitialized = all(err == 50)
264 
266  logical function esputr2001_test_unknown_elements()
267  integer, dimension(4) :: err
268  integer :: icrap
270  icrap = esputr2001_getprojectiletargetidn("Ä", "ö", err(2))
271  call esputr2001_getprojectiletargetidsth("Ä", "ö", icrap, icrap, err(3))
272  call esputr2001_deallocate(err(4))
273  print *, "test_unknown_elements:", err
274  esputr2001_test_unknown_elements = all(err == (/0, 151, 152, 0/))
276 
278  logical function esputr2001_test_negative_energy()
279  integer,dimension(4) :: err
280  integer :: lo, up
281  real(kind=ESPUTR_DP) :: crap
283  call esputr2001_getprojectiletargetidsth("D","Be",lo,up,err(2))
284  crap = esputr2001_yth(-1.d0, 1.d0, lo, up, err(3))
285  call esputr2001_deallocate(err(4))
286  print *, "test_negative_energy:", err
287  esputr2001_test_negative_energy = all(err == (/0, 0, 156, 0/))
289 
291  logical function esputr2001_test_wrong_angle()
292  integer, dimension(6) :: err
293  integer :: lo, up
294  real(kind=ESPUTR_DP) :: crap
296  call esputr2001_getprojectiletargetidsth("D","Be",lo,up,err(2))
297  crap = esputr2001_yth(1000.d0, 1.6d0, lo, up, err(3))
298  crap = esputr2001_yth(1000.d0, -.1d0, lo, up, err(4))
299  crap = esputr2001_yth(1000.d0, 1.1d0, lo, up, err(5))
300  call esputr2001_deallocate(err(6))
301  print *, "test_wrong_angle", err
302  esputr2001_test_wrong_angle = all(err == (/0, 0, 157, 157, 0, 0/))
303  end function esputr2001_test_wrong_angle
304 
306  logical function esputr2001_test_n()
307  logical, dimension(N_COMBINATIONS) :: results
308  integer :: i,err
309 
311  if(err /= 0) goto 2000
312 
313  do i = 1, n_combinations
314  results(i) = test_2001(expected2001(:,i), combinations(1,i), combinations(2,i))
315  end do
316  print *, "test_2001: ", results
317  esputr2001_test_n = all(results)
318 
319  call esputr2001_deallocate(err)
320  if(err /= 0) goto 2000
321 
322  return
323 
324 2000 print *, "FAILURE in esputr2001_test_N: unexpected err value", err
325  esputr2001_test_n = .false.
326  return
327 
328  contains
329 
333  logical function test_2001(expected, proj, targ)
334  real(kind=ESPUTR_DP), dimension(N_E0), intent(in) :: expected
335  character(*), intent(in) :: proj, targ
336  integer :: projTargId, err
337  real(kind=ESPUTR_DP), dimension(N_E0) :: Y
338  logical, dimension(N_E0) :: passed
339  integer :: i
340 
341  projtargid = esputr2001_getprojectiletargetidn(proj,targ,err)
342  if(err /= 0) goto 2000
343  do i = 1, n_e0
344  y(i) = esputr2001_yn(e0(i), projtargid, err)
345  if(err /= 0) goto 2000
346  end do
347 
348  passed = ispassed(expected, y)
349  call printfailed(expected, y, passed)
350  test_2001 = all(passed)
351  return
352 
353 2000 print *, "FAILURE in esputr2001_test_N: unexpected err value", err
354  test_2001 = .false.
355  return
356  end function test_2001
357  end function esputr2001_test_n
358 
359 
366  logical function esputr2001_test_theta()
367  integer :: j, projTargId1, projTargId2, err
368  real(kind=ESPUTR_DP) :: Y
369 
371  if(err /= 0) goto 3000
372  do j=1,n_combinations_theta
374  ,projtargid1, projtargid2, err)
375  if(err /= 0) goto 3000
376  y = esputr2001_yth(etheta(j), 0d0, projtargid1, projtargid2, err)
377  if(err /= 0) goto 3000
378  if(.not.ispassed(y,1.d0)) then
379  print *, "FAILURE in esputr2001_test_theta: expected 1, got", y
380  esputr2001_test_theta = .false.
381  return
382  end if
383  y = esputr2001_yth(etheta(j), thetamax(j), projtargid1, projtargid2, err)
384  if(err /= 0) goto 3000
385  if(.not.ispassed(y,ythetamax(j))) then
386  print *, "FAILURE in esputr2001_test_theta: expected ",ythetamax(j)," got", y
387  print *, " ",combinations_th(1,j),combinations_th(2,j),etheta(j)
388  esputr2001_test_theta = .false.
389  return
390  end if
391  end do
392  call esputr2001_deallocate(err)
393  if(err /= 0) goto 3000
394 
395  print *, "test_2001_theta: ", .true.
396  esputr2001_test_theta = .true.
397  return
398 
399 3000 print *, "FAILURE in esputr2001_test_theta: unexpected err value", err
400  esputr2001_test_theta = .false.
401  call esputr2001_deallocate(err)
402  return
403  end function esputr2001_test_theta
404 
406  logical function esputr2001_test_eth()
407  integer :: err, projTarg_id
408  real(kind=ESPUTR_DP) :: Eth
409  esputr2001_test_eth = .false.
411  if(err /= 0) goto 6100
412  projtarg_id = esputr2001_getprojectiletargetidn("H", "Li", err)
413  if(err /= 0) goto 6100
414  eth = esputr2001_eth(projtarg_id, err)
415  if(err /= 0) goto 6100
416  if(ispassed(eth, 5.6499d0)) then
417  esputr2001_test_eth = .true.
418  else
419  print *, "FAILURE in esputr2001_test_ETH: ", eth
420  end if
421  call esputr2001_deallocate(err)
422  if(err /= 0) goto 6100
423  return
424 6100 print *, "FAILURE in esputr2001_test_ETH: unexpected err value", err
425  call esputr2001_deallocate(err)
426  end function esputr2001_test_eth
427 
429  logical function esputr2001_test_initialized()
430  integer :: err
431  logical :: initialized
433  call esputr2001_init("../data/SPUTER", "../data/SPUTER", err)
434  if(err == 0) goto 8100
436  if(err /= 0) goto 8100
437  call esputr2001_deallocate(err)
438  if(err /= 0) goto 8100
440  if(err /= 0) goto 8100
441  initialized = esputr2001_if_initialized()
442  if(.not. initialized) goto 8100
443  call esputr2001_deallocate(err)
444  if(err /= 0) goto 8100
446  return
447 8100 print *, "FAILURE in esputr2001_test_initialized"
448  call esputr2001_deallocate(err)
449  end function esputr2001_test_initialized
450 
452  logical function esputr2001_test_availableenergyrange()
453  integer :: err
454  integer :: lId, uId
455  real(kind=ESPUTR_DP) :: Emin, Emax
456  call esputr2001_getavailableenergyrange(1, 1, emin, emax, err)
457  if(err == 0) goto 9100
459  if(err /= 0) goto 9100
460  call esputr2001_getprojectiletargetidsth("D", "Be", lid, uid, err)
461  if(err /= 0) goto 9100
462  call esputr2001_getavailableenergyrange(lid, uid, emin, emax, err)
463  if(err /= 0 .or. abs(10-emin) > 1 .or. abs(3000-emax) > 1) goto 9100
464  call esputr2001_getavailableenergyrange(3, 1, emin, emax, err)
465  if(err == 0) goto 9100
466  call esputr2001_getavailableenergyrange(-3, 1, emin, emax, err)
467  if(err == 0) goto 9100
468  call esputr2001_getavailableenergyrange(3, 100000, emin, emax, err)
469  if(err == 0) goto 9100
470  call esputr2001_deallocate(err)
472  return
473 9100 print *, "FAILURE in esputr2001_test_availableEnergyRange"
475  call esputr2001_deallocate(err)
477 
479  logical function esputr2001_test_extrapolate_angular()
480  integer :: err
481  integer,parameter :: n=10
482  real(kind=ESPUTR_DP) :: theta(n)=(/0,10,20,30,40,50,60,70,80,90/)
483  real(kind=ESPUTR_DP) :: Emin, Emax,E,ym,yex
484  integer :: id1,id2,i
485 
487  if(err /= 0) goto 100
488  call esputr2001_getprojectiletargetidsth('H','Fe',id1,id2,err)
489  if(err /= 0) goto 100
490  call esputr2001_getavailableenergyrange(id1,id2,emin,emax,err)
491  if(err /= 0) goto 100
492 
494 
495  theta=theta*esputr_pi/180.
496  do i=1,n
497  ym=esputr2001_yth(emin,theta(i),id1,id2,err)
498  if(err /= 0) goto 100
499  e=0.5*emin
500  yex=esputr2001_yth(e,theta(i),id1,id2,err)
501  if(err /= 0) goto 100
502  if(.not.ispassed(ym,yex)) then
503  print *, "FAILURE in esputr2001_test_extrapolate_angular: ",&
504  "initial and extrapolated values are different"
505  print *," theta, Emin, E ",theta(i),emin,e
506  print *," Y_min, Y_extrap ",ym,yex
508  return
509  end if
510  ym=esputr2001_yth(emax,theta(i),id1,id2,err)
511  if(err /= 0) goto 100
512  e=2.0*emax
513  yex=esputr2001_yth(e,theta(i),id1,id2,err)
514  if(err /= 0) goto 100
515  if(.not.ispassed(ym,yex)) then
516  print *, "FAILURE in esputr2001_test_extrapolate_angular: ",&
517  "initial and extrapolated values are different"
518  print *," theta, Emax, E ",theta(i),emax,e
519  print *," Y_max, Y_extrap ",ym,yex
521  return
522  end if
523  end do
524 
525  print *, "esputr2001_test_extrapolate_angular: ", .true.
527  return
528 
529 100 print *, "FAILURE in esputr2001_test_extrapolate_angular"
531  call esputr2001_deallocate(err)
532 
534 
535 
536 end module esputr2001_test
537 
538 program test2001
539  use esputr2001_test
540  use esputr
541  implicit none
542 
543  esputr_unit = 0
544 
545  if(.not.esputr2001_test_wrong_file()) stop " ERROR detected in esputr2001_test_wrong_file"
546  if(.not.esputr2001_test_wrong_ids()) stop " ERROR detected in esputr2001_test_wrong_ids"
547  if(.not.esputr2001_test_double_init()) stop " ERROR detected in esputr2001_test_double_init"
548  if(.not.esputr2001_test_call_uninitialized()) stop " ERROR detected in esputr2001_test_call_uninitialized"
549  if(.not.esputr2001_test_unknown_elements()) stop " ERROR detected in esputr2001_test_unknown_elements"
550  if(.not.esputr2001_test_negative_energy()) stop " ERROR detected in esputr2001_test_negative_energy"
551  if(.not.esputr2001_test_wrong_angle()) stop " ERROR detected in esputr2001_test_wrong_angle"
552  if(.not.esputr2001_test_n()) stop " ERROR detected in esputr2001_test_N"
553  if(.not.esputr2001_test_theta()) stop " ERROR detected in esputr2001_test_theta"
554  if(.not.esputr2001_test_eth()) stop " ERROR detected in esputr2001_test_ETH"
555  if(.not.esputr2001_test_initialized()) stop " ERROR detected in esputr2001_test_initialized"
556  if(.not.esputr2001_test_availableenergyrange()) stop " ERROR detected in esputr2001_test_availableEnergyRange"
557  if(.not.esputr2001_test_extrapolate_angular()) stop " ERROR detected in esputr2001_test_extrapolate_angular"
558  print *, "ESPUTR2001_TEST COMPLETED"
559 end program test2001
integer, parameter n_e0
Number of tested values of incident energy.
logical function, public esputr2001_test_n()
Test that expected values come out of esputr2001_yn.
real(kind=esputr_dp), dimension(n_combinations_theta) ythetamax
Values of Y(E,ThetaMax)/Y(E,0) for test of the angular dependence.
logical function, public esputr2001_test_wrong_file()
Test for correct error codes if given file does not exist or is corrupted.
character(10), dimension(2, n_combinations_theta), parameter combinations_th
Projectile-target combinations for tests of the angular dependence.
real(kind=esputr_dp), dimension(n_e0, n_combinations), parameter expected2001
Reference values for comparison: sputtering yield for normal incidence.
logical function, public esputr2001_test_double_init()
Test for correct error codes if 2001 model is initialized or deallocateted more than once...
subroutine, public printfailed(expected, calculated, passed)
Print pairs of values (expected(i),calculated(i)) for which passed(i)=.false.
Definition: esputr_test.f90:51
subroutine, public esputr2001_getavailableenergyrange(projTargStartId, projTargEndId, Emin, Emax, err)
Get the minimum and maximum energies for which the angular dependency factor is defined.
Definition: esputr2001.f90:776
character(10), dimension(3, n_combinations), parameter combinations
List of projectile-target combinations for which the reference values of Y(E,0) are defined...
subroutine, public esputr2001_initn(fileNName, err)
Definition: esputr2001.f90:152
logical function, public esputr2001_test_negative_energy()
Test for correct error codes if projectile energy is negative.
integer, parameter n_combinations
Number of tested projectile-target combinations.
logical function, public esputr2001_test_unknown_elements()
test for correct error codes if ID of an unknown (chemical) element is requested
real(kind=esputr_dp), dimension(n_e0), parameter e0
Values of incident energy for which the yields are tested (eV)
logical function, public esputr2001_test_theta()
Regression test for the angular dependence.
integer, parameter n_combinations_theta
Number of projectile-target-energy combinations for test of the angular dependence.
real(esputr_dp), parameter, public esputr_pi
Pi number.
Definition: esputr.f90:79
logical elemental function, public ispassed(expected, calculated)
Definition: esputr_test.f90:39
logical function, public esputr2001_test_wrong_ids()
Test for correct error codes if projectile/target IDs do not exist.
subroutine, public esputr2001_deallocate(err)
Deallocate dynamic arrays used by this module.
Definition: esputr2001.f90:426
logical function, public esputr2001_if_initialized()
Return .true. if module esputr2001 is initialized.
Definition: esputr2001.f90:421
real(esputr_dp) function, public esputr2001_yth(E0, theta, projTargStartId, projTargEndId, err)
Angular dependence of sputtering yield in 2001-model for given incident angle and energy...
Definition: esputr2001.f90:575
integer function, public esputr2001_getprojectiletargetidn(proj, targ, err)
Return ID for a projectile-target combination for 2001-model for normal incidence.
Definition: esputr2001.f90:450
logical function, public esputr2001_test_initialized()
Check esputr2001_if_initialized.
character(*), parameter sputer2001_n_fitvalues_file
Dafault paths to the input files.
logical function, public esputr2001_test_eth()
Check esputr2001_Eth.
logical function, public esputr2001_test_call_uninitialized()
Test for correct error codes if functions are used w/o initialization of the module.
logical function, public esputr2001_test_extrapolate_angular()
Check ESPUTR2001_EXTRAPOLATE_ANGULAR=.TRUE.
logical function, public esputr2001_test_availableenergyrange()
Check test_availableEnergyRange.
real(esputr_dp) function, public esputr2001_eth(projectileTarget_id, err)
Return the threshold energy E_th for the given projectile-target combination.
Definition: esputr2001.f90:702
logical function, public esputr2001_test_wrong_angle()
Test for correct error codes if incident angle is out of bounds.
logical, save, public esputr2001_extrapolate_angular
Switch for extrapolation of the angular dependency to energies for which no data are defined...
Definition: esputr2001.f90:49
real(kind=esputr_dp), dimension(n_combinations_theta) etheta
Incident energy (eV) for test of the angular dependence.
character(*), parameter sputer2001_th_fitvalues_file
real(esputr_dp) function, public esputr2001_yn(E0, projectileTarget_id, err)
Calculate sputtering yield for normal incidence with 2001-model for given incident energy and target-...
Definition: esputr2001.f90:525
subroutine, public esputr2001_getprojectiletargetidsth(proj, targ, thLower, thUpper, err)
Return two IDs for a projectile-target combination for 2001-model for angular dependence.
Definition: esputr2001.f90:482
program test2001
subroutine, public esputr2001_init(fileNName, fileThName, err)
Initialization of the 2001-model.
Definition: esputr2001.f90:128
real(kind=esputr_dp), dimension(n_combinations_theta) thetamax
Angle of maximum for tests of the angular dependence.
integer, save, public esputr_unit
Index of the unit for standard output, default value 6.
Definition: esputr.f90:73