diff --git a/tests/SetEpsTestCasesFromScratch/WFW/Makefile b/tests/SetEpsTestCasesFromScratch/WFW/Makefile
new file mode 100644
index 0000000000000000000000000000000000000000..8c011149caeb550e66cde72a8e46831f81d89ed4
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/Makefile
@@ -0,0 +1,74 @@
+.SUFFIXES: .f90 .F90 .o
+
+# fortran compiler
+FC = gfortran 
+
+# fortran compiler options
+FFLAGS = -g -gdwarf-2 -fbounds-check -fcheck=all -ffpe-trap=invalid -O0 -Wall
+# gfortran version 4.8 does not know -fdiagnostics-color
+# safeguard for major version >= 5
+GFORTAN_VERSION_GE_5 := $(shell echo `gcc -dumpversion | cut -f1 -d. ` \>= 5 | bc)
+ifeq "$(GFORTAN_VERSION_GE_5)" "1"
+	FFLAGS += -fdiagnostics-color=auto
+endif
+
+# implicit rules for compiling fortran files
+%.o:       %.f90 ; $(FC) $(FFLAGS) -c $< 
+%_mod.mod: %.f90 ; $(FC) $(FFLAGS) -c $<
+
+all: eels
+
+eelsmods = quanc8_mod.mod queels_mod.mod seteps_mod.mod param_mod.mod
+doeels.o: doeels.f90 $(eelsmods)
+
+queels_mod.mod: quanc8_mod.mod fint1_mod.mod fint2_mod.mod fint3_mod.mod
+quanc8_mod.mod: fun_mod.mod
+fint1_mod.mod: surlos_mod.mod param_mod.mod
+fint2_mod.mod: surlos_mod.mod param_mod.mod
+fint3_mod.mod: surlos_mod.mod param_mod.mod
+fun_mod.mod: param_mod.mod
+
+seteps_mod.mod: myEels20-seteps.f90
+	$(FC) $(FFLAGS) -c -o seteps.o myEels20-seteps.f90
+
+getoptsubs = getopt.o text.o system.o constants.o date_and_time.o kinds.o dummy_variables.o
+
+getoptmods = sufr_getopt.mod sufr_text.mod sufr_system.mod sufr_constants.mod sufr_date_and_time.mod sufr_kinds.mod sufr_dummy.mod
+
+sufr_getopt.mod: sufr_text.mod
+	$(FC) $(FFLAGS) -ffree-line-length-180 -c -o getopt.o ../getopt-libs/libsufr-0.7.7/src/getopt.f90
+
+sufr_text.mod: sufr_system.mod
+	$(FC) $(FFLAGS) -ffree-line-length-160 -c -o text.o ../getopt-libs/libsufr-0.7.7/src/text.f90
+
+sufr_system.mod: sufr_constants.mod sufr_dummy.mod
+	$(FC) $(FFLAGS) -c -o system.o ../getopt-libs/libsufr-0.7.7/src/system.f90
+
+sufr_constants.mod: sufr_date_and_time.mod
+	$(FC) $(FFLAGS) -ffree-line-length-256 -c -o constants.o ../getopt-libs/libsufr-0.7.7/src/constants.f90
+
+sufr_date_and_time.mod: sufr_kinds.mod
+	$(FC) $(FFLAGS) -ffree-line-length-150 -c -o date_and_time.o ../getopt-libs/libsufr-0.7.7/src/date_and_time.f90
+
+sufr_kinds.mod:
+	$(FC) $(FFLAGS) -c -o kinds.o ../getopt-libs/libsufr-0.7.7/src/kinds.f90
+
+sufr_dummy.mod:
+	$(FC) $(FFLAGS) -c -o dummy_variables.o ../getopt-libs/libsufr-0.7.7/src/dummy_variables.f90
+
+eelssubs = doeels.o usurlo.o quanc8.o fun.o queels.o fint1.o fint2.o fint3.o surlos.o seteps.o phint.o qrat.o param.o
+eels: eels.f90 change_working_dir.o $(eelssubs) $(eelsmods)
+	$(FC) $(FFLAGS) -o eels eels.f90 change_working_dir.o $(eelssubs)
+
+get_commandline_options.o: get_commandline_options.f90 $(getoptmods) $(getoptsubs)
+	$(FC) $(FFLAGS) -c -o get_commandline_options.o get_commandline_options.f90
+
+clean:
+	rm -f *.o
+	rm -rf *.dSYM
+	rm -f *.mod
+	rm -f *.so
+	rm -f eelsou
+	rm -f eels eels.exe
+
+.PHONY: all clean
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/README b/tests/SetEpsTestCasesFromScratch/WFW/README
new file mode 100644
index 0000000000000000000000000000000000000000..d4839456790eb5b2cb8d560f56616f7d3432a629
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/README
@@ -0,0 +1,13 @@
+Command for compilation:
+
+> make
+
+Command for execution:
+
+> doRun.sh
+
+Cleanup:
+
+> make clean
+
+KMS
\ No newline at end of file
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/calltree.txt b/tests/SetEpsTestCasesFromScratch/WFW/calltree.txt
new file mode 100644
index 0000000000000000000000000000000000000000..78ec920fd02b00b1906bb0509bbd3ce2ca96625d
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/calltree.txt
@@ -0,0 +1,16 @@
+Calltrees of EELS
+
+EELS
+  change_working_dir
+  doeels
+    quanc8
+      fun
+    queels
+      quanc8
+        fun
+      fint1, fint2, fint3
+        usurlo
+        surlos
+        phint
+    seteps
+    (extend3)
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/change_working_dir.f90 b/tests/SetEpsTestCasesFromScratch/WFW/change_working_dir.f90
new file mode 100644
index 0000000000000000000000000000000000000000..4685606b6ae636f63c5e444486c7acb2c61e7842
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/change_working_dir.f90
@@ -0,0 +1,25 @@
+subroutine change_working_dir()
+
+! This routine gets the first argument of the commandline and takes it
+! as the path to change the working directory
+! used intrinsic routines:
+! iarg returns the number of commandline arguments without the program cname.
+! chdir changes the directory and returns 0 on success.
+! trim removes blanks from strings.
+
+  character (len = 256) :: argument
+  integer :: status
+
+  if (iargc() == 1) then
+    call getarg(1, argument)
+    status = chdir(trim(argument))
+    if (status /= 0) then
+      write (*,*) '*** change directory failed ***'
+      write (*,*) 'directory tried: ', trim(argument)
+      write (*,*) 'error code (see: man chdir): ', status
+      write (*,*) 'continuing in the start directory'
+    end if
+  end if
+
+  return
+end subroutine change_working_dir
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/doRun.sh b/tests/SetEpsTestCasesFromScratch/WFW/doRun.sh
new file mode 100755
index 0000000000000000000000000000000000000000..f5a8e515567c4f4d1e9bde28d4efd172018c2af5
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/doRun.sh
@@ -0,0 +1,15 @@
+#!/bin/sh -v
+cp ../inputFIles/eelsin001 eelsin
+./eels
+mv seteps.log epsLog/seteps001.log
+
+cp ../inputFIles/eelsin004 eelsin
+./eels
+mv seteps.log epsLog/seteps004.log
+
+cp ../inputFIles/eelsin006 eelsin
+./eels
+mv seteps.log epsLog/seteps006.log
+
+rm eelsin
+rm EELSOU
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/doeels.f90 b/tests/SetEpsTestCasesFromScratch/WFW/doeels.f90
new file mode 100644
index 0000000000000000000000000000000000000000..972e962842154d1157f35bba8928a77eebb10859
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/doeels.f90
@@ -0,0 +1,261 @@
+module doeels_mod
+contains
+subroutine doeels (e0, theta, phia, phib, wmin, wmax, dw, comment, comment_size,   &
+              layers, neps, nper, name, name_size, thick, epsinf, nos, osc, osc_size,&
+              contrl, mode, wn_array, debug, f_array, wn_array_size)
+
+! ******************************************************************
+! *                                                                *
+! * compute the classical eels spectrum of an arbitrary plane-     *
+! * statified medium made from isotropic materials in specular     *
+! * geometry using the dielectric theory of eels.                  *
+! *                                                                *
+! * e0:             impact energy (eV)                             *
+! * theta:          incidence angle (°)                            *
+! * phia, phib:     angular apertures of the elliptic detector (°) *
+! * wmin, wmax, dw: energy-loss interval and step size (cm**-1)    *
+! * comment:        comment lines                                  *
+! * comment_size:   number of comment lines                        *
+! * layers:         number of layers                               *
+! * neps:           number of epsilon values                       *
+! * nper:           number of periodic layers                      *
+! * name:           layer names                                    *
+! * name_size:      number of layers                               *
+! * thick:          layer thickness                                *
+! * epsinf:         epsilon at infinite frequency                  *
+! * nos:            number of oscillators                          *
+! * osc:            oscillator parameters, wTO, Q, lambda          *
+! * osc_size:       number of oscillators                          *
+! * contrl:         'image' for image-charge screening             *
+! * mode:           'kurosawa' for kurosawa model                  *
+! * wn_array:       frequencies                                    *
+! * debug:          logical                                        *
+! * f_array:        spectrum                                       *
+! * wn_array_size:  number of frequencies                          *
+! *                                                                *
+! ******************************************************************
+
+  use quanc8_mod
+  use queels_mod
+  use seteps_mod
+  use param_mod
+
+  implicit none
+
+  integer, parameter :: nt = 5
+
+  double precision, intent(in) :: e0, theta, phia, phib, wmin, wmax, dw
+  character (len = 72) :: comment(comment_size)
+  character (len = 10) :: name(name_size)
+  double precision, intent(in) :: thick(name_size), epsinf(name_size), osc(3, osc_size)
+  character (len = 10) :: contrl, mode
+  integer, intent(in) :: comment_size, name_size, osc_size, wn_array_size
+  integer, intent(in out) :: layers, nper, nos(name_size)
+  double precision, intent(in out) :: wn_array(wn_array_size), f_array(wn_array_size)
+  logical, intent(in), optional :: debug
+
+  integer :: i, iw, neps, nofu, nout, nw, lmax
+  double precision :: a, aerr, alpha, b, beta,              &
+      c1, c2, dx, ener, facru, f, f0,                       &
+      f1, fpic, fun, pi, prefac, psia, psii, qrat, rerr, t, &
+      width, wpic, x, xmin, xmax, z, z1, z2
+  double precision :: table(nt)
+  double complex, allocatable :: eps(:)
+
+! **** log modification start
+  integer :: j
+! **** log modification end
+
+  external fun, qrat
+
+  data aerr / 0.0d0 /, rerr / 1.0d-06 /, f / 0.0d0 /, f1 / 0.0d0 /
+
+! **** log modification start
+  open(unit = 99, file = 'seteps.log')
+! **** log modification end
+
+  if (debug) then
+    write (*,*) 'doeels:'
+    write (*,*) 'comment: ',  size(comment)
+    write (*,*) 'name: ',     size(name)
+    write (*,*) 'thick: ',    size(thick)
+    write (*,*) 'epsinf: ',   size(epsinf)
+    write (*,*) 'osc: ',      size(osc), size(osc, 1), size(osc, 2)
+    write (*,*) 'nos: ',      size(nos)
+    write (*,*) 'wn_array: ', size(wn_array)
+    write (*,*) 'f_array: ',  size(f_array)
+  endif
+
+! *** machine-dependent constants
+! *** epsmac + 1.0 = epsmac , cosh(argmin) = 1.0 , tanh(argmax) = 1.0
+
+  pi = 4 * datan(1.0d0)
+
+  dlimf = 0.0d0
+  rational = .false.
+
+! *** read target specifications
+
+  user = layers == 0
+  if (user) then
+
+    if (layers == 1) rational = .true.
+    if (contrl == 'image') then
+! *** image-charge screening factor
+      if (layers == 1 .and. neps == 2) then
+        dlimf = dsqrt(epsinf(1) * epsinf(2))
+      else
+        dlimf = epsinf(1)
+      endif
+      dlimf = (dlimf - 1.0d0) / (dlimf + 1.0d0)
+    endif
+  endif
+
+! *** initialize constants
+
+  lmax = size(thick)
+  nw = size(wn_array)
+  if (debug) write (*,*) 'lmax: ', lmax
+  allocate(eps(lmax))
+  if (debug) write (*,*) 'eps: ', size(eps)
+  nout = 1 + nw / 20
+  ener = 8065 * e0
+  psia = phia / 180 * pi
+  psii = theta / 180 * pi
+  cospsi = dcos(psii)
+  sinpsi = dsin(psii)
+  tanpsi = dtan(psii)
+  prefac = dsqrt(255500 / e0)/(137 * cospsi)
+  facru = psia / cospsi * dsqrt(0.2624664d0 * e0)
+  elleps = (1.0d0 - phia / phib) * (1.0d0 + phia / phib)
+  acoef = sinpsi**2 + elleps * cospsi**2
+  bcoef = sinpsi * cospsi
+  if (dlimf > 0.0d0) then
+    rational = .false.
+    if (debug) write(*,*) ' = > electron attracted by an image charge = ', dlimf
+! *** dlimf : half the length unit imposed by the image force
+    dlimf = 1.80d0 * dlimf/(e0 * cospsi**2)
+  endif
+  if (debug) write (*,*) 'rational: ', rational
+  if (rational) then
+
+! *** set up coefficients for the rational approximation to the integral
+
+    if (debug) write(*,*) ' = > set up a rational approximation to the integral'
+    call quanc8(fun, 0.0d0, pi / 2, aerr, rerr, alpha, c1, nofu, c2, eps, thick, layers, nper)
+    alpha  = (2 / pi)**2 * alpha
+    c1 = 2 / pi / dsqrt(1.0d0 - elleps) * sinpsi * alpha**2
+    if (c1 > 0.99d0) then
+      if (debug) write(*,*) ' ===> cannot do it'
+      rational = .false.
+    else
+      c2 = 3 * alpha**2 / (1.0d0 - c1)
+      c1 = c1 * c2
+      xmin = wmin / (2 * ener * psia)
+      xmax = wmax / (2 * ener * psia)
+      if (xmin <= 0.0d0) xmin = 0.0d0
+      dx = dmax1(0.02d0, (xmax - xmin) / nt)
+      z1 = 0.0d0
+      z2 = 0.0d0
+      do i = 1, nt
+        x = xmin + i * dx
+        call queels(x, f, aerr, rerr, facru, eps, thick, layers, nper)
+        table(i) = f
+        f = f * (1.0d0 + alpha * x)**2
+        if (dabs(c2 * f - c1) < c2 * rerr) cycle
+        z = (1.0d0 - f) / (c2 * f - c1)
+        if (z <= 0.0d0) cycle
+        z1 = z1 + x * z * (x**2 - z)
+        z2 = z2 + (x * z)**2
+      enddo
+      if (z2 == 0.0d0) then
+        if (debug) write(*,*) ' ===> cannot do it'
+        rational = .false.
+      else
+        beta = z1 / z2
+        z = 0.0d0
+        do i = 1, nt
+          x = xmin + i * dx
+          z = z + (table(i) - qrat(x, alpha, beta, c1, c2))**2
+        enddo
+        z = dsqrt(z) / nt
+        if (z > 5.0d-03) then
+          if (debug) write(*,*) ' ===> cannot do it'
+          rational = .false.
+        else
+          if (debug) write(*, 100) alpha, c1, c2, beta, z
+        endif ! z > 5.0d-03
+      endif ! z2 == 0.0d0
+    endif ! c1 > 0.99d0
+  endif ! rational
+
+! *** loop over the energy losses
+
+  if (debug) write(*, 110)
+
+! **** log modification start
+  write (99, '(i5, i5)')         neps, layers
+  write (99, '(a)')              mode
+  do i = 1, neps
+    write (99, '(a, g15.7, i5)') name(i), epsinf(i), nos(i)
+    do j = 1, nos(i)
+      write (99, '(3g15.7)')     osc(1,j), osc(2,j), osc(3,j)
+    enddo
+  enddo
+  write (99, *)
+! **** log modification end
+
+  do iw = 1, nw
+    f0 = f1
+    f1 = f
+    f = 0.0d0
+    wn = wmin + (iw - 1) * dw
+!    if (debug) write (*,*) 'wn: ', wn
+    if (wn >= 0.0d0) then
+      if (wn /= 0.0d0) then
+        if (.not. user) call seteps(neps, nos, osc, epsinf, wn, name, eps, layers, mode)
+
+        x = wn / (2 * ener * psia)
+        if (rational) then
+          f = qrat(x, alpha, beta, c1, c2) * dimag(-2 / (1.0d0 + eps(1)))
+        else
+          call queels(x, f, aerr, rerr, facru, eps, thick, layers, nper)
+        endif
+        f = prefac * f / wn
+      endif ! wn /= 0.0d0
+
+      wn_array(iw) = wn
+      f_array(iw)  = f
+
+! *** localize a peak using a parabolic interpolation
+
+      if ((iw >= 3) .and. (f1 - f0 > aerr) .and. (f1 - f > aerr)) then
+        a = (f1 - f0) + (f1 - f)
+        if (a > 4 * rerr * f1) then
+          b = 0.5d0 * (f1 - f0 + 3 * (f1 - f))
+          t = b / a
+          wpic = wn - t * dw
+          fpic = f + 0.5d0 * b * t
+          width = dsqrt(8 * fpic / a) * dw
+          if (debug) write(*, 120) wpic, fpic, width
+        endif ! a > 4 * rerr * f1
+      endif ! iw >= 3 ...
+    endif ! wn >= 0.0d0
+    if (mod(iw, nout) == 0) then
+      if (debug) write(*, 130) 100 * iw / nw, wn, f
+    endif
+  enddo
+
+! **** log modification start
+  close (unit = 99)
+! **** log modification end
+
+  return
+100 format(5x, 'alpha = ', f9.4, 4x, 'c1 = ', f9.4, 4x, 'c2 = ', f9.4, 4x,  &
+      'beta = ', f9.4/5x, 'accuracy = ', e9.2)
+110 format(//' run (%)  wn (cm**-1)  pcl(wn) (cm) |',  &
+      ' peak location  amplitude    width')
+120 format(40x, f10.2, d12.4, f10.2)
+130 format(2x, f5.1, 3x, f11.3, d14.5)
+end subroutine doeels
+end module doeels_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/eels b/tests/SetEpsTestCasesFromScratch/WFW/eels
new file mode 100755
index 0000000000000000000000000000000000000000..27712386d9484900bda8e1e215ae9c17c5fa86b8
Binary files /dev/null and b/tests/SetEpsTestCasesFromScratch/WFW/eels differ
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/eels.f90 b/tests/SetEpsTestCasesFromScratch/WFW/eels.f90
new file mode 100644
index 0000000000000000000000000000000000000000..3eb1277e01072b48e1ee02fa199b009c24b473ad
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/eels.f90
@@ -0,0 +1,160 @@
+program eels
+
+! ******************************************************************
+! *                                                                *
+! * compute the classical eels spectrum of an arbitrary plane-     *
+! * statified medium made from isotropic materials in specular     *
+! * geometry using the dielectric theory of eels.                  *
+! *                                                                *
+! ******************************************************************
+
+  use doeels_mod
+
+  implicit none
+
+  double precision :: e0, theta, phia, phib, wmin, wmax, dw
+  integer :: i, j, jos, k, l, layers, neps, nper, nw
+  logical :: user
+  character (len = 72) :: comment(2)
+  character (len = 10) :: contrl, mode
+
+  double precision, allocatable :: thick(:), epsinf(:), osc(:, :)
+  integer, allocatable :: nos(:)
+  character (len = 10), allocatable :: name(:)
+  double precision, allocatable :: wn_array(:), f(:)
+
+  integer :: old_size_1, old_size_2
+  double precision, allocatable :: tmp_osc(:, :)
+  logical :: debug
+  integer :: ioStatus
+
+!  integer, parameter :: name_length = 10
+! *** read spectrometer parameters
+
+  call change_working_dir()
+  open(unit = 11, file = 'eelsin')
+! impact energy (eV)
+  read(11, *) e0
+! incidence angle (°)
+  read(11, *) theta
+! angular apertures of the elliptic detector (°)
+  read(11, *) phia
+  read(11, *) phib
+! energy-loss interval and step size (cm**-1)
+  read(11, *) wmin
+  read(11, *) wmax
+  read(11, *) dw
+! comment lines
+  read(11, '(a72)') (comment(k), k = 1, 2)
+
+  write(*,*) 'program eels (September 2020)'
+  write(*,'(a, f6.2, a, f5.1, a, f5.2, a, f5.2, a)') &
+    ' e0 = ', e0, ' eV, theta = ', theta, '°, phia = ', &
+    phia, '°, phib = ', phib, '°'
+  write(*,'(a, g11.4, a, g11.4, a, g11.4, a)') &
+    ' energy losses from', wmin, ' to', wmax, ', step = ', dw, ' cm**-1'
+  write(*,*) comment(1)
+  write(*,*) comment(2)
+
+  if (phia <= 0.0d0 .or. phib <= 0.0d0) then
+    stop '*** wrong input ***'
+  endif
+  if (e0 <= 0.0d0 .or. theta + phia >= 90.0d0) then
+    stop '*** bad input ***'
+  endif
+
+! *** read target specifications
+
+  read(11, *) layers, nper, mode
+  user = layers == 0
+  if (.not. user) then
+    neps = layers
+    if (nper == -1) then
+      neps = layers + 1
+      nper = 1
+      write(*,*) 'the substrate is a anisotropic uniaxial material'
+    endif
+    if (layers < 0 .or. nper < 1 .or. nper > layers) then
+      stop '*** invalid target specifications ***'
+    endif
+    write(6, 101) layers, nper
+    jos = 0
+    allocate (name(neps), thick(neps), epsinf(neps), nos(neps))
+    do l = 1, neps
+      if (l <= layers) then
+        read(11, 102) name(l), thick(l)
+      endif
+      read(11, *) epsinf(l), nos(l)
+      write(6, 103)
+      if (nos(l) <= 0) then
+        if (l <= layers) write(6, 104) l, name(l), thick(l), epsinf(l)
+        if (l  > layers) write(6, 105) epsinf(l)
+      else
+        do j = 1, nos(l)
+          if (.not. allocated(osc)) then
+            allocate(osc(3, nos(l)))
+          else if (j == 1) then
+ !           call extend3(osc, nos(j))
+            old_size_1 = size(osc, 1)
+            old_size_2 = size(osc, 2)
+            allocate(tmp_osc(old_size_1, old_size_2 + nos(l)))
+            tmp_osc(1:old_size_1, 1:old_size_2) = osc
+            deallocate(osc)
+            call move_alloc(tmp_osc, osc)
+          endif
+          jos = jos + 1
+          read(11, *) (osc(k, jos), k = 1, 3)
+          if ((j == nos(l) / 2 + 1) .and. (nos(l) > 1)) then
+            write(6, 106)
+            write(6, 107)
+          endif
+          if (j == 1) then
+            if (l <= layers) then
+              write(6, 104) l, name(l), thick(l), epsinf(l), (osc(i, jos), i = 1, 3)
+            else
+              write(6, 105) epsinf(l), (osc(i, jos), i = 1, 3)
+            endif
+          else
+            write(6, 108) (osc(i, jos), i = 1, 3)
+          endif
+        enddo
+      endif
+    enddo
+    write(*,*)
+    read(11, 102, IOSTAT = ioStatus) contrl
+    if (ioStatus /= 0) then
+      contrl = ''
+    endif
+  endif
+
+  close (unit = 11)
+
+  nw = 1 + int((wmax - wmin) / dw)
+  allocate (wn_array(nw), f(nw))
+
+  debug = .false.
+  call doeels(e0, theta, phia, phib, wmin, wmax, dw, comment, size(comment),   &
+              layers, neps, nper, name, size(name), thick, epsinf, nos, osc, size(osc, 2),&
+              contrl, mode, wn_array, debug, f, size(wn_array))
+
+  open (unit = 12, file = 'eelsou')
+  write (12, 207) e0, theta, phia, phib
+  write (12, '(a72)') comment(1)
+  do i = 1, nw
+    write (12, '(2e15.7)') wn_array(i), f(i)
+  enddo
+  close (unit = 12)
+
+  stop
+
+101 format(i3, ' layer(s), nper = ', i2//'   l', 2x, 'material', 7x,  &
+      'thickness', 5x, 'epsinf', 4x, 'wto , wp', 5x, 'q', 7x, 'gam/wto')
+102 format(a10, d15.5)
+103 format(1x, 72('-'))
+104 format(1x, i3, 2x, a10, g15.3, f10.4, f12.4, f10.4, f9.4)
+105 format(31x, f10.4, f12.4, f10.4, f9.4)
+106 format(45x, 'wlo , wp', 5x, 'q', 7x, 'gam/wlo')
+107 format(45x, 28('-'))
+108 format(41x, f12.4, f10.4, f9.4)
+207 format('e0 =', f6.2, ' theta =', f5.1, ' phia =', f5.2, ' phib =', f5.2)
+end program eels
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps001.log b/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps001.log
new file mode 100644
index 0000000000000000000000000000000000000000..a1dd64d082b9332ac15b277341920ab217cb6c40
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps001.log
@@ -0,0 +1,331 @@
+    1    1
+No-layers 
+MnO          4.950000        1
+   269.0000       16.00000      0.5000000E-01
+
+   50.00000       4.950000       0.000000    
+   52.00000       4.950000       0.000000    
+   54.00000       4.950000       0.000000    
+   56.00000       4.950000       0.000000    
+   58.00000       4.950000       0.000000    
+   60.00000       4.950000       0.000000    
+   62.00000       4.950000       0.000000    
+   64.00000       4.950000       0.000000    
+   66.00000       4.950000       0.000000    
+   68.00000       4.950000       0.000000    
+   70.00000       4.950000       0.000000    
+   72.00000       4.950000       0.000000    
+   74.00000       4.950000       0.000000    
+   76.00000       4.950000       0.000000    
+   78.00000       4.950000       0.000000    
+   80.00000       4.950000       0.000000    
+   82.00000       4.950000       0.000000    
+   84.00000       4.950000       0.000000    
+   86.00000       4.950000       0.000000    
+   88.00000       4.950000       0.000000    
+   90.00000       4.950000       0.000000    
+   92.00000       4.950000       0.000000    
+   94.00000       4.950000       0.000000    
+   96.00000       4.950000       0.000000    
+   98.00000       4.950000       0.000000    
+   100.0000       4.950000       0.000000    
+   102.0000       4.950000       0.000000    
+   104.0000       4.950000       0.000000    
+   106.0000       4.950000       0.000000    
+   108.0000       4.950000       0.000000    
+   110.0000       4.950000       0.000000    
+   112.0000       4.950000       0.000000    
+   114.0000       4.950000       0.000000    
+   116.0000       4.950000       0.000000    
+   118.0000       4.950000       0.000000    
+   120.0000       4.950000       0.000000    
+   122.0000       4.950000       0.000000    
+   124.0000       4.950000       0.000000    
+   126.0000       4.950000       0.000000    
+   128.0000       4.950000       0.000000    
+   130.0000       4.950000       0.000000    
+   132.0000       4.950000       0.000000    
+   134.0000       4.950000       0.000000    
+   136.0000       4.950000       0.000000    
+   138.0000       4.950000       0.000000    
+   140.0000       4.950000       0.000000    
+   142.0000       4.950000       0.000000    
+   144.0000       4.950000       0.000000    
+   146.0000       4.950000       0.000000    
+   148.0000       4.950000       0.000000    
+   150.0000       4.950000       0.000000    
+   152.0000       4.950000       0.000000    
+   154.0000       4.950000       0.000000    
+   156.0000       4.950000       0.000000    
+   158.0000       4.950000       0.000000    
+   160.0000       4.950000       0.000000    
+   162.0000       4.950000       0.000000    
+   164.0000       4.950000       0.000000    
+   166.0000       4.950000       0.000000    
+   168.0000       4.950000       0.000000    
+   170.0000       4.950000       0.000000    
+   172.0000       4.950000       0.000000    
+   174.0000       4.950000       0.000000    
+   176.0000       4.950000       0.000000    
+   178.0000       4.950000       0.000000    
+   180.0000       4.950000       0.000000    
+   182.0000       4.950000       0.000000    
+   184.0000       4.950000       0.000000    
+   186.0000       4.950000       0.000000    
+   188.0000       4.950000       0.000000    
+   190.0000       4.950000       0.000000    
+   192.0000       4.950000       0.000000    
+   194.0000       4.950000       0.000000    
+   196.0000       4.950000       0.000000    
+   198.0000       4.950000       0.000000    
+   200.0000       4.950000       0.000000    
+   202.0000       4.950000       0.000000    
+   204.0000       4.950000       0.000000    
+   206.0000       4.950000       0.000000    
+   208.0000       4.950000       0.000000    
+   210.0000       4.950000       0.000000    
+   212.0000       4.950000       0.000000    
+   214.0000       4.950000       0.000000    
+   216.0000       4.950000       0.000000    
+   218.0000       4.950000       0.000000    
+   220.0000       4.950000       0.000000    
+   222.0000       4.950000       0.000000    
+   224.0000       4.950000       0.000000    
+   226.0000       4.950000       0.000000    
+   228.0000       4.950000       0.000000    
+   230.0000       4.950000       0.000000    
+   232.0000       4.950000       0.000000    
+   234.0000       4.950000       0.000000    
+   236.0000       4.950000       0.000000    
+   238.0000       4.950000       0.000000    
+   240.0000       4.950000       0.000000    
+   242.0000       4.950000       0.000000    
+   244.0000       4.950000       0.000000    
+   246.0000       4.950000       0.000000    
+   248.0000       4.950000       0.000000    
+   250.0000       4.950000       0.000000    
+   252.0000       4.950000       0.000000    
+   254.0000       4.950000       0.000000    
+   256.0000       4.950000       0.000000    
+   258.0000       4.950000       0.000000    
+   260.0000       4.950000       0.000000    
+   262.0000       4.950000       0.000000    
+   264.0000       4.950000       0.000000    
+   266.0000       4.950000       0.000000    
+   268.0000       4.950000       0.000000    
+   270.0000       4.950000       0.000000    
+   272.0000       4.950000       0.000000    
+   274.0000       4.950000       0.000000    
+   276.0000       4.950000       0.000000    
+   278.0000       4.950000       0.000000    
+   280.0000       4.950000       0.000000    
+   282.0000       4.950000       0.000000    
+   284.0000       4.950000       0.000000    
+   286.0000       4.950000       0.000000    
+   288.0000       4.950000       0.000000    
+   290.0000       4.950000       0.000000    
+   292.0000       4.950000       0.000000    
+   294.0000       4.950000       0.000000    
+   296.0000       4.950000       0.000000    
+   298.0000       4.950000       0.000000    
+   300.0000       4.950000       0.000000    
+   302.0000       4.950000       0.000000    
+   304.0000       4.950000       0.000000    
+   306.0000       4.950000       0.000000    
+   308.0000       4.950000       0.000000    
+   310.0000       4.950000       0.000000    
+   312.0000       4.950000       0.000000    
+   314.0000       4.950000       0.000000    
+   316.0000       4.950000       0.000000    
+   318.0000       4.950000       0.000000    
+   320.0000       4.950000       0.000000    
+   322.0000       4.950000       0.000000    
+   324.0000       4.950000       0.000000    
+   326.0000       4.950000       0.000000    
+   328.0000       4.950000       0.000000    
+   330.0000       4.950000       0.000000    
+   332.0000       4.950000       0.000000    
+   334.0000       4.950000       0.000000    
+   336.0000       4.950000       0.000000    
+   338.0000       4.950000       0.000000    
+   340.0000       4.950000       0.000000    
+   342.0000       4.950000       0.000000    
+   344.0000       4.950000       0.000000    
+   346.0000       4.950000       0.000000    
+   348.0000       4.950000       0.000000    
+   350.0000       4.950000       0.000000    
+   352.0000       4.950000       0.000000    
+   354.0000       4.950000       0.000000    
+   356.0000       4.950000       0.000000    
+   358.0000       4.950000       0.000000    
+   360.0000       4.950000       0.000000    
+   362.0000       4.950000       0.000000    
+   364.0000       4.950000       0.000000    
+   366.0000       4.950000       0.000000    
+   368.0000       4.950000       0.000000    
+   370.0000       4.950000       0.000000    
+   372.0000       4.950000       0.000000    
+   374.0000       4.950000       0.000000    
+   376.0000       4.950000       0.000000    
+   378.0000       4.950000       0.000000    
+   380.0000       4.950000       0.000000    
+   382.0000       4.950000       0.000000    
+   384.0000       4.950000       0.000000    
+   386.0000       4.950000       0.000000    
+   388.0000       4.950000       0.000000    
+   390.0000       4.950000       0.000000    
+   392.0000       4.950000       0.000000    
+   394.0000       4.950000       0.000000    
+   396.0000       4.950000       0.000000    
+   398.0000       4.950000       0.000000    
+   400.0000       4.950000       0.000000    
+   402.0000       4.950000       0.000000    
+   404.0000       4.950000       0.000000    
+   406.0000       4.950000       0.000000    
+   408.0000       4.950000       0.000000    
+   410.0000       4.950000       0.000000    
+   412.0000       4.950000       0.000000    
+   414.0000       4.950000       0.000000    
+   416.0000       4.950000       0.000000    
+   418.0000       4.950000       0.000000    
+   420.0000       4.950000       0.000000    
+   422.0000       4.950000       0.000000    
+   424.0000       4.950000       0.000000    
+   426.0000       4.950000       0.000000    
+   428.0000       4.950000       0.000000    
+   430.0000       4.950000       0.000000    
+   432.0000       4.950000       0.000000    
+   434.0000       4.950000       0.000000    
+   436.0000       4.950000       0.000000    
+   438.0000       4.950000       0.000000    
+   440.0000       4.950000       0.000000    
+   442.0000       4.950000       0.000000    
+   444.0000       4.950000       0.000000    
+   446.0000       4.950000       0.000000    
+   448.0000       4.950000       0.000000    
+   450.0000       4.950000       0.000000    
+   452.0000       4.950000       0.000000    
+   454.0000       4.950000       0.000000    
+   456.0000       4.950000       0.000000    
+   458.0000       4.950000       0.000000    
+   460.0000       4.950000       0.000000    
+   462.0000       4.950000       0.000000    
+   464.0000       4.950000       0.000000    
+   466.0000       4.950000       0.000000    
+   468.0000       4.950000       0.000000    
+   470.0000       4.950000       0.000000    
+   472.0000       4.950000       0.000000    
+   474.0000       4.950000       0.000000    
+   476.0000       4.950000       0.000000    
+   478.0000       4.950000       0.000000    
+   480.0000       4.950000       0.000000    
+   482.0000       4.950000       0.000000    
+   484.0000       4.950000       0.000000    
+   486.0000       4.950000       0.000000    
+   488.0000       4.950000       0.000000    
+   490.0000       4.950000       0.000000    
+   492.0000       4.950000       0.000000    
+   494.0000       4.950000       0.000000    
+   496.0000       4.950000       0.000000    
+   498.0000       4.950000       0.000000    
+   500.0000       4.950000       0.000000    
+   502.0000       4.950000       0.000000    
+   504.0000       4.950000       0.000000    
+   506.0000       4.950000       0.000000    
+   508.0000       4.950000       0.000000    
+   510.0000       4.950000       0.000000    
+   512.0000       4.950000       0.000000    
+   514.0000       4.950000       0.000000    
+   516.0000       4.950000       0.000000    
+   518.0000       4.950000       0.000000    
+   520.0000       4.950000       0.000000    
+   522.0000       4.950000       0.000000    
+   524.0000       4.950000       0.000000    
+   526.0000       4.950000       0.000000    
+   528.0000       4.950000       0.000000    
+   530.0000       4.950000       0.000000    
+   532.0000       4.950000       0.000000    
+   534.0000       4.950000       0.000000    
+   536.0000       4.950000       0.000000    
+   538.0000       4.950000       0.000000    
+   540.0000       4.950000       0.000000    
+   542.0000       4.950000       0.000000    
+   544.0000       4.950000       0.000000    
+   546.0000       4.950000       0.000000    
+   548.0000       4.950000       0.000000    
+   550.0000       4.950000       0.000000    
+   552.0000       4.950000       0.000000    
+   554.0000       4.950000       0.000000    
+   556.0000       4.950000       0.000000    
+   558.0000       4.950000       0.000000    
+   560.0000       4.950000       0.000000    
+   562.0000       4.950000       0.000000    
+   564.0000       4.950000       0.000000    
+   566.0000       4.950000       0.000000    
+   568.0000       4.950000       0.000000    
+   570.0000       4.950000       0.000000    
+   572.0000       4.950000       0.000000    
+   574.0000       4.950000       0.000000    
+   576.0000       4.950000       0.000000    
+   578.0000       4.950000       0.000000    
+   580.0000       4.950000       0.000000    
+   582.0000       4.950000       0.000000    
+   584.0000       4.950000       0.000000    
+   586.0000       4.950000       0.000000    
+   588.0000       4.950000       0.000000    
+   590.0000       4.950000       0.000000    
+   592.0000       4.950000       0.000000    
+   594.0000       4.950000       0.000000    
+   596.0000       4.950000       0.000000    
+   598.0000       4.950000       0.000000    
+   600.0000       4.950000       0.000000    
+   602.0000       4.950000       0.000000    
+   604.0000       4.950000       0.000000    
+   606.0000       4.950000       0.000000    
+   608.0000       4.950000       0.000000    
+   610.0000       4.950000       0.000000    
+   612.0000       4.950000       0.000000    
+   614.0000       4.950000       0.000000    
+   616.0000       4.950000       0.000000    
+   618.0000       4.950000       0.000000    
+   620.0000       4.950000       0.000000    
+   622.0000       4.950000       0.000000    
+   624.0000       4.950000       0.000000    
+   626.0000       4.950000       0.000000    
+   628.0000       4.950000       0.000000    
+   630.0000       4.950000       0.000000    
+   632.0000       4.950000       0.000000    
+   634.0000       4.950000       0.000000    
+   636.0000       4.950000       0.000000    
+   638.0000       4.950000       0.000000    
+   640.0000       4.950000       0.000000    
+   642.0000       4.950000       0.000000    
+   644.0000       4.950000       0.000000    
+   646.0000       4.950000       0.000000    
+   648.0000       4.950000       0.000000    
+   650.0000       4.950000       0.000000    
+   652.0000       4.950000       0.000000    
+   654.0000       4.950000       0.000000    
+   656.0000       4.950000       0.000000    
+   658.0000       4.950000       0.000000    
+   660.0000       4.950000       0.000000    
+   662.0000       4.950000       0.000000    
+   664.0000       4.950000       0.000000    
+   666.0000       4.950000       0.000000    
+   668.0000       4.950000       0.000000    
+   670.0000       4.950000       0.000000    
+   672.0000       4.950000       0.000000    
+   674.0000       4.950000       0.000000    
+   676.0000       4.950000       0.000000    
+   678.0000       4.950000       0.000000    
+   680.0000       4.950000       0.000000    
+   682.0000       4.950000       0.000000    
+   684.0000       4.950000       0.000000    
+   686.0000       4.950000       0.000000    
+   688.0000       4.950000       0.000000    
+   690.0000       4.950000       0.000000    
+   692.0000       4.950000       0.000000    
+   694.0000       4.950000       0.000000    
+   696.0000       4.950000       0.000000    
+   698.0000       4.950000       0.000000    
+   700.0000       4.950000       0.000000    
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps004.log b/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps004.log
new file mode 100644
index 0000000000000000000000000000000000000000..d8ef70b79e68e848183e5225ef0faa9f7232398b
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps004.log
@@ -0,0 +1,331 @@
+    1    1
+No-layers 
+Pt           8.900000        1
+   185541.0      -1.000000      0.1200000    
+
+   50.00000       8.900000       0.000000    
+   52.00000       8.900000       0.000000    
+   54.00000       8.900000       0.000000    
+   56.00000       8.900000       0.000000    
+   58.00000       8.900000       0.000000    
+   60.00000       8.900000       0.000000    
+   62.00000       8.900000       0.000000    
+   64.00000       8.900000       0.000000    
+   66.00000       8.900000       0.000000    
+   68.00000       8.900000       0.000000    
+   70.00000       8.900000       0.000000    
+   72.00000       8.900000       0.000000    
+   74.00000       8.900000       0.000000    
+   76.00000       8.900000       0.000000    
+   78.00000       8.900000       0.000000    
+   80.00000       8.900000       0.000000    
+   82.00000       8.900000       0.000000    
+   84.00000       8.900000       0.000000    
+   86.00000       8.900000       0.000000    
+   88.00000       8.900000       0.000000    
+   90.00000       8.900000       0.000000    
+   92.00000       8.900000       0.000000    
+   94.00000       8.900000       0.000000    
+   96.00000       8.900000       0.000000    
+   98.00000       8.900000       0.000000    
+   100.0000       8.900000       0.000000    
+   102.0000       8.900000       0.000000    
+   104.0000       8.900000       0.000000    
+   106.0000       8.900000       0.000000    
+   108.0000       8.900000       0.000000    
+   110.0000       8.900000       0.000000    
+   112.0000       8.900000       0.000000    
+   114.0000       8.900000       0.000000    
+   116.0000       8.900000       0.000000    
+   118.0000       8.900000       0.000000    
+   120.0000       8.900000       0.000000    
+   122.0000       8.900000       0.000000    
+   124.0000       8.900000       0.000000    
+   126.0000       8.900000       0.000000    
+   128.0000       8.900000       0.000000    
+   130.0000       8.900000       0.000000    
+   132.0000       8.900000       0.000000    
+   134.0000       8.900000       0.000000    
+   136.0000       8.900000       0.000000    
+   138.0000       8.900000       0.000000    
+   140.0000       8.900000       0.000000    
+   142.0000       8.900000       0.000000    
+   144.0000       8.900000       0.000000    
+   146.0000       8.900000       0.000000    
+   148.0000       8.900000       0.000000    
+   150.0000       8.900000       0.000000    
+   152.0000       8.900000       0.000000    
+   154.0000       8.900000       0.000000    
+   156.0000       8.900000       0.000000    
+   158.0000       8.900000       0.000000    
+   160.0000       8.900000       0.000000    
+   162.0000       8.900000       0.000000    
+   164.0000       8.900000       0.000000    
+   166.0000       8.900000       0.000000    
+   168.0000       8.900000       0.000000    
+   170.0000       8.900000       0.000000    
+   172.0000       8.900000       0.000000    
+   174.0000       8.900000       0.000000    
+   176.0000       8.900000       0.000000    
+   178.0000       8.900000       0.000000    
+   180.0000       8.900000       0.000000    
+   182.0000       8.900000       0.000000    
+   184.0000       8.900000       0.000000    
+   186.0000       8.900000       0.000000    
+   188.0000       8.900000       0.000000    
+   190.0000       8.900000       0.000000    
+   192.0000       8.900000       0.000000    
+   194.0000       8.900000       0.000000    
+   196.0000       8.900000       0.000000    
+   198.0000       8.900000       0.000000    
+   200.0000       8.900000       0.000000    
+   202.0000       8.900000       0.000000    
+   204.0000       8.900000       0.000000    
+   206.0000       8.900000       0.000000    
+   208.0000       8.900000       0.000000    
+   210.0000       8.900000       0.000000    
+   212.0000       8.900000       0.000000    
+   214.0000       8.900000       0.000000    
+   216.0000       8.900000       0.000000    
+   218.0000       8.900000       0.000000    
+   220.0000       8.900000       0.000000    
+   222.0000       8.900000       0.000000    
+   224.0000       8.900000       0.000000    
+   226.0000       8.900000       0.000000    
+   228.0000       8.900000       0.000000    
+   230.0000       8.900000       0.000000    
+   232.0000       8.900000       0.000000    
+   234.0000       8.900000       0.000000    
+   236.0000       8.900000       0.000000    
+   238.0000       8.900000       0.000000    
+   240.0000       8.900000       0.000000    
+   242.0000       8.900000       0.000000    
+   244.0000       8.900000       0.000000    
+   246.0000       8.900000       0.000000    
+   248.0000       8.900000       0.000000    
+   250.0000       8.900000       0.000000    
+   252.0000       8.900000       0.000000    
+   254.0000       8.900000       0.000000    
+   256.0000       8.900000       0.000000    
+   258.0000       8.900000       0.000000    
+   260.0000       8.900000       0.000000    
+   262.0000       8.900000       0.000000    
+   264.0000       8.900000       0.000000    
+   266.0000       8.900000       0.000000    
+   268.0000       8.900000       0.000000    
+   270.0000       8.900000       0.000000    
+   272.0000       8.900000       0.000000    
+   274.0000       8.900000       0.000000    
+   276.0000       8.900000       0.000000    
+   278.0000       8.900000       0.000000    
+   280.0000       8.900000       0.000000    
+   282.0000       8.900000       0.000000    
+   284.0000       8.900000       0.000000    
+   286.0000       8.900000       0.000000    
+   288.0000       8.900000       0.000000    
+   290.0000       8.900000       0.000000    
+   292.0000       8.900000       0.000000    
+   294.0000       8.900000       0.000000    
+   296.0000       8.900000       0.000000    
+   298.0000       8.900000       0.000000    
+   300.0000       8.900000       0.000000    
+   302.0000       8.900000       0.000000    
+   304.0000       8.900000       0.000000    
+   306.0000       8.900000       0.000000    
+   308.0000       8.900000       0.000000    
+   310.0000       8.900000       0.000000    
+   312.0000       8.900000       0.000000    
+   314.0000       8.900000       0.000000    
+   316.0000       8.900000       0.000000    
+   318.0000       8.900000       0.000000    
+   320.0000       8.900000       0.000000    
+   322.0000       8.900000       0.000000    
+   324.0000       8.900000       0.000000    
+   326.0000       8.900000       0.000000    
+   328.0000       8.900000       0.000000    
+   330.0000       8.900000       0.000000    
+   332.0000       8.900000       0.000000    
+   334.0000       8.900000       0.000000    
+   336.0000       8.900000       0.000000    
+   338.0000       8.900000       0.000000    
+   340.0000       8.900000       0.000000    
+   342.0000       8.900000       0.000000    
+   344.0000       8.900000       0.000000    
+   346.0000       8.900000       0.000000    
+   348.0000       8.900000       0.000000    
+   350.0000       8.900000       0.000000    
+   352.0000       8.900000       0.000000    
+   354.0000       8.900000       0.000000    
+   356.0000       8.900000       0.000000    
+   358.0000       8.900000       0.000000    
+   360.0000       8.900000       0.000000    
+   362.0000       8.900000       0.000000    
+   364.0000       8.900000       0.000000    
+   366.0000       8.900000       0.000000    
+   368.0000       8.900000       0.000000    
+   370.0000       8.900000       0.000000    
+   372.0000       8.900000       0.000000    
+   374.0000       8.900000       0.000000    
+   376.0000       8.900000       0.000000    
+   378.0000       8.900000       0.000000    
+   380.0000       8.900000       0.000000    
+   382.0000       8.900000       0.000000    
+   384.0000       8.900000       0.000000    
+   386.0000       8.900000       0.000000    
+   388.0000       8.900000       0.000000    
+   390.0000       8.900000       0.000000    
+   392.0000       8.900000       0.000000    
+   394.0000       8.900000       0.000000    
+   396.0000       8.900000       0.000000    
+   398.0000       8.900000       0.000000    
+   400.0000       8.900000       0.000000    
+   402.0000       8.900000       0.000000    
+   404.0000       8.900000       0.000000    
+   406.0000       8.900000       0.000000    
+   408.0000       8.900000       0.000000    
+   410.0000       8.900000       0.000000    
+   412.0000       8.900000       0.000000    
+   414.0000       8.900000       0.000000    
+   416.0000       8.900000       0.000000    
+   418.0000       8.900000       0.000000    
+   420.0000       8.900000       0.000000    
+   422.0000       8.900000       0.000000    
+   424.0000       8.900000       0.000000    
+   426.0000       8.900000       0.000000    
+   428.0000       8.900000       0.000000    
+   430.0000       8.900000       0.000000    
+   432.0000       8.900000       0.000000    
+   434.0000       8.900000       0.000000    
+   436.0000       8.900000       0.000000    
+   438.0000       8.900000       0.000000    
+   440.0000       8.900000       0.000000    
+   442.0000       8.900000       0.000000    
+   444.0000       8.900000       0.000000    
+   446.0000       8.900000       0.000000    
+   448.0000       8.900000       0.000000    
+   450.0000       8.900000       0.000000    
+   452.0000       8.900000       0.000000    
+   454.0000       8.900000       0.000000    
+   456.0000       8.900000       0.000000    
+   458.0000       8.900000       0.000000    
+   460.0000       8.900000       0.000000    
+   462.0000       8.900000       0.000000    
+   464.0000       8.900000       0.000000    
+   466.0000       8.900000       0.000000    
+   468.0000       8.900000       0.000000    
+   470.0000       8.900000       0.000000    
+   472.0000       8.900000       0.000000    
+   474.0000       8.900000       0.000000    
+   476.0000       8.900000       0.000000    
+   478.0000       8.900000       0.000000    
+   480.0000       8.900000       0.000000    
+   482.0000       8.900000       0.000000    
+   484.0000       8.900000       0.000000    
+   486.0000       8.900000       0.000000    
+   488.0000       8.900000       0.000000    
+   490.0000       8.900000       0.000000    
+   492.0000       8.900000       0.000000    
+   494.0000       8.900000       0.000000    
+   496.0000       8.900000       0.000000    
+   498.0000       8.900000       0.000000    
+   500.0000       8.900000       0.000000    
+   502.0000       8.900000       0.000000    
+   504.0000       8.900000       0.000000    
+   506.0000       8.900000       0.000000    
+   508.0000       8.900000       0.000000    
+   510.0000       8.900000       0.000000    
+   512.0000       8.900000       0.000000    
+   514.0000       8.900000       0.000000    
+   516.0000       8.900000       0.000000    
+   518.0000       8.900000       0.000000    
+   520.0000       8.900000       0.000000    
+   522.0000       8.900000       0.000000    
+   524.0000       8.900000       0.000000    
+   526.0000       8.900000       0.000000    
+   528.0000       8.900000       0.000000    
+   530.0000       8.900000       0.000000    
+   532.0000       8.900000       0.000000    
+   534.0000       8.900000       0.000000    
+   536.0000       8.900000       0.000000    
+   538.0000       8.900000       0.000000    
+   540.0000       8.900000       0.000000    
+   542.0000       8.900000       0.000000    
+   544.0000       8.900000       0.000000    
+   546.0000       8.900000       0.000000    
+   548.0000       8.900000       0.000000    
+   550.0000       8.900000       0.000000    
+   552.0000       8.900000       0.000000    
+   554.0000       8.900000       0.000000    
+   556.0000       8.900000       0.000000    
+   558.0000       8.900000       0.000000    
+   560.0000       8.900000       0.000000    
+   562.0000       8.900000       0.000000    
+   564.0000       8.900000       0.000000    
+   566.0000       8.900000       0.000000    
+   568.0000       8.900000       0.000000    
+   570.0000       8.900000       0.000000    
+   572.0000       8.900000       0.000000    
+   574.0000       8.900000       0.000000    
+   576.0000       8.900000       0.000000    
+   578.0000       8.900000       0.000000    
+   580.0000       8.900000       0.000000    
+   582.0000       8.900000       0.000000    
+   584.0000       8.900000       0.000000    
+   586.0000       8.900000       0.000000    
+   588.0000       8.900000       0.000000    
+   590.0000       8.900000       0.000000    
+   592.0000       8.900000       0.000000    
+   594.0000       8.900000       0.000000    
+   596.0000       8.900000       0.000000    
+   598.0000       8.900000       0.000000    
+   600.0000       8.900000       0.000000    
+   602.0000       8.900000       0.000000    
+   604.0000       8.900000       0.000000    
+   606.0000       8.900000       0.000000    
+   608.0000       8.900000       0.000000    
+   610.0000       8.900000       0.000000    
+   612.0000       8.900000       0.000000    
+   614.0000       8.900000       0.000000    
+   616.0000       8.900000       0.000000    
+   618.0000       8.900000       0.000000    
+   620.0000       8.900000       0.000000    
+   622.0000       8.900000       0.000000    
+   624.0000       8.900000       0.000000    
+   626.0000       8.900000       0.000000    
+   628.0000       8.900000       0.000000    
+   630.0000       8.900000       0.000000    
+   632.0000       8.900000       0.000000    
+   634.0000       8.900000       0.000000    
+   636.0000       8.900000       0.000000    
+   638.0000       8.900000       0.000000    
+   640.0000       8.900000       0.000000    
+   642.0000       8.900000       0.000000    
+   644.0000       8.900000       0.000000    
+   646.0000       8.900000       0.000000    
+   648.0000       8.900000       0.000000    
+   650.0000       8.900000       0.000000    
+   652.0000       8.900000       0.000000    
+   654.0000       8.900000       0.000000    
+   656.0000       8.900000       0.000000    
+   658.0000       8.900000       0.000000    
+   660.0000       8.900000       0.000000    
+   662.0000       8.900000       0.000000    
+   664.0000       8.900000       0.000000    
+   666.0000       8.900000       0.000000    
+   668.0000       8.900000       0.000000    
+   670.0000       8.900000       0.000000    
+   672.0000       8.900000       0.000000    
+   674.0000       8.900000       0.000000    
+   676.0000       8.900000       0.000000    
+   678.0000       8.900000       0.000000    
+   680.0000       8.900000       0.000000    
+   682.0000       8.900000       0.000000    
+   684.0000       8.900000       0.000000    
+   686.0000       8.900000       0.000000    
+   688.0000       8.900000       0.000000    
+   690.0000       8.900000       0.000000    
+   692.0000       8.900000       0.000000    
+   694.0000       8.900000       0.000000    
+   696.0000       8.900000       0.000000    
+   698.0000       8.900000       0.000000    
+   700.0000       8.900000       0.000000    
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps006.log b/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps006.log
new file mode 100644
index 0000000000000000000000000000000000000000..cd282a827cad009895cf44b1b38aea81ac0947a9
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/epsLog/seteps006.log
@@ -0,0 +1,333 @@
+    2    2
+No-layers 
+MnO          4.950000        1
+   269.0000       16.00000      0.5000000E-01
+Platinum     8.900000        1
+   269.0000       16.00000      0.5000000E-01
+
+   50.00000       4.950000       0.000000       8.900000       0.000000    
+   52.00000       4.950000       0.000000       8.900000       0.000000    
+   54.00000       4.950000       0.000000       8.900000       0.000000    
+   56.00000       4.950000       0.000000       8.900000       0.000000    
+   58.00000       4.950000       0.000000       8.900000       0.000000    
+   60.00000       4.950000       0.000000       8.900000       0.000000    
+   62.00000       4.950000       0.000000       8.900000       0.000000    
+   64.00000       4.950000       0.000000       8.900000       0.000000    
+   66.00000       4.950000       0.000000       8.900000       0.000000    
+   68.00000       4.950000       0.000000       8.900000       0.000000    
+   70.00000       4.950000       0.000000       8.900000       0.000000    
+   72.00000       4.950000       0.000000       8.900000       0.000000    
+   74.00000       4.950000       0.000000       8.900000       0.000000    
+   76.00000       4.950000       0.000000       8.900000       0.000000    
+   78.00000       4.950000       0.000000       8.900000       0.000000    
+   80.00000       4.950000       0.000000       8.900000       0.000000    
+   82.00000       4.950000       0.000000       8.900000       0.000000    
+   84.00000       4.950000       0.000000       8.900000       0.000000    
+   86.00000       4.950000       0.000000       8.900000       0.000000    
+   88.00000       4.950000       0.000000       8.900000       0.000000    
+   90.00000       4.950000       0.000000       8.900000       0.000000    
+   92.00000       4.950000       0.000000       8.900000       0.000000    
+   94.00000       4.950000       0.000000       8.900000       0.000000    
+   96.00000       4.950000       0.000000       8.900000       0.000000    
+   98.00000       4.950000       0.000000       8.900000       0.000000    
+   100.0000       4.950000       0.000000       8.900000       0.000000    
+   102.0000       4.950000       0.000000       8.900000       0.000000    
+   104.0000       4.950000       0.000000       8.900000       0.000000    
+   106.0000       4.950000       0.000000       8.900000       0.000000    
+   108.0000       4.950000       0.000000       8.900000       0.000000    
+   110.0000       4.950000       0.000000       8.900000       0.000000    
+   112.0000       4.950000       0.000000       8.900000       0.000000    
+   114.0000       4.950000       0.000000       8.900000       0.000000    
+   116.0000       4.950000       0.000000       8.900000       0.000000    
+   118.0000       4.950000       0.000000       8.900000       0.000000    
+   120.0000       4.950000       0.000000       8.900000       0.000000    
+   122.0000       4.950000       0.000000       8.900000       0.000000    
+   124.0000       4.950000       0.000000       8.900000       0.000000    
+   126.0000       4.950000       0.000000       8.900000       0.000000    
+   128.0000       4.950000       0.000000       8.900000       0.000000    
+   130.0000       4.950000       0.000000       8.900000       0.000000    
+   132.0000       4.950000       0.000000       8.900000       0.000000    
+   134.0000       4.950000       0.000000       8.900000       0.000000    
+   136.0000       4.950000       0.000000       8.900000       0.000000    
+   138.0000       4.950000       0.000000       8.900000       0.000000    
+   140.0000       4.950000       0.000000       8.900000       0.000000    
+   142.0000       4.950000       0.000000       8.900000       0.000000    
+   144.0000       4.950000       0.000000       8.900000       0.000000    
+   146.0000       4.950000       0.000000       8.900000       0.000000    
+   148.0000       4.950000       0.000000       8.900000       0.000000    
+   150.0000       4.950000       0.000000       8.900000       0.000000    
+   152.0000       4.950000       0.000000       8.900000       0.000000    
+   154.0000       4.950000       0.000000       8.900000       0.000000    
+   156.0000       4.950000       0.000000       8.900000       0.000000    
+   158.0000       4.950000       0.000000       8.900000       0.000000    
+   160.0000       4.950000       0.000000       8.900000       0.000000    
+   162.0000       4.950000       0.000000       8.900000       0.000000    
+   164.0000       4.950000       0.000000       8.900000       0.000000    
+   166.0000       4.950000       0.000000       8.900000       0.000000    
+   168.0000       4.950000       0.000000       8.900000       0.000000    
+   170.0000       4.950000       0.000000       8.900000       0.000000    
+   172.0000       4.950000       0.000000       8.900000       0.000000    
+   174.0000       4.950000       0.000000       8.900000       0.000000    
+   176.0000       4.950000       0.000000       8.900000       0.000000    
+   178.0000       4.950000       0.000000       8.900000       0.000000    
+   180.0000       4.950000       0.000000       8.900000       0.000000    
+   182.0000       4.950000       0.000000       8.900000       0.000000    
+   184.0000       4.950000       0.000000       8.900000       0.000000    
+   186.0000       4.950000       0.000000       8.900000       0.000000    
+   188.0000       4.950000       0.000000       8.900000       0.000000    
+   190.0000       4.950000       0.000000       8.900000       0.000000    
+   192.0000       4.950000       0.000000       8.900000       0.000000    
+   194.0000       4.950000       0.000000       8.900000       0.000000    
+   196.0000       4.950000       0.000000       8.900000       0.000000    
+   198.0000       4.950000       0.000000       8.900000       0.000000    
+   200.0000       4.950000       0.000000       8.900000       0.000000    
+   202.0000       4.950000       0.000000       8.900000       0.000000    
+   204.0000       4.950000       0.000000       8.900000       0.000000    
+   206.0000       4.950000       0.000000       8.900000       0.000000    
+   208.0000       4.950000       0.000000       8.900000       0.000000    
+   210.0000       4.950000       0.000000       8.900000       0.000000    
+   212.0000       4.950000       0.000000       8.900000       0.000000    
+   214.0000       4.950000       0.000000       8.900000       0.000000    
+   216.0000       4.950000       0.000000       8.900000       0.000000    
+   218.0000       4.950000       0.000000       8.900000       0.000000    
+   220.0000       4.950000       0.000000       8.900000       0.000000    
+   222.0000       4.950000       0.000000       8.900000       0.000000    
+   224.0000       4.950000       0.000000       8.900000       0.000000    
+   226.0000       4.950000       0.000000       8.900000       0.000000    
+   228.0000       4.950000       0.000000       8.900000       0.000000    
+   230.0000       4.950000       0.000000       8.900000       0.000000    
+   232.0000       4.950000       0.000000       8.900000       0.000000    
+   234.0000       4.950000       0.000000       8.900000       0.000000    
+   236.0000       4.950000       0.000000       8.900000       0.000000    
+   238.0000       4.950000       0.000000       8.900000       0.000000    
+   240.0000       4.950000       0.000000       8.900000       0.000000    
+   242.0000       4.950000       0.000000       8.900000       0.000000    
+   244.0000       4.950000       0.000000       8.900000       0.000000    
+   246.0000       4.950000       0.000000       8.900000       0.000000    
+   248.0000       4.950000       0.000000       8.900000       0.000000    
+   250.0000       4.950000       0.000000       8.900000       0.000000    
+   252.0000       4.950000       0.000000       8.900000       0.000000    
+   254.0000       4.950000       0.000000       8.900000       0.000000    
+   256.0000       4.950000       0.000000       8.900000       0.000000    
+   258.0000       4.950000       0.000000       8.900000       0.000000    
+   260.0000       4.950000       0.000000       8.900000       0.000000    
+   262.0000       4.950000       0.000000       8.900000       0.000000    
+   264.0000       4.950000       0.000000       8.900000       0.000000    
+   266.0000       4.950000       0.000000       8.900000       0.000000    
+   268.0000       4.950000       0.000000       8.900000       0.000000    
+   270.0000       4.950000       0.000000       8.900000       0.000000    
+   272.0000       4.950000       0.000000       8.900000       0.000000    
+   274.0000       4.950000       0.000000       8.900000       0.000000    
+   276.0000       4.950000       0.000000       8.900000       0.000000    
+   278.0000       4.950000       0.000000       8.900000       0.000000    
+   280.0000       4.950000       0.000000       8.900000       0.000000    
+   282.0000       4.950000       0.000000       8.900000       0.000000    
+   284.0000       4.950000       0.000000       8.900000       0.000000    
+   286.0000       4.950000       0.000000       8.900000       0.000000    
+   288.0000       4.950000       0.000000       8.900000       0.000000    
+   290.0000       4.950000       0.000000       8.900000       0.000000    
+   292.0000       4.950000       0.000000       8.900000       0.000000    
+   294.0000       4.950000       0.000000       8.900000       0.000000    
+   296.0000       4.950000       0.000000       8.900000       0.000000    
+   298.0000       4.950000       0.000000       8.900000       0.000000    
+   300.0000       4.950000       0.000000       8.900000       0.000000    
+   302.0000       4.950000       0.000000       8.900000       0.000000    
+   304.0000       4.950000       0.000000       8.900000       0.000000    
+   306.0000       4.950000       0.000000       8.900000       0.000000    
+   308.0000       4.950000       0.000000       8.900000       0.000000    
+   310.0000       4.950000       0.000000       8.900000       0.000000    
+   312.0000       4.950000       0.000000       8.900000       0.000000    
+   314.0000       4.950000       0.000000       8.900000       0.000000    
+   316.0000       4.950000       0.000000       8.900000       0.000000    
+   318.0000       4.950000       0.000000       8.900000       0.000000    
+   320.0000       4.950000       0.000000       8.900000       0.000000    
+   322.0000       4.950000       0.000000       8.900000       0.000000    
+   324.0000       4.950000       0.000000       8.900000       0.000000    
+   326.0000       4.950000       0.000000       8.900000       0.000000    
+   328.0000       4.950000       0.000000       8.900000       0.000000    
+   330.0000       4.950000       0.000000       8.900000       0.000000    
+   332.0000       4.950000       0.000000       8.900000       0.000000    
+   334.0000       4.950000       0.000000       8.900000       0.000000    
+   336.0000       4.950000       0.000000       8.900000       0.000000    
+   338.0000       4.950000       0.000000       8.900000       0.000000    
+   340.0000       4.950000       0.000000       8.900000       0.000000    
+   342.0000       4.950000       0.000000       8.900000       0.000000    
+   344.0000       4.950000       0.000000       8.900000       0.000000    
+   346.0000       4.950000       0.000000       8.900000       0.000000    
+   348.0000       4.950000       0.000000       8.900000       0.000000    
+   350.0000       4.950000       0.000000       8.900000       0.000000    
+   352.0000       4.950000       0.000000       8.900000       0.000000    
+   354.0000       4.950000       0.000000       8.900000       0.000000    
+   356.0000       4.950000       0.000000       8.900000       0.000000    
+   358.0000       4.950000       0.000000       8.900000       0.000000    
+   360.0000       4.950000       0.000000       8.900000       0.000000    
+   362.0000       4.950000       0.000000       8.900000       0.000000    
+   364.0000       4.950000       0.000000       8.900000       0.000000    
+   366.0000       4.950000       0.000000       8.900000       0.000000    
+   368.0000       4.950000       0.000000       8.900000       0.000000    
+   370.0000       4.950000       0.000000       8.900000       0.000000    
+   372.0000       4.950000       0.000000       8.900000       0.000000    
+   374.0000       4.950000       0.000000       8.900000       0.000000    
+   376.0000       4.950000       0.000000       8.900000       0.000000    
+   378.0000       4.950000       0.000000       8.900000       0.000000    
+   380.0000       4.950000       0.000000       8.900000       0.000000    
+   382.0000       4.950000       0.000000       8.900000       0.000000    
+   384.0000       4.950000       0.000000       8.900000       0.000000    
+   386.0000       4.950000       0.000000       8.900000       0.000000    
+   388.0000       4.950000       0.000000       8.900000       0.000000    
+   390.0000       4.950000       0.000000       8.900000       0.000000    
+   392.0000       4.950000       0.000000       8.900000       0.000000    
+   394.0000       4.950000       0.000000       8.900000       0.000000    
+   396.0000       4.950000       0.000000       8.900000       0.000000    
+   398.0000       4.950000       0.000000       8.900000       0.000000    
+   400.0000       4.950000       0.000000       8.900000       0.000000    
+   402.0000       4.950000       0.000000       8.900000       0.000000    
+   404.0000       4.950000       0.000000       8.900000       0.000000    
+   406.0000       4.950000       0.000000       8.900000       0.000000    
+   408.0000       4.950000       0.000000       8.900000       0.000000    
+   410.0000       4.950000       0.000000       8.900000       0.000000    
+   412.0000       4.950000       0.000000       8.900000       0.000000    
+   414.0000       4.950000       0.000000       8.900000       0.000000    
+   416.0000       4.950000       0.000000       8.900000       0.000000    
+   418.0000       4.950000       0.000000       8.900000       0.000000    
+   420.0000       4.950000       0.000000       8.900000       0.000000    
+   422.0000       4.950000       0.000000       8.900000       0.000000    
+   424.0000       4.950000       0.000000       8.900000       0.000000    
+   426.0000       4.950000       0.000000       8.900000       0.000000    
+   428.0000       4.950000       0.000000       8.900000       0.000000    
+   430.0000       4.950000       0.000000       8.900000       0.000000    
+   432.0000       4.950000       0.000000       8.900000       0.000000    
+   434.0000       4.950000       0.000000       8.900000       0.000000    
+   436.0000       4.950000       0.000000       8.900000       0.000000    
+   438.0000       4.950000       0.000000       8.900000       0.000000    
+   440.0000       4.950000       0.000000       8.900000       0.000000    
+   442.0000       4.950000       0.000000       8.900000       0.000000    
+   444.0000       4.950000       0.000000       8.900000       0.000000    
+   446.0000       4.950000       0.000000       8.900000       0.000000    
+   448.0000       4.950000       0.000000       8.900000       0.000000    
+   450.0000       4.950000       0.000000       8.900000       0.000000    
+   452.0000       4.950000       0.000000       8.900000       0.000000    
+   454.0000       4.950000       0.000000       8.900000       0.000000    
+   456.0000       4.950000       0.000000       8.900000       0.000000    
+   458.0000       4.950000       0.000000       8.900000       0.000000    
+   460.0000       4.950000       0.000000       8.900000       0.000000    
+   462.0000       4.950000       0.000000       8.900000       0.000000    
+   464.0000       4.950000       0.000000       8.900000       0.000000    
+   466.0000       4.950000       0.000000       8.900000       0.000000    
+   468.0000       4.950000       0.000000       8.900000       0.000000    
+   470.0000       4.950000       0.000000       8.900000       0.000000    
+   472.0000       4.950000       0.000000       8.900000       0.000000    
+   474.0000       4.950000       0.000000       8.900000       0.000000    
+   476.0000       4.950000       0.000000       8.900000       0.000000    
+   478.0000       4.950000       0.000000       8.900000       0.000000    
+   480.0000       4.950000       0.000000       8.900000       0.000000    
+   482.0000       4.950000       0.000000       8.900000       0.000000    
+   484.0000       4.950000       0.000000       8.900000       0.000000    
+   486.0000       4.950000       0.000000       8.900000       0.000000    
+   488.0000       4.950000       0.000000       8.900000       0.000000    
+   490.0000       4.950000       0.000000       8.900000       0.000000    
+   492.0000       4.950000       0.000000       8.900000       0.000000    
+   494.0000       4.950000       0.000000       8.900000       0.000000    
+   496.0000       4.950000       0.000000       8.900000       0.000000    
+   498.0000       4.950000       0.000000       8.900000       0.000000    
+   500.0000       4.950000       0.000000       8.900000       0.000000    
+   502.0000       4.950000       0.000000       8.900000       0.000000    
+   504.0000       4.950000       0.000000       8.900000       0.000000    
+   506.0000       4.950000       0.000000       8.900000       0.000000    
+   508.0000       4.950000       0.000000       8.900000       0.000000    
+   510.0000       4.950000       0.000000       8.900000       0.000000    
+   512.0000       4.950000       0.000000       8.900000       0.000000    
+   514.0000       4.950000       0.000000       8.900000       0.000000    
+   516.0000       4.950000       0.000000       8.900000       0.000000    
+   518.0000       4.950000       0.000000       8.900000       0.000000    
+   520.0000       4.950000       0.000000       8.900000       0.000000    
+   522.0000       4.950000       0.000000       8.900000       0.000000    
+   524.0000       4.950000       0.000000       8.900000       0.000000    
+   526.0000       4.950000       0.000000       8.900000       0.000000    
+   528.0000       4.950000       0.000000       8.900000       0.000000    
+   530.0000       4.950000       0.000000       8.900000       0.000000    
+   532.0000       4.950000       0.000000       8.900000       0.000000    
+   534.0000       4.950000       0.000000       8.900000       0.000000    
+   536.0000       4.950000       0.000000       8.900000       0.000000    
+   538.0000       4.950000       0.000000       8.900000       0.000000    
+   540.0000       4.950000       0.000000       8.900000       0.000000    
+   542.0000       4.950000       0.000000       8.900000       0.000000    
+   544.0000       4.950000       0.000000       8.900000       0.000000    
+   546.0000       4.950000       0.000000       8.900000       0.000000    
+   548.0000       4.950000       0.000000       8.900000       0.000000    
+   550.0000       4.950000       0.000000       8.900000       0.000000    
+   552.0000       4.950000       0.000000       8.900000       0.000000    
+   554.0000       4.950000       0.000000       8.900000       0.000000    
+   556.0000       4.950000       0.000000       8.900000       0.000000    
+   558.0000       4.950000       0.000000       8.900000       0.000000    
+   560.0000       4.950000       0.000000       8.900000       0.000000    
+   562.0000       4.950000       0.000000       8.900000       0.000000    
+   564.0000       4.950000       0.000000       8.900000       0.000000    
+   566.0000       4.950000       0.000000       8.900000       0.000000    
+   568.0000       4.950000       0.000000       8.900000       0.000000    
+   570.0000       4.950000       0.000000       8.900000       0.000000    
+   572.0000       4.950000       0.000000       8.900000       0.000000    
+   574.0000       4.950000       0.000000       8.900000       0.000000    
+   576.0000       4.950000       0.000000       8.900000       0.000000    
+   578.0000       4.950000       0.000000       8.900000       0.000000    
+   580.0000       4.950000       0.000000       8.900000       0.000000    
+   582.0000       4.950000       0.000000       8.900000       0.000000    
+   584.0000       4.950000       0.000000       8.900000       0.000000    
+   586.0000       4.950000       0.000000       8.900000       0.000000    
+   588.0000       4.950000       0.000000       8.900000       0.000000    
+   590.0000       4.950000       0.000000       8.900000       0.000000    
+   592.0000       4.950000       0.000000       8.900000       0.000000    
+   594.0000       4.950000       0.000000       8.900000       0.000000    
+   596.0000       4.950000       0.000000       8.900000       0.000000    
+   598.0000       4.950000       0.000000       8.900000       0.000000    
+   600.0000       4.950000       0.000000       8.900000       0.000000    
+   602.0000       4.950000       0.000000       8.900000       0.000000    
+   604.0000       4.950000       0.000000       8.900000       0.000000    
+   606.0000       4.950000       0.000000       8.900000       0.000000    
+   608.0000       4.950000       0.000000       8.900000       0.000000    
+   610.0000       4.950000       0.000000       8.900000       0.000000    
+   612.0000       4.950000       0.000000       8.900000       0.000000    
+   614.0000       4.950000       0.000000       8.900000       0.000000    
+   616.0000       4.950000       0.000000       8.900000       0.000000    
+   618.0000       4.950000       0.000000       8.900000       0.000000    
+   620.0000       4.950000       0.000000       8.900000       0.000000    
+   622.0000       4.950000       0.000000       8.900000       0.000000    
+   624.0000       4.950000       0.000000       8.900000       0.000000    
+   626.0000       4.950000       0.000000       8.900000       0.000000    
+   628.0000       4.950000       0.000000       8.900000       0.000000    
+   630.0000       4.950000       0.000000       8.900000       0.000000    
+   632.0000       4.950000       0.000000       8.900000       0.000000    
+   634.0000       4.950000       0.000000       8.900000       0.000000    
+   636.0000       4.950000       0.000000       8.900000       0.000000    
+   638.0000       4.950000       0.000000       8.900000       0.000000    
+   640.0000       4.950000       0.000000       8.900000       0.000000    
+   642.0000       4.950000       0.000000       8.900000       0.000000    
+   644.0000       4.950000       0.000000       8.900000       0.000000    
+   646.0000       4.950000       0.000000       8.900000       0.000000    
+   648.0000       4.950000       0.000000       8.900000       0.000000    
+   650.0000       4.950000       0.000000       8.900000       0.000000    
+   652.0000       4.950000       0.000000       8.900000       0.000000    
+   654.0000       4.950000       0.000000       8.900000       0.000000    
+   656.0000       4.950000       0.000000       8.900000       0.000000    
+   658.0000       4.950000       0.000000       8.900000       0.000000    
+   660.0000       4.950000       0.000000       8.900000       0.000000    
+   662.0000       4.950000       0.000000       8.900000       0.000000    
+   664.0000       4.950000       0.000000       8.900000       0.000000    
+   666.0000       4.950000       0.000000       8.900000       0.000000    
+   668.0000       4.950000       0.000000       8.900000       0.000000    
+   670.0000       4.950000       0.000000       8.900000       0.000000    
+   672.0000       4.950000       0.000000       8.900000       0.000000    
+   674.0000       4.950000       0.000000       8.900000       0.000000    
+   676.0000       4.950000       0.000000       8.900000       0.000000    
+   678.0000       4.950000       0.000000       8.900000       0.000000    
+   680.0000       4.950000       0.000000       8.900000       0.000000    
+   682.0000       4.950000       0.000000       8.900000       0.000000    
+   684.0000       4.950000       0.000000       8.900000       0.000000    
+   686.0000       4.950000       0.000000       8.900000       0.000000    
+   688.0000       4.950000       0.000000       8.900000       0.000000    
+   690.0000       4.950000       0.000000       8.900000       0.000000    
+   692.0000       4.950000       0.000000       8.900000       0.000000    
+   694.0000       4.950000       0.000000       8.900000       0.000000    
+   696.0000       4.950000       0.000000       8.900000       0.000000    
+   698.0000       4.950000       0.000000       8.900000       0.000000    
+   700.0000       4.950000       0.000000       8.900000       0.000000    
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/extend3.f90 b/tests/SetEpsTestCasesFromScratch/WFW/extend3.f90
new file mode 100644
index 0000000000000000000000000000000000000000..1ebde11e03092161284a5e2d949845e50271a1c0
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/extend3.f90
@@ -0,0 +1,22 @@
+subroutine extend3(array, extension)
+
+! increase the size of a allocatable array by extension.
+! if the array is not allocated, create one of size extension.
+
+  implicit none
+
+  double precision, intent(in out), allocatable :: array(:, :)
+  integer, intent(in) :: extension
+
+  integer :: old_size_1, old_size_2
+  double precision, allocatable :: tmp_array(:, :)
+
+  old_size_1 = size(array, 1)
+  old_size_2 = size(array, 2)
+  allocate(tmp_array(old_size_1, old_size_2 + extension))
+  tmp_array(1:old_size_1, 1:old_size_2) = array
+  deallocate(array)
+  call move_alloc(tmp_array, array)
+
+  return
+end subroutine extend3
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/fint1.f90 b/tests/SetEpsTestCasesFromScratch/WFW/fint1.f90
new file mode 100644
index 0000000000000000000000000000000000000000..62361a0b908e865c00fe498385a7e814d12e9941
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/fint1.f90
@@ -0,0 +1,64 @@
+module fint1_mod
+contains
+double precision function fint1(u, eps, thick, layers, nper, eps_size)
+
+! ******************************************************************
+! *                                                                *
+! * integration over the azimutal angle from 0.0 to pi             *
+! *                                                                *
+! * eps:      epsilon                                              *
+! * thick:    thickness                                            *
+! * layers:   number of layers                                     *
+! * nper:     number of periodic layers                            *
+! * eps_size: number of layers                                     *
+! *                                                                *
+! ******************************************************************
+
+  use surlos_mod
+  use param_mod
+
+  implicit none
+
+  double precision, intent(in) :: u
+  double complex, intent(in) :: eps(eps_size)
+  double precision, intent(in) :: thick(eps_size)
+  integer, intent(in) :: layers, nper, eps_size
+
+  double precision :: den, dif, e, pi, rom, rop, sum, t, u2
+  double precision :: usurlo
+
+  data pi / 3.141592653589793238d0 /
+
+!  write (*,*) 'fint1:'
+!  write (*,*) 'thick: ', size(thick)
+!  write (*,*) 'eps: ', size(eps)
+
+  if (u == 0.0d0) then
+    fint1 = 0.0d0
+    return
+  endif
+  e = tanpsi * u
+  u2 = u**2
+  rom = (1.0d0 - e)**2 + u2
+  rop = (1.0d0 + e)**2 + u2
+  sum = rop + rom
+  rom = dsqrt(rom)
+  rop = dsqrt(rop)
+  dif = rop - rom
+  den = dsqrt((2.0d0 - dif) * (2.0d0 + dif)) * rop * rom
+  fint1 = pi * u2 * (4 * sum - dif**2 * (sum - rop * rom)) / den**3
+  if (rational) then
+    return
+  endif
+  if (user) then
+    fint1 = fint1 * usurlo(ru * u, wn)
+  else
+    fint1 = fint1 * surlos(ru * u, eps, thick, layers, nper)
+    if (dlimf > 0.0d0) then
+      t = ru * u * dlimf
+      fint1 = fint1 * (1.d0 + t * dlog(t / (t + 0.26d0)))**2 / (1.d0 + 1.40d0 * t)
+    endif
+  endif
+  return
+end function fint1
+end module fint1_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/fint2.f90 b/tests/SetEpsTestCasesFromScratch/WFW/fint2.f90
new file mode 100644
index 0000000000000000000000000000000000000000..12baaf6b79c240f12c579dcc0d27e59add6e7dae
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/fint2.f90
@@ -0,0 +1,66 @@
+module fint2_mod
+contains
+double precision function fint2(u, eps, thick, layers, nper, eps_size)
+
+! ******************************************************************
+! *                                                                *
+! * integration over the azimutal angle from 0.0 to phi < pi       *
+! *                                                                *
+! * eps:      epsilon                                              *
+! * thick:    thickness                                            *
+! * layers:   number of layers                                     *
+! * nper:     number of periodic layers                            *
+! * eps_size: number of layers                                     *
+! *                                                                *
+! ******************************************************************
+
+  use surlos_mod
+  use param_mod
+
+  implicit none
+
+  double precision, intent(in) :: u
+  double complex, intent(in) :: eps(eps_size)
+  double precision, intent(in) :: thick(eps_size)
+  integer, intent(in) :: layers, nper, eps_size
+
+  double precision :: arg, b2, c, phi, t, x
+  double precision :: phint, usurlo
+
+!  write (*,*) 'fint2:'
+!  write (*,*) 'thick: ', size(thick)
+!  write (*,*) 'eps: ', size(eps)
+
+  if (u == 0.0d0) then
+    fint2 = 0.0d0
+    return
+  endif
+  b2 = bcoef**2
+  c = (1.0d0 - elleps) * (cospsi * u)**2 + (bcoef - ccoef) * (bcoef + ccoef)
+  if (dabs(acoef * c) > 1.0d-03 * b2) then
+    x = (bcoef - dsqrt(b2 - acoef * c)) / acoef
+  else
+    x = acoef * c / b2
+    x = 0.5d0 * c * (1.d0 + 0.25d0 * x * (1.d0 + 0.5d0 * x * (1.d0 + 0.625d0 * x))) / bcoef
+  endif
+  arg = x / u
+  if (dabs(arg) > 1.0d0) then
+    arg = dsign(1.0d0, arg)
+  endif
+  phi = dacos(arg)
+  fint2 = phint(phi, tanpsi, u)
+  if (rational) then
+    return
+  endif
+  if (user) then
+    fint2 = fint2 * usurlo(ru * u, wn)
+  else
+    fint2 = fint2 * surlos(ru * u, eps, thick, layers, nper)
+    if (dlimf > 0.0d0) then
+      t = ru * u * dlimf
+      fint2 = fint2 * (1.d0 + t * dlog(t / (t + 0.26d0)))**2 / (1.d0 + 1.40d0 * t)
+    endif
+  endif
+  return
+end function fint2
+end module fint2_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/fint3.f90 b/tests/SetEpsTestCasesFromScratch/WFW/fint3.f90
new file mode 100644
index 0000000000000000000000000000000000000000..7135e6f590a0acc464a660e71f853402881ef047
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/fint3.f90
@@ -0,0 +1,59 @@
+module fint3_mod
+contains
+double precision function fint3(u, eps, thick, layers, nper, eps_size)
+
+! ******************************************************************
+! *                                                                *
+! * integration over the azimutal angle from phi1 > 0 to phi2 < pi *
+! *                                                                *
+! * eps:      epsilon                                              *
+! * thick:    thickness                                            *
+! * layers:   number of layers                                     *
+! * nper:     number of periodic layers                            *
+! * eps_size: number of layers                                     *
+! *                                                                *
+! ******************************************************************
+
+  use surlos_mod
+  use param_mod
+
+  implicit none
+
+  double precision, intent(in) :: u
+  double complex, intent(in) :: eps(eps_size)
+  double precision, intent(in) :: thick(eps_size)
+  integer, intent(in) :: layers, nper, eps_size
+
+  double precision :: arg, phi1, phi2, rac, t
+  double precision :: phint, usurlo
+
+!  write (*,*) 'fint3:'
+!  write (*,*) 'thick: ', size(thick)
+!  write (*,*) 'eps: ', size(eps)
+
+  if (u == 0.0d0) then
+    fint3 = 0.0d0
+    return
+  endif
+  rac = dsign(1.0d0, acoef) * cospsi * dsqrt((1.0d0 - elleps) * acoef * (um - u) * (um + u))
+  arg = (bcoef - rac) / (u * acoef)
+  if (dabs(arg) > 1.0d0) arg = dsign(1.0d0, arg)
+  phi2 = dacos(arg)
+  fint3 = phint(phi2, tanpsi, u)
+  arg = (bcoef + rac) / (u * acoef)
+  if (dabs(arg) > 1.0d0) arg = dsign(1.0d0, arg)
+  phi1 = dacos(arg)
+  fint3 = fint3 - phint(phi1, tanpsi, u)
+  if (rational) return
+  if (user) then
+    fint3 = fint3 * usurlo(ru * u, wn)
+  else
+    fint3 = fint3 * surlos(ru * u, eps, thick, layers, nper)
+    if (dlimf > 0.0d0) then
+      t = ru * u * dlimf
+      fint3 = fint3 * (1.d0 + t * dlog(t / (t + 0.26d0)))**2 / (1.d0 + 1.40d0 * t)
+    endif
+  endif
+  return
+end function fint3
+end module fint3_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/fun.f90 b/tests/SetEpsTestCasesFromScratch/WFW/fun.f90
new file mode 100644
index 0000000000000000000000000000000000000000..b077a2adbb98b22677f9cc19855884d82b8333da
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/fun.f90
@@ -0,0 +1,23 @@
+double precision function fun(phi)
+
+! ******************************************************************
+! *                                                                *
+! * integrand of the expression of the 1st order term in the       *
+! * expansion of the eels integral for a homogeneous target.       *
+! *                                                                *
+! ******************************************************************
+
+  use param_mod
+
+  implicit none
+
+  double precision, intent(in) :: phi
+
+  double precision :: sinphi
+
+  sinphi = dsin(phi)
+  fun = dsqrt((1.0d0 - elleps + elleps * sinphi**2) *   &
+              (1.0d0 - sinpsi * sinphi) *               &
+              (1.0d0 + sinpsi * sinphi))
+  return
+end function fun
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/get_commandline_options.f90 b/tests/SetEpsTestCasesFromScratch/WFW/get_commandline_options.f90
new file mode 100644
index 0000000000000000000000000000000000000000..e9977be96a19336c3dbf6636d20485f8b56650ce
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/get_commandline_options.f90
@@ -0,0 +1,93 @@
+module get_commandline_options_mod
+contains
+subroutine get_commandline_options(eelsin_name, eelsou_name, bosin_name, bosou_name)
+
+! This routine defines the commandline options, parses the commandline and sets the 
+! filenames of I/O files.
+!
+! It uses sufr_getopt from libSUFR and has been derived from getopt_long_example.f90
+!
+! KMS
+
+  use sufr_getopt, only: getopt_t, getopt_long, longOption, optArg, getopt_long_help
+
+  implicit none
+  
+  character (len = :), allocatable, intent(in out) :: eelsin_name, eelsou_name
+  character (len = :), allocatable, intent(in out) :: bosin_name, bosou_name
+    
+  include 'version.inc'
+
+  character :: option
+  integer :: status
+
+  ! Set up the longOpts struct to define the valid options:
+  ! short option, long option, argument (no = 0 / yes = 1), short description
+  type(getopt_t) :: longOpts(8) =                                            &
+      [                                                                      &
+       getopt_t('v', 'version',   0, 'Print version'),                       &
+       getopt_t('V', 'version',   0, 'Print version'),                       &
+       getopt_t('h', 'help',      0, 'Print options'),                       &
+       getopt_t('d', 'dir',       1, 'Change I/O directory'),                &
+       getopt_t('e', 'eelsin',    1, 'Name of EELS input file (eelsin)'),    &
+       getopt_t('f', 'eelsou',    1, 'Name of EELS output file (optional)'), &
+       getopt_t('b', 'bosin',     1, 'Name of BOSON input file (bosin)'),    &
+       getopt_t('c', 'bosou',     1, 'Name of BOSON output file (bosou)')    &
+      ]
+
+  do  ! scan all the command-line parameters
+     
+     ! getopt_long() returns a single character" ">","!",".", or the short-option character (e.g. "a" for -a).
+     !   It also sets two 'global' variables through the SUFR_getopt module:
+     !   - longOption:  the full option (e.g. "-a" or "--all") including the dashes
+     !   - optArg:      the argument following the option (if required and present)
+     option = getopt_long(longOpts)
+     
+     ! Do different things depending on the option returned:
+     select case(option)
+     case('d')  ! Change I/O directory
+        status = chdir(trim(optArg))
+        if (status /= 0) then
+          write (*,*) 'WARNING: change directory failed!'
+          write (*,*) 'Directory tried: ', trim(optarg)
+          write (*,*) 'Error code (see: man chdir): ', status
+          write (*,*) 'Continuing in the start directory.'
+          write (*,*) ''
+        end if
+     case('e')
+        eelsin_name = optArg
+     case('f')
+        eelsou_name = optArg
+     case('b')
+        bosin_name = optArg
+     case('c')
+        bosou_name = optArg
+     case('v')
+        write (*,*) 'eels-boson version: ' // version
+        stop
+     case('V')
+        write (*,*) 'eels-boson version: ' // version
+        stop
+     case('h')
+        call getopt_long_help(longOpts)
+        stop
+     case('!')  ! Unknown option (starting with "-" or "--")
+        write (*,*) 'WARNING: unknown option: ' // trim(optArg)
+        call getopt_long_help(longOpts)
+        stop
+     case('.')  ! Parameter is not an option (i.e., it doesn't start with "-" or "--")
+        write (*,*) 'WARNING: parameter without option: ' // trim(optArg)
+        call getopt_long_help(longOpts)
+        stop
+     case default
+        write (*,*) 'WARNING: unknown option: ' // trim(longOption)
+        call getopt_long_help(longOpts)
+        stop
+     case('>')  ! Last parameter. Exit case statement
+        exit
+     end select
+  end do
+  
+  return
+end subroutine get_commandline_options
+end module get_commandline_options_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/myEels20-seteps.f90 b/tests/SetEpsTestCasesFromScratch/WFW/myEels20-seteps.f90
new file mode 100755
index 0000000000000000000000000000000000000000..27e82c5f232161c2a1c46204cd449542abacf20e
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/myEels20-seteps.f90
@@ -0,0 +1,71 @@
+module seteps_mod
+contains
+!subroutine seteps(nos, osc_size, osc, epsinf, wn, nLayer, eps)
+! Angepasste Version
+subroutine seteps(nLayer, nos, osc, epsinf, wn, name, eps, layers, mode)
+
+  ! ******************************************************************
+  ! * set up long-wavelength dielectric functions of the layers for  *
+  ! * the present frequency wn (in cm**-1)                           *
+  ! ******************************************************************
+  
+  implicit none
+
+  integer, intent(in) :: nLayer
+!  integer, dimension(nLayer),intent(in) :: nos
+!  integer, intent(in) :: osc_size
+!  double precision, dimension(3,osc_size),intent(in) :: osc
+  integer, intent(in) :: nos(:)
+  double precision, intent(in) :: osc(:,:)
+  character (len=10), intent(in) :: name(:)
+  integer, intent(in) :: layers
+  character (len=10), intent(in) :: mode
+
+  !f2py depend(osc_size) osc
+  double precision, dimension(nLayer),intent(in) :: epsinf
+  double precision,  intent(in) :: wn
+  double complex, dimension(nLayer), intent(out) :: eps
+  !f2py depend(nLayer) nos, epsinf, eps
+  
+  double complex :: nomi, deno, addeps
+  double precision :: wn2, b
+  integer j, k, l, m
+  logical debugFirstRun
+
+  common /control/ debugFirstRun
+   
+  j = 0
+  do l = 1, nLayer      ! loop over different thin film layers
+    m = nos(l)/2      ! m number of TO modes = offset to reach the LO mode in the joint TO-LO list
+    nomi = dcmplx(1.0d0, 0.0d0)
+    deno = dcmplx(1.0d0, 0.0d0)
+    addeps = dcmplx(0.0d0, 0.0d0)
+    wn2 = wn**2
+    do k = 1, m     ! loop over all TO modes
+      j = j + 1
+
+      if (osc(1,j) > 0.) then     ! positive TO mode: 'Kurosawa' form: _Multiplicative_ phonon mode
+        b = wn/osc(1, j+m)
+        nomi = nomi * osc(1, j+m)**2 * (1.0 - b * dcmplx(b, osc(3,j+m)/osc(1, j+m)) )
+        deno =deno * (osc(1,j)**2 - wn * dcmplx( wn, osc(3,j) ) )
+      
+      else if (osc(1,j) < 0.) then! Negative TO mode means: _Additive_ Lorentz oscillator with Q
+        addeps = addeps + osc(1,j)**2 * osc(2,j) /dcmplx(osc(1,j)**2 - wn2, -1*wn*osc(3,j))  ! Sign of imaginary part changed (WFW)
+      
+      else                      ! osc(1,j) = 0   -> it is a Drude term
+        addeps = addeps - dcmplx(osc(1,j+m)**2, wn*(osc(3,j)-osc(3,j+m))) /dcmplx(wn2, wn*osc(3,j))
+      end if
+
+    enddo
+    j = j+m     ! we have already looped over the LO modes, therefore increase the index
+    eps(l) = epsinf(l) * (nomi / deno + addeps) ! brackets changed by HHe 230915
+  enddo
+  debugFirstRun = .false.
+
+! **** log modification start
+  write (99, '(30g15.7)') wn, (eps(j), j = 1, nLayer)
+! **** log modification end
+
+  return
+end subroutine seteps
+end module seteps_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/param.f90 b/tests/SetEpsTestCasesFromScratch/WFW/param.f90
new file mode 100644
index 0000000000000000000000000000000000000000..a688b3cc98a5f11152df9c2432ada9863c71d093
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/param.f90
@@ -0,0 +1,5 @@
+module param_mod
+  double precision :: acoef, bcoef, ccoef, elleps, cospsi, sinpsi, tanpsi
+  double precision :: ru, um, dlimf, wn
+  logical :: user, rational
+end module param_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/phint.f90 b/tests/SetEpsTestCasesFromScratch/WFW/phint.f90
new file mode 100644
index 0000000000000000000000000000000000000000..57f15b5119872c2e2527c95ceac70168f8bfc8c8
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/phint.f90
@@ -0,0 +1,74 @@
+double precision function phint(phi, a, u)
+
+! *******************************************************************
+! *                                                                 *
+! * evaluate the integral from zero to phi of                       *
+! *                                                                 *
+! *                 u                 2                             *
+! *  ( ----------------------------- )  dphi                        *
+! *                          2     2                                *
+! *    (1 - a * u * cos(phi))  +  u                                 *
+! *                                                                 *
+! * for 0 <= phi <= pi , u >= 0 and a >= 0                          *
+! *                                                                 *
+! * Reference:                                                      *
+! * Ph. Lambin, J. P. Vigneron, and A. A. Lucas,                    *
+! * Phys. Rev. B 32 (1985) 8203-8215.                               *
+! *                                                                 *
+! *******************************************************************
+
+  implicit none
+
+  double precision, intent(in) :: phi
+  double precision, intent(in) :: a
+  double precision, intent(in) :: u
+
+  double precision :: ai, ar, bi, br, c, cpr, d, e, esr, pi, qr, ri, rm, root
+  double precision :: rp, rr, s, spr, tm, tp, u2, x, zeta, zetai, zetar, zr
+
+  pi = 3.141592653589793238d0
+  c = dcos(phi)
+  s = dsin(phi)
+  u2 = u**2
+  e = a*u
+  if (u < 1.0d0 .and. e < 1.0d-02 * (1.0d0 + u2)) then
+    zr = 1.0d0 + u2
+    esr = e / zr
+    phint = u2 / zr**2 * ((( (4.0d0 / 3.0d0) * (2.0d0 + c**2) * s * (5.0d0 - 3 * u2) *  &
+            esr + (phi + c * s) * (5.0d0 - u2)) * esr + 4 * s) * esr + phi)
+  else
+    rm = dsqrt((1.0d0 - e)**2 + u2)
+    tm = 0.5d0 * datan2(u, 1.0d0 - e)
+    rp = dsqrt((1.0d0 + e)**2 + u2)
+    tp = 0.5d0 * datan2(u, 1.0d0 + e)
+    root = dsqrt(rm * rp)
+    cpr = dcos(tm + tp)
+    spr = dsin(tm + tp)
+    x = 0.0d0       ! ensure initialization
+    if (c >= 0.0d0) then
+      x = s / (1.0d0 + c)
+    elseif (dabs(s) > 1.0d-07) then
+      x = (1.0d0 - c) / s
+    endif
+    if ((c >= 0.0d0) .or. (dabs(s) > 1.0d-07)) then
+      zeta = dsqrt(rm / rp)
+      zetar = -zeta * dsin(tm - tp)
+      zetai =  zeta * dcos(tm - tp)
+      br = 0.5d0 * dlog(((zetar + x)**2 + zetai**2) / ((zetar - x)**2 + zetai**2))
+      bi = datan2(zetai, zetar + x) - datan2(zetai, zetar - x)
+      rr = -(br * spr - bi * cpr) / root
+      ri = -(bi * spr + br * cpr) / root
+      d  =  e * s / ((1.0d0 - e * c)**2 + u2)
+      ar =  d * (1.0d0 - e * c) - rr + u * ri
+      ai = -d *  u              - ri - u * rr
+    else
+      rr = -pi / root * cpr
+      ri =  pi / root * spr
+      ar = -rr + u * ri
+      ai = -ri - u * rr
+    endif
+    qr = (ar * (cpr - spr) * (cpr + spr) + 2 * ai * cpr * spr) / (rm * rp)
+    phint = 0.5d0 * (ri / u - qr)
+  endif
+  return
+end function phint
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/qrat.f90 b/tests/SetEpsTestCasesFromScratch/WFW/qrat.f90
new file mode 100644
index 0000000000000000000000000000000000000000..7bbb966b70cc9d60ff1185d0fec5f9c293d5e29c
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/qrat.f90
@@ -0,0 +1,14 @@
+double precision function qrat(x, alpha, beta, c1, c2)
+
+!         1 + x * (beta + c1 * x)
+! qrat = ---------------------------------------------
+!        (1 + x * (beta + c2 * x)) * (1 + alpha * x)^2
+
+  implicit none
+
+  double precision, intent(in) :: x, alpha, beta, c1, c2
+
+  qrat = (1.0d0 + x * (beta + c1 * x)) / ((1.0d0 + x * (beta + c2 * x)) * (1.0d0 + alpha * x)**2)
+
+  return
+end function qrat
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/quanc8.f90 b/tests/SetEpsTestCasesFromScratch/WFW/quanc8.f90
new file mode 100644
index 0000000000000000000000000000000000000000..86ee4f36463a6f8150bb5f52b50528ca849879f5
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/quanc8.f90
@@ -0,0 +1,240 @@
+module quanc8_mod
+contains
+subroutine quanc8(fun, a, b, abserr, relerr, result, errest, nofun, flag, eps, thick, layers, nper)
+
+! estimate the integral of fun(x) from a to b
+! to a user provided tolerance.
+! an automatic adaptive routine based on
+! the 8-panel newton-cotes rule (g. forsythe et al, 1977, p. 92)
+!
+! input ..
+!
+! fun     the name of the integrand function subprogram fun(x).
+! a       the lower limit of integration.
+! b       the upper limit of integration.(b may be less than a.)
+! relerr  a relative error tolerance. (should be non-negative)
+! abserr  an absolute error tolerance. (should be non-negative)
+!
+! output ..
+!
+! result  an approximation to the integral hopefully satisfying the
+!         least stringent of the two error tolerances.
+! errest  an estimate of the magnitude of the actual error.
+! nofun   the number of function values used in calculation of result.
+! flag    a reliability indicator.  if flag is zero, then result
+!         probably satisfies the error tolerance.  if flag is
+!         xxx.yyy , then  xxx = the number of intervals which have
+!         not converged and 0.yyy = the fraction of the interval
+!         left to do when the limit on  nofun  was approached.
+! 
+! additional input ..
+!
+! eps     epsilon
+! thick   thickness
+! layers  number of layers
+! nper    number of periodic layers
+
+  implicit none
+
+  double precision :: fun
+  double precision, intent(in) :: a
+  double precision, intent(in) :: b
+  double precision, intent(in out) :: abserr
+  double precision, intent(in) :: relerr
+  double precision, intent(out) :: result
+  double precision, intent(out) :: errest
+  integer, intent(out) :: nofun
+  double precision, intent(out) :: flag
+
+  external fun
+
+  double precision, intent(in) :: thick(:)
+  double complex, intent(in) :: eps(:)
+  integer, intent(in) :: layers, nper
+
+  double precision :: w0, w1, w2, w3, w4, area, x0, f0, stone, step, cor11, temp
+  double precision :: qprev, qnow, qdiff, qleft, esterr, tolerr
+  double precision :: qright(31), f(16), x(16), fsave(8, 30), xsave(8, 30)
+  double precision :: dabs, dmax1
+
+  integer :: levmin, levmax, levout, nomax, nofin, lev, nim, i, j
+
+! ***   stage 1 ***   general initialization
+! set constants.
+
+!  write (*,*) 'quanc8:'
+!  write (*,*) 'thick: ', size(thick)
+!  write (*,*) 'eps: ', size(eps)
+
+  levmin = 1
+  levmax = 30
+  levout = 6
+  nomax = 5000
+  nofin = nomax - 8 * (levmax - levout + 2**(levout + 1))
+
+! trouble when nofun reaches nofin
+
+  w0 =   3956.0d0 / 14175.0d0
+  w1 =  23552.0d0 / 14175.0d0
+  w2 =  -3712.0d0 / 14175.0d0
+  w3 =  41984.0d0 / 14175.0d0
+  w4 = -18160.0d0 / 14175.0d0
+
+! initialize running sums to zero.
+
+  flag   = 0.0d0
+  result = 0.0d0
+  cor11  = 0.0d0
+  errest = 0.0d0
+  area   = 0.0d0
+  nofun = 0
+  if (a == b) return
+
+! ***   stage 2 ***   initialization for first interval
+
+  lev = 0
+  nim = 1
+  x0 = a
+  x(16) = b
+  qprev  = 0.0d0
+  f0 = fun(x0, eps, thick, layers, nper, size(eps))
+  stone = (b - a) / 16
+  x(8)  =  (x0    + x(16)) / 2
+  x(4)  =  (x0    + x(8))  / 2
+  x(12) =  (x(8)  + x(16)) / 2
+  x(2)  =  (x0    + x(4))  / 2
+  x(6)  =  (x(4)  + x(8))  / 2
+  x(10) =  (x(8)  + x(12)) / 2
+  x(14) =  (x(12) + x(16)) / 2
+!***  !$OMP PARALLEL shared (f, x, eps, thick, layers, nper) private (j)
+!***  !$OMP DO
+  do j = 2, 16, 2
+    f(j) = fun(x(j), eps, thick, layers, nper, size(eps))
+  enddo
+!***  !$OMP END DO NOWAIT
+!***  !$OMP END PARALLEL
+  nofun = 9
+
+  do
+
+! ***   stage 3 ***   central calculation
+! requires qprev, x0, x2, x4, ..., x16, f0, f2, f4, ..., f16.
+! calculates x1, x3, ...x15, f1, f3, ...f15, qleft, qright, qnow, qdiff, area.
+
+    x(1) = (x0 + x(2)) / 2
+    f(1) = fun(x(1), eps, thick, layers, nper, size(eps))
+    do j = 3, 15, 2
+      x(j) = (x(j - 1) + x(j + 1)) / 2
+    enddo
+!***  !$OMP PARALLEL shared (f, x, eps, thick, layers, nper) private (j)
+!***  !$OMP DO SCHEDULE(auto)
+    do j = 3, 15, 2
+      f(j) = fun(x(j), eps, thick, layers, nper, size(eps))
+    enddo
+!***  !$OMP END DO NOWAIT
+!***  !$OMP END PARALLEL
+    nofun = nofun + 8
+    step = (x(16) - x0) / 16.0d0
+    qleft  =  (w0 * (f0 + f(8))  + w1 * (f(1) + f(7)) + w2 * (f(2) + f(6))  &
+        + w3 * (f(3) + f(5))  +  w4 * f(4)) * step
+    qright(lev + 1) = (w0 * (f(8) + f(16)) + w1 * (f(9) + f(15)) + w2 * (f(10) + f(14))  &
+        + w3 * (f(11) + f(13)) + w4 * f(12)) * step
+    qnow = qleft + qright(lev + 1)
+    qdiff = qnow - qprev
+    area = area + qdiff
+
+! ***   stage 4 *** interval convergence test
+
+    esterr = dabs(qdiff) / 1023
+    tolerr = dmax1(abserr, relerr * dabs(area)) * (step / stone)
+
+    if (lev >= levmin) then
+      if (lev >= levmax) then
+! current level is levmax.
+        flag = flag + 1.0d0
+      else
+        if (nofun > nofin) then
+! ***   stage 6   ***   trouble section
+! number of function values is about to exceed limit.
+          nofin = 2 * nofin
+          levmax = levout
+          flag = flag + (b - x0) / (b - a)
+        else
+          if (esterr > tolerr) then
+! ***   stage 5   ***   no convergence
+! locate next interval.
+            nim = 2 * nim
+            lev = lev + 1
+! store right hand elements for future use.
+            do i = 1, 8
+              fsave(i, lev) = f(i + 8)
+              xsave(i, lev) = x(i + 8)
+            enddo
+! assemble left hand elements for immediate use.
+            qprev = qleft
+            do i = 1, 8
+              f(18 - 2 * i) = f(9 - i)
+              x(18 - 2 * i) = x(9 - i)
+            enddo
+            cycle
+          endif
+        endif
+      endif
+
+! ***   stage 7   ***   interval converged
+! add contributions into running sums.
+      result = result + qnow
+      errest = errest + esterr
+      cor11  = cor11  + qdiff / 1023
+! locate next interval.
+      do while (nim /= 2 * (nim / 2))
+        nim = nim / 2
+        lev = lev - 1
+      enddo
+      nim = nim + 1
+
+      if (lev <= 0) exit
+
+! assemble elements required for the next interval.
+      qprev = qright(lev)
+      x0 = x(16)
+      f0 = f(16)
+      do i = 1, 8
+        f(2*i) = fsave(i, lev)
+        x(2*i) = xsave(i, lev)
+      enddo
+      cycle
+    else
+! ***   stage 5   ***   no convergence
+! locate next interval.
+      nim = 2 * nim
+      lev = lev + 1
+! store right hand elements for future use.
+      do i = 1, 8
+        fsave(i, lev) = f(i + 8)
+        xsave(i, lev) = x(i + 8)
+      enddo
+! assemble left hand elements for immediate use.
+      qprev = qleft
+      do i = 1, 8
+        f(18 - 2 * i) = f(9 - i)
+        x(18 - 2 * i) = x(9 - i)
+      enddo
+    endif
+
+   enddo
+
+ ! ***   stage 8   ***   finalize and return
+  result = result + cor11
+
+! make sure errest not less than roundoff level.
+  if (errest /= 0.0d0) then
+    temp = dabs(result) + errest
+    do while (temp == dabs(result))
+      errest = 2 * errest
+      temp = dabs(result) + errest
+    enddo
+  endif
+  return
+end subroutine quanc8
+end module quanc8_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/queels.f90 b/tests/SetEpsTestCasesFromScratch/WFW/queels.f90
new file mode 100644
index 0000000000000000000000000000000000000000..d2128df921e17e578004094b2218052d79c1cbe1
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/queels.f90
@@ -0,0 +1,92 @@
+module queels_mod
+contains
+subroutine queels(x, f, aerr, rerr, facru, eps, thick, layers, nper)
+
+! ******************************************************************
+! *                                                                *
+! * perform q-space integration for computing the eels spectrum of *
+! * a isotropic target using polar coordinates.                    *
+! *                                                                *
+! * x is the dimensionless energy loss hbar*omega/(2*e0*phia)      *
+! * aerr and rerr are the desired absolute and relative accuracies *
+! * facru*x is the units of wavevectors omega/v_perpendicular      *
+! * f is the q-integral multiplied by (2/pi)**2                    *
+! *                                                                *
+! * eps:    epsilon                                                *
+! * thick:  thickness                                              *
+! * layers: number of layers                                       *
+! * nper:   number of periodic layers                              *
+! *                                                                *
+! ******************************************************************
+
+  use quanc8_mod
+  use fint1_mod
+  use fint2_mod
+  use fint3_mod
+  use param_mod
+
+  implicit none
+
+  double precision, intent(in) :: x
+  double precision, intent(out) :: f
+  double precision, intent(in out) :: aerr
+  double precision, intent(in out) :: rerr
+  double precision, intent(in) :: facru
+  double complex, intent(in) :: eps(:)
+  double precision, intent(in) :: thick(:)
+  integer, intent(in) :: layers, nper
+
+  double precision :: error, flag
+  double precision :: u1, u2, ut, y
+  integer :: ie, nofu
+  dimension error(3), flag(3)
+
+!  write (*,*) 'queels:'
+!  write (*,*) 'eps: ', size(eps)
+!  write (*,*) 'thick: ', size(thick)
+
+  f = 0.0d0
+  if (x <= 0.0d0) then
+    return
+  endif
+  ru = facru * x
+  ccoef = cospsi**2 / x
+  ut = ccoef - bcoef
+  u1 = dabs(ut)
+  u2 = ccoef + bcoef
+  if (ut > 0.0d0) then
+    call quanc8(fint1, 0.0d0, u1, aerr, rerr, y, error(1), nofu, flag(1), eps, thick, layers, nper)
+    f = y
+  else
+    flag(1) = 0.0d0
+  endif
+  if (u2 > u1) then
+    call quanc8(fint2, u1, u2, aerr, rerr, y, error(2), nofu, flag(2), eps, thick, layers, nper)
+    f = f + y
+  else
+    flag(2) = 0.0d0
+  endif
+  if (dabs(acoef) > x * (1.0d0 - elleps) * bcoef) then
+    um = dsqrt(ccoef / x / (1.0d0 - elleps) + bcoef**2 / acoef)
+    if (um > u2) then
+      call quanc8(fint3, u2, um, aerr, rerr, y, error(3), nofu, flag(3), eps, thick, layers, nper)
+      f = f + y
+    endif
+    if (um < u1) then
+      call quanc8(fint3, um, u1, aerr, rerr, y, error(3), nofu, flag(3), eps, thick, layers, nper)
+      f = f - y
+    endif
+  else
+    flag(3) = 0.0d0
+  endif
+  do ie = 1, 3
+    if (flag(ie) == 0.0d0) cycle
+    write(*,*) ' +++ flag(', ie, ') =', flag(ie), ', error =', error(ie), ' +++'
+    if (flag(ie) - aint(flag(ie)) > 0.5d-02) then
+      stop '*** execution aborted ***'
+    endif
+  enddo
+  f = (2 / 3.141592653589793238d0)**2 * f
+  return
+end subroutine queels
+end module queels_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/surlos.f90 b/tests/SetEpsTestCasesFromScratch/WFW/surlos.f90
new file mode 100644
index 0000000000000000000000000000000000000000..66552e98a2e78ab9c2a4cd0b42c08d7a457c9a4e
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/surlos.f90
@@ -0,0 +1,174 @@
+module surlos_mod
+contains
+
+logical function zero(z)
+  double complex, intent(in) :: z
+  zero = (dble(z) == 0.0d0) .and. (dimag(z) == 0.0d0)
+end function zero  
+
+double precision function surlos(dk, eps, thick, layers, nper)
+
+! ******************************************************************
+! *                                                                *
+! * eels surface loss function for an arbitrary multilayered target*
+! *                                                                *
+! * dk:                                                            *
+! * eps:    epsilon                                                *
+! * thick:  thickness                                              *
+! * layers: number of layers                                       *
+! * nper:   number of periodic layers                              *
+! *                                                                *
+! ******************************************************************
+
+  implicit none
+
+  double precision, intent(in) :: dk
+  double complex, intent(in) :: eps(:)
+  double precision, intent(in) :: thick(:)
+  integer, intent(in) :: layers, nper
+
+  integer :: lmax
+  logical :: static, skip
+  integer :: lstart, n
+  double precision, allocatable :: arg(:)
+  double precision :: argmin, argmax, cn, cnm1, epsmac, sn, snm1, tn
+  double complex :: a, b, csi, pnm2, pnm1, pn, pp, qnm2, qnm1, qn, qp
+
+  epsmac = epsilon(1.0d0)
+  argmin = dsqrt(2 * epsmac)
+  epsmac = epsmac / 2
+  argmax = 0.5d0 * dlog(2 / epsmac)
+
+!  write (*,*) 'surlos:'
+!  write (*,*) 'thick: ', size(thick)
+!  write (*,*) 'eps: ', size(eps)
+
+  lmax = size(eps)
+  allocate (arg(lmax))
+  lstart = layers - nper + 1
+  static = .true.
+  skip = .false.
+
+  do n = 1, layers
+    arg(n) = dk * thick(n)
+    if (arg(n) > argmax .or. zero(eps(n))) then
+      csi  = eps(n)
+      skip = .true.
+      exit
+    endif
+    static = .not. (n >= lstart .and. arg(n) > argmin)
+  enddo
+
+  if (.not. skip) then
+! *** periodic continued fraction, period = nper
+
+    do ! Do loop is only for the option to skip out of it.
+      if (nper <= 1) then
+        csi = eps(layers)
+      else
+        if (static) then
+          pn = 0.0d0
+          qn = 0.0d0
+          do n = lstart, layers
+            pn = pn + thick(n) * eps(n)
+            qn = qn + thick(n) / eps(n)
+          enddo
+          if (zero(qn)) then
+            n = lstart
+            if (n <= 1) then
+              surlos = 0.0d0
+              return
+            endif
+            n = n - 1
+            csi = eps(n) / dtanh(arg(n))
+            exit
+          endif ! zero(qn)
+          csi = cdsqrt(pn / qn)
+          if ((dimag(csi) < 0.0d0) .and. (dble(qn) < 0.0d0)) then
+            csi = -csi
+          endif
+        else ! static
+          cn = dcosh(arg(lstart))
+          sn = dsinh(arg(lstart))
+          pnm1 = 1.0d0
+          pn = cn
+          pp = eps(lstart) * sn
+          qnm1 = 0.0d0
+          qn = sn / eps(lstart)
+          qp = pn
+          do  n = lstart + 1, layers
+            cnm1 = cn
+            snm1 = sn
+            cn = dcosh(arg(n))
+            sn = dsinh(arg(n))
+            a = eps(n) * sn
+            pp = cn * pp + a * pn
+            qp = cn * qp + a * qn
+            b = (eps(n - 1) / eps(n)) * (sn / snm1)
+            a = cnm1 * b + cn
+            pnm2 = pnm1
+            pnm1 = pn
+            qnm2 = qnm1
+            qnm1 = qn
+            pn = a * pnm1 - b * pnm2
+            qn = a * qnm1 - b * qnm2
+          enddo
+          if (zero(qn)) then
+            a = qp - pn
+            if (zero(a)) then
+              n = lstart
+              if (n <= 1) then
+                surlos = 0.0d0
+                return
+              endif
+              n = n - 1
+              csi = eps(n) / dtanh(arg(n))
+              exit
+            endif
+            csi = pp / a
+          else
+            a = 0.5d0 * (pn - qp) / qn
+            b = cdsqrt(a**2 + pp / qn)
+            pn = a - pn / qn
+            if (cdabs(pn + b) > cdabs(pn - b)) then
+              b = -b
+            endif
+            csi = a + b
+          endif ! zero(qn)
+        endif ! static
+! *** small-dk limit of the periodic tail
+
+      endif ! nper <= 1
+
+      n = lstart
+
+      exit
+    enddo
+  endif ! .not. skip
+
+! *** backward algorithm
+
+  do
+    n = n - 1
+    if (n <= 0) then
+      a = csi + 1.0d0
+      if (zero(a)) then
+        surlos = 2 / epsmac
+      else
+        surlos = dimag(-2 / a)
+      endif
+      return
+    endif ! n <= 0
+
+    if (arg(n) /= 0.0d0) then
+      tn = dtanh(arg(n))
+      b = eps(n) + csi * tn
+      if (zero(b)) then
+        surlos = 0.0d0
+        return
+      endif
+      csi = eps(n) * (csi + tn * eps(n)) / b
+    endif
+  enddo
+end function surlos
+end module surlos_mod
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/usurlo.f90 b/tests/SetEpsTestCasesFromScratch/WFW/usurlo.f90
new file mode 100644
index 0000000000000000000000000000000000000000..222946c95f302c8015f157572135fbf0d44c1174
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/usurlo.f90
@@ -0,0 +1,23 @@
+double precision function usurlo(dq, wn)
+
+! ******************************************************************
+! *                                                                *
+! * user-supplied dielectric surface loss function aimag(g(dq, wn)) *
+! * input arguments :                                              *
+! *    dq : modulus of the two-dimensional surface wave vector     *
+! *         (angstroem**-1)                                        *
+! *    wn : frequency (cm**-1)                                     *
+! *                                                                *
+! ******************************************************************
+
+  implicit none
+
+  double precision, intent(in out) :: dq
+  double precision, intent(in out) :: wn
+
+  if ((wn .GT. 0) .AND. (dq .GT. 0)) then
+    write(*,*) 'hello, here is the user loss function'
+  endif
+  usurlo = 1.0d0
+  return
+end function usurlo
diff --git a/tests/SetEpsTestCasesFromScratch/WFW/version.inc b/tests/SetEpsTestCasesFromScratch/WFW/version.inc
new file mode 100644
index 0000000000000000000000000000000000000000..453b451b102cb59869bcbda41f7d309b7459ada2
--- /dev/null
+++ b/tests/SetEpsTestCasesFromScratch/WFW/version.inc
@@ -0,0 +1,2 @@
+! version of eels-boson
+  character (len = *), parameter :: version = '1.0.0'