ESPUTR
calculation of sputtering yields
esputr2001.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 
25 module esputr2001
26 
27 !***********************************************************************************
28 ! DEFINITION OF PARAMETRS AND GLOBAL VARIABLES
29 !***********************************************************************************
30  use esputr
31  implicit none
33  public esputr2001_check
49  logical,public,save :: esputr2001_extrapolate_angular=.false.
51  integer, parameter, public :: esputr2001_max_name_length = 16
52  private
55  integer, parameter, private :: nconstants_n = 5
58  integer, parameter, private :: nconstants_th = 6
60  integer,save, private :: ncombinations_n
62  integer,save, private :: ncombinations_th
75  real(ESPUTR_DP), dimension(:,:), allocatable, save, private :: fitvalues_n
93  real(ESPUTR_DP), dimension(:,:), allocatable, save, private :: fitvalues_th
101  character(ESPUTR2001_MAX_NAME_LENGTH), dimension(:,:), allocatable, save, private :: projectiles_targets_names_n
109  character(ESPUTR2001_MAX_NAME_LENGTH), dimension(:,:), allocatable, save, private :: projectiles_targets_names_th
113  integer, save, private :: nprojectilestargetsth = 0
114 
115  contains
116 
117 !***********************************************************************************
118 ! INITIALIZATION/DEINITIALIZATION ROUTINES
119 !***********************************************************************************
120 
127  subroutine esputr2001_init(fileNName, fileThName, err)
129  character(*), intent(in) :: fileNName
131  character(*), intent(in) :: fileThName
133  integer, intent(out) :: err
134 
135  integer :: res
136 
137  err = 0
138  ! read data for normal incidence
139  call esputr2001_initn(filenname, err)
140  ! read data for angular dependence
141  if(err /= 0) return
142  call esputr2001_initth(filethname, err)
143  if(err /= 0) return
144  call esputr2001_check(res, err)
145  if( res /=0 ) then
146  write(esputr_unit, *) "ERROR in esputr2001_init: created module is invalid"
147  err=400
148  end if
149  end subroutine esputr2001_init
150 
151  subroutine esputr2001_initn(fileNName, err)
153  character(*), intent(in) :: fileNName
154  integer, intent(out) :: err
155  err = 0
156  if(allocated(fitvalues_n)) then
157  write(esputr_unit, *) "ERROR in esputr2001_initN: esputr2001_initN has already been called; &
158  &call esputr2001_deallocate first."
159  err = 100
160  return
161  end if
162  call init2001_(filenname, fitvalues_n, nconstants_n, &
164  if(err == 0) then
165  write(esputr_unit, *) " Number of projectile-target combinations = ", size(fitvalues_n, 2)
166  end if
167  end subroutine esputr2001_initn
168 
169  subroutine esputr2001_initth(fileTHName, err)
171  character(*), intent(in) :: fileTHName
172  integer, intent(out) :: err
173  err = 0
174  if(allocated(fitvalues_th)) then
175  write(esputr_unit, *) "ERROR in esputr2001_initTH: esputr2001_initTH has already been called; &
176  &call esputr2001_deallocate first."
177  err = 100
178  return
179  end if
180  call init2001_(filethname, fitvalues_th, nconstants_th, &
182  if(err == 0) then
183  nprojectilestargetsth = numberofprojtargcombinations()
184  write(esputr_unit, *) " Number of projectile-target combinations = ", nprojectilestargetsth
185  write(esputr_unit, *) " Number of projectile-target-energy combinations = ", size(projectiles_targets_names_th, 1)
186  end if
187 
188  contains
189 
192  integer function numberofprojtargcombinations()
193  character(ESPUTR_MAX_LINE_LENGTH) :: currentCombination
194  character(ESPUTR_MAX_LINE_LENGTH) :: lastCombination
195  integer :: i
196  lastcombination = ""
197  numberofprojtargcombinations = 0
198  do i = 1, size(projectiles_targets_names_th, 1)
199  currentcombination = projectiles_targets_names_th(i, 1) // projectiles_targets_names_th(i, 2)
200  if(currentcombination /= lastcombination) then
201  numberofprojtargcombinations = numberofprojtargcombinations + 1
202  lastcombination = currentcombination
203  end if
204  end do
205  end function numberofprojtargcombinations
206  end subroutine esputr2001_initth
207 
212  subroutine init2001_(fileName, fitvalues, nConstants, projTargNames, nCombinations, err)
213 
214  character(*), intent(in) :: fileName
222  real(ESPUTR_DP), dimension(:,:), allocatable, intent(inout) :: fitvalues
226  integer, intent(in) :: nConstants
234  character(ESPUTR2001_MAX_NAME_LENGTH), dimension(:,:), allocatable, intent(inout) :: projTargNames
236  integer,intent(out) :: nCombinations
237  integer, intent(out) :: err
238 
239  integer, parameter :: UNIT = 3
240  integer :: nLines
241  integer :: i, j, err_
242  character(ESPUTR_MAX_LINE_LENGTH) :: line
243  intrinsic trim, size
244 
245  i = 0
246  j = 1
247 
248  ! -1 for the header line
249  ncombinations = numberoflines(filename, .true., err=err)
250  if (err /= 0) then
251  write(esputr_unit, *) "ERROR in esputr2001_init: error while determining number of lines in "//trim(filename)
252  err=300
253  return
254  end if
255  if (ncombinations<1) then
256  write(esputr_unit, *) "ERROR in esputr2001_init: "//trim(filename)//" contains no data"
257  err=300
258  return
259  end if
260  nlines = numberoflines(filename, .false., err)
261  if (err /= 0) then
262  write(esputr_unit, *) "ERROR in esputr2001_init: error while determining number of lines in "//trim(filename)
263  err=300
264  return
265  end if
266 
267  allocate(fitvalues(nconstants,ncombinations), stat=err_); if(err_/=0) goto 3200
268  allocate(projtargnames(ncombinations,2), stat=err_); if(err_/=0) goto 3200
269 
270  open(unit, iostat=err, file=filename, status='old', action='read')
271  if (err /= 0 ) goto 3300
272 
273  do i = 1, nlines
274  read(unit, '(A)', iostat=err) line
275  if (err /= 0 ) goto 3350
276  if(line(1:1) /= esputr_comment_start) then
277  read(line, *, iostat=err) projtargnames(j,:), fitvalues(1:nconstants,j)
278  if (err /= 0 ) goto 3350
279  j = j+1
280  end if
281  end do
282 
283  close(unit)
284 
285  write(esputr_unit, *) "esputr2001_init: initialization from file "//trim(filename)//" completed"
286  return
287 
288 3200 write(esputr_unit, *) "ERROR in esputr2001_init: could not allocate memory for data from file "//trim(filename)
289  write(esputr_unit, *) " Number of entries = ",ncombinations,&
290  " number of parameter for each entry = ",nconstants
291  err = 200
292  return
293 3300 write(esputr_unit, *) "ERROR in esputr2001_init: cannot open "//trim(filename)
294  err = 300
295  return
296 3350 write(esputr_unit, *) "ERROR in esputr2001_init while reading line", i, "of "//trim(filename)
297  call esputr2001_deallocate(err)
298  err = 300
299  close(unit)
300  return
301 
302  end subroutine init2001_
303 
305  subroutine esputr2001_check(res, err)
318  integer, intent(out) :: res
320  integer, intent(out) :: err
321 
322  integer :: i,n,m,nn,mm
323  character(ESPUTR_MAX_LINE_LENGTH) :: currentCombination, lastCombination
324  real(ESPUTR_DP) :: lastEnergy,lambda,q,Eth,Etf,E0,Esp
325  intrinsic size, trim
326 
327  err = 0
328  res = 0
329 
330  if ( (.not.allocated(fitvalues_n)).or.(.not.allocated(fitvalues_th)) .or. &
331  (.not.allocated(projectiles_targets_names_n)) .or. &
332  (.not.allocated(projectiles_targets_names_th)) ) then
333  write(esputr_unit, *) "ERROR detected in esputr2001_check: some or all arrays are not allocated"
334  res = 1
335  return
336  end if
337 
338  n=size(fitvalues_n,2)
339  m=size(fitvalues_th,2)
340  nn=size(projectiles_targets_names_n,1)
342  if ( ncombinations_n /= n .or. ncombinations_th /= m .or. &
343  ncombinations_n /= nn .or. ncombinations_th /= mm ) then
344  write(esputr_unit, *) "ERROR detected in esputr2001_check: inconsistent array size"
345  write(esputr_unit, *) " NCOMBINATIONS_N, size(FITVALUES_N), size(PROJECTILES_TARGETS_NAMES_N) ",&
346  ncombinations_n, n, nn
347  write(esputr_unit, *) " NCOMBINATIONS_N, size(FITVALUES_TH), size(PROJECTILES_TARGETS_NAMES_TH) ",&
348  ncombinations_th, m, mm
349  res=2
350  return
351  end if
352 
353  !cycle over the normal incidence data
354  do i = 1, ncombinations_n
355  lambda=fitvalues_n(1,i)
356  q=fitvalues_n(2,i)
357  eth=fitvalues_n(4,i)
358  etf=fitvalues_n(5,i)
359  if(lambda <= 0.) then
360  write(esputr_unit, *) "ERROR detected in esputr2001_check: wrong lambda = ",lambda
361  write(esputr_unit, *) " pos, proj, targ ",i, &
363  res = 3
364  return
365  else if(q <= 0. ) then
366  write(esputr_unit, *) "ERROR detected in esputr2001_check: wrong q = ", q
367  write(esputr_unit, *) " pos, proj, targ ",i, &
369  res = 4
370  return
371  else if(eth <= 0.) then
372  write(esputr_unit, *) "ERROR detected in esputr2001_check: wrong E_th = ", eth
373  write(esputr_unit, *) " pos, proj, targ ",i, &
375  res = 5
376  return
377  else if(etf < 0.) then
378  write(esputr_unit, *) "ERROR detected in esputr2001_check: wrong eps (E_tf) = ", etf
379  write(esputr_unit, *) " pos, proj, targ ",i, &
381  res = 6
382  return
383  end if
384  end do
385 
386  !cycle over the angular dependence data
387  lastcombination = ""
388  lastenergy = -1.
389  do i = 1, ncombinations_th
390  currentcombination = projectiles_targets_names_th(i,1) // projectiles_targets_names_th(i,2)
391  e0=fitvalues_th(1,i)
392  esp=fitvalues_th(6,i)
393  if(e0 < 0.) then
394  write(esputr_unit, *) "ERROR detected in esputr2001_check: wrong E0 = ", e0
395  write(esputr_unit, *) " pos, proj, targ ",i, &
397  res = 7
398  return
399  else if(esp < 0.) then
400  write(esputr_unit, *) "ERROR detected in esputr2001_check: wrong E_sp = ", esp
401  write(esputr_unit, *) " pos, proj, targ ",i, &
403  res = 8
404  return
405  else if( currentcombination == lastcombination .and. e0 <= lastenergy ) then
406  write(esputr_unit, *) "ERROR detected in esputr2001_check: ", &
407  "incident energy for angular dependence is not monotonically increasing "
408  write(esputr_unit, *) " pos, proj, targ ",i, &
410  res = 9
411  return
412  end if
413  lastenergy = fitvalues_th(1,i)
414  lastcombination = currentcombination
415  end do
416 
417  end subroutine esputr2001_check
418 
420  logical function esputr2001_if_initialized()
421  esputr2001_if_initialized = allocated(fitvalues_n) .and. allocated(fitvalues_th)
422  end function esputr2001_if_initialized
423 
425  subroutine esputr2001_deallocate(err)
427  integer, intent(out) :: err
428  integer, dimension(4) :: errs
429  err = 0
430  errs = 0
431  if(allocated(fitvalues_n)) deallocate(fitvalues_n, stat=errs(1))
432  if(allocated(fitvalues_th)) deallocate(fitvalues_th, stat=errs(2))
433  if(allocated(projectiles_targets_names_n)) deallocate(projectiles_targets_names_n, stat=errs(3))
434  if(allocated(projectiles_targets_names_th)) deallocate(projectiles_targets_names_th, stat=errs(4))
435  if(.not. all(errs==0)) then
436  write(esputr_unit, *) "WARNING from esputr2001_deallocate: problem while deallocating memory"
437  err = -200
438  end if
439  return
440  end subroutine esputr2001_deallocate
441 
442 !***********************************************************************************
443 ! GET INDEX
444 !***********************************************************************************
445 
449  integer function esputr2001_getprojectiletargetidn(proj, targ, err)
451  character(*), intent(in) :: proj
453  character(*), intent(in) :: targ
457  integer, intent(out) :: err
458  intrinsic trim
459  err = 0
460 
461  if(.not. allocated(projectiles_targets_names_n)) then
462  write(esputr_unit, *) "ERROR in esputr2001_getProjectileTargetIdN: arrays are not initialized"
463  write(esputr_unit, *) " Call esputr2001_init first!"
465  err = 50
466  return
467  end if
468 
470 
472  write(esputr_unit, *) "ERROR in esputr2001_getProjectileTargetIdN: projectile-target combination "&
473  //trim(proj)//"-"//trim(targ)// " is not found (normal incidence)"
474  err = 151
475  end if
477 
481  subroutine esputr2001_getprojectiletargetidsth(proj, targ, thLower, thUpper, err)
483  character(*), intent(in) :: proj
485  character(*), intent(in) :: targ
487  integer, intent(out) :: thLower
489  integer, intent(out) :: thUpper
493  integer, intent(out) :: err
494  intrinsic trim
495  err = 0
496 
497  if(.not. allocated(projectiles_targets_names_th)) then
498  write(esputr_unit, *) "ERROR in esputr2001_getProjectileTargetIdsTh: arrays are not initialized"
499  write(esputr_unit, *) " Call esputr2001_init first!"
500  thlower = 0
501  thupper = 0
502  err = 50
503  return
504  end if
505 
506  thlower = getindexof2(proj, targ, projectiles_targets_names_th, thupper)
507 
508  if(thlower == 0 .or. thupper == 0) then
509  write(esputr_unit, *) "ERROR in esputr2001_getProjectileTargetIdTh: projectile-target combination "&
510  //trim(proj)//"-"//trim(targ)// " is not found (angular dependence)"
511  err = 152
512  end if
514 
515 !***********************************************************************************
516 ! CALCULATION OF SPUTTERING YIELDS
517 !***********************************************************************************
518 
524  real(ESPUTR_DP) function esputr2001_yn(E0, projectileTarget_id, err)
526  real(ESPUTR_DP), intent(in) :: E0
528  integer, intent(in) :: projectileTarget_id
530  integer, intent(out) :: err
531 
532  real(ESPUTR_DP) :: lambda, q, mu, E_th, E_tf, &
533  powerMuTerm, denumerator, numerator, eps
534 
535  err = 0
536 
537  if(.not. allocated(fitvalues_n)) then
538  write(esputr_unit, *) "ERROR in esputr2001_yn: arrays are not initialized"
539  write(esputr_unit, *) " Call esputr2001_init first!"
540  esputr2001_yn = -1
541  err = 50
542  return
543  end if
544  if(projectiletarget_id < 1 .or. projectiletarget_id > ncombinations_n ) then
545  write(esputr_unit, *) "ERROR in esputr2001_yn: projectileTarget_id is out of bounds", projectiletarget_id
546  esputr2001_yn = -1
547  err = 100
548  return
549  end if
550 
551  e_th = fitvalues_n(4,projectiletarget_id)
552 
553  if (e0>e_th) then
554  lambda = fitvalues_n(1,projectiletarget_id)
555  q = fitvalues_n(2,projectiletarget_id)
556  mu = fitvalues_n(3,projectiletarget_id)
557  e_tf = fitvalues_n(5,projectiletarget_id)
558  eps = e0/e_tf
559  powermuterm = (e0/e_th - 1)**mu
560  numerator = powermuterm * log(1 + 1.2288*eps)
561  denumerator = lambda + powermuterm * (eps + .1728*sqrt(eps) + .008*eps**.1504)
562  esputr2001_yn = 0.5 * q * numerator/denumerator
563  else
564  esputr2001_yn = 0
565  end if
566 
567  end function esputr2001_yn
568 
574  real(ESPUTR_DP) function esputr2001_yth(E0, theta, projTargStartId, projTargEndId, err)
575  !Incident energy, eV
576  real(ESPUTR_DP), intent(in) :: E0
580  real(ESPUTR_DP), intent(in) :: theta
582  integer, intent(in) :: projTargStartId
584  integer, intent(in) :: projTargEndId
593  integer, intent(out) :: err
594  real(ESPUTR_DP) :: E_sp, f, c, b, cosTerm, theta0, S, dE, E00
595  integer :: i1, i2
596 
597  err = 0
598 
599  if(.not. allocated(fitvalues_th)) then
600  write(esputr_unit, *) "ERROR in esputr2001_yth: arrays are not initialized"
601  write(esputr_unit, *) "Call esputr2001_init first"
602  esputr2001_yth = -1
603  err = 50
604  return
605  end if
606 
607  if(projtargstartid < 1) then
608  write(esputr_unit, *) "ERROR in esputr2001_yth: projTargStartId is out of bounds ",projtargstartid
609  esputr2001_yth = -1
610  err = 153
611  return
612  end if
613 
614  if(projtargendid > ncombinations_th) then
615  write(esputr_unit, *) "ERROR in esputr2001_yth: projTargEndId is out of bounds ",projtargendid
616  esputr2001_yth = -1
617  err = 154
618  return
619  end if
620 
621  if(projtargstartid > projtargendid ) then
622  write(esputr_unit, *) "ERROR in esputr2001_yth: &
623  &projTargStartId and projTargEndId are inconsistent ",&
624  projtargstartid,projtargendid
625  esputr2001_yth = -1
626  err = 155
627  return
628  end if
629 
630  if(e0 < 0) then
631  write(esputr_unit, *) "ERROR in esputr2001_yth_: incident energy cannot be < 0"
632  err = 156
633  esputr2001_yth = -1
634  return
635  end if
636 
637  if(theta < 0 .or. theta > esputr_pi2) then
638  write(esputr_unit, *) "ERROR in esputr2001_yth: incorrect incident angle theta (radian) ", theta
639  write(esputr_unit, *) " Incident angle cannot be < 0 or > pi/2"
640  err = 157
641  esputr2001_yth = -1
642  return
643  end if
644 
645  !Find element of the array
646  i1=findindex(projtargstartid, projtargendid, e0, fitvalues_th(1,:), err)
647  e00=e0
649  if(err == 21) then
650  err=0
651  e00=fitvalues_th(1,i1)
652  end if
653  else
654  if(err == 21) goto 4102
655  end if
656  if(err /= 0) goto 4100
657 
658  !VK linear interpolation
659  !Here it is assumed that E0 in the table is always monotonically increasing
660  i2=i1+1
661  s=fitvalues_th(1,i2)-fitvalues_th(1,i1)
662  s=1./s
663  de=e00-fitvalues_th(1,i1)
664 
665  f=fitvalues_th(2,i1)+(fitvalues_th(2,i2)-fitvalues_th(2,i1))*s*de
666  b=fitvalues_th(3,i1)+(fitvalues_th(3,i2)-fitvalues_th(3,i1))*s*de
667  c=fitvalues_th(4,i1)+(fitvalues_th(4,i2)-fitvalues_th(4,i1))*s*de
668  e_sp=fitvalues_th(6,i1)+(fitvalues_th(6,i2)-fitvalues_th(6,i1))*s*de
669 
670  theta0 = esputr_pi - acos(sqrt(e_sp/(e00+e_sp))) !VK always <= Pi/2 if both E_sp>=0 and E0>0
671 
672  costerm = cos((theta*esputr_pi2/theta0)**c)
673 
674  if(costerm > 0) then
675  esputr2001_yth = costerm**(-f) * exp(b * (1-1/costerm))
676  else
677  esputr2001_yth = 0
678  end if
679 
680  return
681 
682 4100 write(esputr_unit, *) "ERROR in esputr2001_yth: failed to find fitting parameters for this energy"
683  write(esputr_unit, *) " E0, E_min, E_max ",e0, &
684  fitvalues_th(1,projtargstartid),fitvalues_th(1,projtargendid)
685  esputr2001_yth = -1
686  err = 400
687  return
688 4102 write(esputr_unit, *) "ERROR in esputr2001_yth: no data available for this energy"
689  write(esputr_unit, *) " E0, E_min, E_max ",e0, &
690  fitvalues_th(1,projtargstartid),fitvalues_th(1,projtargendid)
691  esputr2001_yth = -1
692  err = 158
693  return
694  end function esputr2001_yth
695 
696 !***********************************************************************************
697 ! AUXILIARY FUNCTIONS
698 !***********************************************************************************
699 
701  real(ESPUTR_DP) function esputr2001_eth(projectileTarget_id, err)
703  integer, intent(in) :: projectileTarget_id
705  integer, intent(out) :: err
706  if(.not. allocated(fitvalues_n)) then
707  esputr2001_eth = -1
708  write(esputr_unit, *) "ERROR in esputr2001_Eth: arrays are not initialized"
709  write(esputr_unit, *) " Call esputr2001_init first!"
710  err = 50
711  return
712  end if
713  esputr2001_eth = fitvalues_n(4, projectiletarget_id)
714  end function esputr2001_eth
715 
717  subroutine esputr2001_availablecombinationsn(combinations, err)
719  character(ESPUTR2001_MAX_NAME_LENGTH), dimension(:,:), allocatable, intent(inout) :: combinations
721  integer, intent(out) :: err
722  err = 0
723  if(.not.allocated(projectiles_targets_names_n)) then
724  err = 50
725  write(esputr_unit, *) "ERROR in esputr2001_availableCombinationsN: arrays are not initialized"
726  write(esputr_unit, *) " Call esputr2001_init first!"
727  return
728  end if
729  allocate(combinations(size(projectiles_targets_names_n,1), size(projectiles_targets_names_n,2)), stat = err)
730  if(err /= 0) then
731  write(esputr_unit, *) "ERROR in esputr2001_availableCombinationsN: error while allocating memory", err
732  err = 200
733  return
734  end if
735  combinations = projectiles_targets_names_n
736  end subroutine esputr2001_availablecombinationsn
737 
739  subroutine esputr2001_availablecombinationsth(combinations, err)
741  character(ESPUTR2001_MAX_NAME_LENGTH*2), dimension(:,:), allocatable, intent(inout) :: combinations
743  integer, intent(out) :: err
744  character(ESPUTR_MAX_LINE_LENGTH) :: currentCombination, lastCombination
745  integer :: i, numberOfCombination
746 
747  if(.not.allocated(projectiles_targets_names_th)) then
748  err = 50
749  write(esputr_unit, *) "ERROR in esputr2001_availableCombinationsTH: arrays are not initialized"
750  write(esputr_unit, *) " Call esputr2001_init first!"
751  return
752  end if
753  err = 0
754 
755  allocate(combinations(nprojectilestargetsth, 2), stat = err)
756  if(err /= 0) then
757  write(esputr_unit, *) "ERROR in esputr2001_availableCombinationsTH: error while allocating memory", err
758  err = 200
759  return
760  end if
761 
762  numberofcombination = 0
763  lastcombination = ""
764  do i = 1, size(projectiles_targets_names_th, 1)
765  currentcombination = projectiles_targets_names_th(i, 1) // projectiles_targets_names_th(i, 2)
766  if(currentcombination /= lastcombination) then
767  numberofcombination = numberofcombination + 1
768  combinations(numberofcombination,:) = (/ projectiles_targets_names_th(i, 1), projectiles_targets_names_th(i, 2) /)
769  lastcombination = currentcombination
770  end if
771  end do
773 
775  subroutine esputr2001_getavailableenergyrange(projTargStartId, projTargEndId, Emin, Emax, err)
777  integer, intent(in) :: projTargStartId
779  integer, intent(in) :: projTargEndId
781  real(kind=ESPUTR_DP), intent(out) :: Emin
783  real(kind=ESPUTR_DP), intent(out) :: Emax
785  integer, intent(out) :: err
786  err = 0
787  if(.not.allocated(fitvalues_th)) then
788  err = 50
789  write(esputr_unit, *) "ERROR in esputr2001_getAvailableEnergyRange: arrays are not initialized"
790  write(esputr_unit, *) " Call esputr2001_init first!"
791  return
792  end if
793  if(size(fitvalues_th,2) < projtargendid .or. &
794  0 >= projtargstartid .or. &
795  projtargstartid > projtargendid) then
796  write(esputr_unit, *) "ERROR in esputr2001_getAvailableEnergyRange: lower/upper bound is invalid",&
797  projtargstartid, projtargstartid
798  err = 100
799  return
800  end if
801  emin = fitvalues_th(1, projtargstartid)
802  emax = fitvalues_th(1, projtargendid)
804 
807  integer function getindexof2(subj1, subj2, list, lastIndex)
808 
809  character(*), intent(in) :: subj1, subj2
811  character(*), dimension(:,:), intent(in) :: list
814  integer, optional, intent(inout) :: lastIndex
815  integer :: i, j, n
816  intrinsic size,present
817  getindexof2 = 0
818  if(present(lastindex)) lastindex = 0
819  n=size(list, 1)
820  foreachitem: do i = 1, n
821  match: if(list(i,1) == subj1 .and. list(i,2) == subj2) then
822  getindexof2 = i
823  mustfindlast: if(present(lastindex)) then
824  lastindex = i
825  findlast: do j = i+1, n
826  if(list(j,1) == subj1 .and. list(j,2) == subj2) then
827  lastindex = j
828  else
829  exit findlast
830  end if
831  end do findlast
832  end if mustfindlast
833  exit foreachitem
834  end if match
835  end do foreachitem
836  end function getindexof2
837 
842  integer function findindex(loBound, upBound, x, arr, err)
843 
844  integer, intent(in) :: loBound
846  integer, intent(in) :: upBound
848  real(ESPUTR_DP), intent(in) :: x
850  real(ESPUTR_DP), dimension(:), intent(in) :: arr
852  integer :: err
853 
854  integer :: i1, i2, i
855 
856  err = 0
857 
858  i1 = lobound
859  i2 = upbound
860 
861  if(arr(lobound) > x) then
862  err=21
863  findindex=lobound
864  return
865  end if
866  if(arr(upbound) < x) then
867  err=21
868  findindex=upbound
869  return
870  end if
871 
872  do
873  i = (i1 + i2) / 2
874  if(i1+1 == i2) then
875  exit
876  else if(i1 == i2) then
877  if(i1 == upbound) then
878  i1 = i1 - 1
879  end if
880  exit
881  else if(arr(i) < x) then
882  i1 = i
883  else
884  i2 = i
885  end if
886  end do
887  findindex=i1
888  end function findindex
889 
890 end module esputr2001
integer, parameter, public esputr2001_max_name_length
Maximum length of the names of (chemical) elements.
Definition: esputr2001.f90:51
integer function, public numberoflines(fileName, ignoreComments, err)
Return number of lines in the file, without blank lines and comment lines (started with #) ...
Definition: esputr.f90:95
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
subroutine, public esputr2001_initn(fileNName, err)
Definition: esputr2001.f90:152
integer, parameter, private nconstants_n
Number of parameters read from the input file for 2001-model for normal incidence (for one target/pro...
Definition: esputr2001.f90:55
real(esputr_dp), parameter, public esputr_pi
Pi number.
Definition: esputr.f90:79
subroutine, public esputr2001_deallocate(err)
Deallocate dynamic arrays used by this module.
Definition: esputr2001.f90:426
subroutine, public esputr2001_check(res, err)
Check integrity and validity of data in the module.
Definition: esputr2001.f90:306
logical function, public esputr2001_if_initialized()
Return .true. if module esputr2001 is initialized.
Definition: esputr2001.f90:421
real(esputr_dp), parameter, public esputr_pi2
Pi divided by 2.
Definition: esputr.f90:81
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
subroutine, public esputr2001_availablecombinationsth(combinations, err)
Return the list of available projectile-target combinations for angular dependence.
Definition: esputr2001.f90:740
integer, save, private nprojectilestargetsth
Number of projectile-target combinations loaded for angular dependence.
Definition: esputr2001.f90:113
integer, parameter, private nconstants_th
Number of parameters read from the input file for 2001-model for angular dependence (for one target/p...
Definition: esputr2001.f90:58
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, save, public esputr2001_extrapolate_angular
Switch for extrapolation of the angular dependency to energies for which no data are defined...
Definition: esputr2001.f90:49
character(*), parameter, public esputr_comment_start
chracter which is used to start comments in the data files
Definition: esputr.f90:86
real(esputr_dp), dimension(:,:), allocatable, save, private fitvalues_th
Array with parameters read for angular dependence for 2001-model.
Definition: esputr2001.f90:93
real(esputr_dp), dimension(:,:), allocatable, save, private fitvalues_n
Array with parameters of fitting formula for normal incidence for 2001-model.
Definition: esputr2001.f90:75
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
integer, save, private ncombinations_th
Number of entries loaded for 2001-model for angular dependence.
Definition: esputr2001.f90:62
subroutine, public esputr2001_initth(fileTHName, err)
Definition: esputr2001.f90:170
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
subroutine, public esputr2001_init(fileNName, fileThName, err)
Initialization of the 2001-model.
Definition: esputr2001.f90:128
character(esputr2001_max_name_length), dimension(:,:), allocatable, save, private projectiles_targets_names_th
Array of strings which contains the names of the target-projectile combinations defined for 2001-mode...
Definition: esputr2001.f90:109
subroutine, public esputr2001_availablecombinationsn(combinations, err)
Return the list of available projectile-target combinations for normal incidence. ...
Definition: esputr2001.f90:718
character(esputr2001_max_name_length), dimension(:,:), allocatable, save, private projectiles_targets_names_n
Array of strings which contains the names of the target-projectile combinations defined for 2001-mode...
Definition: esputr2001.f90:101
integer, save, public esputr_unit
Index of the unit for standard output, default value 6.
Definition: esputr.f90:73
integer, save, private ncombinations_n
Number of entries loaded for 2001-model for normal incidence.
Definition: esputr2001.f90:60